/[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.160 - (hide annotations) (download)
Tue Jul 12 22:44:56 2005 UTC (18 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57l_post
Changes since 1.159: +4 -4 lines
although horizGridFile is for 2.D type input, better in namelist 4 than 5.

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

  ViewVC Help
Powered by ViewVC 1.1.22