/[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.105 - (hide annotations) (download)
Sat Jan 3 00:39:42 2004 UTC (20 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52f_post, checkpoint52i_pre, hrcube_1, hrcube_2, checkpoint52e_post, checkpoint52f_pre, checkpoint52i_post, checkpoint52h_pre
Changes since 1.104: +1 -0 lines
Header was lost; put it back.

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

  ViewVC Help
Powered by ViewVC 1.1.22