/[MITgcm]/MITgcm/model/src/set_defaults.F
ViewVC logotype

Diff of /MITgcm/model/src/set_defaults.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.1 by adcroft, Tue Dec 15 00:20:35 1998 UTC revision 1.116 by heimbach, Wed Jun 7 01:55:13 2006 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7    CBOP
8    C     !ROUTINE: SET_DEFAULTS
9    C     !INTERFACE:
10        SUBROUTINE SET_DEFAULTS(        SUBROUTINE SET_DEFAULTS(
11       O   viscArDefault, diffKrTDefault, diffKrSDefault,       O   viscArDefault, diffKrTDefault, diffKrSDefault,
12       O   hFacMinDrDefault, delRdefault,       O   hFacMinDrDefault, delRdefault, rkFacDefault,
13       I   myThid )       I   myThid )
 C     /==========================================================\  
 C     | SUBROUTINE SET_DEFAULTS                                  |  
 C     | o Routine to set model "parameters"                      |  
 C     |==========================================================|  
 C     | Notes:                                                   |  
 C     | ======                                                   |  
 C     | The present version of this routine is a place-holder.   |  
 C     | A production version needs to handle parameters from an  |  
 C     | external file and possibly reading in some initial field |  
 C     | values.                                                  |  
 C     \==========================================================/  
       IMPLICIT NONE  
14    
15  C     === Global variables ===  C     !DESCRIPTION:
16    C     Routine to set model "parameter defaults".
17    
18    C     !USES:
19          IMPLICIT NONE
20  #include "SIZE.h"  #include "SIZE.h"
21  #include "EEPARAMS.h"  #include "EEPARAMS.h"
22  #include "PARAMS.h"  #include "PARAMS.h"
23    Cml#include "EOS.h"
24  #include "GRID.h"  #include "GRID.h"
 #include "CG2D.h"  
25    
26  C     === Routine arguments ===  C     !INPUT/OUTPUT PARAMETERS:
27  C     myThid - Number of this instance of INI_PARMS  C     myThid - Number of this instance of INI_PARMS
28        INTEGER myThid        INTEGER myThid
29        _RL viscArDefault        _RL viscArDefault
# Line 34  C     myThid - Number of this instance o Line 31  C     myThid - Number of this instance o
31        _RL diffKrSDefault        _RL diffKrSDefault
32        _RL hFacMinDrDefault        _RL hFacMinDrDefault
33        _RL delRDefault(Nr)        _RL delRDefault(Nr)
34          _RS rkFacDefault
35    
36  C     === Local variables ===  C     !LOCAL VARIABLES:
37  C     K, I, J - Loop counters  C     K, I, J - Loop counters
38        INTEGER K, I, J        INTEGER K, I, J
39    CEOP
40    
41  C--   Grid parameters  C--   Grid parameters
42  C     Vertical gridding  C     Vertical gridding
43        rkFac = 1.D0        rkFacDefault        = 1. _d 0
44        horiVertRatio = 1.D0        horiVertRatio       = 1. _d 0
45          Ro_SeaLevel         = 0.
46        DO k=1,Nr        DO k=1,Nr
47         delRdefault(k) = 1.D2         delRdefault(k)     = 0.
48          ENDDO
49          DO k=1,Nr+1
50           delRc(k)           = UNSET_RL
51        ENDDO        ENDDO
52    
53  C     Horizontal gridding  C     Horizontal gridding
54          delXFile            = ' '
55          delYFile            = ' '
56          horizGridFile       = ' '
57  C     In cartesian coords distances are in metres  C     In cartesian coords distances are in metres
58        usingCartesianGrid = .TRUE.        usingCartesianGrid  = .FALSE.
59        DO i=1,Nx        DO i=1,Nx
60         delX(i) = 20.D0 * 1000.D0         delX(i)            = UNSET_RL
61        ENDDO        ENDDO
62        DO j=1,Ny        DO j=1,Ny
63         delY(j) = 20.D0 * 1000.D0         delY(j)            = UNSET_RL
64        ENDDO        ENDDO
65  C     In spherical polar distances are in degrees  C     In spherical polar distances are in degrees
66        usingSphericalPolarGrid = .FALSE.        usingSphericalPolarGrid = .FALSE.
67        phiMin    = -5.0        phiMin              = 0.0
68        thetaMin  = 0.        thetaMin            = 0.
69        rSphere   = 6370. * 1.D3        rSphere             = 6370. _d 3
70        IF ( usingSphericalPolarGrid ) THEN  C     General curvilinear coordinate system
71         DO i=1,Nx        usingCurvilinearGrid= .FALSE.
72          delX(i) = 1.D0  C     General cylindrical coordinate system
73         ENDDO        usingCylindricalGrid= .FALSE.
74         DO j=1,Ny  C     Coriolis map:
75          delY(j) = 1.D0        useConstantF        = .FALSE.
76         ENDDO        useBetaPlaneF       = .FALSE.
77        ENDIF        useSphereF          = .FALSE.
78  C  
79    
80  C--   Set default "physical" parameters  C--   Set default "physical" parameters
81        DO K =1,Nr        nh_Am2              = 1. _d 0
82         tRef(K) = 30.D0 - FLOAT( K )        gravity             = 9.81 _d 0
83        ENDDO        rhoNil              = 999.8 _d 0
84        gravity  = 9.81D0  C-- jmc : the default is to set rhoConstFresh to rhoConst (=rhoNil by default)
85        rhoNil   = 999.8D0  C         (so that the default produces same results as before)
86        f0       = 1.D-4  c     rhoConstFresh       = 999.8 _d 0
87        beta     = 1.D-11        f0                  = 1. _d -4
88        viscAh   = 1.D3        beta                = 1. _d -11
89        diffKhT  = 1.D3  C-    Earth rotation period is 86400*365.25/366.25 (use to be 1.day)
90        diffKhS  = 1.D3        rotationPeriod      = 86164. _d 0
91        viscArDefault = 1.D-3        viscAh              = 0. _d 3
92        no_slip_sides = .TRUE.        viscAhGrid          = 0. _d 0
93        no_slip_bottom = .TRUE.        viscAhGridMin       = 0. _d 0
94        diffKrTDefault = 1.D-5        viscAhGridMax       = 1. _d 21
95        diffKrSDefault = 1.D-5        viscAhMax           = 1. _d 21
96        viscA4   = 0.        viscAhReMax         = 0. _d 0
97        diffK4T  = 0.        viscC2leith         = 0. _d 0
98        diffK4S  = 0.        viscC2leithD        = 0. _d 0
99        GMmaxslope   =   1.D-2        viscC2smag          = 0. _d 0
100        GMlength     = 200.D3        diffKhT             = 0. _d 3
101        GMalpha      = 0.D0        diffKhS             = 0. _d 3
102        GMdepth      = 1000.D0        viscArDefault       = 0. _d -3
103        GMkbackground= 0.D0        no_slip_sides       = .TRUE.
104        GMmaxval     = 2500.D0        no_slip_bottom      = .TRUE.
105        HeatCapacity_Cp = 3994.D0        sideDragFactor      = 2. _d 0
106        tAlpha       = 2.D-4        bottomDragLinear    = 0.
107        sBeta        = 7.4D-4        bottomDragQuadratic = 0.
108        eosType      = 'LINEAR'        smoothAbsFuncRange  = 0. _d 0
109          diffKrTDefault      = 0. _d -3
110          diffKrSDefault      = 0. _d -3
111          diffKrBL79surf      = 0. _d 0
112          diffKrBL79deep      = 0. _d 0
113          diffKrBL79scl       = 200. _d 0
114          diffKrBL79Ho        = -2000. _d 0
115          viscA4              = 0. _d 11
116          viscA4Grid          = 0. _d 0
117          viscA4GridMax       = 1. _d 21
118          viscA4GridMin       = 0. _d 0
119          viscA4Max           = 1. _d 21
120          viscA4ReMax         = 0. _d 0
121          viscC4leith         = 0. _d 0
122          viscC4leithD        = 0. _d 0
123          viscC4smag          = 0. _d 0
124          diffK4T             = 0. _d 11
125          diffK4S             = 0. _d 11
126          cosPower            = 0.
127          HeatCapacity_Cp     = 3994. _d 0
128    Cml      tAlpha              = 2. _d -4
129    Cml      sBeta               = 7.4 _d -4
130          eosType             = 'LINEAR'
131        buoyancyRelation    = 'OCEANIC'        buoyancyRelation    = 'OCEANIC'
132        implicitFreeSurface = .TRUE.        hFacMin             = 1. _d 0
133        rigidLid            = .FALSE.        hFacMinDrDefault    = 0. _d 0
134        hFacMin             = 1.D0        implicitIntGravWave = .FALSE.
135        hFacMinDrDefault    = 0.D0        staggerTimeStep     = .FALSE.
136        momViscosity        = .TRUE.        momViscosity        = .TRUE.
137        momAdvection        = .TRUE.        momAdvection        = .TRUE.
138        momForcing          = .TRUE.        momForcing          = .TRUE.
139        useCoriolis         = .TRUE.        useCoriolis         = .TRUE.
140        momPressureForcing  = .TRUE.        momPressureForcing  = .TRUE.
141        momStepping         = .TRUE.        momStepping         = .TRUE.
142          vectorInvariantMomentum = .FALSE.
143        tempStepping        = .TRUE.        tempStepping        = .TRUE.
144          tempAdvection       = .TRUE.
145          tempForcing         = .TRUE.
146        saltStepping        = .TRUE.        saltStepping        = .TRUE.
147        metricTerms         = .FALSE.        saltAdvection       = .TRUE.
148          saltForcing         = .TRUE.
149          metricTerms         = .TRUE.
150          useNHMTerms         = .FALSE.
151          useFullLeith        = .FALSE.
152          useAreaViscLength   = .FALSE.
153          useStrainTensionVisc= .FALSE.
154        implicitDiffusion   = .FALSE.        implicitDiffusion   = .FALSE.
155        openBoundaries      = .FALSE.        implicitViscosity   = .FALSE.
156          momImplVertAdv      = .FALSE.
157          tempImplVertAdv     = .FALSE.
158          saltImplVertAdv     = .FALSE.
159          nonHydrostatic      = .FALSE.
160          quasiHydrostatic    = .FALSE.
161          globalFiles         = .FALSE.
162          useSingleCpuIO      = .FALSE.
163          allowFreezing       = .FALSE.
164          useOldFreezing      = .FALSE.
165          ivdc_kappa          = 0. _d 0
166          usePickupBeforeC35    = .FALSE.
167          usePickupBeforeC54    = .FALSE.
168          debugMode             = .FALSE.
169          tempAdvScheme       = 2
170          saltAdvScheme       = 2
171          multiDimAdvection   = .TRUE.
172          useCDscheme         = .FALSE.
173          useEnergyConservingCoriolis = .FALSE.
174          useJamartWetPoints  = .FALSE.
175          useJamartMomAdv     = .FALSE.
176          SadournyCoriolis    = .FALSE.
177          upwindVorticity     = .FALSE.
178          highOrderVorticity  = .FALSE.
179          useAbsVorticity     = .FALSE.
180          upwindShear         = .FALSE.
181          selectKEscheme      = 0
182          debugLevel          = debLevA
183          inAdMode            = .FALSE.
184          inAdExact           = .TRUE.
185    
186    C--   Set (free)surface-related parameters
187          implicitFreeSurface = .FALSE.
188          rigidLid            = .FALSE.
189          implicSurfPress     = 1. _d 0
190          implicDiv2DFlow     = 1. _d 0
191          exactConserv        = .FALSE.
192          uniformLin_PhiSurf  = .TRUE.
193          nonlinFreeSurf      = 0
194          hFacInf             = 0.2 _d 0
195          hFacSup             = 2.0 _d 0
196          select_rStar        = 0
197          useRealFreshWaterFlux = .FALSE.
198          temp_EvPrRn = UNSET_RL
199          salt_EvPrRn = 0.
200          balanceEmPmR        = .FALSE.
201          balanceQnet         = .FALSE.
202          balancePrintMean    = .FALSE.
203    
204    C--   Atmospheric physical parameters (e.g.: EOS)
205          celsius2K = 273.16 _d 0
206          atm_Po =  1. _d 5
207          atm_Cp = 1004. _d 0
208          atm_Rd = UNSET_RL
209          atm_kappa = 2. _d 0 / 7. _d 0
210          atm_Rq = 0. _d 0
211          integr_GeoPot = 2
212          selectFindRoSurf = 0
213    
214  C--   Elliptic solver parameters  C--   Elliptic solver parameters
215        cg2dMaxIters       = 150        cg2dMaxIters       = 150
216        cg2dTargetResidual = 1.D-7        cg2dTargetResidual = 1. _d -7
217          cg2dTargetResWunit = -1.
218        cg2dChkResFreq     = 1        cg2dChkResFreq     = 1
219          cg2dpcOffDFac      = 0.51 _d 0
220          cg2dPreCondFreq    = 1
221        cg3dMaxIters       = 150        cg3dMaxIters       = 150
222        cg3dTargetResidual = 1.D-7        cg3dTargetResidual = 1. _d -7
223        cg3dChkResFreq     = 1        cg3dChkResFreq     = 1
       cg2dpcOffDFac      = 0.51D0  
224    
225  C--   Time stepping parameters  C--   Time stepping parameters
226        deltaT            = 0.        deltaT            = 0. _d 0
227          deltaTmom         = 0. _d 0
228          deltaTfreesurf    = 0. _d 0
229          DO k=1,Nr
230            dTtracerLev(k)  = 0. _d 0
231          ENDDO
232          baseTime          = 0. _d 0
233        nIter0            = 0        nIter0            = 0
234        startTime         = deltaT*float(nIter0)        startTime         = deltaT*float(nIter0)
235        nTimeSteps        = 100        pickupSuff        = ' '
236        endTime           = deltaT*float(nTimeSteps)        nTimeSteps        = 0
237        abEps             = 0.01        nEndIter          = nIter0+nTimeSteps
238        pchkPtFreq        = deltaT*0        endTime           = deltaT*float(nEndIter)
239          momForcingOutAB   = UNSET_I
240          tracForcingOutAB  = UNSET_I
241          momDissip_In_AB   = .TRUE.
242          doAB_onGtGs       = .TRUE.
243          abEps             = 0.01 _d 0
244    #ifdef ALLOW_ADAMSBASHFORTH_3
245          alph_AB           = 0.5 _d 0
246          beta_AB           = 5. _d 0 / 12. _d 0
247          startFromPickupAB2= .FALSE.
248    #else
249          alph_AB           = UNSET_RL
250          beta_AB           = UNSET_RL
251          startFromPickupAB2= .TRUE.
252    #endif
253          pChkPtFreq        = deltaT*0
254        chkPtFreq         = deltaT*0        chkPtFreq         = deltaT*0
255        dumpFreq          = deltaT*50        outputTypesInclusive = .FALSE.
256          pickup_read_mdsio = .TRUE.
257          pickup_write_mdsio= .TRUE.
258          pickup_write_immed= .FALSE.
259          dumpFreq          = deltaT*0
260          adjDumpFreq       = deltaT*0
261          diagFreq          = deltaT*0
262          dumpInitAndLast   = .TRUE.
263          snapshot_mdsio    = .TRUE.
264          monitorFreq       = -1.
265          adjMonitorFreq    = 0.
266          monitor_stdio     = .TRUE.
267        taveFreq          = deltaT*0        taveFreq          = deltaT*0
268          timeave_mdsio     = .TRUE.
269          tave_lastIter     = 0.5 _d 0
270        writeStatePrec    = precFloat64        writeStatePrec    = precFloat64
271        writeBinaryPrec   = precFloat32        writeBinaryPrec   = precFloat32
272        readBinaryPrec    = precFloat32        readBinaryPrec    = precFloat32
273        nCheckLev         = 1        nCheckLev         = 1
274        checkPtSuff(1)    = 'ckptA'        checkPtSuff(1)    = 'ckptA'
275        checkPtSuff(2)    = 'ckptB'        checkPtSuff(2)    = 'ckptB'
276        cAdjFreq          = -1.D0        cAdjFreq          =  0. _d 0
277        tauCD             =  0.D0        tauCD             =  0. _d 0
278        tauThetaClimRelax =  0.D0        tauThetaClimRelax =  0. _d 0
279        tauSaltClimRelax  =  0.D0        tauSaltClimRelax  =  0. _d 0
280          tauTr1ClimRelax   =  0. _d 0
281        periodicExternalForcing = .FALSE.        periodicExternalForcing = .FALSE.
282        externForcingPeriod     = 0.        externForcingPeriod     = 0.
283        externForcingCycle      = 0.        externForcingCycle      = 0.
284          tCylIn             = 0.
285          tCylOut            = 20.
286    
287  C--   Input files  C--   Input files
288        bathyFile       = ' '        bathyFile       = ' '
289          topoFile        = ' '
290          shelfIceFile    = ' '
291        hydrogSaltFile  = ' '        hydrogSaltFile  = ' '
292        hydrogThetaFile = ' '        hydrogThetaFile = ' '
293        zonalWindFile   = ' '        zonalWindFile   = ' '
294        meridWindFile   = ' '        meridWindFile   = ' '
295        thetaClimFile   = ' '        thetaClimFile   = ' '
296        saltClimFile    = ' '        saltClimFile    = ' '
297          EmPmRfile       = ' '
298          saltFluxFile    = ' '
299          surfQfile       = ' '
300          surfQnetFile    = ' '
301          surfQswFile     = ' '
302          uVelInitFile    = ' '
303          vVelInitFile    = ' '
304          pSurfInitFile   = ' '
305          dQdTFile        = ' '
306          ploadFile       = ' '
307          eddyTauxFile    = ' '
308          eddyTauyFile    = ' '
309          lambdaThetaFile = ' '
310          lambdaSaltFile  = ' '
311          mdsioLocalDir   = ' '
312    
 C--   OBCS  
       DO I=1,Nx  
        OB_Jnorth(I)=0  
        OB_Jsouth(I)=0  
       ENDDO  
       DO J=1,Ny  
        OB_Ieast(J)=0  
        OB_Iwest(J)=0  
       ENDDO  
   
 C  
313        RETURN        RETURN
314        END        END
   

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.116

  ViewVC Help
Powered by ViewVC 1.1.22