/[MITgcm]/MITgcm/model/src/ini_parms.F
ViewVC logotype

Annotation of /MITgcm/model/src/ini_parms.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.133 - (hide annotations) (download)
Mon Oct 18 21:36:08 2004 UTC (19 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint55i_post, checkpoint55h_post
Changes since 1.132: +26 -12 lines
set flags: fluidIsAir, fluidIsWater, usingPCoords, usingZCoords
 according to buoyancyRelation

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

  ViewVC Help
Powered by ViewVC 1.1.22