/[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.117 - (show annotations) (download)
Fri Jul 9 22:32:35 2004 UTC (19 years, 10 months ago) by jmc
Branch: MAIN
Changes since 1.116: +2 -2 lines
Only update cg2d preconditioner every "cg2dPreCondFreq" iter. (default=1)

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

  ViewVC Help
Powered by ViewVC 1.1.22