/[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.151 - (hide annotations) (download)
Wed Apr 6 18:25:30 2005 UTC (19 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57f_post
Changes since 1.150: +21 -9 lines
add baseTime parameter = model base time (time origin)

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

  ViewVC Help
Powered by ViewVC 1.1.22