/[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.128 - (show annotations) (download)
Wed Oct 13 04:37:37 2004 UTC (19 years, 7 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint55g_post, checkpoint55f_post
Changes since 1.127: +4 -1 lines
 o I am *sick* of moving these variables around.  But Jean-Michel has
   all but threatened a hissy fit if they aren't removed from PARAMS.h.
   So now here they are *back* in MNC_PARAMS.h where they were just a
   few days ago.

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

  ViewVC Help
Powered by ViewVC 1.1.22