/[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.111 - (hide annotations) (download)
Wed Jun 2 13:23:55 2004 UTC (20 years ago) by adcroft
Branch: MAIN
Changes since 1.110: +3 -1 lines
Added Sadourny discretization of Coriolis in V.I. mode
 - moved some PARAMETERS from mom_*_coriolis.F to PARAMS.h
 - re-enabled use of omega3 in mom_vecinv.F

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

  ViewVC Help
Powered by ViewVC 1.1.22