/[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.137 - (hide annotations) (download)
Thu Nov 18 15:17:06 2004 UTC (19 years, 6 months ago) by heimbach
Branch: MAIN
Changes since 1.136: +2 -2 lines
Allow case externForcingCycle = externForcingPeriod

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

  ViewVC Help
Powered by ViewVC 1.1.22