/[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.27 by adcroft, Thu Sep 6 14:23:57 2001 UTC revision 1.58 by adcroft, Sat Feb 7 16:27:19 2004 UTC
# Line 3  C $Name$ Line 3  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, rkFacDefault,       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"
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 36  C     myThid - Number of this instance o Line 45  C     myThid - Number of this instance o
45        _RL delRDefault(Nr)        _RL delRDefault(Nr)
46        _RS rkFacDefault        _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
# Line 48  C     Vertical gridding Line 59  C     Vertical gridding
59        DO k=1,Nr        DO k=1,Nr
60         delRdefault(k) = 0.         delRdefault(k) = 0.
61        ENDDO        ENDDO
62          DO k=1,Nr+1
63           delRc(k) = UNSET_RL
64          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 = .FALSE.
69        DO i=1,Nx        DO i=1,Nx
70         delX(i) = UNSET_RL         delX(i) = UNSET_RL
71        ENDDO        ENDDO
# Line 69  C     General curvilinear coordinate sys Line 83  C     General curvilinear coordinate sys
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    C-- jmc : the default is to set rhoConstFresh to rhoConst (=rhoNil by default)
91    C         (so that the default produces same results as before)
92    c     rhoConstFresh       = 999.8D0
93        f0                  = 1.D-4        f0                  = 1.D-4
94        beta                = 1.D-11        beta                = 1.D-11
95        omega               = 2.D0 * PI / ( 3600.D0 * 24.D0 )  C-    Always use 1 day in the past but should be 86164 (=86400*365.25/366.25)
96          rotationPeriod      = 86400. _d 0
97        viscAh              = 0.D3        viscAh              = 0.D3
98          viscAhGrid          = 0.D0
99          viscAhMax           = 1.D21
100        viscAstrain         = 0.D3        viscAstrain         = 0.D3
101        viscAtension        = 0.D3        viscAtension        = 0.D3
102        diffKhT             = 0.D3        diffKhT             = 0.D3
# Line 86  C--   Set default "physical" parameters Line 107  C--   Set default "physical" parameters
107        diffKrTDefault      = 0.D-3        diffKrTDefault      = 0.D-3
108        diffKrSDefault      = 0.D-3        diffKrSDefault      = 0.D-3
109        viscA4              = 0.D11        viscA4              = 0.D11
110          viscA4Grid          = 0.D0
111          viscA4Max           = 1.D21
112        diffK4T             = 0.D11        diffK4T             = 0.D11
113        diffK4S             = 0.D11        diffK4S             = 0.D11
114        cosPower            = 0.        cosPower            = 0.
115        HeatCapacity_Cp     = 3994.D0        HeatCapacity_Cp     = 3994.D0
116        tAlpha              = 2.D-4  Cml      tAlpha              = 2.D-4
117        sBeta               = 7.4D-4  Cml      sBeta               = 7.4D-4
118        eosType             = 'LINEAR'        eosType             = 'LINEAR'
119        buoyancyRelation    = 'OCEANIC'        buoyancyRelation    = 'OCEANIC'
       implicitFreeSurface = .TRUE.  
       rigidLid            = .FALSE.  
       implicSurfPress     = 1.D0  
       implicDiv2DFlow     = 1.D0  
120        hFacMin             = 1.D0        hFacMin             = 1.D0
121        hFacMinDrDefault    = 0.D0        hFacMinDrDefault    = 0.D0
       exactConserv        = .FALSE.  
       uniformLin_PhiSurf  = .TRUE.  
       nonlinFreeSurf      = 0  
       hFacInf             = 1.D0  
       hFacSup             = 1.D0  
122        staggerTimeStep     = .FALSE.        staggerTimeStep     = .FALSE.
123        momViscosity        = .TRUE.        momViscosity        = .TRUE.
124        momAdvection        = .TRUE.        momAdvection        = .TRUE.
# Line 114  C--   Set default "physical" parameters Line 128  C--   Set default "physical" parameters
128        momStepping         = .TRUE.        momStepping         = .TRUE.
129        vectorInvariantMomentum = .FALSE.        vectorInvariantMomentum = .FALSE.
130        tempStepping        = .TRUE.        tempStepping        = .TRUE.
131          tempAdvection       = .TRUE.
132          tempForcing         = .TRUE.
133        saltStepping        = .TRUE.        saltStepping        = .TRUE.
134          saltAdvection       = .TRUE.
135          saltForcing         = .TRUE.
136        tr1Stepping         = .FALSE.        tr1Stepping         = .FALSE.
137        metricTerms         = .TRUE.        metricTerms         = .TRUE.
138          useNHMTerms         = .FALSE.
139        implicitDiffusion   = .FALSE.        implicitDiffusion   = .FALSE.
140        implicitViscosity   = .FALSE.        implicitViscosity   = .FALSE.
141          momImplVertAdv      = .FALSE.
142          tempImplVertAdv     = .FALSE.
143          saltImplVertAdv     = .FALSE.
144        nonHydrostatic      = .FALSE.        nonHydrostatic      = .FALSE.
145          quasiHydrostatic    = .FALSE.
146        globalFiles         = .FALSE.        globalFiles         = .FALSE.
147          useSingleCpuIO      = .FALSE.
148        allowFreezing       = .FALSE.        allowFreezing       = .FALSE.
149          useOldFreezing      = .FALSE.
150        ivdc_kappa          = 0.D0        ivdc_kappa          = 0.D0
151        groundAtK1          = .FALSE.        groundAtK1          = .FALSE.
       zonal_filt_lat      = 90.  
       zonal_filt_sinpow   = 2  
       zonal_filt_cospow   = 2  
152        bottomDragLinear    = 0.        bottomDragLinear    = 0.
153        bottomDragQuadratic = 0.        bottomDragQuadratic = 0.
154        usePickupBeforeC35    = .FALSE.        usePickupBeforeC35    = .FALSE.
# Line 136  C--   Set default "physical" parameters Line 158  C--   Set default "physical" parameters
158        tempAdvScheme       = 2        tempAdvScheme       = 2
159        saltAdvScheme       = 2        saltAdvScheme       = 2
160        tracerAdvScheme     = 2        tracerAdvScheme     = 2
161          multiDimAdvection   = .TRUE.
162          useCDscheme         = .FALSE.
163          useEnergyConservingCoriolis = .FALSE.
164          useJamartWetPoints  = .FALSE.
165          debugLevel          = debLevA
166    
167    C--   Set (free)surface-related parameters
168          implicitFreeSurface = .TRUE.
169          rigidLid            = .FALSE.
170          implicSurfPress     = 1.D0
171          implicDiv2DFlow     = 1.D0
172          exactConserv        = .FALSE.
173          uniformLin_PhiSurf  = .TRUE.
174          nonlinFreeSurf      = 0
175          hFacInf             = 0.2 _d 0
176          hFacSup             = 2.0 _d 0
177          select_rStar        = 0
178          useRealFreshWaterFlux = .FALSE.
179          temp_EvPrRn = UNSET_RL
180          salt_EvPrRn = 0.
181          trac_EvPrRn = UNSET_RL
182    
183  C--   Atmospheric physical parameters (e.g.: EOS)  C--   Atmospheric physical parameters (e.g.: EOS)
184        atm_po =  1.D5        celsius2K = 273.16 _d 0
185        atm_cp =  1004.D0        atm_Po =  1. _d 5
186        atm_kappa = 2.D0 / 7.D0        atm_Cp = 1004. _d 0
187        Integr_GeoPot = 2        atm_Rd = UNSET_RL
188          atm_kappa = 2. _d 0 / 7. _d 0
189          atm_Rq = 0. _d 0
190          integr_GeoPot = 2
191          selectFindRoSurf = 0
192    
193  C--   Elliptic solver parameters  C--   Elliptic solver parameters
194        cg2dMaxIters       = 150        cg2dMaxIters       = 150
# Line 157  C--   Time stepping parameters Line 204  C--   Time stepping parameters
204        deltaT            = 0.        deltaT            = 0.
205        nIter0            = 0        nIter0            = 0
206        startTime         = deltaT*float(nIter0)        startTime         = deltaT*float(nIter0)
207          pickupSuff        = ' '
208        nTimeSteps        = 0        nTimeSteps        = 0
209        nEndIter          = nIter0+nTimeSteps        nEndIter          = nIter0+nTimeSteps
210        endTime           = deltaT*float(nEndIter)        endTime           = deltaT*float(nEndIter)
211          forcing_In_AB     = .TRUE.
212        abEps             = 0.01        abEps             = 0.01
213        pchkPtFreq        = deltaT*0        pchkPtFreq        = deltaT*0
214        chkPtFreq         = deltaT*0        chkPtFreq         = deltaT*0
# Line 167  C--   Time stepping parameters Line 216  C--   Time stepping parameters
216        diagFreq          = deltaT*0        diagFreq          = deltaT*0
217        monitorFreq       = -1.        monitorFreq       = -1.
218        taveFreq          = deltaT*0        taveFreq          = deltaT*0
219          tave_lastIter     = 0.5 _d 0
220        writeStatePrec    = precFloat64        writeStatePrec    = precFloat64
221        writeBinaryPrec   = precFloat32        writeBinaryPrec   = precFloat32
222        readBinaryPrec    = precFloat32        readBinaryPrec    = precFloat32
# Line 198  C--   Input files Line 248  C--   Input files
248        vVelInitFile    = ' '        vVelInitFile    = ' '
249        pSurfInitFile   = ' '        pSurfInitFile   = ' '
250        dQdTFile        = ' '        dQdTFile        = ' '
251          ploadFile       = ' '
252          mdsioLocalDir   = ' '
253    
254  C  C
255        RETURN        RETURN
256        END        END
   

Legend:
Removed from v.1.27  
changed lines
  Added in v.1.58

  ViewVC Help
Powered by ViewVC 1.1.22