/[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.108 - (show annotations) (download)
Thu Mar 4 04:00:12 2004 UTC (20 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube5, checkpoint52l_post, checkpoint53, checkpoint52m_post, checkpoint53a_post, checkpoint52n_post
Changes since 1.107: +3 -3 lines
adding parameter adjDumpFreq

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

  ViewVC Help
Powered by ViewVC 1.1.22