/[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.134 - (show annotations) (download)
Fri Oct 29 16:30:11 2004 UTC (19 years, 7 months ago) by jmc
Branch: MAIN
Changes since 1.133: +11 -1 lines
add separated viscosity for Divergence and Vorticity

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

  ViewVC Help
Powered by ViewVC 1.1.22