/[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.199 - (hide annotations) (download)
Mon Oct 1 13:28:59 2007 UTC (16 years, 8 months ago) by jmc
Branch: MAIN
Changes since 1.198: +3 -2 lines
Change EmPmR units: from m/s to kg/m2/s

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

  ViewVC Help
Powered by ViewVC 1.1.22