/[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.142 - (show annotations) (download)
Mon Jan 3 23:16:32 2005 UTC (19 years, 4 months ago) by jmc
Branch: MAIN
Changes since 1.141: +3 -9 lines
debugMode & debugLevel: go back to what it was before.
  version 1.137 (ini_parms.F) & 1.77 (set_defaults.F)

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

  ViewVC Help
Powered by ViewVC 1.1.22