/[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.26 by adcroft, Fri Aug 17 18:40:30 2001 UTC revision 1.124 by dimitri, Thu Apr 5 00:02:49 2007 UTC
# Line 3  C $Name$ Line 3  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, rkFacDefault,       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  #include "GRID.h"  Cml#include "EOS.h"
24    c#include "GRID.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 36  C     myThid - Number of this instance o Line 33  C     myThid - Number of this instance o
33        _RL delRDefault(Nr)        _RL delRDefault(Nr)
34        _RS rkFacDefault        _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        rkFacDefault         = 1.D0        delRFile            = ' '
44        horiVertRatio        = 1.D0        delRcFile           = ' '
45        Ro_SeaLevel = 0.        rkFacDefault        = 1. _d 0
46          horiVertRatio       = 1. _d 0
47          Ro_SeaLevel         = 0.
48        DO k=1,Nr        DO k=1,Nr
49         delRdefault(k) = 0.         delRdefault(k)     = 0.
50        ENDDO        ENDDO
51          DO k=1,Nr+1
52  C     Horizontal gridding         delRc(k)           = UNSET_RL
53          ENDDO
54    C-    vertical profile
55          tRefFile            = ' '
56          sRefFile            = ' '
57          rhoRefFile          = ' '
58    
59    C-    Horizontal gridding
60          delXFile            = ' '
61          delYFile            = ' '
62          horizGridFile       = ' '
63          deepAtmosphere      = .FALSE.
64  C     In cartesian coords distances are in metres  C     In cartesian coords distances are in metres
65        usingCartesianGrid = .TRUE.        usingCartesianGrid  = .FALSE.
66        DO i=1,Nx        DO i=1,Nx
67         delX(i) = UNSET_RL         delX(i)            = UNSET_RL
68        ENDDO        ENDDO
69        DO j=1,Ny        DO j=1,Ny
70         delY(j) = UNSET_RL         delY(j)            = UNSET_RL
71        ENDDO        ENDDO
72  C     In spherical polar distances are in degrees  C     In spherical polar distances are in degrees
73        usingSphericalPolarGrid = .FALSE.        usingSphericalPolarGrid = .FALSE.
74        phiMin               = 0.0        phiMin              = 0.0
75        thetaMin             = 0.        thetaMin            = 0.
76        rSphere              = 6370. * 1.D3        rSphere             = 6370. _d 3
77  C     General curvilinear coordinate system  C     General curvilinear coordinate system
78        usingCurvilinearGrid = .FALSE.        usingCurvilinearGrid= .FALSE.
79    C     General cylindrical coordinate system
80          usingCylindricalGrid= .FALSE.
81    C     Coriolis map:
82          useConstantF        = .FALSE.
83          useBetaPlaneF       = .FALSE.
84          useSphereF          = .TRUE.
85          use3dCoriolis       = .TRUE.
86    
87  C--   Set default "physical" parameters  C--   Set default "physical" parameters
88        DO K =1,Nr        nh_Am2              = 1. _d 0
89         tRef(K) = 30.D0 - FLOAT( K )        gravity             = 9.81 _d 0
90        ENDDO        rhoNil              = 999.8 _d 0
91        gravity             = 9.81D0  C-- jmc : the default is to set rhoConstFresh to rhoConst (=rhoNil by default)
92        rhoNil              = 999.8D0  C         (so that the default produces same results as before)
93        f0                  = 1.D-4  c     rhoConstFresh       = 999.8 _d 0
94        beta                = 1.D-11        f0                  = 1. _d -4
95        omega               = 2.D0 * PI / ( 3600.D0 * 24.D0 )        beta                = 1. _d -11
96        viscAh              = 0.D3  C-    Earth rotation period is 86400*365.25/366.25 (use to be 1.day)
97        diffKhT             = 0.D3        rotationPeriod      = 86164. _d 0
98        diffKhS             = 0.D3        viscAh              = 0. _d 3
99        viscArDefault       = 0.D-3        viscAhGrid          = 0. _d 0
100          viscAhGridMin       = 0. _d 0
101          viscAhGridMax       = 1. _d 21
102          viscAhMax           = 1. _d 21
103          viscAhReMax         = 0. _d 0
104          viscC2leith         = 0. _d 0
105          viscC2leithD        = 0. _d 0
106          viscC2smag          = 0. _d 0
107          diffKhT             = 0. _d 3
108          diffKhS             = 0. _d 3
109          viscArDefault       = 0. _d -3
110        no_slip_sides       = .TRUE.        no_slip_sides       = .TRUE.
111        no_slip_bottom      = .TRUE.        no_slip_bottom      = .TRUE.
112        diffKrTDefault      = 0.D-3        sideDragFactor      = 2. _d 0
113        diffKrSDefault      = 0.D-3        bottomDragLinear    = 0.
114        viscA4              = 0.D11        bottomDragQuadratic = 0.
115        diffK4T             = 0.D11        smoothAbsFuncRange  = 0. _d 0
116        diffK4S             = 0.D11        diffKrTDefault      = 0. _d -3
117          diffKrSDefault      = 0. _d -3
118          diffKrBL79surf      = 0. _d 0
119          diffKrBL79deep      = 0. _d 0
120          diffKrBL79scl       = 200. _d 0
121          diffKrBL79Ho        = -2000. _d 0
122          viscA4              = 0. _d 11
123          viscA4Grid          = 0. _d 0
124          viscA4GridMax       = 1. _d 21
125          viscA4GridMin       = 0. _d 0
126          viscA4Max           = 1. _d 21
127          viscA4ReMax         = 0. _d 0
128          viscC4leith         = 0. _d 0
129          viscC4leithD        = 0. _d 0
130          viscC4smag          = 0. _d 0
131          diffK4T             = 0. _d 11
132          diffK4S             = 0. _d 11
133        cosPower            = 0.        cosPower            = 0.
134        HeatCapacity_Cp     = 3994.D0        HeatCapacity_Cp     = 3994. _d 0
135        tAlpha              = 2.D-4  Cml      tAlpha              = 2. _d -4
136        sBeta               = 7.4D-4  Cml      sBeta               = 7.4 _d -4
137        eosType             = 'LINEAR'        eosType             = 'LINEAR'
138        buoyancyRelation    = 'OCEANIC'        buoyancyRelation    = 'OCEANIC'
139        implicitFreeSurface = .TRUE.        hFacMin             = 1. _d 0
140        rigidLid            = .FALSE.        hFacMinDrDefault    = 0. _d 0
141        implicSurfPress     = 1.D0        implicitIntGravWave = .FALSE.
       implicDiv2DFlow     = 1.D0  
       hFacMin             = 1.D0  
       hFacMinDrDefault    = 0.D0  
       exactConserv        = .FALSE.  
       uniformLin_PhiSurf  = .TRUE.  
       nonlinFreeSurf      = 0  
       hFacInf             = 1.D0  
       hFacSup             = 1.D0  
142        staggerTimeStep     = .FALSE.        staggerTimeStep     = .FALSE.
143        momViscosity        = .TRUE.        momViscosity        = .TRUE.
144        momAdvection        = .TRUE.        momAdvection        = .TRUE.
# Line 112  C--   Set default "physical" parameters Line 148  C--   Set default "physical" parameters
148        momStepping         = .TRUE.        momStepping         = .TRUE.
149        vectorInvariantMomentum = .FALSE.        vectorInvariantMomentum = .FALSE.
150        tempStepping        = .TRUE.        tempStepping        = .TRUE.
151          tempAdvection       = .TRUE.
152          tempForcing         = .TRUE.
153        saltStepping        = .TRUE.        saltStepping        = .TRUE.
154        tr1Stepping         = .FALSE.        saltAdvection       = .TRUE.
155          saltForcing         = .TRUE.
156        metricTerms         = .TRUE.        metricTerms         = .TRUE.
157          useNHMTerms         = .FALSE.
158          useFullLeith        = .FALSE.
159          useAreaViscLength   = .FALSE.
160          useStrainTensionVisc= .FALSE.
161        implicitDiffusion   = .FALSE.        implicitDiffusion   = .FALSE.
162        implicitViscosity   = .FALSE.        implicitViscosity   = .FALSE.
163          momImplVertAdv      = .FALSE.
164          tempImplVertAdv     = .FALSE.
165          saltImplVertAdv     = .FALSE.
166        nonHydrostatic      = .FALSE.        nonHydrostatic      = .FALSE.
167          quasiHydrostatic    = .FALSE.
168        globalFiles         = .FALSE.        globalFiles         = .FALSE.
169          useSingleCpuIO      = .FALSE.
170        allowFreezing       = .FALSE.        allowFreezing       = .FALSE.
171        ivdc_kappa          = 0.D0        useOldFreezing      = .FALSE.
172        groundAtK1          = .FALSE.        ivdc_kappa          = 0. _d 0
173        zonal_filt_lat      = 90.        usePickupBeforeC54    = .FALSE.
       zonal_filt_sinpow   = 2  
       zonal_filt_cospow   = 2  
       bottomDragLinear    = 0.  
       bottomDragQuadratic = 0.  
       usePickupBeforeC35    = .FALSE.  
174        debugMode             = .FALSE.        debugMode             = .FALSE.
       readPickupWithTracer  = .FALSE.  
       writePickupWithTracer = .FALSE.  
175        tempAdvScheme       = 2        tempAdvScheme       = 2
176        saltAdvScheme       = 2        saltAdvScheme       = 2
177        tracerAdvScheme     = 2        multiDimAdvection   = .TRUE.
178          useMultiDimAdvec    = .FALSE.
179          useCDscheme         = .FALSE.
180          useEnergyConservingCoriolis = .FALSE.
181          useJamartWetPoints  = .FALSE.
182          useJamartMomAdv     = .FALSE.
183          SadournyCoriolis    = .FALSE.
184          upwindVorticity     = .FALSE.
185          highOrderVorticity  = .FALSE.
186          useAbsVorticity     = .FALSE.
187          upwindShear         = .FALSE.
188          selectKEscheme      = 0
189          debugLevel          = debLevA
190          inAdMode            = .FALSE.
191          inAdExact           = .TRUE.
192    
193    C--   Set (free)surface-related parameters
194          implicitFreeSurface = .FALSE.
195          rigidLid            = .FALSE.
196          implicSurfPress     = 1. _d 0
197          implicDiv2DFlow     = 1. _d 0
198          exactConserv        = .FALSE.
199          linFSConserveTr     = .FALSE.
200          uniformLin_PhiSurf  = .TRUE.
201          nonlinFreeSurf      = 0
202          hFacInf             = 0.2 _d 0
203          hFacSup             = 2.0 _d 0
204          select_rStar        = 0
205          useRealFreshWaterFlux = .FALSE.
206          temp_EvPrRn = UNSET_RL
207          salt_EvPrRn = 0.
208          balanceEmPmR        = .FALSE.
209          balanceQnet         = .FALSE.
210          balancePrintMean    = .FALSE.
211    
212  C--   Atmospheric physical parameters (e.g.: EOS)  C--   Atmospheric physical parameters (e.g.: EOS)
213        atm_po =  1.D5        celsius2K = 273.16 _d 0
214        atm_cp =  1004.D0        atm_Po =  1. _d 5
215        atm_kappa = 2.D0 / 7.D0        atm_Cp = 1004. _d 0
216        Integr_GeoPot = 2        atm_Rd = UNSET_RL
217          atm_kappa = 2. _d 0 / 7. _d 0
218          atm_Rq = 0. _d 0
219          integr_GeoPot = 2
220          selectFindRoSurf = 0
221    
222  C--   Elliptic solver parameters  C--   Elliptic solver parameters
223        cg2dMaxIters       = 150        cg2dMaxIters       = 150
224        cg2dTargetResidual = 1.D-7        cg2dTargetResidual = 1. _d -7
225        cg2dTargetResWunit = -1.        cg2dTargetResWunit = -1.
226        cg2dChkResFreq     = 1        cg2dChkResFreq     = 1
227        cg2dpcOffDFac      = 0.51D0        cg2dpcOffDFac      = 0.51 _d 0
228          cg2dPreCondFreq    = 1
229        cg3dMaxIters       = 150        cg3dMaxIters       = 150
230        cg3dTargetResidual = 1.D-7        cg3dTargetResidual = 1. _d -7
231        cg3dChkResFreq     = 1        cg3dChkResFreq     = 1
232    
233  C--   Time stepping parameters  C--   Time stepping parameters
234        deltaT            = 0.        deltaT            = 0. _d 0
235          deltaTmom         = 0. _d 0
236          deltaTfreesurf    = 0. _d 0
237          DO k=1,Nr
238            dTtracerLev(k)  = 0. _d 0
239          ENDDO
240          baseTime          = 0. _d 0
241        nIter0            = 0        nIter0            = 0
242        startTime         = deltaT*float(nIter0)        startTime         = deltaT*float(nIter0)
243          pickupSuff        = ' '
244        nTimeSteps        = 0        nTimeSteps        = 0
245        nEndIter          = nIter0+nTimeSteps        nEndIter          = nIter0+nTimeSteps
246        endTime           = deltaT*float(nEndIter)        endTime           = deltaT*float(nEndIter)
247        abEps             = 0.01        momForcingOutAB   = UNSET_I
248        pchkPtFreq        = deltaT*0        tracForcingOutAB  = UNSET_I
249          momDissip_In_AB   = .TRUE.
250          doAB_onGtGs       = .TRUE.
251          abEps             = 0.01 _d 0
252    #ifdef ALLOW_ADAMSBASHFORTH_3
253          alph_AB           = 0.5 _d 0
254          beta_AB           = 5. _d 0 / 12. _d 0
255          startFromPickupAB2= .FALSE.
256    #else
257          alph_AB           = UNSET_RL
258          beta_AB           = UNSET_RL
259          startFromPickupAB2= .TRUE.
260    #endif
261          pChkPtFreq        = deltaT*0
262        chkPtFreq         = deltaT*0        chkPtFreq         = deltaT*0
263          outputTypesInclusive = .FALSE.
264          pickup_read_mdsio = .TRUE.
265          pickup_write_mdsio= .TRUE.
266          pickup_write_immed= .FALSE.
267        dumpFreq          = deltaT*0        dumpFreq          = deltaT*0
268          adjDumpFreq       = deltaT*0
269        diagFreq          = deltaT*0        diagFreq          = deltaT*0
270          dumpInitAndLast   = .TRUE.
271          snapshot_mdsio    = .TRUE.
272        monitorFreq       = -1.        monitorFreq       = -1.
273          adjMonitorFreq    = 0.
274          monitor_stdio     = .TRUE.
275        taveFreq          = deltaT*0        taveFreq          = deltaT*0
276          timeave_mdsio     = .TRUE.
277          tave_lastIter     = 0.5 _d 0
278        writeStatePrec    = precFloat64        writeStatePrec    = precFloat64
279        writeBinaryPrec   = precFloat32        writeBinaryPrec   = precFloat32
280        readBinaryPrec    = precFloat32        readBinaryPrec    = precFloat32
281        nCheckLev         = 1        nCheckLev         = 1
282        checkPtSuff(1)    = 'ckptA'        checkPtSuff(1)    = 'ckptA'
283        checkPtSuff(2)    = 'ckptB'        checkPtSuff(2)    = 'ckptB'
284        cAdjFreq          =  0.D0        cAdjFreq          =  0. _d 0
285        tauCD             =  0.D0        tauCD             =  0. _d 0
286        tauThetaClimRelax =  0.D0        tauThetaClimRelax =  0. _d 0
287        tauSaltClimRelax  =  0.D0        tauSaltClimRelax  =  0. _d 0
288        tauTr1ClimRelax   =  0.D0        tauTr1ClimRelax   =  0. _d 0
289        periodicExternalForcing = .FALSE.        periodicExternalForcing = .FALSE.
290        externForcingPeriod     = 0.        externForcingPeriod     = 0.
291        externForcingCycle      = 0.        externForcingCycle      = 0.
292          tCylIn             = 0.
293          tCylOut            = 20.
294    
295  C--   Input files  C--   Input files
296        bathyFile       = ' '        bathyFile       = ' '
297        topoFile        = ' '        topoFile        = ' '
298          shelfIceFile    = ' '
299        hydrogSaltFile  = ' '        hydrogSaltFile  = ' '
300        hydrogThetaFile = ' '        hydrogThetaFile = ' '
301          diffKr3dSfile   = ' '
302          diffKr3dTfile   = ' '
303        zonalWindFile   = ' '        zonalWindFile   = ' '
304        meridWindFile   = ' '        meridWindFile   = ' '
305        thetaClimFile   = ' '        thetaClimFile   = ' '
306        saltClimFile    = ' '        saltClimFile    = ' '
307        EmPmRfile       = ' '        EmPmRfile       = ' '
308          saltFluxFile    = ' '
309        surfQfile       = ' '        surfQfile       = ' '
310        surfQswfile     = ' '        surfQnetFile    = ' '
311          surfQswFile     = ' '
312        uVelInitFile    = ' '        uVelInitFile    = ' '
313        vVelInitFile    = ' '        vVelInitFile    = ' '
314        pSurfInitFile   = ' '        pSurfInitFile   = ' '
315        dQdTFile        = ' '        dQdTFile        = ' '
316          ploadFile       = ' '
317          eddyTauxFile    = ' '
318          eddyTauyFile    = ' '
319          lambdaThetaFile = ' '
320          lambdaSaltFile  = ' '
321          mdsioLocalDir   = ' '
322          the_run_name    = ' '
323    
 C  
324        RETURN        RETURN
325        END        END
   

Legend:
Removed from v.1.26  
changed lines
  Added in v.1.124

  ViewVC Help
Powered by ViewVC 1.1.22