/[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.160 - (show annotations) (download)
Tue Jul 12 22:44:56 2005 UTC (18 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57l_post
Changes since 1.159: +4 -4 lines
although horizGridFile is for 2.D type input, better in namelist 4 than 5.

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_parms.F,v 1.159 2005/07/12 16:31:41 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, horizGridFile
214
215 C-- Input files
216 NAMELIST /PARM05/
217 & bathyFile, topoFile,
218 & hydrogThetaFile, hydrogSaltFile,
219 & zonalWindFile, meridWindFile,
220 & thetaClimFile, saltClimFile,
221 & surfQfile, surfQnetFile, surfQswFile, EmPmRfile, saltFluxFile,
222 & lambdaThetaFile, lambdaSaltFile,
223 & uVelInitFile, vVelInitFile, pSurfInitFile,
224 & dQdTFile, ploadFile,tCylIn,tCylOut,
225 & eddyTauxFile, eddyTauyFile,
226 & mdsioLocalDir,
227 & the_run_name
228 CEOP
229
230 C
231 _BEGIN_MASTER(myThid)
232
233 C Defaults values for input parameters
234 CALL SET_DEFAULTS(
235 O viscArDefault, diffKrTDefault, diffKrSDefault,
236 O hFacMinDrDefault, delRdefault, rkFacDefault,
237 I myThid )
238
239 C-- Initialise "which vertical coordinate system used" flags.
240 zCoordInputData = .FALSE.
241 pCoordInputData = .FALSE.
242 rCoordInputData = .FALSE.
243 coordsSet = 0
244
245 C-- Initialise retired parameters to unlikely value
246 nRetired = 0
247 tempDiffusion = .TRUE.
248 saltDiffusion = .TRUE.
249 tracerAdvScheme = UNSET_I
250 trac_EvPrRn = UNSET_RL
251 zonal_filt_lat = UNSET_RL
252 gravitySign = UNSET_RL
253 rkFac = UNSET_RL
254 groundAtK1 = .FALSE.
255
256 C-- Open the parameter file
257 OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
258 OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
259 OPEN(UNIT=modelDataUnit,FILE='data',STATUS='OLD',
260 & IOSTAT=errIO)
261 IF ( errIO .LT. 0 ) THEN
262 WRITE(msgBuf,'(A)')
263 & 'S/R INI_PARMS'
264 CALL PRINT_ERROR( msgBuf , 1)
265 WRITE(msgBuf,'(A)')
266 & 'Unable to open model parameter'
267 CALL PRINT_ERROR( msgBuf , 1)
268 WRITE(msgBuf,'(A)')
269 & 'file "data"'
270 CALL PRINT_ERROR( msgBuf , 1)
271 CALL MODELDATA_EXAMPLE( myThid )
272 STOP 'ABNORMAL END: S/R INI_PARMS'
273 ENDIF
274
275 DO WHILE ( .TRUE. )
276 READ(modelDataUnit,FMT='(A)',END=1001) RECORD
277 IL = MAX(ILNBLNK(RECORD),1)
278 IF ( RECORD(1:1) .NE. commentCharacter ) THEN
279 CALL NML_SET_TERMINATOR( RECORD )
280 WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
281 ENDIF
282 WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
283 ENDDO
284 1001 CONTINUE
285 CLOSE(modelDataUnit)
286
287 C-- Report contents of model parameter file
288 WRITE(msgBuf,'(A)')
289 &'// ======================================================='
290 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
291 & SQUEEZE_RIGHT , 1)
292 WRITE(msgBuf,'(A)') '// Model parameter file "data"'
293 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
294 & SQUEEZE_RIGHT , 1)
295 WRITE(msgBuf,'(A)')
296 &'// ======================================================='
297 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
298 & SQUEEZE_RIGHT , 1)
299 iUnit = scrUnit2
300 REWIND(iUnit)
301 DO WHILE ( .TRUE. )
302 READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
303 IL = MAX(ILNBLNK(RECORD),1)
304 WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
305 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
306 & SQUEEZE_RIGHT , 1)
307 ENDDO
308 2001 CONTINUE
309 CLOSE(iUnit)
310 WRITE(msgBuf,'(A)') ' '
311 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
312 & SQUEEZE_RIGHT , 1)
313
314
315 C-- Read settings from model parameter file "data".
316 iUnit = scrUnit1
317 REWIND(iUnit)
318
319 C-- Set default "physical" parameters
320 viscAhW = UNSET_RL
321 viscA4W = UNSET_RL
322 viscAhD = UNSET_RL
323 viscAhZ = UNSET_RL
324 viscA4D = UNSET_RL
325 viscA4Z = UNSET_RL
326 viscAz = UNSET_RL
327 viscAr = UNSET_RL
328 viscAp = UNSET_RL
329 diffKzT = UNSET_RL
330 diffKpT = UNSET_RL
331 diffKrT = UNSET_RL
332 diffKzS = UNSET_RL
333 diffKpS = UNSET_RL
334 diffKrS = UNSET_RL
335 DO k=1,Nr
336 diffKrNrT(k) = UNSET_RL
337 diffKrNrS(k) = UNSET_RL
338 ENDDO
339 gBaro = UNSET_RL
340 rhoConst = UNSET_RL
341 omega = UNSET_RL
342 hFacMinDr = UNSET_RL
343 hFacMinDz = UNSET_RL
344 hFacMinDp = UNSET_RL
345 rhoConstFresh = UNSET_RL
346 convertFW2Salt = UNSET_RL
347 tAlpha = UNSET_RL
348 sBeta = UNSET_RL
349 tempVertAdvScheme = 0
350 saltVertAdvScheme = 0
351 C-- z,p,r coord input switching.
352 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM01'
353 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
354 & SQUEEZE_RIGHT , 1)
355 READ(UNIT=iUnit,NML=PARM01) !,IOSTAT=errIO)
356 IF ( errIO .LT. 0 ) THEN
357 WRITE(msgBuf,'(A)')
358 & 'S/R INI_PARMS'
359 CALL PRINT_ERROR( msgBuf , 1)
360 WRITE(msgBuf,'(A)')
361 & 'Error reading numerical model '
362 CALL PRINT_ERROR( msgBuf , 1)
363 WRITE(msgBuf,'(A)')
364 & 'parameter file "data"'
365 CALL PRINT_ERROR( msgBuf , 1)
366 WRITE(msgBuf,'(A)')
367 & 'Problem in namelist PARM01'
368 CALL PRINT_ERROR( msgBuf , 1)
369 CALL MODELDATA_EXAMPLE( myThid )
370 STOP 'ABNORMAL END: S/R INI_PARMS'
371 ELSE
372 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM01 : OK'
373 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
374 & SQUEEZE_RIGHT , 1)
375 ENDIF
376
377 C- set the type of vertical coordinate and type of fluid
378 C according to buoyancyRelation
379 usingPCoords = .FALSE.
380 usingZCoords = .FALSE.
381 fluidIsAir = .FALSE.
382 fluidIsWater = .FALSE.
383 IF ( buoyancyRelation.EQ.'ATMOSPHERIC' ) THEN
384 usingPCoords = .TRUE.
385 fluidIsAir = .TRUE.
386 ELSEIF ( buoyancyRelation.EQ.'OCEANICP') THEN
387 usingPCoords = .TRUE.
388 fluidIsWater = .TRUE.
389 ELSEIF ( buoyancyRelation.EQ.'OCEANIC' ) THEN
390 usingZCoords = .TRUE.
391 fluidIsWater = .TRUE.
392 ELSE
393 WRITE(msgBuf,'(2A)') 'S/R INI_PARMS:',
394 & ' Bad value of buoyancyRelation '
395 CALL PRINT_ERROR( msgBuf , myThid)
396 STOP 'ABNORMAL END: S/R INI_PARMS'
397 ENDIF
398
399 IF ( implicitFreeSurface ) freeSurfFac = 1.D0
400 IF ( rigidLid ) freeSurfFac = 0.D0
401 IF ( gBaro .EQ. UNSET_RL ) gBaro=gravity
402 IF ( rhoConst .EQ. UNSET_RL ) rhoConst=rhoNil
403 IF ( rhoConstFresh .EQ. UNSET_RL ) rhoConstFresh=rhoConst
404 IF ( omega .EQ. UNSET_RL ) THEN
405 omega = 0. _d 0
406 IF ( rotationPeriod .NE. 0. _d 0 )
407 & omega = 2.D0 * PI / rotationPeriod
408 ELSEIF ( omega .EQ. 0. _d 0 ) THEN
409 rotationPeriod = 0. _d 0
410 ELSE
411 rotationPeriod = 2.D0 * PI / omega
412 ENDIF
413 IF (atm_Rd .EQ. UNSET_RL) THEN
414 atm_Rd = atm_Cp * atm_kappa
415 ELSE
416 atm_kappa = atm_Rd / atm_Cp
417 ENDIF
418 C-- On/Off flags for each terms of the momentum equation
419 nonHydrostatic = momStepping .AND. nonHydrostatic
420 quasiHydrostatic = momStepping .AND. quasiHydrostatic
421 momAdvection = momStepping .AND. momAdvection
422 momViscosity = momStepping .AND. momViscosity
423 momForcing = momStepping .AND. momForcing
424 useCoriolis = momStepping .AND. useCoriolis
425 useCDscheme = momStepping .AND. useCDscheme
426 momPressureForcing= momStepping .AND. momPressureForcing
427 momImplVertAdv = momAdvection .AND. momImplVertAdv
428 implicitViscosity= momViscosity .AND. implicitViscosity
429 C-- Momentum viscosity on/off flag.
430 IF ( momViscosity ) THEN
431 vfFacMom = 1.D0
432 ELSE
433 vfFacMom = 0.D0
434 ENDIF
435 C-- Momentum advection on/off flag.
436 IF ( momAdvection ) THEN
437 afFacMom = 1.D0
438 ELSE
439 afFacMom = 0.D0
440 ENDIF
441 C-- Momentum forcing on/off flag.
442 IF ( momForcing ) THEN
443 foFacMom = 1.D0
444 ELSE
445 foFacMom = 0.D0
446 ENDIF
447 C-- Coriolis term on/off flag.
448 IF ( useCoriolis ) THEN
449 cfFacMom = 1.D0
450 ELSE
451 cfFacMom = 0.D0
452 ENDIF
453 C-- Pressure term on/off flag.
454 IF ( momPressureForcing ) THEN
455 pfFacMom = 1.D0
456 ELSE
457 pfFacMom = 0.D0
458 ENDIF
459 C-- Metric terms on/off flag.
460 IF ( metricTerms ) THEN
461 mTFacMom = 1.D0
462 ELSE
463 mTFacMom = 0.D0
464 ENDIF
465 C-- Non-hydrostatic/quasi-hydrostatic
466 IF (nonHydrostatic.AND.quasiHydrostatic) THEN
467 WRITE(msgBuf,'(A)')
468 & 'Illegal: both nonHydrostatic = quasiHydrostatic = TRUE'
469 CALL PRINT_ERROR( msgBuf , myThid)
470 STOP 'ABNORMAL END: S/R INI_PARMS'
471 ENDIF
472 C-- Advection and Forcing for Temp and salt on/off flags
473 tempAdvection = tempStepping .AND. tempAdvection
474 tempForcing = tempStepping .AND. tempForcing
475 saltAdvection = saltStepping .AND. saltAdvection
476 saltForcing = saltStepping .AND. saltForcing
477 tempImplVertAdv = tempAdvection .AND. tempImplVertAdv
478 saltImplVertAdv = saltAdvection .AND. saltImplVertAdv
479 IF (tempVertAdvScheme.EQ.0) tempVertAdvScheme = tempAdvScheme
480 IF (saltVertAdvScheme.EQ.0) saltVertAdvScheme = saltAdvScheme
481 C-- horizontal viscosity for vertical moments
482 IF ( viscAhW .EQ. UNSET_RL ) viscAhW = viscAh
483 IF ( viscA4W .EQ. UNSET_RL ) viscA4W = viscA4
484 C-- horizontal viscosity (acting on Divergence or Vorticity)
485 IF ( viscAhD .EQ. UNSET_RL ) viscAhD = viscAh
486 IF ( viscAhZ .EQ. UNSET_RL ) viscAhZ = viscAh
487 IF ( viscA4D .EQ. UNSET_RL ) viscA4D = viscA4
488 IF ( viscA4Z .EQ. UNSET_RL ) viscA4Z = viscA4
489 C-- useAnisotropicViscAGridMax requires that viscA*GridMax be set
490 IF ( useAnisotropicViscAGridMax ) THEN
491 IF ( viscAhGridMax .EQ. 1.D21 ) viscAhGridMax = 0.25
492 IF ( viscA4GridMax .EQ. 1.D21 ) viscA4GridMax = 0.25
493 ENDIF
494 C-- z,p,r coord input switching.
495 IF ( viscAz .NE. UNSET_RL ) zCoordInputData = .TRUE.
496 IF ( viscAp .NE. UNSET_RL ) pCoordInputData = .TRUE.
497 IF ( viscAr .NE. UNSET_RL ) rCoordInputData = .TRUE.
498 IF ( viscAr .EQ. UNSET_RL ) viscAr = viscAz
499 IF ( viscAr .EQ. UNSET_RL ) viscAr = viscAp
500 IF ( viscAr .EQ. UNSET_RL ) viscAr = viscArDefault
501
502 IF ( diffKzT .NE. UNSET_RL ) zCoordInputData = .TRUE.
503 IF ( diffKpT .NE. UNSET_RL ) pCoordInputData = .TRUE.
504 IF ( diffKrT .NE. UNSET_RL ) rCoordInputData = .TRUE.
505 IF ( diffKrT .EQ. UNSET_RL ) diffKrT = diffKzT
506 IF ( diffKrT .EQ. UNSET_RL ) diffKrT = diffKpT
507 IF ( diffKrT .EQ. UNSET_RL ) diffKrT = diffKrTDefault
508 diffKrSet = .TRUE.
509 DO k=1,Nr
510 IF ( diffKrNrT(k).EQ. UNSET_RL ) diffKrSet = .FALSE.
511 ENDDO
512 IF ( .NOT.diffKrSet ) THEN
513 DO k=1,Nr
514 diffKrNrT(k) = diffKrT
515 ENDDO
516 ELSEIF ( diffKrT.NE.diffKrTDefault ) THEN
517 WRITE(msgBuf,'(2A)') 'S/R INI_PARMS: Cannot set both ',
518 & 'diffKrNrT and diffKrT (or Kp,Kz) in input file data'
519 CALL PRINT_ERROR( msgBuf , myThid)
520 STOP 'ABNORMAL END: S/R INI_PARMS'
521 ENDIF
522
523 IF ( diffKzS .NE. UNSET_RL ) zCoordInputData = .TRUE.
524 IF ( diffKpS .NE. UNSET_RL ) pCoordInputData = .TRUE.
525 IF ( diffKrS .NE. UNSET_RL ) rCoordInputData = .TRUE.
526 IF ( diffKrS .EQ. UNSET_RL ) diffKrS = diffKzS
527 IF ( diffKrS .EQ. UNSET_RL ) diffKrS = diffKpS
528 IF ( diffKrS .EQ. UNSET_RL ) diffKrS = diffKrSDefault
529 diffKrSet = .TRUE.
530 DO k=1,Nr
531 IF ( diffKrNrS(k).EQ. UNSET_RL ) diffKrSet = .FALSE.
532 ENDDO
533 IF ( .NOT.diffKrSet ) THEN
534 DO k=1,Nr
535 diffKrNrS(k) = diffKrS
536 ENDDO
537 ELSEIF ( diffKrS.NE.diffKrSDefault ) THEN
538 WRITE(msgBuf,'(2A)') 'S/R INI_PARMS: Cannot set both ',
539 & 'diffKrNrS and diffKrS (or Kp,Kz) in input file data'
540 CALL PRINT_ERROR( msgBuf , myThid)
541 STOP 'ABNORMAL END: S/R INI_PARMS'
542 ENDIF
543
544 IF ( hFacMinDz .NE. UNSET_RL ) zCoordInputData = .TRUE.
545 IF ( hFacMinDp .NE. UNSET_RL ) pCoordInputData = .TRUE.
546 IF ( hFacMinDr .NE. UNSET_RL ) rCoordInputData = .TRUE.
547 IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr = hFacMinDz
548 IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr = hFacMinDp
549 IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr = hFacMinDrDefault
550
551 IF (convertFW2Salt.EQ.UNSET_RL) THEN
552 convertFW2Salt = 35.
553 IF (useRealFreshWaterFlux) convertFW2Salt=-1
554 ENDIF
555
556 IF ( ivdc_kappa .NE. 0. .AND. .NOT. implicitDiffusion ) THEN
557 WRITE(msgBuf,'(A,A)')
558 & 'S/R INI_PARMS: To use ivdc_kappa you must enable implicit',
559 & ' vertical diffusion.'
560 CALL PRINT_ERROR( msgBuf , myThid)
561 STOP 'ABNORMAL END: S/R INI_PARMS'
562 ENDIF
563
564 coordsSet = 0
565 IF ( zCoordInputData ) coordsSet = coordsSet + 1
566 IF ( pCoordInputData ) coordsSet = coordsSet + 1
567 IF ( rCoordInputData ) coordsSet = coordsSet + 1
568 IF ( coordsSet .GT. 1 ) THEN
569 WRITE(msgBuf,'(A)')
570 & 'S/R INI_PARMS: Cannot mix z, p and r in the input data.'
571 CALL PRINT_ERROR( msgBuf , myThid)
572 STOP 'ABNORMAL END: S/R INI_PARMS'
573 ENDIF
574 IF ( rhoConst .LE. 0. ) THEN
575 WRITE(msgBuf,'(A)')
576 & 'S/R INI_PARMS: rhoConst must be greater than 0.'
577 CALL PRINT_ERROR( msgBuf , myThid)
578 STOP 'ABNORMAL END: S/R INI_PARMS'
579 ELSE
580 recip_rhoConst = 1.D0 / rhoConst
581 ENDIF
582 IF ( rhoNil .LE. 0. ) THEN
583 WRITE(msgBuf,'(A)')
584 & 'S/R INI_PARMS: rhoNil must be greater than 0.'
585 CALL PRINT_ERROR( msgBuf , myThid)
586 STOP 'ABNORMAL END: S/R INI_PARMS'
587 ELSE
588 recip_rhoNil = 1.D0 / rhoNil
589 ENDIF
590 IF ( HeatCapacity_Cp .LE. 0. ) THEN
591 WRITE(msgBuf,'(A)')
592 & 'S/R INI_PARMS: HeatCapacity_Cp must be greater than 0.'
593 CALL PRINT_ERROR( msgBuf , myThid)
594 STOP 'ABNORMAL END: S/R INI_PARMS'
595 ELSE
596 recip_Cp = 1.D0 / HeatCapacity_Cp
597 ENDIF
598 IF ( gravity .LE. 0. ) THEN
599 WRITE(msgBuf,'(A)')
600 & 'S/R INI_PARMS: gravity must be greater than 0.'
601 CALL PRINT_ERROR( msgBuf , myThid)
602 STOP 'ABNORMAL END: S/R INI_PARMS'
603 ELSE
604 recip_gravity = 1.D0 / gravity
605 ENDIF
606 C This flags are now passed to RW and MDSIO packages in ini_model_io.F
607 C Set globalFiles flag for READ_WRITE_FLD package
608 c CALL SET_WRITE_GLOBAL_FLD( globalFiles )
609 C Set globalFiles flag for READ_WRITE_REC package
610 c CALL SET_WRITE_GLOBAL_REC( globalFiles )
611 C Set globalFiles flag for READ_WRITE_REC package
612 c CALL SET_WRITE_GLOBAL_PICKUP( globalFiles )
613
614 C Check for retired parameters still being used
615 nRetired = 0
616 IF ( zonal_filt_lat .NE. UNSET_RL ) THEN
617 nRetired = nRetired+1
618 WRITE(msgBuf,'(A,A)')
619 & 'S/R INI_PARMS: Paramater "zonal_filt_lat" is',
620 & ' no longer allowed in file "data".'
621 CALL PRINT_ERROR( msgBuf , myThid)
622 WRITE(msgBuf,'(A,A)')
623 & 'S/R INI_PARMS: Paramater "zonal_filt_lat" is',
624 & ' now read from file "data.zonfilt".'
625 CALL PRINT_ERROR( msgBuf , myThid)
626 ENDIF
627 IF ( gravitySign .NE. UNSET_RL ) THEN
628 nRetired = nRetired+1
629 WRITE(msgBuf,'(A,A)')
630 & 'S/R INI_PARMS: "gravitySign" is set according to vertical ',
631 & ' coordinate and is no longer allowed in file "data".'
632 CALL PRINT_ERROR( msgBuf , myThid)
633 ENDIF
634 IF ( tracerAdvScheme .NE. UNSET_I ) THEN
635 nRetired = nRetired+1
636 WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "tracerAdvScheme" ',
637 & '(old passive tracer code) is no longer allowed in file "data"'
638 CALL PRINT_ERROR( msgBuf , myThid)
639 ENDIF
640 IF ( trac_EvPrRn .NE. UNSET_RL ) THEN
641 nRetired = nRetired+1
642 WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "trac_EvPrRn" ',
643 & '(old passive tracer code) is no longer allowed in file "data"'
644 CALL PRINT_ERROR( msgBuf , myThid)
645 ENDIF
646 IF ( .NOT. tempDiffusion ) THEN
647 nRetired = nRetired+1
648 WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "tempDiffusion" ',
649 & 'is no longer allowed in file "data"'
650 CALL PRINT_ERROR( msgBuf , myThid)
651 WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: to turn off diffusion',
652 & ' => set diffusivity to zero'
653 CALL PRINT_ERROR( msgBuf , myThid)
654 ENDIF
655 IF ( .NOT. saltDiffusion ) THEN
656 nRetired = nRetired+1
657 WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "saltDiffusion" ',
658 & 'is no longer allowed in file "data"'
659 CALL PRINT_ERROR( msgBuf , myThid)
660 WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: to turn off diffusion',
661 & ' => set diffusivity to zero'
662 CALL PRINT_ERROR( msgBuf , myThid)
663 ENDIF
664
665 C-- Elliptic solver parameters
666 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM02'
667 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
668 & SQUEEZE_RIGHT , 1)
669 READ(UNIT=iUnit,NML=PARM02) !,IOSTAT=errIO)
670 IF ( errIO .LT. 0 ) THEN
671 WRITE(msgBuf,'(A)')
672 & 'S/R INI_PARMS'
673 CALL PRINT_ERROR( msgBuf , 1)
674 WRITE(msgBuf,'(A)')
675 & 'Error reading numerical model '
676 CALL PRINT_ERROR( msgBuf , 1)
677 WRITE(msgBuf,'(A)')
678 & 'parameter file "data".'
679 CALL PRINT_ERROR( msgBuf , 1)
680 WRITE(msgBuf,'(A)')
681 & 'Problem in namelist PARM02'
682 CALL PRINT_ERROR( msgBuf , 1)
683 CALL MODELDATA_EXAMPLE( myThid )
684 STOP 'ABNORMAL END: S/R INI_PARMS'
685 ELSE
686 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM02 : OK'
687 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
688 & SQUEEZE_RIGHT , 1)
689 ENDIF
690
691 C-- Time stepping parameters
692 rCD = -1.D0
693 latBandClimRelax = UNSET_RL
694 deltaTtracer = 0. _d 0
695 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM03'
696 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
697 & SQUEEZE_RIGHT , 1)
698 READ(UNIT=iUnit,NML=PARM03) !,IOSTAT=errIO)
699 IF ( errIO .LT. 0 ) THEN
700 WRITE(msgBuf,'(A)')
701 & 'S/R INI_PARMS'
702 CALL PRINT_ERROR( msgBuf , 1)
703 WRITE(msgBuf,'(A)')
704 & 'Error reading numerical model '
705 CALL PRINT_ERROR( msgBuf , 1)
706 WRITE(msgBuf,'(A)')
707 & 'parameter file "data"'
708 CALL PRINT_ERROR( msgBuf , 1)
709 WRITE(msgBuf,'(A)')
710 & 'Problem in namelist PARM03'
711 CALL PRINT_ERROR( msgBuf , 1)
712 CALL MODELDATA_EXAMPLE( myThid )
713 STOP 'ABNORMAL END: S/R INI_PARMS'
714 ELSE
715 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM03 : OK'
716 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
717 & SQUEEZE_RIGHT , 1)
718 ENDIF
719 C Process "timestepping" params
720 C o Time step size
721 IF ( deltaTtracer .NE. dTtracerLev(1) .AND.
722 & deltaTtracer .NE. 0. .AND. dTtracerLev(1) .NE. 0. ) THEN
723 WRITE(msgBuf,'(A)')
724 & 'S/R INI_PARMS: deltaTtracer & dTtracerLev(1) not equal'
725 CALL PRINT_ERROR( msgBuf , myThid)
726 STOP 'ABNORMAL END: S/R INI_PARMS'
727 ELSEIF ( dTtracerLev(1) .NE. 0. ) THEN
728 deltaTtracer = dTtracerLev(1)
729 ENDIF
730 IF ( deltaT .EQ. 0. ) deltaT = deltaTmom
731 IF ( deltaT .EQ. 0. ) deltaT = deltaTtracer
732 IF ( deltaTmom .EQ. 0. ) deltaTmom = deltaT
733 IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT
734 IF ( deltaTClock .EQ. 0. ) deltaTClock = deltaT
735 DO k=1,Nr
736 IF (dTtracerLev(k).EQ.0.) dTtracerLev(k)= deltaTtracer
737 ENDDO
738 C Note that this line should set deltaFreesurf=deltaTmom
739 C but this would change a lot of existing set-ups so we are
740 C obliged to set the default inappropriately.
741 C Be advised that when using asynchronous time stepping
742 C it is better to set deltaTreesurf=deltaTtracer
743 IF ( deltaTfreesurf .EQ. 0. ) deltaTfreesurf = deltaTmom
744 IF ( periodicExternalForcing ) THEN
745 IF ( externForcingCycle*externForcingPeriod .EQ. 0. ) THEN
746 WRITE(msgBuf,'(A)')
747 & 'S/R INI_PARMS: externForcingCycle,externForcingPeriod =0'
748 CALL PRINT_ERROR( msgBuf , 1)
749 STOP 'ABNORMAL END: S/R INI_PARMS'
750 ENDIF
751 IF ( INT(externForcingCycle/externForcingPeriod) .NE.
752 & externForcingCycle/externForcingPeriod ) THEN
753 WRITE(msgBuf,'(A)')
754 & 'S/R INI_PARMS: externForcingCycle <> N*externForcingPeriod'
755 CALL PRINT_ERROR( msgBuf , 1)
756 STOP 'ABNORMAL END: S/R INI_PARMS'
757 ENDIF
758 IF ( externForcingCycle.lt.externForcingPeriod ) THEN
759 WRITE(msgBuf,'(A)')
760 & 'S/R INI_PARMS: externForcingCycle < externForcingPeriod'
761 CALL PRINT_ERROR( msgBuf , 1)
762 STOP 'ABNORMAL END: S/R INI_PARMS'
763 ENDIF
764 IF ( externForcingPeriod.lt.deltaTclock ) THEN
765 WRITE(msgBuf,'(A)')
766 & 'S/R INI_PARMS: externForcingPeriod < deltaTclock'
767 CALL PRINT_ERROR( msgBuf , 1)
768 STOP 'ABNORMAL END: S/R INI_PARMS'
769 ENDIF
770 ENDIF
771 C o Convection frequency
772 IF ( cAdjFreq .LT. 0. ) THEN
773 cAdjFreq = deltaTClock
774 ENDIF
775 IF ( ivdc_kappa .NE. 0. .AND. cAdjFreq .NE. 0. ) THEN
776 WRITE(msgBuf,'(A,A)')
777 & 'S/R INI_PARMS: You have enabled both ivdc_kappa and',
778 & ' convective adjustment.'
779 CALL PRINT_ERROR( msgBuf , myThid)
780 STOP 'ABNORMAL END: S/R INI_PARMS'
781 ENDIF
782 IF (useCDscheme) THEN
783 C o CD coupling (CD scheme):
784 IF ( tauCD .EQ. 0.D0 ) tauCD = deltaTmom
785 IF ( rCD .LT. 0. ) rCD = 1. _d 0 - deltaTMom/tauCD
786 ENDIF
787 C o Temperature climatology relaxation time scale
788 IF ( tauThetaClimRelax .EQ. 0.D0 ) THEN
789 doThetaClimRelax = .FALSE.
790 ELSE
791 doThetaClimRelax = .TRUE.
792 ENDIF
793 C o Salinity climatology relaxation time scale
794 IF ( tauSaltClimRelax .EQ. 0.D0 ) THEN
795 doSaltClimRelax = .FALSE.
796 ELSE
797 doSaltClimRelax = .TRUE.
798 ENDIF
799 C o Tracer 1 climatology relaxation time scale
800 IF ( tauTr1ClimRelax .EQ. 0.D0 ) THEN
801 doTr1ClimRelax = .FALSE.
802 lambdaTr1ClimRelax = 0.D0
803 ELSE
804 doTr1ClimRelax = .TRUE.
805 lambdaTr1ClimRelax = 1./tauTr1ClimRelax
806 ENDIF
807
808 C o Base time
809 IF ( nIter0.NE.0 .AND. startTime.NE.0. .AND. baseTime.EQ.0. )
810 & baseTime = startTime - deltaTClock*float(nIter0)
811 C o Start time
812 IF ( nIter0 .NE. 0 .AND. startTime .EQ. 0. )
813 & startTime = baseTime + deltaTClock*float(nIter0)
814 C o nIter0
815 IF ( nIter0 .EQ. 0 .AND. startTime .NE. baseTime )
816 & nIter0 = NINT( (startTime-baseTime)/deltaTClock )
817
818 C o nTimeSteps 1
819 IF ( nTimeSteps .EQ. 0 .AND. nEndIter .NE. 0 )
820 & nTimeSteps = nEndIter-nIter0
821 C o nTimeSteps 2
822 IF ( nTimeSteps .EQ. 0 .AND. endTime .NE. 0. )
823 & nTimeSteps = NINT((endTime-startTime)/deltaTclock)
824 C o nEndIter 1
825 IF ( nEndIter .EQ. 0 .AND. nTimeSteps .NE. 0 )
826 & nEndIter = nIter0+nTimeSteps
827 C o nEndIter 2
828 IF ( nEndIter .EQ. 0 .AND. endTime .NE. 0. )
829 & nEndIter = NINT((endTime-baseTime)/deltaTclock)
830 C o End Time 1
831 IF ( endTime .EQ. 0. .AND. nTimeSteps .NE. 0 )
832 & endTime = startTime + deltaTClock*float(nTimeSteps)
833 C o End Time 2
834 IF ( endTime .EQ. 0. .AND. nEndIter .NE. 0 )
835 & endTime = baseTime + deltaTClock*float(nEndIter)
836
837 C o Consistent?
838 IF ( startTime .NE. baseTime+deltaTClock*float(nIter0) ) THEN
839 WRITE(msgBuf,'(A)')
840 & 'S/R INI_PARMS: startTime, baseTime and nIter0 are inconsistent'
841 CALL PRINT_ERROR( msgBuf , 1)
842 WRITE(msgBuf,'(A)')
843 & 'S/R INI_PARMS: Perhaps more than two were set at once'
844 CALL PRINT_ERROR( msgBuf , 1)
845 STOP 'ABNORMAL END: S/R INI_PARMS'
846 ENDIF
847 IF ( nEndIter .NE. nIter0+nTimeSteps ) THEN
848 WRITE(msgBuf,'(A)')
849 & 'S/R INI_PARMS: nIter0, nTimeSteps and nEndIter are inconsistent'
850 CALL PRINT_ERROR( msgBuf , 1)
851 WRITE(msgBuf,'(A)')
852 & 'S/R INI_PARMS: Perhaps more than two were set at once'
853 CALL PRINT_ERROR( msgBuf , 1)
854 STOP 'ABNORMAL END: S/R INI_PARMS'
855 ENDIF
856 IF ( nTimeSteps .NE. NINT((endTime-startTime)/deltaTClock) )
857 & THEN
858 WRITE(msgBuf,'(A)')
859 & 'S/R INI_PARMS: both endTime and nTimeSteps have been set'
860 CALL PRINT_ERROR( msgBuf , 1)
861 WRITE(msgBuf,'(A)')
862 & 'S/R INI_PARMS: but are inconsistent'
863 CALL PRINT_ERROR( msgBuf , 1)
864 STOP 'ABNORMAL END: S/R INI_PARMS'
865 ENDIF
866
867 C o Monitor (should also add CPP flag for monitor?)
868 IF (monitorFreq.LT.0.) THEN
869 monitorFreq=0.
870 IF (dumpFreq.NE.0.) monitorFreq=dumpFreq
871 IF (diagFreq.NE.0..AND.diagFreq.LT.monitorFreq)
872 & monitorFreq=diagFreq
873 IF (taveFreq.NE.0..AND.taveFreq.LT.monitorFreq)
874 & monitorFreq=taveFreq
875 IF (chkPtFreq.NE.0..AND.chkPtFreq.LT.monitorFreq)
876 & monitorFreq=chkPtFreq
877 IF (pChkPtFreq.NE.0..AND.pChkPtFreq.LT.monitorFreq)
878 & monitorFreq=pChkPtFreq
879 IF (monitorFreq.EQ.0.) monitorFreq=deltaTclock
880 ENDIF
881
882 C-- Grid parameters
883 C In cartesian coords distances are in metres
884 DO K =1,Nr
885 delZ(K) = UNSET_RL
886 delP(K) = UNSET_RL
887 delR(K) = UNSET_RL
888 ENDDO
889 C In spherical polar distances are in degrees
890 recip_rSphere = 1.D0/rSphere
891 dxSpacing = UNSET_RL
892 dySpacing = UNSET_RL
893 delXfile = ' '
894 delYfile = ' '
895 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM04'
896 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
897 & SQUEEZE_RIGHT , 1)
898 READ(UNIT=iUnit,NML=PARM04,IOSTAT=errIO)
899 IF ( errIO .LT. 0 ) THEN
900 WRITE(msgBuf,'(A)')
901 & 'S/R INI_PARMS'
902 CALL PRINT_ERROR( msgBuf , 1)
903 WRITE(msgBuf,'(A)')
904 & 'Error reading numerical model '
905 CALL PRINT_ERROR( msgBuf , 1)
906 WRITE(msgBuf,'(A)')
907 & 'parameter file "data"'
908 CALL PRINT_ERROR( msgBuf , 1)
909 WRITE(msgBuf,'(A)')
910 & 'Problem in namelist PARM04'
911 CALL PRINT_ERROR( msgBuf , 1)
912 CALL MODELDATA_EXAMPLE( myThid )
913 STOP 'ABNORMAL END: S/R INI_PARMS'
914 ELSE
915 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM04 : OK'
916 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
917 & SQUEEZE_RIGHT , 1)
918 ENDIF
919
920 C Check for retired parameters still being used
921 IF ( rkFac .NE. UNSET_RL ) THEN
922 nRetired = nRetired+1
923 WRITE(msgBuf,'(A,A)')
924 & 'S/R INI_PARMS: "rkFac" has been replaced by -rkSign ',
925 & ' and is no longer allowed in file "data".'
926 CALL PRINT_ERROR( msgBuf , myThid)
927 ENDIF
928 IF ( groundAtK1 ) THEN
929 c nRetired = nRetired+1
930 WRITE(msgBuf,'(A,A)')
931 & 'S/R INI_PARMS: "groundAtK1" is set according to vertical ',
932 & ' coordinate and is no longer allowed in file "data".'
933 CALL PRINT_ERROR( msgBuf , myThid)
934 ENDIF
935
936 C X coordinate
937 IF ( delXfile .NE. ' ' ) THEN
938 IF ( delX(1) .NE. UNSET_RL .OR. dxSpacing .NE. UNSET_RL ) THEN
939 WRITE(msgBuf,'(A,A)') 'Too many specifications for delX:',
940 & 'Specify only one of delX, dxSpacing or delXfile'
941 CALL PRINT_ERROR( msgBuf , 1)
942 STOP 'ABNORMAL END: S/R INI_PARMS'
943 ELSE
944 _BEGIN_MASTER( myThid )
945 IF (readBinaryPrec.EQ.precFloat32) THEN
946 OPEN(37,FILE=delXfile,STATUS='OLD',FORM='UNFORMATTED',
947 & ACCESS='DIRECT',RECL=WORDLENGTH*Nx)
948 READ(37,rec=1) tmp4delX
949 #ifdef _BYTESWAPIO
950 call MDS_BYTESWAPR4( Nx, tmp4delX )
951 #endif
952 CLOSE(37)
953 DO i=1,Nx
954 delX(i) = tmp4delX(i)
955 ENDDO
956 ELSEIF (readBinaryPrec.EQ.precFloat64) THEN
957 OPEN(37,FILE=delXfile,STATUS='OLD',FORM='UNFORMATTED',
958 & ACCESS='DIRECT',RECL=WORDLENGTH*2*Nx)
959 READ(37,rec=1) tmp8delX
960 #ifdef _BYTESWAPIO
961 call MDS_BYTESWAPR8( Nx, tmp8delX )
962 #endif
963 CLOSE(37)
964 DO i=1,Nx
965 delX(i) = tmp8delX(i)
966 ENDDO
967 ENDIF
968 _END_MASTER(myThid)
969 ENDIF
970 ENDIF
971 IF ( dxSpacing .NE. UNSET_RL ) THEN
972 DO i=1,Nx
973 delX(i) = dxSpacing
974 ENDDO
975 ENDIF
976 C Y coordinate
977 IF ( delYfile .NE. ' ' ) THEN
978 IF ( delY(1) .NE. UNSET_RL .OR. dySpacing .NE. UNSET_RL ) THEN
979 WRITE(msgBuf,'(A,A)') 'Too many specifications for delY:',
980 & 'Specify only one of delY, dySpacing or delYfile'
981 CALL PRINT_ERROR( msgBuf , 1)
982 STOP 'ABNORMAL END: S/R INI_PARMS'
983 ELSE
984 _BEGIN_MASTER( myThid )
985 IF (readBinaryPrec.EQ.precFloat32) THEN
986 OPEN(37,FILE=delYfile,STATUS='OLD',FORM='UNFORMATTED',
987 & ACCESS='DIRECT',RECL=WORDLENGTH*Ny)
988 READ(37,rec=1) tmp4delY
989 #ifdef _BYTESWAPIO
990 call MDS_BYTESWAPR4( Ny, tmp4delY )
991 #endif
992 CLOSE(37)
993 DO j=1,Ny
994 delY(j) = tmp4delY(j)
995 ENDDO
996 ELSEIF (readBinaryPrec.EQ.precFloat64) THEN
997 OPEN(37,FILE=delYfile,STATUS='OLD',FORM='UNFORMATTED',
998 & ACCESS='DIRECT',RECL=WORDLENGTH*2*Ny)
999 READ(37,rec=1) tmp8delY
1000 #ifdef _BYTESWAPIO
1001 call MDS_BYTESWAPR8( Ny, tmp8delY )
1002 #endif
1003 CLOSE(37)
1004 DO j=1,Ny
1005 delY(j) = tmp8delY(j)
1006 ENDDO
1007 ENDIF
1008 _END_MASTER(myThid)
1009 ENDIF
1010 ENDIF
1011 IF ( dySpacing .NE. UNSET_RL ) THEN
1012 DO i=1,Ny
1013 delY(i) = dySpacing
1014 ENDDO
1015 ENDIF
1016 C
1017 IF ( rSphere .NE. 0 ) THEN
1018 recip_rSphere = 1.D0/rSphere
1019 ELSE
1020 recip_rSphere = 0.
1021 ENDIF
1022 C-- Check for conflicting grid definitions.
1023 goptCount = 0
1024 IF ( usingCartesianGrid ) goptCount = goptCount+1
1025 IF ( usingSphericalPolarGrid ) goptCount = goptCount+1
1026 IF ( usingCurvilinearGrid ) goptCount = goptCount+1
1027 IF ( usingCylindricalGrid ) goptCount = goptCount+1
1028 IF ( goptCount .GT. 1 ) THEN
1029 WRITE(msgBuf,'(A)')
1030 & 'S/R INI_PARMS: More than one coordinate system requested'
1031 CALL PRINT_ERROR( msgBuf , myThid)
1032 STOP 'ABNORMAL END: S/R INI_PARMS'
1033 ENDIF
1034 IF ( goptCount .LT. 1 ) THEN
1035 C- No horizontal grid is specified => use Cartesian grid as default:
1036 WRITE(msgBuf,'(A)')
1037 & 'S/R INI_PARMS: No horizontal grid requested'
1038 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
1039 & SQUEEZE_RIGHT , myThid)
1040 WRITE(msgBuf,'(A)')
1041 & 'S/R INI_PARMS: => Use Cartesian Grid as default'
1042 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
1043 & SQUEEZE_RIGHT , myThid)
1044 usingCartesianGrid = .TRUE.
1045 ENDIF
1046 C-- Make metric term settings consistent with underlying grid.
1047 IF ( usingCartesianGrid ) THEN
1048 usingSphericalPolarMterms = .FALSE.
1049 metricTerms = .FALSE.
1050 useNHMTerms = .FALSE.
1051 mTFacMom = 0.
1052 useBetaPlaneF = .TRUE.
1053 ENDIF
1054 C-- Make metric term settings consistent with underlying grid.
1055 IF ( usingCylindricalGrid) THEN
1056 usingSphericalPolarMterms = .FALSE.
1057 metricTerms = .FALSE.
1058 useNHMTerms = .FALSE.
1059 mTFacMom = 1.
1060 useBetaPlaneF = .TRUE.
1061 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; Cylinder OK'
1062 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1063 & SQUEEZE_RIGHT , 1)
1064
1065 ENDIF
1066
1067 IF ( usingSphericalPolarGrid ) THEN
1068 useSphereF = .TRUE.
1069 usingSphericalPolarMterms = metricTerms
1070 ENDIF
1071 IF ( usingCurvilinearGrid ) THEN
1072 useSphereF = .TRUE.
1073 metricTerms = .FALSE.
1074 useNHMTerms = .FALSE.
1075 ENDIF
1076 C-- Set default for latitude-band where relaxation to climatology applies
1077 IF ( latBandClimRelax .EQ. UNSET_RL) THEN
1078 IF ( usingCartesianGrid ) latBandClimRelax = delY(1)*Ny*Ny
1079 IF ( usingSphericalPolarGrid ) latBandClimRelax= 180. _d 0
1080 IF ( usingCurvilinearGrid ) latBandClimRelax= 180. _d 0
1081 ENDIF
1082 C-- set cell Center depth and put Interface at the middle between 2 C
1083 setCenterDr = .FALSE.
1084 IF (delRc(1).NE.UNSET_RL) setCenterDr=.TRUE.
1085 DO K=1,Nr+1
1086 IF (delRc(K).EQ.UNSET_RL) setCenterDr = .FALSE.
1087 ENDDO
1088 C-- p, z, r coord parameters
1089 DO K = 1, Nr
1090 IF ( delZ(K) .NE. UNSET_RL ) zCoordInputData = .TRUE.
1091 IF ( delP(K) .NE. UNSET_RL ) pCoordInputData = .TRUE.
1092 IF ( delR(K) .NE. UNSET_RL ) rCoordInputData = .TRUE.
1093 IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delZ(K)
1094 IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delP(K)
1095 IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delRDefault(K)
1096 IF (.NOT.setCenterDr .AND. delR(K).EQ.delRDefault(K) ) THEN
1097 WRITE(msgBuf,'(A,I4)')
1098 & 'S/R INI_PARMS: No value for delZ/delP/delR at K = ',K
1099 CALL PRINT_ERROR( msgBuf , 1)
1100 STOP 'ABNORMAL END: S/R INI_PARMS'
1101 ELSEIF ( setCenterDr .AND. delR(K).NE.delRDefault(K) ) THEN
1102 WRITE(msgBuf,'(2A,I4)') 'S/R INI_PARMS:',
1103 & ' Cannot specify both delRc and delZ/delP/delR at K=', K
1104 CALL PRINT_ERROR( msgBuf , 1)
1105 STOP 'ABNORMAL END: S/R INI_PARMS'
1106 ENDIF
1107 ENDDO
1108 C Check for multiple coordinate systems
1109 CoordsSet = 0
1110 IF ( zCoordInputData ) coordsSet = coordsSet + 1
1111 IF ( pCoordInputData ) coordsSet = coordsSet + 1
1112 IF ( rCoordInputData ) coordsSet = coordsSet + 1
1113 IF ( coordsSet .GT. 1 ) THEN
1114 WRITE(msgBuf,'(A)')
1115 & 'S/R INI_PARMS: Cannot mix z, p and r in the input data.'
1116 CALL PRINT_ERROR( msgBuf , myThid)
1117 STOP 'ABNORMAL END: S/R INI_PARMS'
1118 ENDIF
1119
1120 C-- When using the dynamical pressure in EOS (with Z-coord.),
1121 C needs to activate specific part of the code (restart & exchange)
1122 c useDynP_inEos_Zc = .FALSE.
1123 useDynP_inEos_Zc = ( fluidIsWater .AND. usingZCoords
1124 & .AND. ( eosType .EQ. 'JMD95P' .OR.
1125 & eosType .EQ. 'UNESCO' .OR.
1126 & eosType .EQ. 'MDJWF' ) )
1127
1128 C-- Input files
1129 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM05'
1130 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1131 & SQUEEZE_RIGHT , 1)
1132 READ(UNIT=iUnit,NML=PARM05) !,IOSTAT=errIO)
1133 IF ( errIO .LT. 0 ) THEN
1134 WRITE(msgBuf,'(A)')
1135 & 'Error reading numerical model '
1136 CALL PRINT_ERROR( msgBuf , 1)
1137 WRITE(msgBuf,'(A)')
1138 & 'parameter file "data"'
1139 CALL PRINT_ERROR( msgBuf , 1)
1140 WRITE(msgBuf,'(A)')
1141 & 'Problem in namelist PARM05'
1142 CALL PRINT_ERROR( msgBuf , 1)
1143 CALL MODELDATA_EXAMPLE( myThid )
1144 STOP 'ABNORMAL END: S/R INI_PARMS'
1145 ELSE
1146 WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM05 : OK'
1147 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1148 & SQUEEZE_RIGHT , 1)
1149 ENDIF
1150
1151 C-- Set factors required for mixing pressure and meters as vertical coordinate.
1152 C rkSign is a "sign" parameter which is used where the orientation of the vertical
1153 C coordinate (pressure or meters) relative to the vertical index (K) is important.
1154 C rkSign = -1 applies when K and the coordinate are in the opposite sense.
1155 C rkSign = 1 applies when K and the coordinate are in the same sense.
1156 C horiVertRatio is a parameter that maps horizontal units to vertical units.
1157 C It is used in certain special cases where lateral and vertical terms are
1158 C being combined and a single frame of reference is needed.
1159 rkSign = -1. _d 0
1160 horiVertRatio = 1. _d 0
1161 gravitySign = -1. _d 0
1162 IF ( usingPCoords ) THEN
1163 gravitySign = 1. _d 0
1164 horiVertRatio = Gravity * rhoConst
1165 ENDIF
1166 convertEmP2rUnit = rhoConstFresh*recip_rhoConst*horiVertRatio
1167 recip_horiVertRatio = 1./horiVertRatio
1168
1169 c-- gradually replacing debugMode by debugLevel
1170 IF ( debugMode ) debugLevel = debLevB
1171
1172 c-- flag for approximate adjoint
1173 IF ( inAdExact ) THEN
1174 inAdTrue = .FALSE.
1175 inAdFALSE = .FALSE.
1176 ELSE
1177 inAdTrue = .TRUE.
1178 inAdFALSE = .FALSE.
1179 ENDIF
1180 C
1181 CLOSE(iUnit)
1182
1183 C-- Check whether any retired parameters were found.
1184 C-- Stop if they were
1185 IF ( nRetired .GT. 0 ) THEN
1186 WRITE(msgBuf,'(A)')
1187 & 'Error reading '
1188 CALL PRINT_ERROR( msgBuf , 1)
1189 WRITE(msgBuf,'(A)')
1190 & 'parameter file "data"'
1191 CALL PRINT_ERROR( msgBuf , 1)
1192 WRITE(msgBuf,'(A)')
1193 & 'some out of date parameters were found in the namelist'
1194 CALL PRINT_ERROR( msgBuf , 1)
1195 STOP 'ABNORMAL END: S/R INI_PARMS'
1196 ENDIF
1197
1198 _END_MASTER(myThid)
1199
1200 C-- Everyone else must wait for the parameters to be loaded
1201 _BARRIER
1202 C
1203 RETURN
1204 END

  ViewVC Help
Powered by ViewVC 1.1.22