/[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.190 - (hide annotations) (download)
Tue Jan 2 20:42:08 2007 UTC (17 years, 4 months ago) by dfer
Branch: MAIN
Changes since 1.189: +3 -3 lines
initial check in: correction of tracer source/sink due to Linear
Free surface

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

  ViewVC Help
Powered by ViewVC 1.1.22