/[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.103 - (hide annotations) (download)
Sun Dec 28 17:04:00 2003 UTC (20 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52e_pre
Changes since 1.102: +10 -4 lines
use CartesianGrid as default only if no horizontal grid is specified

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

  ViewVC Help
Powered by ViewVC 1.1.22