/[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.163 - (show annotations) (download)
Fri Aug 5 23:44:28 2005 UTC (18 years, 9 months ago) by ce107
Branch: MAIN
Changes since 1.162: +6 -1 lines
Changed SCRATCH files to named files to avoid mysterious runtime error on
Blue Gene/L. Linux/PPC64 also complains at runtime but completes execution.
Introduce TARGET_BGL to avoid scraping scratch files.

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

  ViewVC Help
Powered by ViewVC 1.1.22