/[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.158 - (show annotations) (download)
Wed Jun 22 00:24:42 2005 UTC (18 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57j_post, checkpoint57k_post
Changes since 1.157: +29 -21 lines
rkSign & usingPCoords replace -rkFac & groundAtK1 (<- removed)

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

  ViewVC Help
Powered by ViewVC 1.1.22