/[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.132 - (hide annotations) (download)
Mon Oct 18 16:04:20 2004 UTC (19 years, 7 months ago) by edhill
Branch: MAIN
Changes since 1.131: +2 -3 lines
 o remove all the *_ioinc flags and replace them with the single global
   outputTypesInclusive flag

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

  ViewVC Help
Powered by ViewVC 1.1.22