/[MITgcm]/MITgcm/model/src/ini_parms.F
ViewVC logotype

Contents of /MITgcm/model/src/ini_parms.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.184 - (show annotations) (download)
Mon Mar 20 15:11:18 2006 UTC (18 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58f_post, checkpoint58d_post, checkpoint58e_post, checkpoint58g_post, checkpoint58c_post
Changes since 1.183: +26 -8 lines
move calendarDumps from "data" to "data.cal" and clean-up the code
 with a simple call to pkg/cal S/R: CAL_TIME2WRITE
 (the former piece of code started to spread over newly checked-in S/R)
add useEXF & useCAL flags (for now, set in hard-coded way)

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

  ViewVC Help
Powered by ViewVC 1.1.22