/[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.112 - (show annotations) (download)
Wed Jun 9 14:03:35 2004 UTC (19 years, 11 months ago) by adcroft
Branch: MAIN
Changes since 1.111: +2 -1 lines
Added vertical diffusivity profile (T/S) due to Bryan and Lewis, 1979.
New parameters:
 diffKrBL79surf - surface diffusivity
 diffKrBL79deep - deep diffusivity
 diffKrBL79Ho   - turning depth for arctan function
 diffKrBL79scl  - depth scale for arctan function
This diffusivity is added to all other diffusivities. The defaults are
set so as to give zero diffusivity.

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

  ViewVC Help
Powered by ViewVC 1.1.22