/[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.95 - (hide annotations) (download)
Thu Apr 17 13:16:23 2003 UTC (21 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint50c_post, checkpoint50c_pre, checkpoint50d_post, checkpoint50f_post, checkpoint50f_pre, checkpoint50g_post, checkpoint50e_pre, checkpoint50e_post, checkpoint50d_pre, checkpoint50b_post
Changes since 1.94: +6 -8 lines
new flag "useCDscheme" (default=F);

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

  ViewVC Help
Powered by ViewVC 1.1.22