/[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.4 by adcroft, Tue Jun 29 18:33:26 1999 UTC revision 1.83 by heimbach, Thu Feb 10 05:25:37 2005 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, 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    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 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        rkFacDefault         = 1.D0
44        horiVertRatio        = 1.D0        horiVertRatio        = 1.D0
45          Ro_SeaLevel = 0.
46        DO k=1,Nr        DO k=1,Nr
47         delRdefault(k) = 0.         delRdefault(k) = 0.
48        ENDDO        ENDDO
49          DO k=1,Nr+1
50           delRc(k) = UNSET_RL
51          ENDDO
52    
53  C     Horizontal gridding  C     Horizontal gridding
54  C     In cartesian coords distances are in metres  C     In cartesian coords distances are in metres
55        usingCartesianGrid = .TRUE.        usingCartesianGrid = .FALSE.
56        DO i=1,Nx        DO i=1,Nx
57         delX(i) = 0.         delX(i) = UNSET_RL
58        ENDDO        ENDDO
59        DO j=1,Ny        DO j=1,Ny
60         delY(j) = 0.         delY(j) = UNSET_RL
61        ENDDO        ENDDO
62  C     In spherical polar distances are in degrees  C     In spherical polar distances are in degrees
63        usingSphericalPolarGrid = .FALSE.        usingSphericalPolarGrid = .FALSE.
64        phiMin               = 0.0        phiMin               = 0.0
65        thetaMin             = 0.        thetaMin             = 0.
66        rSphere              = 6370. * 1.D3        rSphere              = 6370. * 1.D3
67    C     General curvilinear coordinate system
68          usingCurvilinearGrid = .FALSE.
69    C     General cylindrical coordinate system
70          usingCylindricalGrid = .FALSE.
71    C     Coriolis map:
72          useConstantF  = .FALSE.
73          useBetaPlaneF = .FALSE.
74          useSphereF    = .FALSE.
75    
76    
77  C--   Set default "physical" parameters  C--   Set default "physical" parameters
78        DO K =1,Nr        DO K =1,Nr
79         tRef(K) = 30.D0 - FLOAT( K )         tRef(K) = 30.D0 - FLOAT( K )
80    Cml       sRef(K) = 35.D0
81        ENDDO        ENDDO
82        gravity             = 9.81D0        gravity             = 9.81D0
83        rhoNil              = 999.8D0        rhoNil              = 999.8D0
84    C-- jmc : the default is to set rhoConstFresh to rhoConst (=rhoNil by default)
85    C         (so that the default produces same results as before)
86    c     rhoConstFresh       = 999.8D0
87        f0                  = 1.D-4        f0                  = 1.D-4
88        beta                = 1.D-11        beta                = 1.D-11
89    C-    Always use 1 day in the past but should be 86164 (=86400*365.25/366.25)
90          rotationPeriod      = 86400. _d 0
91        viscAh              = 0.D3        viscAh              = 0.D3
92          viscAhGrid          = 0.D0
93          viscAhMax           = 1.D21
94          viscC2leith         = 0.D0
95          viscAstrain         = 0.D3
96          viscAtension        = 0.D3
97        diffKhT             = 0.D3        diffKhT             = 0.D3
98        diffKhS             = 0.D3        diffKhS             = 0.D3
99        viscArDefault       = 0.D-3        viscArDefault       = 0.D-3
# Line 79  C--   Set default "physical" parameters Line 101  C--   Set default "physical" parameters
101        no_slip_bottom      = .TRUE.        no_slip_bottom      = .TRUE.
102        diffKrTDefault      = 0.D-3        diffKrTDefault      = 0.D-3
103        diffKrSDefault      = 0.D-3        diffKrSDefault      = 0.D-3
104          diffKrBL79surf      = 0.D0
105          diffKrBL79deep      = 0.D0
106          diffKrBL79scl       = 200.D0
107          diffKrBL79Ho        = -2000.D0
108        viscA4              = 0.D11        viscA4              = 0.D11
109          viscA4Grid          = 0.D0
110          viscA4GridMax       = 0.D0
111          viscA4GridMin       = 0.D0
112          viscA4Max           = 1.D21
113          viscC4leith         = 0.D0
114        diffK4T             = 0.D11        diffK4T             = 0.D11
115        diffK4S             = 0.D11        diffK4S             = 0.D11
116        cosPower            = 0.        cosPower            = 0.
       GMmaxslope          = 1.D-2  
       GMlength            = 200.D3  
       GMalpha             = 0.D0  
       GMdepth             = 1000.D0  
       GMkbackground       = 0.D0  
       GMmaxval            = 2500.D0  
117        HeatCapacity_Cp     = 3994.D0        HeatCapacity_Cp     = 3994.D0
118        tAlpha              = 2.D-4  Cml      tAlpha              = 2.D-4
119        sBeta               = 7.4D-4  Cml      sBeta               = 7.4D-4
120        eosType             = 'LINEAR'        eosType             = 'LINEAR'
121        buoyancyRelation    = 'OCEANIC'        buoyancyRelation    = 'OCEANIC'
       implicitFreeSurface = .TRUE.  
       rigidLid            = .FALSE.  
122        hFacMin             = 1.D0        hFacMin             = 1.D0
123        hFacMinDrDefault    = 0.D0        hFacMinDrDefault    = 0.D0
124          staggerTimeStep     = .FALSE.
125        momViscosity        = .TRUE.        momViscosity        = .TRUE.
126        momAdvection        = .TRUE.        momAdvection        = .TRUE.
127        momForcing          = .TRUE.        momForcing          = .TRUE.
128        useCoriolis         = .TRUE.        useCoriolis         = .TRUE.
129        momPressureForcing  = .TRUE.        momPressureForcing  = .TRUE.
130        momStepping         = .TRUE.        momStepping         = .TRUE.
131          vectorInvariantMomentum = .FALSE.
132        tempStepping        = .TRUE.        tempStepping        = .TRUE.
133          tempAdvection       = .TRUE.
134          tempForcing         = .TRUE.
135        saltStepping        = .TRUE.        saltStepping        = .TRUE.
136        metricTerms         = .FALSE.        saltAdvection       = .TRUE.
137          saltForcing         = .TRUE.
138          metricTerms         = .TRUE.
139          useNHMTerms         = .FALSE.
140        implicitDiffusion   = .FALSE.        implicitDiffusion   = .FALSE.
141        openBoundaries      = .FALSE.        implicitViscosity   = .FALSE.
142          momImplVertAdv      = .FALSE.
143          tempImplVertAdv     = .FALSE.
144          saltImplVertAdv     = .FALSE.
145        nonHydrostatic      = .FALSE.        nonHydrostatic      = .FALSE.
146          quasiHydrostatic    = .FALSE.
147        globalFiles         = .FALSE.        globalFiles         = .FALSE.
148          useSingleCpuIO      = .FALSE.
149        allowFreezing       = .FALSE.        allowFreezing       = .FALSE.
150          useOldFreezing      = .FALSE.
151          ivdc_kappa          = 0.D0
152          groundAtK1          = .FALSE.
153          bottomDragLinear    = 0.
154          bottomDragQuadratic = 0.
155          usePickupBeforeC35    = .FALSE.
156          usePickupBeforeC54    = .FALSE.
157          debugMode             = .FALSE.
158          readPickupWithTracer  = .FALSE.
159          writePickupWithTracer = .FALSE.
160          tempAdvScheme       = 2
161          saltAdvScheme       = 2
162          multiDimAdvection   = .TRUE.
163          useCDscheme         = .FALSE.
164          useEnergyConservingCoriolis = .FALSE.
165          useJamartWetPoints  = .FALSE.
166          useJamartMomAdv     = .FALSE.
167          SadournyCoriolis    = .FALSE.
168          upwindVorticity     = .FALSE.
169          highOrderVorticity  = .FALSE.
170          useAbsVorticity     = .FALSE.
171          debugLevel          = debLevA
172          inAdMode            = .FALSE.
173          inAdExact           = .TRUE.
174    
175    C--   Set (free)surface-related parameters
176          implicitFreeSurface = .TRUE.
177          rigidLid            = .FALSE.
178          implicSurfPress     = 1.D0
179          implicDiv2DFlow     = 1.D0
180          exactConserv        = .FALSE.
181          uniformLin_PhiSurf  = .TRUE.
182          nonlinFreeSurf      = 0
183          hFacInf             = 0.2 _d 0
184          hFacSup             = 2.0 _d 0
185          select_rStar        = 0
186          useRealFreshWaterFlux = .FALSE.
187          temp_EvPrRn = UNSET_RL
188          salt_EvPrRn = 0.
189    
190    C--   Atmospheric physical parameters (e.g.: EOS)
191          celsius2K = 273.16 _d 0
192          atm_Po =  1. _d 5
193          atm_Cp = 1004. _d 0
194          atm_Rd = UNSET_RL
195          atm_kappa = 2. _d 0 / 7. _d 0
196          atm_Rq = 0. _d 0
197          integr_GeoPot = 2
198          selectFindRoSurf = 0
199    
200  C--   Elliptic solver parameters  C--   Elliptic solver parameters
201        cg2dMaxIters       = 150        cg2dMaxIters       = 150
202        cg2dTargetResidual = 1.D-7        cg2dTargetResidual = 1.D-7
203          cg2dTargetResWunit = -1.
204        cg2dChkResFreq     = 1        cg2dChkResFreq     = 1
205        cg2dpcOffDFac      = 0.51D0        cg2dpcOffDFac      = 0.51D0
206          cg2dPreCondFreq    = 1
207        cg3dMaxIters       = 150        cg3dMaxIters       = 150
208        cg3dTargetResidual = 1.D-7        cg3dTargetResidual = 1.D-7
209        cg3dChkResFreq     = 1        cg3dChkResFreq     = 1
210    
211  C--   Time stepping parameters  C--   Time stepping parameters
212        deltaT            = 0.        deltaT            = 0. _d 0
213          deltaTmom         = 0. _d 0
214          deltaTfreesurf    = 0. _d 0
215          DO k=1,Nr
216            dTtracerLev(k)  = 0. _d 0
217          ENDDO
218        nIter0            = 0        nIter0            = 0
219        startTime         = deltaT*float(nIter0)        startTime         = deltaT*float(nIter0)
220          pickupSuff        = ' '
221        nTimeSteps        = 0        nTimeSteps        = 0
222        endTime           = deltaT*float(nTimeSteps)        nEndIter          = nIter0+nTimeSteps
223          endTime           = deltaT*float(nEndIter)
224          forcing_In_AB     = .TRUE.
225        abEps             = 0.01        abEps             = 0.01
226        pchkPtFreq        = deltaT*0        pchkPtFreq        = deltaT*0
227        chkPtFreq         = deltaT*0        chkPtFreq         = deltaT*0
228          outputTypesInclusive = .FALSE.
229          pickup_read_mdsio = .TRUE.
230          pickup_write_mdsio= .TRUE.
231          pickup_write_immed= .FALSE.
232        dumpFreq          = deltaT*0        dumpFreq          = deltaT*0
233          adjDumpFreq       = deltaT*0
234          diagFreq          = deltaT*0
235          snapshot_mdsio    = .TRUE.
236          monitorFreq       = -1.
237          adjMonitorFreq    = 0.
238          monitor_stdio     = .TRUE.
239        taveFreq          = deltaT*0        taveFreq          = deltaT*0
240          timeave_mdsio     = .TRUE.
241          tave_lastIter     = 0.5 _d 0
242        writeStatePrec    = precFloat64        writeStatePrec    = precFloat64
243        writeBinaryPrec   = precFloat32        writeBinaryPrec   = precFloat32
244        readBinaryPrec    = precFloat32        readBinaryPrec    = precFloat32
245        nCheckLev         = 1        nCheckLev         = 1
246        checkPtSuff(1)    = 'ckptA'        checkPtSuff(1)    = 'ckptA'
247        checkPtSuff(2)    = 'ckptB'        checkPtSuff(2)    = 'ckptB'
248        cAdjFreq          = -1.D0        cAdjFreq          =  0.D0
249        tauCD             =  0.D0        tauCD             =  0.D0
250        tauThetaClimRelax =  0.D0        tauThetaClimRelax =  0.D0
251        tauSaltClimRelax  =  0.D0        tauSaltClimRelax  =  0.D0
252          tauTr1ClimRelax   =  0.D0
253        periodicExternalForcing = .FALSE.        periodicExternalForcing = .FALSE.
254        externForcingPeriod     = 0.        externForcingPeriod     = 0.
255        externForcingCycle      = 0.        externForcingCycle      = 0.
256          tCylIn             = 0.
257          tCylOut            = 20.
258    
259  C--   Input files  C--   Input files
260        bathyFile       = ' '        bathyFile       = ' '
261          topoFile        = ' '
262        hydrogSaltFile  = ' '        hydrogSaltFile  = ' '
263        hydrogThetaFile = ' '        hydrogThetaFile = ' '
264        zonalWindFile   = ' '        zonalWindFile   = ' '
# Line 156  C--   Input files Line 266  C--   Input files
266        thetaClimFile   = ' '        thetaClimFile   = ' '
267        saltClimFile    = ' '        saltClimFile    = ' '
268        EmPmRfile       = ' '        EmPmRfile       = ' '
269          saltFluxFile    = ' '
270        surfQfile       = ' '        surfQfile       = ' '
271          surfQnetFile    = ' '
272  C--   OBCS        surfQswFile     = ' '
273        DO I=1,Nx        uVelInitFile    = ' '
274         OB_Jnorth(I)=0        vVelInitFile    = ' '
275         OB_Jsouth(I)=0        pSurfInitFile   = ' '
276        ENDDO        dQdTFile        = ' '
277        DO J=1,Ny        ploadFile       = ' '
278         OB_Ieast(J)=0        mdsioLocalDir   = ' '
        OB_Iwest(J)=0  
       ENDDO  
279    
280  C  C
281        RETURN        RETURN
282        END        END
   

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.83

  ViewVC Help
Powered by ViewVC 1.1.22