/[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.52 by jmc, Wed Oct 15 22:55:51 2003 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    CBOP
7    C     !ROUTINE: SET_DEFAULTS
8    C     !INTERFACE:
9        SUBROUTINE SET_DEFAULTS(        SUBROUTINE SET_DEFAULTS(
10       O   viscArDefault, diffKrTDefault, diffKrSDefault,       O   viscArDefault, diffKrTDefault, diffKrSDefault,
11       O   hFacMinDrDefault, delRdefault,       O   hFacMinDrDefault, delRdefault, rkFacDefault,
12       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  
13    
14    C     !DESCRIPTION: \bv
15    C     *==========================================================*
16    C     | SUBROUTINE SET_DEFAULTS                                  
17    C     | o Routine to set model "parameters"                      
18    C     *==========================================================*
19    C     | Notes:                                                    
20    C     | ======                                                    
21    C     | The present version of this routine is a place-holder.    
22    C     | A production version needs to handle parameters from an  
23    C     | external file and possibly reading in some initial field  
24    C     | values.                                                  
25    C     *==========================================================*
26    C     \ev
27    
28    C     !USES:
29          IMPLICIT NONE
30  C     === Global variables ===  C     === Global variables ===
31  #include "SIZE.h"  #include "SIZE.h"
32  #include "EEPARAMS.h"  #include "EEPARAMS.h"
33  #include "PARAMS.h"  #include "PARAMS.h"
34    Cml#include "EOS.h"
35  #include "GRID.h"  #include "GRID.h"
 #include "CG2D.h"  
36    
37    C     !INPUT/OUTPUT PARAMETERS:
38  C     === Routine arguments ===  C     === Routine arguments ===
39  C     myThid - Number of this instance of INI_PARMS  C     myThid - Number of this instance of INI_PARMS
40        INTEGER myThid        INTEGER myThid
# Line 34  C     myThid - Number of this instance o Line 43  C     myThid - Number of this instance o
43        _RL diffKrSDefault        _RL diffKrSDefault
44        _RL hFacMinDrDefault        _RL hFacMinDrDefault
45        _RL delRDefault(Nr)        _RL delRDefault(Nr)
46          _RS rkFacDefault
47    
48    C     !LOCAL VARIABLES:
49  C     === Local variables ===  C     === Local variables ===
50  C     K, I, J - Loop counters  C     K, I, J - Loop counters
51        INTEGER K, I, J        INTEGER K, I, J
52    CEOP
53    
54  C--   Grid parameters  C--   Grid parameters
55  C     Vertical gridding  C     Vertical gridding
56        rkFac = 1.D0        rkFacDefault         = 1.D0
57        horiVertRatio = 1.D0        horiVertRatio        = 1.D0
58          Ro_SeaLevel = 0.
59        DO k=1,Nr        DO k=1,Nr
60         delRdefault(k) = 1.D2         delRdefault(k) = 0.
61          ENDDO
62          DO k=1,Nr+1
63           delRc(k) = UNSET_RL
64        ENDDO        ENDDO
65    
66  C     Horizontal gridding  C     Horizontal gridding
67  C     In cartesian coords distances are in metres  C     In cartesian coords distances are in metres
68        usingCartesianGrid = .TRUE.        usingCartesianGrid = .TRUE.
69        DO i=1,Nx        DO i=1,Nx
70         delX(i) = 20.D0 * 1000.D0         delX(i) = UNSET_RL
71        ENDDO        ENDDO
72        DO j=1,Ny        DO j=1,Ny
73         delY(j) = 20.D0 * 1000.D0         delY(j) = UNSET_RL
74        ENDDO        ENDDO
75  C     In spherical polar distances are in degrees  C     In spherical polar distances are in degrees
76        usingSphericalPolarGrid = .FALSE.        usingSphericalPolarGrid = .FALSE.
77        phiMin    = -5.0        phiMin               = 0.0
78        thetaMin  = 0.        thetaMin             = 0.
79        rSphere   = 6370. * 1.D3        rSphere              = 6370. * 1.D3
80        IF ( usingSphericalPolarGrid ) THEN  C     General curvilinear coordinate system
81         DO i=1,Nx        usingCurvilinearGrid = .FALSE.
         delX(i) = 1.D0  
        ENDDO  
        DO j=1,Ny  
         delY(j) = 1.D0  
        ENDDO  
       ENDIF  
 C  
82    
83  C--   Set default "physical" parameters  C--   Set default "physical" parameters
84        DO K =1,Nr        DO K =1,Nr
85         tRef(K) = 30.D0 - FLOAT( K )         tRef(K) = 30.D0 - FLOAT( K )
86    Cml       sRef(K) = 35.D0
87        ENDDO        ENDDO
88        gravity  = 9.81D0        gravity             = 9.81D0
89        rhoNil   = 999.8D0        rhoNil              = 999.8D0
90        f0       = 1.D-4        rhoConstFresh       = 999.8D0
91        beta     = 1.D-11        f0                  = 1.D-4
92        viscAh   = 1.D3        beta                = 1.D-11
93        diffKhT  = 1.D3  C-    Always use 1 day in the past but should be 86164 (=86400*365.25/366.25)
94        diffKhS  = 1.D3        rotationPeriod      = 86400. _d 0
95        viscArDefault = 1.D-3        viscAh              = 0.D3
96        no_slip_sides = .TRUE.        viscAstrain         = 0.D3
97        no_slip_bottom = .TRUE.        viscAtension        = 0.D3
98        diffKrTDefault = 1.D-5        diffKhT             = 0.D3
99        diffKrSDefault = 1.D-5        diffKhS             = 0.D3
100        viscA4   = 0.        viscArDefault       = 0.D-3
101        diffK4T  = 0.        no_slip_sides       = .TRUE.
102        diffK4S  = 0.        no_slip_bottom      = .TRUE.
103        GMmaxslope   =   1.D-2        diffKrTDefault      = 0.D-3
104        GMlength     = 200.D3        diffKrSDefault      = 0.D-3
105        GMalpha      = 0.D0        viscA4              = 0.D11
106        GMdepth      = 1000.D0        diffK4T             = 0.D11
107        GMkbackground= 0.D0        diffK4S             = 0.D11
108        GMmaxval     = 2500.D0        cosPower            = 0.
109        HeatCapacity_Cp = 3994.D0        HeatCapacity_Cp     = 3994.D0
110        tAlpha       = 2.D-4  Cml      tAlpha              = 2.D-4
111        sBeta        = 7.4D-4  Cml      sBeta               = 7.4D-4
112        eosType      = 'LINEAR'        eosType             = 'LINEAR'
113        buoyancyRelation    = 'OCEANIC'        buoyancyRelation    = 'OCEANIC'
       implicitFreeSurface = .TRUE.  
       rigidLid            = .FALSE.  
114        hFacMin             = 1.D0        hFacMin             = 1.D0
115        hFacMinDrDefault    = 0.D0        hFacMinDrDefault    = 0.D0
116          staggerTimeStep     = .FALSE.
117        momViscosity        = .TRUE.        momViscosity        = .TRUE.
118        momAdvection        = .TRUE.        momAdvection        = .TRUE.
119        momForcing          = .TRUE.        momForcing          = .TRUE.
120        useCoriolis         = .TRUE.        useCoriolis         = .TRUE.
121        momPressureForcing  = .TRUE.        momPressureForcing  = .TRUE.
122        momStepping         = .TRUE.        momStepping         = .TRUE.
123          vectorInvariantMomentum = .FALSE.
124        tempStepping        = .TRUE.        tempStepping        = .TRUE.
125          tempAdvection       = .TRUE.
126          tempForcing         = .TRUE.
127        saltStepping        = .TRUE.        saltStepping        = .TRUE.
128        metricTerms         = .FALSE.        saltAdvection       = .TRUE.
129          saltForcing         = .TRUE.
130          tr1Stepping         = .FALSE.
131          metricTerms         = .TRUE.
132          useNHMTerms         = .TRUE.
133        implicitDiffusion   = .FALSE.        implicitDiffusion   = .FALSE.
134        openBoundaries      = .FALSE.        implicitViscosity   = .FALSE.
135          nonHydrostatic      = .FALSE.
136          quasiHydrostatic    = .FALSE.
137          globalFiles         = .FALSE.
138          useSingleCpuIO      = .FALSE.
139          allowFreezing       = .FALSE.
140          ivdc_kappa          = 0.D0
141          groundAtK1          = .FALSE.
142          bottomDragLinear    = 0.
143          bottomDragQuadratic = 0.
144          usePickupBeforeC35    = .FALSE.
145          debugMode             = .FALSE.
146          readPickupWithTracer  = .FALSE.
147          writePickupWithTracer = .FALSE.
148          tempAdvScheme       = 2
149          saltAdvScheme       = 2
150          tracerAdvScheme     = 2
151          multiDimAdvection   = .TRUE.
152          useCDscheme         = .FALSE.
153          useEnergyConservingCoriolis = .FALSE.
154          useJamartWetPoints  = .FALSE.
155          debugLevel          = debLevA
156    
157    C--   Set (free)surface-related parameters
158          implicitFreeSurface = .TRUE.
159          rigidLid            = .FALSE.
160          implicSurfPress     = 1.D0
161          implicDiv2DFlow     = 1.D0
162          exactConserv        = .FALSE.
163          uniformLin_PhiSurf  = .TRUE.
164          nonlinFreeSurf      = 0
165          hFacInf             = 0.2 _d 0
166          hFacSup             = 2.0 _d 0
167          select_rStar        = 0
168          useRealFreshWaterFlux = .FALSE.
169          temp_EvPrRn = UNSET_RL
170          salt_EvPrRn = 0.
171          trac_EvPrRn = UNSET_RL
172    
173    C--   Atmospheric physical parameters (e.g.: EOS)
174          celsius2K = 273.16 _d 0
175          atm_Po =  1. _d 5
176          atm_Cp = 1004. _d 0
177          atm_Rd = UNSET_RL
178          atm_kappa = 2. _d 0 / 7. _d 0
179          atm_Rq = 0. _d 0
180          integr_GeoPot = 2
181          selectFindRoSurf = 0
182    
183  C--   Elliptic solver parameters  C--   Elliptic solver parameters
184        cg2dMaxIters       = 150        cg2dMaxIters       = 150
185        cg2dTargetResidual = 1.D-7        cg2dTargetResidual = 1.D-7
186          cg2dTargetResWunit = -1.
187        cg2dChkResFreq     = 1        cg2dChkResFreq     = 1
188          cg2dpcOffDFac      = 0.51D0
189        cg3dMaxIters       = 150        cg3dMaxIters       = 150
190        cg3dTargetResidual = 1.D-7        cg3dTargetResidual = 1.D-7
191        cg3dChkResFreq     = 1        cg3dChkResFreq     = 1
       cg2dpcOffDFac      = 0.51D0  
192    
193  C--   Time stepping parameters  C--   Time stepping parameters
194        deltaT            = 0.        deltaT            = 0.
195        nIter0            = 0        nIter0            = 0
196        startTime         = deltaT*float(nIter0)        startTime         = deltaT*float(nIter0)
197        nTimeSteps        = 100        pickupSuff        = ' '
198        endTime           = deltaT*float(nTimeSteps)        nTimeSteps        = 0
199          nEndIter          = nIter0+nTimeSteps
200          endTime           = deltaT*float(nEndIter)
201          forcing_In_AB     = .TRUE.
202        abEps             = 0.01        abEps             = 0.01
203        pchkPtFreq        = deltaT*0        pchkPtFreq        = deltaT*0
204        chkPtFreq         = deltaT*0        chkPtFreq         = deltaT*0
205        dumpFreq          = deltaT*50        dumpFreq          = deltaT*0
206          diagFreq          = deltaT*0
207          monitorFreq       = -1.
208        taveFreq          = deltaT*0        taveFreq          = deltaT*0
209          tave_lastIter     = 0.5 _d 0
210        writeStatePrec    = precFloat64        writeStatePrec    = precFloat64
211        writeBinaryPrec   = precFloat32        writeBinaryPrec   = precFloat32
212        readBinaryPrec    = precFloat32        readBinaryPrec    = precFloat32
213        nCheckLev         = 1        nCheckLev         = 1
214        checkPtSuff(1)    = 'ckptA'        checkPtSuff(1)    = 'ckptA'
215        checkPtSuff(2)    = 'ckptB'        checkPtSuff(2)    = 'ckptB'
216        cAdjFreq          = -1.D0        cAdjFreq          =  0.D0
217        tauCD             =  0.D0        tauCD             =  0.D0
218        tauThetaClimRelax =  0.D0        tauThetaClimRelax =  0.D0
219        tauSaltClimRelax  =  0.D0        tauSaltClimRelax  =  0.D0
220          tauTr1ClimRelax   =  0.D0
221        periodicExternalForcing = .FALSE.        periodicExternalForcing = .FALSE.
222        externForcingPeriod     = 0.        externForcingPeriod     = 0.
223        externForcingCycle      = 0.        externForcingCycle      = 0.
224    
225  C--   Input files  C--   Input files
226        bathyFile       = ' '        bathyFile       = ' '
227          topoFile        = ' '
228        hydrogSaltFile  = ' '        hydrogSaltFile  = ' '
229        hydrogThetaFile = ' '        hydrogThetaFile = ' '
230        zonalWindFile   = ' '        zonalWindFile   = ' '
231        meridWindFile   = ' '        meridWindFile   = ' '
232        thetaClimFile   = ' '        thetaClimFile   = ' '
233        saltClimFile    = ' '        saltClimFile    = ' '
234          EmPmRfile       = ' '
235  C--   OBCS        surfQfile       = ' '
236        DO I=1,Nx        surfQswfile     = ' '
237         OB_Jnorth(I)=0        uVelInitFile    = ' '
238         OB_Jsouth(I)=0        vVelInitFile    = ' '
239        ENDDO        pSurfInitFile   = ' '
240        DO J=1,Ny        dQdTFile        = ' '
241         OB_Ieast(J)=0        ploadFile       = ' '
242         OB_Iwest(J)=0        mdsioLocalDir   = ' '
       ENDDO  
243    
244  C  C
245        RETURN        RETURN
246        END        END
   

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

  ViewVC Help
Powered by ViewVC 1.1.22