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

Annotation of /MITgcm/model/src/ini_parms.F

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


Revision 1.165 - (hide annotations) (download)
Wed Aug 24 23:09:26 2005 UTC (18 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57r_post
Changes since 1.164: +5 -4 lines
"dumpInitAndLast" replaces "nodumps" (& partly MINIMAL_TAVE_OUTPUT)

1 jmc 1.165 C $Header: /u/gcmpack/MITgcm/model/src/ini_parms.F,v 1.164 2005/08/15 23:05:28 molod Exp $
2 heimbach 1.58 C $Name: $
3 cnh 1.1
4 edhill 1.121 #include "PACKAGES_CONFIG.h"
5 adcroft 1.22 #include "CPP_OPTIONS.h"
6 cnh 1.1
7 edhill 1.121 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
8 cnh 1.70 CBOP
9     C !ROUTINE: INI_PARMS
10     C !INTERFACE:
11 cnh 1.1 SUBROUTINE INI_PARMS( myThid )
12 cnh 1.70
13 edhill 1.121 C !DESCRIPTION:
14     C Routine to set model "parameters".
15    
16 cnh 1.70 C !USES:
17 adcroft 1.38 IMPLICIT NONE
18 cnh 1.1 #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "PARAMS.h"
21 cnh 1.28 #include "GRID.h"
22 mlosch 1.82 #include "EOS.h"
23 cnh 1.1
24 cnh 1.70 C !INPUT/OUTPUT PARAMETERS:
25 cnh 1.1 C myThid - Number of this instance of INI_PARMS
26     INTEGER myThid
27    
28 cnh 1.70 C !LOCAL VARIABLES:
29 cnh 1.1 C dxSpacing, dySpacing - Default spacing in X and Y.
30     C Units are that of coordinate system
31     C i.e. cartesian => metres
32     C s. polar => degrees
33 jmc 1.139 C deltaTtracer :: Timestep for tracer equations ( s )
34 cnh 1.1 C goptCount - Used to count the nuber of grid options
35     C (only one is allowed! )
36     C msgBuf - Informational/error meesage buffer
37     C errIO - IO error flag
38     C iUnit - Work variable for IO unit number
39     C record - Work variable for IO buffer
40     C K, I, J - Loop counters
41 cnh 1.28 C xxxDefault - Default value for variable xxx
42     _RL dxSpacing
43     _RL dySpacing
44 jmc 1.139 _RL deltaTtracer
45 cnh 1.1 CHARACTER*(MAX_LEN_MBUF) msgBuf
46     CHARACTER*(MAX_LEN_PREC) record
47     INTEGER goptCount
48 jmc 1.89 INTEGER K, i, j, IL, iUnit
49 cnh 1.1 INTEGER errIO
50     INTEGER IFNBLNK
51     EXTERNAL IFNBLNK
52     INTEGER ILNBLNK
53     EXTERNAL ILNBLNK
54 cnh 1.28 C Default values for variables which have vertical coordinate system
55     C dependency.
56     _RL viscArDefault
57     _RL diffKrTDefault
58     _RL diffKrSDefault
59     _RL hFacMinDrDefault
60 adcroft 1.39 _RL delRDefault(Nr)
61 adcroft 1.41 _RS rkFacDefault
62 cnh 1.75 C zCoordInputData :: Variables used to select between different coordinate systems.
63     C pCoordInputData :: The vertical coordinate system in the rest of the model is
64     C rCoordInputData :: written in terms of r. In the model "data" file input data can
65     C coordsSet :: be interms of z, p or r.
66     C :: e.g. delZ or delP or delR for the vertical grid spacing.
67     C :: The following rules apply:
68     C :: All parameters must use the same vertical coordinate system.
69     C :: e.g. delZ and viscAz is legal but
70     C :: delZ and viscAr is an error.
71     C :: Similarly specifyinh delZ and delP is an error.
72     C :: zCoord..., pCoord..., rCoord... are used to flag when z, p or r are
73     C :: used. coordsSet counts how many vertical coordinate systems have been
74     C used to specify variables. coordsSet > 1 is an error.
75 cnh 1.28 C
76 jmc 1.100
77 cnh 1.28 LOGICAL zCoordInputData
78     LOGICAL pCoordInputData
79     LOGICAL rCoordInputData
80     INTEGER coordsSet
81 jmc 1.131 LOGICAL diffKrSet
82 jmc 1.100
83     C Variables which have vertical coordinate system dependency.
84     C delZ :: Vertical grid spacing ( m ).
85     C delP :: Vertical grid spacing ( Pa ).
86     C viscAz :: Eddy viscosity coeff. for mixing of
87     C momentum vertically ( m^2/s )
88     C viscAp :: Eddy viscosity coeff. for mixing of
89     C momentum vertically ( Pa^2/s )
90     C diffKzT :: Laplacian diffusion coeff. for mixing of
91     C heat vertically ( m^2/s )
92     C diffKpT :: Laplacian diffusion coeff. for mixing of
93     C heat vertically ( Pa^2/s )
94     C diffKzS :: Laplacian diffusion coeff. for mixing of
95     C salt vertically ( m^2/s )
96     C diffKpS :: Laplacian diffusion coeff. for mixing of
97     C salt vertically ( Pa^2/s )
98     _RL delZ(Nr)
99     _RL delP(Nr)
100     _RL viscAz
101     _RL viscAp
102     _RL diffKzT
103     _RL diffKpT
104 jmc 1.131 _RL diffKrT
105 jmc 1.100 _RL diffKzS
106     _RL diffKpS
107 jmc 1.131 _RL diffKrS
108 cnh 1.75
109     C Retired main data file parameters. Kept here to trap use of old data files.
110 jmc 1.136 C tracerAdvScheme :: tracer advection scheme (old passive tracer code)
111     C trac_EvPrRn :: tracer conc. in Rain & Evap (old passive tracer code)
112     C saltDiffusion :: diffusion of salinity on/off (flag not used)
113     C tempDiffusion :: diffusion of temperature on/off (flag not used)
114     C zonal_filt_lat :: Moved to package "zonal_filt"
115 jmc 1.158 C groundAtK1 :: put the surface(k=1) at the ground (replaced by usingPCoords)
116     C rkFac :: removed from namelist ; replaced by -rkSign
117 cnh 1.75 C nRetired :: Counter used to trap gracefully namelists containing "retired"
118     C :: parameters. These are parameters that are either no-longer used
119     C or that have moved to a different input file and/or namelist.
120 jmc 1.136 LOGICAL tempDiffusion, saltDiffusion
121     INTEGER tracerAdvScheme
122     _RL trac_EvPrRn
123 cnh 1.75 _RL zonal_filt_lat
124 jmc 1.158 _RL rkFac
125     LOGICAL groundAtK1
126 cnh 1.75 INTEGER nRetired
127 cnh 1.1
128     C-- Continuous equation parameters
129     NAMELIST /PARM01/
130 adcroft 1.156 & gravitySign, nh_Am2,
131 jmc 1.93 & gravity, gBaro, rhonil, tAlpha, sBeta,
132     & f0, beta, omega, rotationPeriod,
133 baylor 1.149 & viscAh, viscAhW, viscAhMax,
134     & viscAhGrid, viscAhGridMax, viscAhGridMin,
135     & viscC2leith, viscC4leith,
136 dimitri 1.153 & useFullLeith, useAnisotropicViscAGridMax,
137     & viscC2leithD, viscC4leithD, viscC2Smag,
138 jmc 1.134 & viscAhD, viscAhZ, viscA4D, viscA4Z,
139 mlosch 1.140 & viscA4, viscA4W,
140     & viscA4Max, viscA4Grid, viscA4GridMax, viscA4GridMin,
141 baylor 1.149 & viscAz, cosPower, viscAstrain, viscAtension,
142 dimitri 1.135 & diffKhT, diffKzT, diffK4T,
143 adcroft 1.51 & diffKhS, diffKzS, diffK4S,
144 jmc 1.89 & tRef, sRef, eosType, integr_GeoPot, selectFindRoSurf,
145 jmc 1.98 & atm_Cp, atm_Rd, atm_Rq,
146 adcroft 1.39 & no_slip_sides,no_slip_bottom,
147 cnh 1.1 & momViscosity, momAdvection, momForcing, useCoriolis,
148 dimitri 1.155 & useConstantF,
149 adcroft 1.66 & momPressureForcing, metricTerms, vectorInvariantMomentum,
150 cnh 1.1 & tempDiffusion, tempAdvection, tempForcing,
151 cnh 1.8 & saltDiffusion, saltAdvection, saltForcing,
152 jmc 1.55 & implicSurfPress, implicDiv2DFlow,
153 adcroft 1.24 & implicitFreeSurface, rigidLid, freeSurfFac, hFacMin, hFacMinDz,
154 jmc 1.63 & exactConserv,uniformLin_PhiSurf,nonlinFreeSurf,hFacInf,hFacSup,
155 jmc 1.90 & select_rStar,
156 adcroft 1.53 & staggerTimeStep,
157 heimbach 1.123 & tempStepping, saltStepping, momStepping,
158 adcroft 1.45 & implicitDiffusion, implicitViscosity,
159 jmc 1.104 & tempImplVertAdv, saltImplVertAdv, momImplVertAdv,
160 jmc 1.131 & viscAr, diffKrT, diffKrS, diffKrNrT, diffKrNrS, hFacMinDr,
161 cnh 1.29 & viscAp, diffKpT, diffKpS, hFacMinDp,
162 adcroft 1.112 & diffKrBL79surf, diffKrBL79deep, diffKrBL79scl, diffKrBL79Ho,
163 mlosch 1.84 & rhoConst, rhoConstFresh, buoyancyRelation, HeatCapacity_Cp,
164 adcroft 1.40 & writeBinaryPrec, readBinaryPrec, writeStatePrec,
165 dimitri 1.91 & nonHydrostatic, quasiHydrostatic, globalFiles, useSingleCpuIO,
166 jmc 1.101 & allowFreezing, useOldFreezing, ivdc_kappa,
167 heimbach 1.58 & bottomDragLinear,bottomDragQuadratic,
168 jmc 1.116 & usePickupBeforeC35, usePickupBeforeC54, debugMode, debugLevel,
169 jmc 1.115 & tempAdvScheme, tempVertAdvScheme,
170     & saltAdvScheme, saltVertAdvScheme, tracerAdvScheme,
171 adcroft 1.73 & multiDimAdvection, useEnergyConservingCoriolis,
172 adcroft 1.113 & useCDscheme, useJamartWetPoints, useJamartMomAdv, useNHMTerms,
173 adcroft 1.111 & SadournyCoriolis, upwindVorticity, highOrderVorticity,
174 jmc 1.157 & useAbsVorticity, upwindShear,
175 jmc 1.76 & useRealFreshWaterFlux, convertFW2Salt,
176     & temp_EvPrRn, salt_EvPrRn, trac_EvPrRn,
177 heimbach 1.146 & zonal_filt_lat,
178     & inAdExact
179 cnh 1.1
180     C-- Elliptic solver parameters
181     NAMELIST /PARM02/
182 adcroft 1.59 & cg2dMaxIters, cg2dChkResFreq, cg2dTargetResidual,
183 jmc 1.117 & cg2dTargetResWunit, cg2dpcOffDFac, cg2dPreCondFreq,
184 cnh 1.34 & cg3dMaxIters, cg3dChkResFreq, cg3dTargetResidual
185 cnh 1.1
186     C-- Time stepping parammeters
187     NAMELIST /PARM03/
188 adcroft 1.96 & nIter0, nTimeSteps, nEndIter, pickupSuff,
189 jmc 1.165 & deltaT, deltaTClock, deltaTmom,
190     & deltaTtracer, dTtracerLev, deltaTfreesurf,
191 jmc 1.154 & forcing_In_AB, abEps, alph_AB, beta_AB, startFromPickupAB2,
192     & tauCD, rCD,
193 jmc 1.151 & baseTime, startTime, endTime, chkPtFreq,
194 jmc 1.165 & dumpFreq, dumpInitAndLast, adjDumpFreq, taveFreq, tave_lastIter,
195 heimbach 1.146 & diagFreq, monitorFreq, adjMonitorFreq, pChkPtFreq, cAdjFreq,
196 edhill 1.132 & outputTypesInclusive,
197 jmc 1.99 & tauThetaClimRelax, tauSaltClimRelax, latBandClimRelax,
198     & tauTr1ClimRelax,
199 dimitri 1.147 & periodicExternalForcing, externForcingPeriod, externForcingCycle,
200 jmc 1.165 & calendarDumps
201 cnh 1.1
202     C-- Gridding parameters
203     NAMELIST /PARM04/
204 adcroft 1.48 & usingCartesianGrid, dxSpacing, dySpacing, delX, delY, delZ,
205 cnh 1.1 & usingSphericalPolarGrid, phiMin, thetaMin, rSphere,
206 jmc 1.160 & usingCurvilinearGrid, usingCylindricalGrid,
207 jmc 1.78 & delP, delR, rkFac, Ro_SeaLevel, groundAtK1, delRc,
208 jmc 1.162 & delXFile, delYFile, horizGridFile
209 cnh 1.1
210 cnh 1.15 C-- Input files
211     NAMELIST /PARM05/
212 jmc 1.160 & bathyFile, topoFile,
213 jmc 1.159 & hydrogThetaFile, hydrogSaltFile,
214 adcroft 1.41 & zonalWindFile, meridWindFile,
215     & thetaClimFile, saltClimFile,
216 jmc 1.143 & surfQfile, surfQnetFile, surfQswFile, EmPmRfile, saltFluxFile,
217 heimbach 1.152 & lambdaThetaFile, lambdaSaltFile,
218 heimbach 1.57 & uVelInitFile, vVelInitFile, pSurfInitFile,
219 afe 1.144 & dQdTFile, ploadFile,tCylIn,tCylOut,
220 heimbach 1.148 & eddyTauxFile, eddyTauyFile,
221 edhill 1.119 & mdsioLocalDir,
222     & the_run_name
223 edhill 1.121 CEOP
224 cnh 1.15
225 cnh 1.1 C
226     _BEGIN_MASTER(myThid)
227    
228 adcroft 1.39 C Defaults values for input parameters
229     CALL SET_DEFAULTS(
230     O viscArDefault, diffKrTDefault, diffKrSDefault,
231 adcroft 1.41 O hFacMinDrDefault, delRdefault, rkFacDefault,
232 adcroft 1.39 I myThid )
233    
234 cnh 1.28 C-- Initialise "which vertical coordinate system used" flags.
235     zCoordInputData = .FALSE.
236     pCoordInputData = .FALSE.
237     rCoordInputData = .FALSE.
238     coordsSet = 0
239    
240 jmc 1.131 C-- Initialise retired parameters to unlikely value
241 cnh 1.75 nRetired = 0
242 jmc 1.136 tempDiffusion = .TRUE.
243     saltDiffusion = .TRUE.
244     tracerAdvScheme = UNSET_I
245     trac_EvPrRn = UNSET_RL
246 cnh 1.75 zonal_filt_lat = UNSET_RL
247 jmc 1.99 gravitySign = UNSET_RL
248 jmc 1.158 rkFac = UNSET_RL
249     groundAtK1 = .FALSE.
250 cnh 1.75
251 cnh 1.1 C-- Open the parameter file
252 ce107 1.163 #ifdef TARGET_BGL
253     OPEN(UNIT=scrUnit1,FILE='scratch1',STATUS='UNKNOWN')
254     OPEN(UNIT=scrUnit2,FILE='scratch2',STATUS='UNKNOWN')
255     #else
256 cnh 1.1 OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
257     OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
258 ce107 1.163 #endif
259 cnh 1.34 OPEN(UNIT=modelDataUnit,FILE='data',STATUS='OLD',
260 cnh 1.35 & IOSTAT=errIO)
261     IF ( errIO .LT. 0 ) THEN
262 cnh 1.1 WRITE(msgBuf,'(A)')
263     & 'S/R INI_PARMS'
264     CALL PRINT_ERROR( msgBuf , 1)
265     WRITE(msgBuf,'(A)')
266     & 'Unable to open model parameter'
267     CALL PRINT_ERROR( msgBuf , 1)
268     WRITE(msgBuf,'(A)')
269     & 'file "data"'
270     CALL PRINT_ERROR( msgBuf , 1)
271     CALL MODELDATA_EXAMPLE( myThid )
272     STOP 'ABNORMAL END: S/R INI_PARMS'
273 cnh 1.35 ENDIF
274 cnh 1.1
275 cnh 1.35 DO WHILE ( .TRUE. )
276     READ(modelDataUnit,FMT='(A)',END=1001) RECORD
277     IL = MAX(ILNBLNK(RECORD),1)
278 cnh 1.107 IF ( RECORD(1:1) .NE. commentCharacter ) THEN
279     CALL NML_SET_TERMINATOR( RECORD )
280     WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
281     ENDIF
282     WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
283 cnh 1.35 ENDDO
284 cnh 1.1 1001 CONTINUE
285     CLOSE(modelDataUnit)
286    
287     C-- Report contents of model parameter file
288     WRITE(msgBuf,'(A)')
289     &'// ======================================================='
290 cnh 1.34 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
291     & SQUEEZE_RIGHT , 1)
292 cnh 1.1 WRITE(msgBuf,'(A)') '// Model parameter file "data"'
293 cnh 1.34 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
294     & SQUEEZE_RIGHT , 1)
295 cnh 1.1 WRITE(msgBuf,'(A)')
296     &'// ======================================================='
297     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
298     & SQUEEZE_RIGHT , 1)
299     iUnit = scrUnit2
300     REWIND(iUnit)
301 cnh 1.35 DO WHILE ( .TRUE. )
302 cnh 1.1 READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
303     IL = MAX(ILNBLNK(RECORD),1)
304     WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
305 cnh 1.34 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
306     & SQUEEZE_RIGHT , 1)
307 cnh 1.35 ENDDO
308 cnh 1.1 2001 CONTINUE
309     CLOSE(iUnit)
310     WRITE(msgBuf,'(A)') ' '
311     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
312     & SQUEEZE_RIGHT , 1)
313    
314    
315     C-- Read settings from model parameter file "data".
316     iUnit = scrUnit1
317     REWIND(iUnit)
318    
319     C-- Set default "physical" parameters
320 mlosch 1.126 viscAhW = UNSET_RL
321 mlosch 1.140 viscA4W = UNSET_RL
322 jmc 1.134 viscAhD = UNSET_RL
323     viscAhZ = UNSET_RL
324     viscA4D = UNSET_RL
325     viscA4Z = UNSET_RL
326 cnh 1.28 viscAz = UNSET_RL
327     viscAr = UNSET_RL
328     viscAp = UNSET_RL
329     diffKzT = UNSET_RL
330     diffKpT = UNSET_RL
331     diffKrT = UNSET_RL
332     diffKzS = UNSET_RL
333     diffKpS = UNSET_RL
334     diffKrS = UNSET_RL
335 jmc 1.131 DO k=1,Nr
336     diffKrNrT(k) = UNSET_RL
337     diffKrNrS(k) = UNSET_RL
338     ENDDO
339 adcroft 1.39 gBaro = UNSET_RL
340     rhoConst = UNSET_RL
341 jmc 1.93 omega = UNSET_RL
342 cnh 1.28 hFacMinDr = UNSET_RL
343     hFacMinDz = UNSET_RL
344     hFacMinDp = UNSET_RL
345 jmc 1.102 rhoConstFresh = UNSET_RL
346 jmc 1.76 convertFW2Salt = UNSET_RL
347 mlosch 1.82 tAlpha = UNSET_RL
348     sBeta = UNSET_RL
349 jmc 1.115 tempVertAdvScheme = 0
350     saltVertAdvScheme = 0
351     C-- z,p,r coord input switching.
352 jmc 1.124 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM01'
353     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
354     & SQUEEZE_RIGHT , 1)
355 adcroft 1.41 READ(UNIT=iUnit,NML=PARM01) !,IOSTAT=errIO)
356 cnh 1.35 IF ( errIO .LT. 0 ) THEN
357 cnh 1.1 WRITE(msgBuf,'(A)')
358     & 'S/R INI_PARMS'
359     CALL PRINT_ERROR( msgBuf , 1)
360     WRITE(msgBuf,'(A)')
361     & 'Error reading numerical model '
362     CALL PRINT_ERROR( msgBuf , 1)
363     WRITE(msgBuf,'(A)')
364     & 'parameter file "data"'
365     CALL PRINT_ERROR( msgBuf , 1)
366     WRITE(msgBuf,'(A)')
367     & 'Problem in namelist PARM01'
368     CALL PRINT_ERROR( msgBuf , 1)
369     CALL MODELDATA_EXAMPLE( myThid )
370     STOP 'ABNORMAL END: S/R INI_PARMS'
371 jmc 1.72 ELSE
372     WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM01 : OK'
373     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
374     & SQUEEZE_RIGHT , 1)
375 cnh 1.35 ENDIF
376 jmc 1.89
377 jmc 1.133 C- set the type of vertical coordinate and type of fluid
378     C according to buoyancyRelation
379     usingPCoords = .FALSE.
380     usingZCoords = .FALSE.
381     fluidIsAir = .FALSE.
382     fluidIsWater = .FALSE.
383     IF ( buoyancyRelation.EQ.'ATMOSPHERIC' ) THEN
384     usingPCoords = .TRUE.
385     fluidIsAir = .TRUE.
386     ELSEIF ( buoyancyRelation.EQ.'OCEANICP') THEN
387     usingPCoords = .TRUE.
388     fluidIsWater = .TRUE.
389     ELSEIF ( buoyancyRelation.EQ.'OCEANIC' ) THEN
390     usingZCoords = .TRUE.
391     fluidIsWater = .TRUE.
392     ELSE
393     WRITE(msgBuf,'(2A)') 'S/R INI_PARMS:',
394     & ' Bad value of buoyancyRelation '
395     CALL PRINT_ERROR( msgBuf , myThid)
396     STOP 'ABNORMAL END: S/R INI_PARMS'
397     ENDIF
398    
399 jmc 1.161 IF ( .NOT.rigidLid .AND.
400     & .NOT.implicitFreeSurface ) THEN
401     C- No barotropic solver selected => use implicitFreeSurface as default
402     WRITE(msgBuf,'(A)')
403 jmc 1.162 & 'S/R INI_PARMS: No request for barotropic solver'
404 jmc 1.161 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
405     & SQUEEZE_RIGHT , myThid)
406     WRITE(msgBuf,'(A)')
407     & 'S/R INI_PARMS: => Use implicitFreeSurface as default'
408     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
409     & SQUEEZE_RIGHT , myThid)
410     implicitFreeSurface = .TRUE.
411     ENDIF
412 cnh 1.28 IF ( implicitFreeSurface ) freeSurfFac = 1.D0
413     IF ( rigidLid ) freeSurfFac = 0.D0
414 adcroft 1.39 IF ( gBaro .EQ. UNSET_RL ) gBaro=gravity
415     IF ( rhoConst .EQ. UNSET_RL ) rhoConst=rhoNil
416 jmc 1.102 IF ( rhoConstFresh .EQ. UNSET_RL ) rhoConstFresh=rhoConst
417 jmc 1.93 IF ( omega .EQ. UNSET_RL ) THEN
418 jmc 1.94 omega = 0. _d 0
419     IF ( rotationPeriod .NE. 0. _d 0 )
420     & omega = 2.D0 * PI / rotationPeriod
421     ELSEIF ( omega .EQ. 0. _d 0 ) THEN
422     rotationPeriod = 0. _d 0
423 jmc 1.93 ELSE
424     rotationPeriod = 2.D0 * PI / omega
425     ENDIF
426 jmc 1.89 IF (atm_Rd .EQ. UNSET_RL) THEN
427     atm_Rd = atm_Cp * atm_kappa
428     ELSE
429     atm_kappa = atm_Rd / atm_Cp
430     ENDIF
431 jmc 1.104 C-- On/Off flags for each terms of the momentum equation
432     nonHydrostatic = momStepping .AND. nonHydrostatic
433     quasiHydrostatic = momStepping .AND. quasiHydrostatic
434     momAdvection = momStepping .AND. momAdvection
435     momViscosity = momStepping .AND. momViscosity
436     momForcing = momStepping .AND. momForcing
437     useCoriolis = momStepping .AND. useCoriolis
438     useCDscheme = momStepping .AND. useCDscheme
439     momPressureForcing= momStepping .AND. momPressureForcing
440     momImplVertAdv = momAdvection .AND. momImplVertAdv
441     implicitViscosity= momViscosity .AND. implicitViscosity
442 cnh 1.28 C-- Momentum viscosity on/off flag.
443 cnh 1.9 IF ( momViscosity ) THEN
444 cnh 1.28 vfFacMom = 1.D0
445 cnh 1.9 ELSE
446 cnh 1.28 vfFacMom = 0.D0
447 cnh 1.9 ENDIF
448 cnh 1.28 C-- Momentum advection on/off flag.
449 cnh 1.9 IF ( momAdvection ) THEN
450 cnh 1.28 afFacMom = 1.D0
451 cnh 1.9 ELSE
452 cnh 1.28 afFacMom = 0.D0
453 cnh 1.9 ENDIF
454 cnh 1.28 C-- Momentum forcing on/off flag.
455 cnh 1.9 IF ( momForcing ) THEN
456 cnh 1.28 foFacMom = 1.D0
457 cnh 1.9 ELSE
458 cnh 1.28 foFacMom = 0.D0
459 cnh 1.9 ENDIF
460 cnh 1.28 C-- Coriolis term on/off flag.
461 cnh 1.9 IF ( useCoriolis ) THEN
462 cnh 1.28 cfFacMom = 1.D0
463 cnh 1.9 ELSE
464 cnh 1.28 cfFacMom = 0.D0
465 cnh 1.9 ENDIF
466 cnh 1.28 C-- Pressure term on/off flag.
467 cnh 1.9 IF ( momPressureForcing ) THEN
468 cnh 1.28 pfFacMom = 1.D0
469 cnh 1.9 ELSE
470 cnh 1.28 pfFacMom = 0.D0
471 cnh 1.9 ENDIF
472 cnh 1.28 C-- Metric terms on/off flag.
473 cnh 1.14 IF ( metricTerms ) THEN
474 cnh 1.28 mTFacMom = 1.D0
475 cnh 1.14 ELSE
476 jmc 1.56 mTFacMom = 0.D0
477 adcroft 1.88 ENDIF
478     C-- Non-hydrostatic/quasi-hydrostatic
479     IF (nonHydrostatic.AND.quasiHydrostatic) THEN
480     WRITE(msgBuf,'(A)')
481     & 'Illegal: both nonHydrostatic = quasiHydrostatic = TRUE'
482     CALL PRINT_ERROR( msgBuf , myThid)
483     STOP 'ABNORMAL END: S/R INI_PARMS'
484 cnh 1.14 ENDIF
485 jmc 1.79 C-- Advection and Forcing for Temp and salt on/off flags
486     tempAdvection = tempStepping .AND. tempAdvection
487     tempForcing = tempStepping .AND. tempForcing
488     saltAdvection = saltStepping .AND. saltAdvection
489     saltForcing = saltStepping .AND. saltForcing
490 jmc 1.104 tempImplVertAdv = tempAdvection .AND. tempImplVertAdv
491     saltImplVertAdv = saltAdvection .AND. saltImplVertAdv
492 jmc 1.115 IF (tempVertAdvScheme.EQ.0) tempVertAdvScheme = tempAdvScheme
493     IF (saltVertAdvScheme.EQ.0) saltVertAdvScheme = saltAdvScheme
494 mlosch 1.126 C-- horizontal viscosity for vertical moments
495     IF ( viscAhW .EQ. UNSET_RL ) viscAhW = viscAh
496 mlosch 1.140 IF ( viscA4W .EQ. UNSET_RL ) viscA4W = viscA4
497 jmc 1.134 C-- horizontal viscosity (acting on Divergence or Vorticity)
498     IF ( viscAhD .EQ. UNSET_RL ) viscAhD = viscAh
499     IF ( viscAhZ .EQ. UNSET_RL ) viscAhZ = viscAh
500     IF ( viscA4D .EQ. UNSET_RL ) viscA4D = viscA4
501     IF ( viscA4Z .EQ. UNSET_RL ) viscA4Z = viscA4
502 dimitri 1.153 C-- useAnisotropicViscAGridMax requires that viscA*GridMax be set
503     IF ( useAnisotropicViscAGridMax ) THEN
504     IF ( viscAhGridMax .EQ. 1.D21 ) viscAhGridMax = 0.25
505     IF ( viscA4GridMax .EQ. 1.D21 ) viscA4GridMax = 0.25
506     ENDIF
507 cnh 1.28 C-- z,p,r coord input switching.
508     IF ( viscAz .NE. UNSET_RL ) zCoordInputData = .TRUE.
509     IF ( viscAp .NE. UNSET_RL ) pCoordInputData = .TRUE.
510     IF ( viscAr .NE. UNSET_RL ) rCoordInputData = .TRUE.
511     IF ( viscAr .EQ. UNSET_RL ) viscAr = viscAz
512     IF ( viscAr .EQ. UNSET_RL ) viscAr = viscAp
513     IF ( viscAr .EQ. UNSET_RL ) viscAr = viscArDefault
514    
515     IF ( diffKzT .NE. UNSET_RL ) zCoordInputData = .TRUE.
516     IF ( diffKpT .NE. UNSET_RL ) pCoordInputData = .TRUE.
517     IF ( diffKrT .NE. UNSET_RL ) rCoordInputData = .TRUE.
518     IF ( diffKrT .EQ. UNSET_RL ) diffKrT = diffKzT
519     IF ( diffKrT .EQ. UNSET_RL ) diffKrT = diffKpT
520     IF ( diffKrT .EQ. UNSET_RL ) diffKrT = diffKrTDefault
521 jmc 1.131 diffKrSet = .TRUE.
522     DO k=1,Nr
523     IF ( diffKrNrT(k).EQ. UNSET_RL ) diffKrSet = .FALSE.
524     ENDDO
525     IF ( .NOT.diffKrSet ) THEN
526     DO k=1,Nr
527     diffKrNrT(k) = diffKrT
528     ENDDO
529     ELSEIF ( diffKrT.NE.diffKrTDefault ) THEN
530     WRITE(msgBuf,'(2A)') 'S/R INI_PARMS: Cannot set both ',
531     & 'diffKrNrT and diffKrT (or Kp,Kz) in input file data'
532     CALL PRINT_ERROR( msgBuf , myThid)
533     STOP 'ABNORMAL END: S/R INI_PARMS'
534     ENDIF
535 cnh 1.28
536     IF ( diffKzS .NE. UNSET_RL ) zCoordInputData = .TRUE.
537     IF ( diffKpS .NE. UNSET_RL ) pCoordInputData = .TRUE.
538     IF ( diffKrS .NE. UNSET_RL ) rCoordInputData = .TRUE.
539     IF ( diffKrS .EQ. UNSET_RL ) diffKrS = diffKzS
540     IF ( diffKrS .EQ. UNSET_RL ) diffKrS = diffKpS
541     IF ( diffKrS .EQ. UNSET_RL ) diffKrS = diffKrSDefault
542 jmc 1.131 diffKrSet = .TRUE.
543     DO k=1,Nr
544     IF ( diffKrNrS(k).EQ. UNSET_RL ) diffKrSet = .FALSE.
545     ENDDO
546     IF ( .NOT.diffKrSet ) THEN
547     DO k=1,Nr
548     diffKrNrS(k) = diffKrS
549     ENDDO
550     ELSEIF ( diffKrS.NE.diffKrSDefault ) THEN
551     WRITE(msgBuf,'(2A)') 'S/R INI_PARMS: Cannot set both ',
552     & 'diffKrNrS and diffKrS (or Kp,Kz) in input file data'
553     CALL PRINT_ERROR( msgBuf , myThid)
554     STOP 'ABNORMAL END: S/R INI_PARMS'
555     ENDIF
556 cnh 1.28
557     IF ( hFacMinDz .NE. UNSET_RL ) zCoordInputData = .TRUE.
558     IF ( hFacMinDp .NE. UNSET_RL ) pCoordInputData = .TRUE.
559     IF ( hFacMinDr .NE. UNSET_RL ) rCoordInputData = .TRUE.
560 adcroft 1.50 IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr = hFacMinDz
561     IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr = hFacMinDp
562 cnh 1.28 IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr = hFacMinDrDefault
563 cnh 1.8
564 jmc 1.76 IF (convertFW2Salt.EQ.UNSET_RL) THEN
565     convertFW2Salt = 35.
566     IF (useRealFreshWaterFlux) convertFW2Salt=-1
567     ENDIF
568    
569 adcroft 1.46 IF ( ivdc_kappa .NE. 0. .AND. .NOT. implicitDiffusion ) THEN
570 jmc 1.79 WRITE(msgBuf,'(A,A)')
571 adcroft 1.46 & 'S/R INI_PARMS: To use ivdc_kappa you must enable implicit',
572     & ' vertical diffusion.'
573 jmc 1.55 CALL PRINT_ERROR( msgBuf , myThid)
574     STOP 'ABNORMAL END: S/R INI_PARMS'
575     ENDIF
576    
577 cnh 1.28 coordsSet = 0
578     IF ( zCoordInputData ) coordsSet = coordsSet + 1
579     IF ( pCoordInputData ) coordsSet = coordsSet + 1
580     IF ( rCoordInputData ) coordsSet = coordsSet + 1
581     IF ( coordsSet .GT. 1 ) THEN
582     WRITE(msgBuf,'(A)')
583     & 'S/R INI_PARMS: Cannot mix z, p and r in the input data.'
584 cnh 1.8 CALL PRINT_ERROR( msgBuf , myThid)
585     STOP 'ABNORMAL END: S/R INI_PARMS'
586     ENDIF
587 cnh 1.28 IF ( rhoConst .LE. 0. ) THEN
588     WRITE(msgBuf,'(A)')
589     & 'S/R INI_PARMS: rhoConst must be greater than 0.'
590     CALL PRINT_ERROR( msgBuf , myThid)
591     STOP 'ABNORMAL END: S/R INI_PARMS'
592     ELSE
593     recip_rhoConst = 1.D0 / rhoConst
594 adcroft 1.38 ENDIF
595     IF ( rhoNil .LE. 0. ) THEN
596     WRITE(msgBuf,'(A)')
597     & 'S/R INI_PARMS: rhoNil must be greater than 0.'
598     CALL PRINT_ERROR( msgBuf , myThid)
599     STOP 'ABNORMAL END: S/R INI_PARMS'
600     ELSE
601     recip_rhoNil = 1.D0 / rhoNil
602 cnh 1.33 ENDIF
603 adcroft 1.39 IF ( HeatCapacity_Cp .LE. 0. ) THEN
604     WRITE(msgBuf,'(A)')
605     & 'S/R INI_PARMS: HeatCapacity_Cp must be greater than 0.'
606     CALL PRINT_ERROR( msgBuf , myThid)
607     STOP 'ABNORMAL END: S/R INI_PARMS'
608     ELSE
609     recip_Cp = 1.D0 / HeatCapacity_Cp
610     ENDIF
611 cnh 1.33 IF ( gravity .LE. 0. ) THEN
612     WRITE(msgBuf,'(A)')
613     & 'S/R INI_PARMS: gravity must be greater than 0.'
614     CALL PRINT_ERROR( msgBuf , myThid)
615     STOP 'ABNORMAL END: S/R INI_PARMS'
616     ELSE
617     recip_gravity = 1.D0 / gravity
618 cnh 1.28 ENDIF
619 adcroft 1.109 C This flags are now passed to RW and MDSIO packages in ini_model_io.F
620 adcroft 1.42 C Set globalFiles flag for READ_WRITE_FLD package
621 adcroft 1.109 c CALL SET_WRITE_GLOBAL_FLD( globalFiles )
622 adcroft 1.42 C Set globalFiles flag for READ_WRITE_REC package
623 adcroft 1.109 c CALL SET_WRITE_GLOBAL_REC( globalFiles )
624 adcroft 1.42 C Set globalFiles flag for READ_WRITE_REC package
625 adcroft 1.109 c CALL SET_WRITE_GLOBAL_PICKUP( globalFiles )
626 cnh 1.1
627 cnh 1.75 C Check for retired parameters still being used
628     nRetired = 0
629     IF ( zonal_filt_lat .NE. UNSET_RL ) THEN
630     nRetired = nRetired+1
631     WRITE(msgBuf,'(A,A)')
632     & 'S/R INI_PARMS: Paramater "zonal_filt_lat" is',
633     & ' no longer allowed in file "data".'
634     CALL PRINT_ERROR( msgBuf , myThid)
635     WRITE(msgBuf,'(A,A)')
636     & 'S/R INI_PARMS: Paramater "zonal_filt_lat" is',
637     & ' now read from file "data.zonfilt".'
638     CALL PRINT_ERROR( msgBuf , myThid)
639     ENDIF
640 jmc 1.99 IF ( gravitySign .NE. UNSET_RL ) THEN
641     nRetired = nRetired+1
642     WRITE(msgBuf,'(A,A)')
643     & 'S/R INI_PARMS: "gravitySign" is set according to vertical ',
644     & ' coordinate and is no longer allowed in file "data".'
645     CALL PRINT_ERROR( msgBuf , myThid)
646     ENDIF
647 jmc 1.136 IF ( tracerAdvScheme .NE. UNSET_I ) THEN
648     nRetired = nRetired+1
649     WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "tracerAdvScheme" ',
650     & '(old passive tracer code) is no longer allowed in file "data"'
651     CALL PRINT_ERROR( msgBuf , myThid)
652     ENDIF
653     IF ( trac_EvPrRn .NE. UNSET_RL ) THEN
654     nRetired = nRetired+1
655     WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "trac_EvPrRn" ',
656     & '(old passive tracer code) is no longer allowed in file "data"'
657     CALL PRINT_ERROR( msgBuf , myThid)
658     ENDIF
659     IF ( .NOT. tempDiffusion ) THEN
660     nRetired = nRetired+1
661     WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "tempDiffusion" ',
662     & 'is no longer allowed in file "data"'
663     CALL PRINT_ERROR( msgBuf , myThid)
664     WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: to turn off diffusion',
665     & ' => set diffusivity to zero'
666     CALL PRINT_ERROR( msgBuf , myThid)
667     ENDIF
668     IF ( .NOT. saltDiffusion ) THEN
669     nRetired = nRetired+1
670     WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "saltDiffusion" ',
671     & 'is no longer allowed in file "data"'
672     CALL PRINT_ERROR( msgBuf , myThid)
673     WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: to turn off diffusion',
674     & ' => set diffusivity to zero'
675     CALL PRINT_ERROR( msgBuf , myThid)
676     ENDIF
677 cnh 1.75
678 cnh 1.1 C-- Elliptic solver parameters
679 jmc 1.124 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM02'
680     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
681     & SQUEEZE_RIGHT , 1)
682 adcroft 1.41 READ(UNIT=iUnit,NML=PARM02) !,IOSTAT=errIO)
683 cnh 1.35 IF ( errIO .LT. 0 ) THEN
684 cnh 1.1 WRITE(msgBuf,'(A)')
685     & 'S/R INI_PARMS'
686     CALL PRINT_ERROR( msgBuf , 1)
687     WRITE(msgBuf,'(A)')
688     & 'Error reading numerical model '
689     CALL PRINT_ERROR( msgBuf , 1)
690     WRITE(msgBuf,'(A)')
691     & 'parameter file "data".'
692     CALL PRINT_ERROR( msgBuf , 1)
693     WRITE(msgBuf,'(A)')
694     & 'Problem in namelist PARM02'
695     CALL PRINT_ERROR( msgBuf , 1)
696     CALL MODELDATA_EXAMPLE( myThid )
697     STOP 'ABNORMAL END: S/R INI_PARMS'
698 jmc 1.72 ELSE
699     WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM02 : OK'
700     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
701     & SQUEEZE_RIGHT , 1)
702 cnh 1.35 ENDIF
703 cnh 1.1
704     C-- Time stepping parameters
705 cnh 1.28 rCD = -1.D0
706 jmc 1.99 latBandClimRelax = UNSET_RL
707 jmc 1.139 deltaTtracer = 0. _d 0
708 jmc 1.124 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM03'
709     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
710     & SQUEEZE_RIGHT , 1)
711 adcroft 1.41 READ(UNIT=iUnit,NML=PARM03) !,IOSTAT=errIO)
712 cnh 1.35 IF ( errIO .LT. 0 ) THEN
713 cnh 1.1 WRITE(msgBuf,'(A)')
714     & 'S/R INI_PARMS'
715     CALL PRINT_ERROR( msgBuf , 1)
716     WRITE(msgBuf,'(A)')
717     & 'Error reading numerical model '
718     CALL PRINT_ERROR( msgBuf , 1)
719     WRITE(msgBuf,'(A)')
720     & 'parameter file "data"'
721     CALL PRINT_ERROR( msgBuf , 1)
722     WRITE(msgBuf,'(A)')
723     & 'Problem in namelist PARM03'
724     CALL PRINT_ERROR( msgBuf , 1)
725     CALL MODELDATA_EXAMPLE( myThid )
726     STOP 'ABNORMAL END: S/R INI_PARMS'
727 jmc 1.72 ELSE
728     WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM03 : OK'
729     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
730     & SQUEEZE_RIGHT , 1)
731 cnh 1.35 ENDIF
732 cnh 1.4 C Process "timestepping" params
733     C o Time step size
734 jmc 1.139 IF ( deltaTtracer .NE. dTtracerLev(1) .AND.
735     & deltaTtracer .NE. 0. .AND. dTtracerLev(1) .NE. 0. ) THEN
736     WRITE(msgBuf,'(A)')
737     & 'S/R INI_PARMS: deltaTtracer & dTtracerLev(1) not equal'
738     CALL PRINT_ERROR( msgBuf , myThid)
739     STOP 'ABNORMAL END: S/R INI_PARMS'
740     ELSEIF ( dTtracerLev(1) .NE. 0. ) THEN
741     deltaTtracer = dTtracerLev(1)
742     ENDIF
743 cnh 1.4 IF ( deltaT .EQ. 0. ) deltaT = deltaTmom
744     IF ( deltaT .EQ. 0. ) deltaT = deltaTtracer
745     IF ( deltaTmom .EQ. 0. ) deltaTmom = deltaT
746     IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT
747 cnh 1.7 IF ( deltaTClock .EQ. 0. ) deltaTClock = deltaT
748 jmc 1.139 DO k=1,Nr
749     IF (dTtracerLev(k).EQ.0.) dTtracerLev(k)= deltaTtracer
750     ENDDO
751 jmc 1.89 C Note that this line should set deltaFreesurf=deltaTmom
752 adcroft 1.80 C but this would change a lot of existing set-ups so we are
753     C obliged to set the default inappropriately.
754     C Be advised that when using asynchronous time stepping
755     C it is better to set deltaTreesurf=deltaTtracer
756     IF ( deltaTfreesurf .EQ. 0. ) deltaTfreesurf = deltaTmom
757 adcroft 1.19 IF ( periodicExternalForcing ) THEN
758     IF ( externForcingCycle*externForcingPeriod .EQ. 0. ) THEN
759     WRITE(msgBuf,'(A)')
760     & 'S/R INI_PARMS: externForcingCycle,externForcingPeriod =0'
761     CALL PRINT_ERROR( msgBuf , 1)
762     STOP 'ABNORMAL END: S/R INI_PARMS'
763     ENDIF
764     IF ( INT(externForcingCycle/externForcingPeriod) .NE.
765     & externForcingCycle/externForcingPeriod ) THEN
766     WRITE(msgBuf,'(A)')
767     & 'S/R INI_PARMS: externForcingCycle <> N*externForcingPeriod'
768     CALL PRINT_ERROR( msgBuf , 1)
769     STOP 'ABNORMAL END: S/R INI_PARMS'
770     ENDIF
771 heimbach 1.137 IF ( externForcingCycle.lt.externForcingPeriod ) THEN
772 adcroft 1.19 WRITE(msgBuf,'(A)')
773     & 'S/R INI_PARMS: externForcingCycle < externForcingPeriod'
774     CALL PRINT_ERROR( msgBuf , 1)
775     STOP 'ABNORMAL END: S/R INI_PARMS'
776     ENDIF
777     IF ( externForcingPeriod.lt.deltaTclock ) THEN
778     WRITE(msgBuf,'(A)')
779     & 'S/R INI_PARMS: externForcingPeriod < deltaTclock'
780     CALL PRINT_ERROR( msgBuf , 1)
781     STOP 'ABNORMAL END: S/R INI_PARMS'
782     ENDIF
783     ENDIF
784 cnh 1.9 C o Convection frequency
785     IF ( cAdjFreq .LT. 0. ) THEN
786     cAdjFreq = deltaTClock
787     ENDIF
788 adcroft 1.46 IF ( ivdc_kappa .NE. 0. .AND. cAdjFreq .NE. 0. ) THEN
789     WRITE(msgBuf,'(A,A)')
790     & 'S/R INI_PARMS: You have enabled both ivdc_kappa and',
791     & ' convective adjustment.'
792     CALL PRINT_ERROR( msgBuf , myThid)
793     STOP 'ABNORMAL END: S/R INI_PARMS'
794     ENDIF
795 jmc 1.95 IF (useCDscheme) THEN
796     C o CD coupling (CD scheme):
797     IF ( tauCD .EQ. 0.D0 ) tauCD = deltaTmom
798     IF ( rCD .LT. 0. ) rCD = 1. _d 0 - deltaTMom/tauCD
799 cnh 1.14 ENDIF
800 cnh 1.18 C o Temperature climatology relaxation time scale
801 cnh 1.28 IF ( tauThetaClimRelax .EQ. 0.D0 ) THEN
802 cnh 1.18 doThetaClimRelax = .FALSE.
803     ELSE
804     doThetaClimRelax = .TRUE.
805     ENDIF
806     C o Salinity climatology relaxation time scale
807 cnh 1.28 IF ( tauSaltClimRelax .EQ. 0.D0 ) THEN
808 cnh 1.18 doSaltClimRelax = .FALSE.
809     ELSE
810     doSaltClimRelax = .TRUE.
811 heimbach 1.64 ENDIF
812     C o Tracer 1 climatology relaxation time scale
813     IF ( tauTr1ClimRelax .EQ. 0.D0 ) THEN
814     doTr1ClimRelax = .FALSE.
815     lambdaTr1ClimRelax = 0.D0
816     ELSE
817     doTr1ClimRelax = .TRUE.
818     lambdaTr1ClimRelax = 1./tauTr1ClimRelax
819 cnh 1.18 ENDIF
820 adcroft 1.41
821 jmc 1.151 C o Base time
822     IF ( nIter0.NE.0 .AND. startTime.NE.0. .AND. baseTime.EQ.0. )
823     & baseTime = startTime - deltaTClock*float(nIter0)
824 adcroft 1.41 C o Start time
825     IF ( nIter0 .NE. 0 .AND. startTime .EQ. 0. )
826 jmc 1.151 & startTime = baseTime + deltaTClock*float(nIter0)
827 adcroft 1.41 C o nIter0
828 jmc 1.151 IF ( nIter0 .EQ. 0 .AND. startTime .NE. baseTime )
829     & nIter0 = NINT( (startTime-baseTime)/deltaTClock )
830 adcroft 1.46
831     C o nTimeSteps 1
832     IF ( nTimeSteps .EQ. 0 .AND. nEndIter .NE. 0 )
833     & nTimeSteps = nEndIter-nIter0
834     C o nTimeSteps 2
835 adcroft 1.41 IF ( nTimeSteps .EQ. 0 .AND. endTime .NE. 0. )
836 jmc 1.151 & nTimeSteps = NINT((endTime-startTime)/deltaTclock)
837 adcroft 1.46 C o nEndIter 1
838     IF ( nEndIter .EQ. 0 .AND. nTimeSteps .NE. 0 )
839     & nEndIter = nIter0+nTimeSteps
840     C o nEndIter 2
841     IF ( nEndIter .EQ. 0 .AND. endTime .NE. 0. )
842 jmc 1.151 & nEndIter = NINT((endTime-baseTime)/deltaTclock)
843 adcroft 1.46 C o End Time 1
844     IF ( endTime .EQ. 0. .AND. nTimeSteps .NE. 0 )
845     & endTime = startTime + deltaTClock*float(nTimeSteps)
846     C o End Time 2
847     IF ( endTime .EQ. 0. .AND. nEndIter .NE. 0 )
848 jmc 1.151 & endTime = baseTime + deltaTClock*float(nEndIter)
849 adcroft 1.46
850 adcroft 1.41 C o Consistent?
851 jmc 1.151 IF ( startTime .NE. baseTime+deltaTClock*float(nIter0) ) THEN
852     WRITE(msgBuf,'(A)')
853     & 'S/R INI_PARMS: startTime, baseTime and nIter0 are inconsistent'
854     CALL PRINT_ERROR( msgBuf , 1)
855     WRITE(msgBuf,'(A)')
856     & 'S/R INI_PARMS: Perhaps more than two were set at once'
857     CALL PRINT_ERROR( msgBuf , 1)
858     STOP 'ABNORMAL END: S/R INI_PARMS'
859     ENDIF
860 adcroft 1.46 IF ( nEndIter .NE. nIter0+nTimeSteps ) THEN
861     WRITE(msgBuf,'(A)')
862     & 'S/R INI_PARMS: nIter0, nTimeSteps and nEndIter are inconsistent'
863     CALL PRINT_ERROR( msgBuf , 1)
864     WRITE(msgBuf,'(A)')
865     & 'S/R INI_PARMS: Perhaps more than two were set at once'
866     CALL PRINT_ERROR( msgBuf , 1)
867     STOP 'ABNORMAL END: S/R INI_PARMS'
868     ENDIF
869 jmc 1.151 IF ( nTimeSteps .NE. NINT((endTime-startTime)/deltaTClock) )
870 adcroft 1.46 & THEN
871 adcroft 1.41 WRITE(msgBuf,'(A)')
872     & 'S/R INI_PARMS: both endTime and nTimeSteps have been set'
873     CALL PRINT_ERROR( msgBuf , 1)
874     WRITE(msgBuf,'(A)')
875     & 'S/R INI_PARMS: but are inconsistent'
876     CALL PRINT_ERROR( msgBuf , 1)
877     STOP 'ABNORMAL END: S/R INI_PARMS'
878 adcroft 1.60 ENDIF
879    
880     C o Monitor (should also add CPP flag for monitor?)
881     IF (monitorFreq.LT.0.) THEN
882     monitorFreq=0.
883 adcroft 1.62 IF (dumpFreq.NE.0.) monitorFreq=dumpFreq
884 adcroft 1.67 IF (diagFreq.NE.0..AND.diagFreq.LT.monitorFreq)
885     & monitorFreq=diagFreq
886 adcroft 1.62 IF (taveFreq.NE.0..AND.taveFreq.LT.monitorFreq)
887     & monitorFreq=taveFreq
888     IF (chkPtFreq.NE.0..AND.chkPtFreq.LT.monitorFreq)
889     & monitorFreq=chkPtFreq
890     IF (pChkPtFreq.NE.0..AND.pChkPtFreq.LT.monitorFreq)
891     & monitorFreq=pChkPtFreq
892 adcroft 1.60 IF (monitorFreq.EQ.0.) monitorFreq=deltaTclock
893 cnh 1.4 ENDIF
894 adcroft 1.21
895 cnh 1.1 C-- Grid parameters
896     C In cartesian coords distances are in metres
897 cnh 1.26 DO K =1,Nr
898 cnh 1.28 delZ(K) = UNSET_RL
899     delP(K) = UNSET_RL
900     delR(K) = UNSET_RL
901 cnh 1.1 ENDDO
902     C In spherical polar distances are in degrees
903 cnh 1.28 recip_rSphere = 1.D0/rSphere
904 adcroft 1.39 dxSpacing = UNSET_RL
905     dySpacing = UNSET_RL
906 jmc 1.124 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM04'
907     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
908     & SQUEEZE_RIGHT , 1)
909 mlosch 1.82 READ(UNIT=iUnit,NML=PARM04,IOSTAT=errIO)
910 cnh 1.35 IF ( errIO .LT. 0 ) THEN
911 cnh 1.1 WRITE(msgBuf,'(A)')
912     & 'S/R INI_PARMS'
913     CALL PRINT_ERROR( msgBuf , 1)
914     WRITE(msgBuf,'(A)')
915     & 'Error reading numerical model '
916     CALL PRINT_ERROR( msgBuf , 1)
917     WRITE(msgBuf,'(A)')
918     & 'parameter file "data"'
919     CALL PRINT_ERROR( msgBuf , 1)
920     WRITE(msgBuf,'(A)')
921     & 'Problem in namelist PARM04'
922     CALL PRINT_ERROR( msgBuf , 1)
923     CALL MODELDATA_EXAMPLE( myThid )
924     STOP 'ABNORMAL END: S/R INI_PARMS'
925 jmc 1.72 ELSE
926     WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM04 : OK'
927     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
928     & SQUEEZE_RIGHT , 1)
929 cnh 1.35 ENDIF
930 adcroft 1.48
931 jmc 1.158 C Check for retired parameters still being used
932     IF ( rkFac .NE. UNSET_RL ) THEN
933     nRetired = nRetired+1
934     WRITE(msgBuf,'(A,A)')
935     & 'S/R INI_PARMS: "rkFac" has been replaced by -rkSign ',
936     & ' and is no longer allowed in file "data".'
937     CALL PRINT_ERROR( msgBuf , myThid)
938     ENDIF
939     IF ( groundAtK1 ) THEN
940     c nRetired = nRetired+1
941     WRITE(msgBuf,'(A,A)')
942     & 'S/R INI_PARMS: "groundAtK1" is set according to vertical ',
943     & ' coordinate and is no longer allowed in file "data".'
944     CALL PRINT_ERROR( msgBuf , myThid)
945     ENDIF
946    
947 jmc 1.162 C X coordinate : Check for multiple definitions
948     goptCount = 0
949     IF ( delX(1) .NE. UNSET_RL ) goptCount = goptCount + 1
950     IF ( dxSpacing .NE. UNSET_RL ) goptCount = goptCount + 1
951     IF ( delXFile .NE. ' ' ) goptCount = goptCount + 1
952     IF ( goptCount.GT.1 ) THEN
953 adcroft 1.48 WRITE(msgBuf,'(A,A)') 'Too many specifications for delX:',
954     & 'Specify only one of delX, dxSpacing or delXfile'
955     CALL PRINT_ERROR( msgBuf , 1)
956     STOP 'ABNORMAL END: S/R INI_PARMS'
957     ENDIF
958 adcroft 1.39 IF ( dxSpacing .NE. UNSET_RL ) THEN
959     DO i=1,Nx
960     delX(i) = dxSpacing
961     ENDDO
962     ENDIF
963 jmc 1.162 C Y coordinate : Check for multiple definitions
964     goptCount = 0
965     IF ( delY(1) .NE. UNSET_RL ) goptCount = goptCount + 1
966     IF ( dySpacing .NE. UNSET_RL ) goptCount = goptCount + 1
967     IF ( delYFile .NE. ' ' ) goptCount = goptCount + 1
968     IF ( goptCount.GT.1 ) THEN
969 adcroft 1.48 WRITE(msgBuf,'(A,A)') 'Too many specifications for delY:',
970     & 'Specify only one of delY, dySpacing or delYfile'
971     CALL PRINT_ERROR( msgBuf , 1)
972     STOP 'ABNORMAL END: S/R INI_PARMS'
973     ENDIF
974 adcroft 1.39 IF ( dySpacing .NE. UNSET_RL ) THEN
975 jmc 1.162 DO j=1,Ny
976     delY(j) = dySpacing
977 adcroft 1.39 ENDDO
978     ENDIF
979 adcroft 1.48 C
980 cnh 1.14 IF ( rSphere .NE. 0 ) THEN
981 cnh 1.28 recip_rSphere = 1.D0/rSphere
982 cnh 1.14 ELSE
983 cnh 1.26 recip_rSphere = 0.
984 adcroft 1.11 ENDIF
985 cnh 1.28 C-- Check for conflicting grid definitions.
986 cnh 1.1 goptCount = 0
987     IF ( usingCartesianGrid ) goptCount = goptCount+1
988     IF ( usingSphericalPolarGrid ) goptCount = goptCount+1
989 adcroft 1.59 IF ( usingCurvilinearGrid ) goptCount = goptCount+1
990 afe 1.114 IF ( usingCylindricalGrid ) goptCount = goptCount+1
991 adcroft 1.59 IF ( goptCount .GT. 1 ) THEN
992 cnh 1.1 WRITE(msgBuf,'(A)')
993     & 'S/R INI_PARMS: More than one coordinate system requested'
994     CALL PRINT_ERROR( msgBuf , myThid)
995     STOP 'ABNORMAL END: S/R INI_PARMS'
996 cnh 1.14 ENDIF
997 adcroft 1.59 IF ( goptCount .LT. 1 ) THEN
998 jmc 1.103 C- No horizontal grid is specified => use Cartesian grid as default:
999 adcroft 1.59 WRITE(msgBuf,'(A)')
1000 jmc 1.103 & 'S/R INI_PARMS: No horizontal grid requested'
1001     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
1002     & SQUEEZE_RIGHT , myThid)
1003     WRITE(msgBuf,'(A)')
1004     & 'S/R INI_PARMS: => Use Cartesian Grid as default'
1005     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
1006     & SQUEEZE_RIGHT , myThid)
1007     usingCartesianGrid = .TRUE.
1008 adcroft 1.59 ENDIF
1009 cnh 1.28 C-- Make metric term settings consistent with underlying grid.
1010 cnh 1.14 IF ( usingCartesianGrid ) THEN
1011     usingSphericalPolarMterms = .FALSE.
1012     metricTerms = .FALSE.
1013 adcroft 1.87 useNHMTerms = .FALSE.
1014 jmc 1.56 mTFacMom = 0.
1015 cnh 1.18 useBetaPlaneF = .TRUE.
1016 cnh 1.14 ENDIF
1017 afe 1.114 C-- Make metric term settings consistent with underlying grid.
1018     IF ( usingCylindricalGrid) THEN
1019     usingSphericalPolarMterms = .FALSE.
1020     metricTerms = .FALSE.
1021     useNHMTerms = .FALSE.
1022     mTFacMom = 1.
1023     useBetaPlaneF = .TRUE.
1024     WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; Cylinder OK'
1025     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1026     & SQUEEZE_RIGHT , 1)
1027 jmc 1.133
1028 afe 1.114 ENDIF
1029    
1030 cnh 1.14 IF ( usingSphericalPolarGrid ) THEN
1031     useSphereF = .TRUE.
1032 jmc 1.56 usingSphericalPolarMterms = metricTerms
1033 adcroft 1.59 ENDIF
1034     IF ( usingCurvilinearGrid ) THEN
1035     useSphereF = .TRUE.
1036 adcroft 1.87 metricTerms = .FALSE.
1037     useNHMTerms = .FALSE.
1038 cnh 1.1 ENDIF
1039 jmc 1.99 C-- Set default for latitude-band where relaxation to climatology applies
1040 jmc 1.162 C note: done later (once domain size is known) if using CartesianGrid
1041 jmc 1.99 IF ( latBandClimRelax .EQ. UNSET_RL) THEN
1042     IF ( usingSphericalPolarGrid ) latBandClimRelax= 180. _d 0
1043     IF ( usingCurvilinearGrid ) latBandClimRelax= 180. _d 0
1044     ENDIF
1045 jmc 1.78 C-- set cell Center depth and put Interface at the middle between 2 C
1046     setCenterDr = .FALSE.
1047     IF (delRc(1).NE.UNSET_RL) setCenterDr=.TRUE.
1048     DO K=1,Nr+1
1049     IF (delRc(K).EQ.UNSET_RL) setCenterDr = .FALSE.
1050     ENDDO
1051 cnh 1.28 C-- p, z, r coord parameters
1052     DO K = 1, Nr
1053     IF ( delZ(K) .NE. UNSET_RL ) zCoordInputData = .TRUE.
1054     IF ( delP(K) .NE. UNSET_RL ) pCoordInputData = .TRUE.
1055     IF ( delR(K) .NE. UNSET_RL ) rCoordInputData = .TRUE.
1056     IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delZ(K)
1057     IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delP(K)
1058 adcroft 1.39 IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delRDefault(K)
1059 jmc 1.78 IF (.NOT.setCenterDr .AND. delR(K).EQ.delRDefault(K) ) THEN
1060 adcroft 1.41 WRITE(msgBuf,'(A,I4)')
1061     & 'S/R INI_PARMS: No value for delZ/delP/delR at K = ',K
1062 jmc 1.78 CALL PRINT_ERROR( msgBuf , 1)
1063     STOP 'ABNORMAL END: S/R INI_PARMS'
1064     ELSEIF ( setCenterDr .AND. delR(K).NE.delRDefault(K) ) THEN
1065     WRITE(msgBuf,'(2A,I4)') 'S/R INI_PARMS:',
1066     & ' Cannot specify both delRc and delZ/delP/delR at K=', K
1067 adcroft 1.41 CALL PRINT_ERROR( msgBuf , 1)
1068     STOP 'ABNORMAL END: S/R INI_PARMS'
1069     ENDIF
1070 cnh 1.28 ENDDO
1071     C Check for multiple coordinate systems
1072 adcroft 1.39 CoordsSet = 0
1073 cnh 1.28 IF ( zCoordInputData ) coordsSet = coordsSet + 1
1074     IF ( pCoordInputData ) coordsSet = coordsSet + 1
1075     IF ( rCoordInputData ) coordsSet = coordsSet + 1
1076     IF ( coordsSet .GT. 1 ) THEN
1077     WRITE(msgBuf,'(A)')
1078     & 'S/R INI_PARMS: Cannot mix z, p and r in the input data.'
1079     CALL PRINT_ERROR( msgBuf , myThid)
1080     STOP 'ABNORMAL END: S/R INI_PARMS'
1081     ENDIF
1082 jmc 1.92
1083     C-- When using the dynamical pressure in EOS (with Z-coord.),
1084     C needs to activate specific part of the code (restart & exchange)
1085     c useDynP_inEos_Zc = .FALSE.
1086 jmc 1.133 useDynP_inEos_Zc = ( fluidIsWater .AND. usingZCoords
1087 jmc 1.92 & .AND. ( eosType .EQ. 'JMD95P' .OR.
1088     & eosType .EQ. 'UNESCO' .OR.
1089     & eosType .EQ. 'MDJWF' ) )
1090 cnh 1.15
1091     C-- Input files
1092 jmc 1.124 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM05'
1093     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1094     & SQUEEZE_RIGHT , 1)
1095 adcroft 1.41 READ(UNIT=iUnit,NML=PARM05) !,IOSTAT=errIO)
1096 cnh 1.35 IF ( errIO .LT. 0 ) THEN
1097 cnh 1.15 WRITE(msgBuf,'(A)')
1098     & 'Error reading numerical model '
1099     CALL PRINT_ERROR( msgBuf , 1)
1100     WRITE(msgBuf,'(A)')
1101     & 'parameter file "data"'
1102     CALL PRINT_ERROR( msgBuf , 1)
1103     WRITE(msgBuf,'(A)')
1104     & 'Problem in namelist PARM05'
1105     CALL PRINT_ERROR( msgBuf , 1)
1106     CALL MODELDATA_EXAMPLE( myThid )
1107     STOP 'ABNORMAL END: S/R INI_PARMS'
1108 jmc 1.72 ELSE
1109     WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM05 : OK'
1110     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1111     & SQUEEZE_RIGHT , 1)
1112 cnh 1.35 ENDIF
1113 cnh 1.25
1114 cnh 1.30 C-- Set factors required for mixing pressure and meters as vertical coordinate.
1115 jmc 1.158 C rkSign is a "sign" parameter which is used where the orientation of the vertical
1116 cnh 1.30 C coordinate (pressure or meters) relative to the vertical index (K) is important.
1117 jmc 1.158 C rkSign = -1 applies when K and the coordinate are in the opposite sense.
1118     C rkSign = 1 applies when K and the coordinate are in the same sense.
1119 cnh 1.30 C horiVertRatio is a parameter that maps horizontal units to vertical units.
1120     C It is used in certain special cases where lateral and vertical terms are
1121     C being combined and a single frame of reference is needed.
1122 jmc 1.158 rkSign = -1. _d 0
1123     horiVertRatio = 1. _d 0
1124     gravitySign = -1. _d 0
1125 jmc 1.133 IF ( usingPCoords ) THEN
1126 jmc 1.99 gravitySign = 1. _d 0
1127 jmc 1.85 horiVertRatio = Gravity * rhoConst
1128     ENDIF
1129 jmc 1.102 convertEmP2rUnit = rhoConstFresh*recip_rhoConst*horiVertRatio
1130 cnh 1.32 recip_horiVertRatio = 1./horiVertRatio
1131 adcroft 1.37
1132 heimbach 1.97 c-- gradually replacing debugMode by debugLevel
1133 jmc 1.142 IF ( debugMode ) debugLevel = debLevB
1134    
1135 heimbach 1.146 c-- flag for approximate adjoint
1136     IF ( inAdExact ) THEN
1137     inAdTrue = .FALSE.
1138     inAdFALSE = .FALSE.
1139     ELSE
1140     inAdTrue = .TRUE.
1141     inAdFALSE = .FALSE.
1142     ENDIF
1143     C
1144 cnh 1.25 CLOSE(iUnit)
1145 cnh 1.75
1146     C-- Check whether any retired parameters were found.
1147     C-- Stop if they were
1148     IF ( nRetired .GT. 0 ) THEN
1149     WRITE(msgBuf,'(A)')
1150     & 'Error reading '
1151     CALL PRINT_ERROR( msgBuf , 1)
1152     WRITE(msgBuf,'(A)')
1153     & 'parameter file "data"'
1154     CALL PRINT_ERROR( msgBuf , 1)
1155     WRITE(msgBuf,'(A)')
1156     & 'some out of date parameters were found in the namelist'
1157     CALL PRINT_ERROR( msgBuf , 1)
1158     STOP 'ABNORMAL END: S/R INI_PARMS'
1159     ENDIF
1160 cnh 1.1
1161     _END_MASTER(myThid)
1162    
1163     C-- Everyone else must wait for the parameters to be loaded
1164     _BARRIER
1165     C
1166     RETURN
1167     END

  ViewVC Help
Powered by ViewVC 1.1.22