/[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.93 - (hide annotations) (download)
Mon Mar 17 17:10:42 2003 UTC (21 years, 2 months ago) by jmc
Branch: MAIN
Changes since 1.92: +9 -2 lines
set the Earth rotation either directly (omega) or from the rotation period

1 jmc 1.93 C $Header: /u/gcmpack/MITgcm/model/src/ini_parms.F,v 1.92 2003/02/18 15:35:36 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 adcroft 1.87 & 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     omega = 2.D0 * PI / rotationPeriod
306     ELSE
307     rotationPeriod = 2.D0 * PI / omega
308     ENDIF
309 jmc 1.89 IF (atm_Rd .EQ. UNSET_RL) THEN
310     atm_Rd = atm_Cp * atm_kappa
311     ELSE
312     atm_kappa = atm_Rd / atm_Cp
313     ENDIF
314 cnh 1.28 C-- Momentum viscosity on/off flag.
315 cnh 1.9 IF ( momViscosity ) THEN
316 cnh 1.28 vfFacMom = 1.D0
317 cnh 1.9 ELSE
318 cnh 1.28 vfFacMom = 0.D0
319 cnh 1.9 ENDIF
320 cnh 1.28 C-- Momentum advection on/off flag.
321 cnh 1.9 IF ( momAdvection ) THEN
322 cnh 1.28 afFacMom = 1.D0
323 cnh 1.9 ELSE
324 cnh 1.28 afFacMom = 0.D0
325 cnh 1.9 ENDIF
326 cnh 1.28 C-- Momentum forcing on/off flag.
327 cnh 1.9 IF ( momForcing ) THEN
328 cnh 1.28 foFacMom = 1.D0
329 cnh 1.9 ELSE
330 cnh 1.28 foFacMom = 0.D0
331 cnh 1.9 ENDIF
332 cnh 1.28 C-- Coriolis term on/off flag.
333 cnh 1.9 IF ( useCoriolis ) THEN
334 cnh 1.28 cfFacMom = 1.D0
335 cnh 1.9 ELSE
336 cnh 1.28 cfFacMom = 0.D0
337 cnh 1.9 ENDIF
338 cnh 1.28 C-- Pressure term on/off flag.
339 cnh 1.9 IF ( momPressureForcing ) THEN
340 cnh 1.28 pfFacMom = 1.D0
341 cnh 1.9 ELSE
342 cnh 1.28 pfFacMom = 0.D0
343 cnh 1.9 ENDIF
344 cnh 1.28 C-- Metric terms on/off flag.
345 cnh 1.14 IF ( metricTerms ) THEN
346 cnh 1.28 mTFacMom = 1.D0
347 cnh 1.14 ELSE
348 jmc 1.56 mTFacMom = 0.D0
349 adcroft 1.88 ENDIF
350     C-- Non-hydrostatic/quasi-hydrostatic
351     IF (nonHydrostatic.AND.quasiHydrostatic) THEN
352     WRITE(msgBuf,'(A)')
353     & 'Illegal: both nonHydrostatic = quasiHydrostatic = TRUE'
354     CALL PRINT_ERROR( msgBuf , myThid)
355     STOP 'ABNORMAL END: S/R INI_PARMS'
356 cnh 1.14 ENDIF
357 jmc 1.79 C-- Advection and Forcing for Temp and salt on/off flags
358     tempAdvection = tempStepping .AND. tempAdvection
359     tempForcing = tempStepping .AND. tempForcing
360     saltAdvection = saltStepping .AND. saltAdvection
361     saltForcing = saltStepping .AND. saltForcing
362 cnh 1.28 C-- z,p,r coord input switching.
363     IF ( viscAz .NE. UNSET_RL ) zCoordInputData = .TRUE.
364     IF ( viscAp .NE. UNSET_RL ) pCoordInputData = .TRUE.
365     IF ( viscAr .NE. UNSET_RL ) rCoordInputData = .TRUE.
366     IF ( viscAr .EQ. UNSET_RL ) viscAr = viscAz
367     IF ( viscAr .EQ. UNSET_RL ) viscAr = viscAp
368     IF ( viscAr .EQ. UNSET_RL ) viscAr = viscArDefault
369    
370     IF ( diffKzT .NE. UNSET_RL ) zCoordInputData = .TRUE.
371     IF ( diffKpT .NE. UNSET_RL ) pCoordInputData = .TRUE.
372     IF ( diffKrT .NE. UNSET_RL ) rCoordInputData = .TRUE.
373     IF ( diffKrT .EQ. UNSET_RL ) diffKrT = diffKzT
374     IF ( diffKrT .EQ. UNSET_RL ) diffKrT = diffKpT
375     IF ( diffKrT .EQ. UNSET_RL ) diffKrT = diffKrTDefault
376    
377     IF ( diffKzS .NE. UNSET_RL ) zCoordInputData = .TRUE.
378     IF ( diffKpS .NE. UNSET_RL ) pCoordInputData = .TRUE.
379     IF ( diffKrS .NE. UNSET_RL ) rCoordInputData = .TRUE.
380     IF ( diffKrS .EQ. UNSET_RL ) diffKrS = diffKzS
381     IF ( diffKrS .EQ. UNSET_RL ) diffKrS = diffKpS
382     IF ( diffKrS .EQ. UNSET_RL ) diffKrS = diffKrSDefault
383    
384     IF ( hFacMinDz .NE. UNSET_RL ) zCoordInputData = .TRUE.
385     IF ( hFacMinDp .NE. UNSET_RL ) pCoordInputData = .TRUE.
386     IF ( hFacMinDr .NE. UNSET_RL ) rCoordInputData = .TRUE.
387 adcroft 1.50 IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr = hFacMinDz
388     IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr = hFacMinDp
389 cnh 1.28 IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr = hFacMinDrDefault
390 cnh 1.8
391 jmc 1.76 IF (convertFW2Salt.EQ.UNSET_RL) THEN
392     convertFW2Salt = 35.
393     IF (useRealFreshWaterFlux) convertFW2Salt=-1
394     ENDIF
395    
396 adcroft 1.46 IF ( ivdc_kappa .NE. 0. .AND. .NOT. implicitDiffusion ) THEN
397 jmc 1.79 WRITE(msgBuf,'(A,A)')
398 adcroft 1.46 & 'S/R INI_PARMS: To use ivdc_kappa you must enable implicit',
399     & ' vertical diffusion.'
400 jmc 1.55 CALL PRINT_ERROR( msgBuf , myThid)
401     STOP 'ABNORMAL END: S/R INI_PARMS'
402     ENDIF
403    
404 cnh 1.28 coordsSet = 0
405     IF ( zCoordInputData ) coordsSet = coordsSet + 1
406     IF ( pCoordInputData ) coordsSet = coordsSet + 1
407     IF ( rCoordInputData ) coordsSet = coordsSet + 1
408     IF ( coordsSet .GT. 1 ) THEN
409     WRITE(msgBuf,'(A)')
410     & 'S/R INI_PARMS: Cannot mix z, p and r in the input data.'
411 cnh 1.8 CALL PRINT_ERROR( msgBuf , myThid)
412     STOP 'ABNORMAL END: S/R INI_PARMS'
413     ENDIF
414 cnh 1.28 IF ( rhoConst .LE. 0. ) THEN
415     WRITE(msgBuf,'(A)')
416     & 'S/R INI_PARMS: rhoConst must be greater than 0.'
417     CALL PRINT_ERROR( msgBuf , myThid)
418     STOP 'ABNORMAL END: S/R INI_PARMS'
419     ELSE
420     recip_rhoConst = 1.D0 / rhoConst
421 adcroft 1.38 ENDIF
422     IF ( rhoNil .LE. 0. ) THEN
423     WRITE(msgBuf,'(A)')
424     & 'S/R INI_PARMS: rhoNil must be greater than 0.'
425     CALL PRINT_ERROR( msgBuf , myThid)
426     STOP 'ABNORMAL END: S/R INI_PARMS'
427     ELSE
428     recip_rhoNil = 1.D0 / rhoNil
429 cnh 1.33 ENDIF
430 adcroft 1.39 IF ( HeatCapacity_Cp .LE. 0. ) THEN
431     WRITE(msgBuf,'(A)')
432     & 'S/R INI_PARMS: HeatCapacity_Cp must be greater than 0.'
433     CALL PRINT_ERROR( msgBuf , myThid)
434     STOP 'ABNORMAL END: S/R INI_PARMS'
435     ELSE
436     recip_Cp = 1.D0 / HeatCapacity_Cp
437     ENDIF
438 cnh 1.33 IF ( gravity .LE. 0. ) THEN
439     WRITE(msgBuf,'(A)')
440     & 'S/R INI_PARMS: gravity must be greater than 0.'
441     CALL PRINT_ERROR( msgBuf , myThid)
442     STOP 'ABNORMAL END: S/R INI_PARMS'
443     ELSE
444     recip_gravity = 1.D0 / gravity
445 cnh 1.28 ENDIF
446 adcroft 1.42 C Set globalFiles flag for READ_WRITE_FLD package
447     CALL SET_WRITE_GLOBAL_FLD( globalFiles )
448     C Set globalFiles flag for READ_WRITE_REC package
449     CALL SET_WRITE_GLOBAL_REC( globalFiles )
450     C Set globalFiles flag for READ_WRITE_REC package
451     CALL SET_WRITE_GLOBAL_PICKUP( globalFiles )
452 cnh 1.1
453 cnh 1.75 C Check for retired parameters still being used
454     nRetired = 0
455     IF ( zonal_filt_lat .NE. UNSET_RL ) THEN
456     nRetired = nRetired+1
457     WRITE(msgBuf,'(A,A)')
458     & 'S/R INI_PARMS: Paramater "zonal_filt_lat" is',
459     & ' no longer allowed in file "data".'
460     CALL PRINT_ERROR( msgBuf , myThid)
461     WRITE(msgBuf,'(A,A)')
462     & 'S/R INI_PARMS: Paramater "zonal_filt_lat" is',
463     & ' now read from file "data.zonfilt".'
464     CALL PRINT_ERROR( msgBuf , myThid)
465     ENDIF
466    
467 cnh 1.1 C-- Elliptic solver parameters
468 adcroft 1.41 READ(UNIT=iUnit,NML=PARM02) !,IOSTAT=errIO)
469 cnh 1.35 IF ( errIO .LT. 0 ) THEN
470 cnh 1.1 WRITE(msgBuf,'(A)')
471     & 'S/R INI_PARMS'
472     CALL PRINT_ERROR( msgBuf , 1)
473     WRITE(msgBuf,'(A)')
474     & 'Error reading numerical model '
475     CALL PRINT_ERROR( msgBuf , 1)
476     WRITE(msgBuf,'(A)')
477     & 'parameter file "data".'
478     CALL PRINT_ERROR( msgBuf , 1)
479     WRITE(msgBuf,'(A)')
480     & 'Problem in namelist PARM02'
481     CALL PRINT_ERROR( msgBuf , 1)
482     CALL MODELDATA_EXAMPLE( myThid )
483     STOP 'ABNORMAL END: S/R INI_PARMS'
484 jmc 1.72 ELSE
485     WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM02 : OK'
486     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
487     & SQUEEZE_RIGHT , 1)
488 cnh 1.35 ENDIF
489 cnh 1.1
490     C-- Time stepping parameters
491 cnh 1.28 rCD = -1.D0
492 adcroft 1.41 READ(UNIT=iUnit,NML=PARM03) !,IOSTAT=errIO)
493 cnh 1.35 IF ( errIO .LT. 0 ) THEN
494 cnh 1.1 WRITE(msgBuf,'(A)')
495     & 'S/R INI_PARMS'
496     CALL PRINT_ERROR( msgBuf , 1)
497     WRITE(msgBuf,'(A)')
498     & 'Error reading numerical model '
499     CALL PRINT_ERROR( msgBuf , 1)
500     WRITE(msgBuf,'(A)')
501     & 'parameter file "data"'
502     CALL PRINT_ERROR( msgBuf , 1)
503     WRITE(msgBuf,'(A)')
504     & 'Problem in namelist PARM03'
505     CALL PRINT_ERROR( msgBuf , 1)
506     CALL MODELDATA_EXAMPLE( myThid )
507     STOP 'ABNORMAL END: S/R INI_PARMS'
508 jmc 1.72 ELSE
509     WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM03 : OK'
510     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
511     & SQUEEZE_RIGHT , 1)
512 cnh 1.35 ENDIF
513 cnh 1.4 C Process "timestepping" params
514     C o Time step size
515     IF ( deltaT .EQ. 0. ) deltaT = deltaTmom
516     IF ( deltaT .EQ. 0. ) deltaT = deltaTtracer
517     IF ( deltaTmom .EQ. 0. ) deltaTmom = deltaT
518     IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT
519 cnh 1.7 IF ( deltaTClock .EQ. 0. ) deltaTClock = deltaT
520 jmc 1.89 C Note that this line should set deltaFreesurf=deltaTmom
521 adcroft 1.80 C but this would change a lot of existing set-ups so we are
522     C obliged to set the default inappropriately.
523     C Be advised that when using asynchronous time stepping
524     C it is better to set deltaTreesurf=deltaTtracer
525     IF ( deltaTfreesurf .EQ. 0. ) deltaTfreesurf = deltaTmom
526 adcroft 1.19 IF ( periodicExternalForcing ) THEN
527     IF ( externForcingCycle*externForcingPeriod .EQ. 0. ) THEN
528     WRITE(msgBuf,'(A)')
529     & 'S/R INI_PARMS: externForcingCycle,externForcingPeriod =0'
530     CALL PRINT_ERROR( msgBuf , 1)
531     STOP 'ABNORMAL END: S/R INI_PARMS'
532     ENDIF
533     IF ( INT(externForcingCycle/externForcingPeriod) .NE.
534     & externForcingCycle/externForcingPeriod ) THEN
535     WRITE(msgBuf,'(A)')
536     & 'S/R INI_PARMS: externForcingCycle <> N*externForcingPeriod'
537     CALL PRINT_ERROR( msgBuf , 1)
538     STOP 'ABNORMAL END: S/R INI_PARMS'
539     ENDIF
540     IF ( externForcingCycle.le.externForcingPeriod ) THEN
541     WRITE(msgBuf,'(A)')
542     & 'S/R INI_PARMS: externForcingCycle < externForcingPeriod'
543     CALL PRINT_ERROR( msgBuf , 1)
544     STOP 'ABNORMAL END: S/R INI_PARMS'
545     ENDIF
546     IF ( externForcingPeriod.lt.deltaTclock ) THEN
547     WRITE(msgBuf,'(A)')
548     & 'S/R INI_PARMS: externForcingPeriod < deltaTclock'
549     CALL PRINT_ERROR( msgBuf , 1)
550     STOP 'ABNORMAL END: S/R INI_PARMS'
551     ENDIF
552     ENDIF
553 cnh 1.9 C o Convection frequency
554     IF ( cAdjFreq .LT. 0. ) THEN
555     cAdjFreq = deltaTClock
556     ENDIF
557 adcroft 1.46 IF ( ivdc_kappa .NE. 0. .AND. cAdjFreq .NE. 0. ) THEN
558     WRITE(msgBuf,'(A,A)')
559     & 'S/R INI_PARMS: You have enabled both ivdc_kappa and',
560     & ' convective adjustment.'
561     CALL PRINT_ERROR( msgBuf , myThid)
562     STOP 'ABNORMAL END: S/R INI_PARMS'
563     ENDIF
564 cnh 1.14 C o CD coupling
565 cnh 1.28 IF ( tauCD .EQ. 0.D0 ) THEN
566 cnh 1.14 tauCD = deltaTmom
567     ENDIF
568     IF ( rCD .LT. 0. ) THEN
569     rCD = 1. - deltaTMom/tauCD
570     ENDIF
571 cnh 1.18 C o Temperature climatology relaxation time scale
572 cnh 1.28 IF ( tauThetaClimRelax .EQ. 0.D0 ) THEN
573 cnh 1.18 doThetaClimRelax = .FALSE.
574 cnh 1.28 lambdaThetaClimRelax = 0.D0
575 cnh 1.18 ELSE
576     doThetaClimRelax = .TRUE.
577     lambdaThetaClimRelax = 1./tauThetaClimRelax
578     ENDIF
579     C o Salinity climatology relaxation time scale
580 cnh 1.28 IF ( tauSaltClimRelax .EQ. 0.D0 ) THEN
581 cnh 1.18 doSaltClimRelax = .FALSE.
582 cnh 1.28 lambdaSaltClimRelax = 0.D0
583 cnh 1.18 ELSE
584     doSaltClimRelax = .TRUE.
585     lambdaSaltClimRelax = 1./tauSaltClimRelax
586 heimbach 1.64 ENDIF
587     C o Tracer 1 climatology relaxation time scale
588     IF ( tauTr1ClimRelax .EQ. 0.D0 ) THEN
589     doTr1ClimRelax = .FALSE.
590     lambdaTr1ClimRelax = 0.D0
591     ELSE
592     doTr1ClimRelax = .TRUE.
593     lambdaTr1ClimRelax = 1./tauTr1ClimRelax
594 cnh 1.18 ENDIF
595 adcroft 1.41
596     C o Start time
597     IF ( nIter0 .NE. 0 .AND. startTime .EQ. 0. )
598     & startTime = deltaTClock*float(nIter0)
599     C o nIter0
600     IF ( nIter0 .EQ. 0 .AND. startTime .NE. 0. )
601     & nIter0 = INT( startTime/deltaTClock )
602 adcroft 1.46
603     C o nTimeSteps 1
604     IF ( nTimeSteps .EQ. 0 .AND. nEndIter .NE. 0 )
605     & nTimeSteps = nEndIter-nIter0
606     C o nTimeSteps 2
607 adcroft 1.41 IF ( nTimeSteps .EQ. 0 .AND. endTime .NE. 0. )
608 adcroft 1.46 & nTimeSteps = int(0.5+(endTime-startTime)/deltaTclock)
609     C o nEndIter 1
610     IF ( nEndIter .EQ. 0 .AND. nTimeSteps .NE. 0 )
611     & nEndIter = nIter0+nTimeSteps
612     C o nEndIter 2
613     IF ( nEndIter .EQ. 0 .AND. endTime .NE. 0. )
614     & nEndIter = int(0.5+endTime/deltaTclock)
615     C o End Time 1
616     IF ( endTime .EQ. 0. .AND. nTimeSteps .NE. 0 )
617     & endTime = startTime + deltaTClock*float(nTimeSteps)
618     C o End Time 2
619     IF ( endTime .EQ. 0. .AND. nEndIter .NE. 0 )
620     & endTime = deltaTClock*float(nEndIter)
621    
622 adcroft 1.41 C o Consistent?
623 adcroft 1.46 IF ( nEndIter .NE. nIter0+nTimeSteps ) THEN
624     WRITE(msgBuf,'(A)')
625     & 'S/R INI_PARMS: nIter0, nTimeSteps and nEndIter are inconsistent'
626     CALL PRINT_ERROR( msgBuf , 1)
627     WRITE(msgBuf,'(A)')
628     & 'S/R INI_PARMS: Perhaps more than two were set at once'
629     CALL PRINT_ERROR( msgBuf , 1)
630     STOP 'ABNORMAL END: S/R INI_PARMS'
631     ENDIF
632     IF ( nTimeSteps .NE. int(0.5+(endTime-startTime)/deltaTClock) )
633     & THEN
634 adcroft 1.41 WRITE(msgBuf,'(A)')
635     & 'S/R INI_PARMS: both endTime and nTimeSteps have been set'
636     CALL PRINT_ERROR( msgBuf , 1)
637     WRITE(msgBuf,'(A)')
638     & 'S/R INI_PARMS: but are inconsistent'
639     CALL PRINT_ERROR( msgBuf , 1)
640     STOP 'ABNORMAL END: S/R INI_PARMS'
641 adcroft 1.60 ENDIF
642    
643     C o Monitor (should also add CPP flag for monitor?)
644     IF (monitorFreq.LT.0.) THEN
645     monitorFreq=0.
646 adcroft 1.62 IF (dumpFreq.NE.0.) monitorFreq=dumpFreq
647 adcroft 1.67 IF (diagFreq.NE.0..AND.diagFreq.LT.monitorFreq)
648     & monitorFreq=diagFreq
649 adcroft 1.62 IF (taveFreq.NE.0..AND.taveFreq.LT.monitorFreq)
650     & monitorFreq=taveFreq
651     IF (chkPtFreq.NE.0..AND.chkPtFreq.LT.monitorFreq)
652     & monitorFreq=chkPtFreq
653     IF (pChkPtFreq.NE.0..AND.pChkPtFreq.LT.monitorFreq)
654     & monitorFreq=pChkPtFreq
655 adcroft 1.60 IF (monitorFreq.EQ.0.) monitorFreq=deltaTclock
656 cnh 1.4 ENDIF
657 adcroft 1.21
658 cnh 1.1 C-- Grid parameters
659     C In cartesian coords distances are in metres
660 adcroft 1.41 rkFac = UNSET_RS
661 cnh 1.26 DO K =1,Nr
662 cnh 1.28 delZ(K) = UNSET_RL
663     delP(K) = UNSET_RL
664     delR(K) = UNSET_RL
665 cnh 1.1 ENDDO
666     C In spherical polar distances are in degrees
667 cnh 1.28 recip_rSphere = 1.D0/rSphere
668 adcroft 1.39 dxSpacing = UNSET_RL
669     dySpacing = UNSET_RL
670 adcroft 1.48 delXfile = ' '
671     delYfile = ' '
672 mlosch 1.82 READ(UNIT=iUnit,NML=PARM04,IOSTAT=errIO)
673 cnh 1.35 IF ( errIO .LT. 0 ) THEN
674 cnh 1.1 WRITE(msgBuf,'(A)')
675     & 'S/R INI_PARMS'
676     CALL PRINT_ERROR( msgBuf , 1)
677     WRITE(msgBuf,'(A)')
678     & 'Error reading numerical model '
679     CALL PRINT_ERROR( msgBuf , 1)
680     WRITE(msgBuf,'(A)')
681     & 'parameter file "data"'
682     CALL PRINT_ERROR( msgBuf , 1)
683     WRITE(msgBuf,'(A)')
684     & 'Problem in namelist PARM04'
685     CALL PRINT_ERROR( msgBuf , 1)
686     CALL MODELDATA_EXAMPLE( myThid )
687     STOP 'ABNORMAL END: S/R INI_PARMS'
688 jmc 1.72 ELSE
689     WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM04 : OK'
690     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
691     & SQUEEZE_RIGHT , 1)
692 cnh 1.35 ENDIF
693 adcroft 1.48
694     C X coordinate
695     IF ( delXfile .NE. ' ' ) THEN
696     IF ( delX(1) .NE. UNSET_RL .OR. dxSpacing .NE. UNSET_RL ) THEN
697     WRITE(msgBuf,'(A,A)') 'Too many specifications for delX:',
698     & 'Specify only one of delX, dxSpacing or delXfile'
699     CALL PRINT_ERROR( msgBuf , 1)
700     STOP 'ABNORMAL END: S/R INI_PARMS'
701     ELSE
702     _BEGIN_MASTER( myThid )
703     IF (readBinaryPrec.EQ.precFloat32) THEN
704     OPEN(37,FILE=delXfile,STATUS='OLD',FORM='UNFORMATTED',
705     & ACCESS='DIRECT',RECL=WORDLENGTH*Nx)
706 jmc 1.89 READ(37,rec=1) tmp4delX
707 adcroft 1.48 #ifdef _BYTESWAPIO
708 jmc 1.89 call MDS_BYTESWAPR4( Nx, tmp4delX )
709 adcroft 1.48 #endif
710     CLOSE(37)
711 jmc 1.89 DO i=1,Nx
712     delX(i) = tmp4delX(i)
713     ENDDO
714 adcroft 1.48 ELSEIF (readBinaryPrec.EQ.precFloat64) THEN
715     OPEN(37,FILE=delXfile,STATUS='OLD',FORM='UNFORMATTED',
716     & ACCESS='DIRECT',RECL=WORDLENGTH*2*Nx)
717 jmc 1.89 READ(37,rec=1) tmp8delX
718 adcroft 1.48 #ifdef _BYTESWAPIO
719 jmc 1.89 call MDS_BYTESWAPR8( Nx, tmp8delX )
720 adcroft 1.48 #endif
721     CLOSE(37)
722 jmc 1.89 DO i=1,Nx
723     delX(i) = tmp8delX(i)
724     ENDDO
725 adcroft 1.48 ENDIF
726     _END_MASTER(myThid)
727     ENDIF
728     ENDIF
729 adcroft 1.39 IF ( dxSpacing .NE. UNSET_RL ) THEN
730     DO i=1,Nx
731     delX(i) = dxSpacing
732     ENDDO
733     ENDIF
734 adcroft 1.48 C Y coordinate
735     IF ( delYfile .NE. ' ' ) THEN
736     IF ( delY(1) .NE. UNSET_RL .OR. dySpacing .NE. UNSET_RL ) THEN
737     WRITE(msgBuf,'(A,A)') 'Too many specifications for delY:',
738     & 'Specify only one of delY, dySpacing or delYfile'
739     CALL PRINT_ERROR( msgBuf , 1)
740     STOP 'ABNORMAL END: S/R INI_PARMS'
741     ELSE
742     _BEGIN_MASTER( myThid )
743     IF (readBinaryPrec.EQ.precFloat32) THEN
744     OPEN(37,FILE=delYfile,STATUS='OLD',FORM='UNFORMATTED',
745     & ACCESS='DIRECT',RECL=WORDLENGTH*Ny)
746 jmc 1.89 READ(37,rec=1) tmp4delY
747 adcroft 1.48 #ifdef _BYTESWAPIO
748 jmc 1.89 call MDS_BYTESWAPR4( Ny, tmp4delY )
749 adcroft 1.48 #endif
750     CLOSE(37)
751 jmc 1.89 DO j=1,Ny
752     delY(j) = tmp4delY(j)
753     ENDDO
754 adcroft 1.48 ELSEIF (readBinaryPrec.EQ.precFloat64) THEN
755     OPEN(37,FILE=delYfile,STATUS='OLD',FORM='UNFORMATTED',
756     & ACCESS='DIRECT',RECL=WORDLENGTH*2*Ny)
757 jmc 1.89 READ(37,rec=1) tmp8delY
758 adcroft 1.48 #ifdef _BYTESWAPIO
759 jmc 1.89 call MDS_BYTESWAPR8( Ny, tmp8delY )
760 adcroft 1.48 #endif
761     CLOSE(37)
762 jmc 1.89 DO j=1,Ny
763     delY(j) = tmp8delY(j)
764     ENDDO
765 adcroft 1.48 ENDIF
766     _END_MASTER(myThid)
767     ENDIF
768     ENDIF
769 adcroft 1.39 IF ( dySpacing .NE. UNSET_RL ) THEN
770 adcroft 1.48 DO i=1,Ny
771     delY(i) = dySpacing
772 adcroft 1.39 ENDDO
773     ENDIF
774 adcroft 1.48 C
775 cnh 1.14 IF ( rSphere .NE. 0 ) THEN
776 cnh 1.28 recip_rSphere = 1.D0/rSphere
777 cnh 1.14 ELSE
778 cnh 1.26 recip_rSphere = 0.
779 adcroft 1.11 ENDIF
780 cnh 1.28 C-- Check for conflicting grid definitions.
781 cnh 1.1 goptCount = 0
782     IF ( usingCartesianGrid ) goptCount = goptCount+1
783     IF ( usingSphericalPolarGrid ) goptCount = goptCount+1
784 adcroft 1.59 IF ( usingCurvilinearGrid ) goptCount = goptCount+1
785     IF ( goptCount .GT. 1 ) THEN
786 cnh 1.1 WRITE(msgBuf,'(A)')
787     & 'S/R INI_PARMS: More than one coordinate system requested'
788     CALL PRINT_ERROR( msgBuf , myThid)
789     STOP 'ABNORMAL END: S/R INI_PARMS'
790 cnh 1.14 ENDIF
791 adcroft 1.59 IF ( goptCount .LT. 1 ) THEN
792     WRITE(msgBuf,'(A)')
793     & 'S/R INI_PARMS: No coordinate system requested'
794     CALL PRINT_ERROR( msgBuf , myThid)
795     STOP 'ABNORMAL END: S/R INI_PARMS'
796     ENDIF
797 cnh 1.28 C-- Make metric term settings consistent with underlying grid.
798 cnh 1.14 IF ( usingCartesianGrid ) THEN
799     usingSphericalPolarMterms = .FALSE.
800     metricTerms = .FALSE.
801 adcroft 1.87 useNHMTerms = .FALSE.
802 jmc 1.56 mTFacMom = 0.
803 cnh 1.18 useBetaPlaneF = .TRUE.
804 cnh 1.14 ENDIF
805     IF ( usingSphericalPolarGrid ) THEN
806     useConstantF = .FALSE.
807     useBetaPlaneF = .FALSE.
808     useSphereF = .TRUE.
809 jmc 1.56 usingSphericalPolarMterms = metricTerms
810 adcroft 1.59 ENDIF
811     IF ( usingCurvilinearGrid ) THEN
812     useSphereF = .TRUE.
813 adcroft 1.87 metricTerms = .FALSE.
814     useNHMTerms = .FALSE.
815 cnh 1.1 ENDIF
816 jmc 1.78 C-- set cell Center depth and put Interface at the middle between 2 C
817     setCenterDr = .FALSE.
818     IF (delRc(1).NE.UNSET_RL) setCenterDr=.TRUE.
819     DO K=1,Nr+1
820     IF (delRc(K).EQ.UNSET_RL) setCenterDr = .FALSE.
821     ENDDO
822 cnh 1.28 C-- p, z, r coord parameters
823     DO K = 1, Nr
824     IF ( delZ(K) .NE. UNSET_RL ) zCoordInputData = .TRUE.
825     IF ( delP(K) .NE. UNSET_RL ) pCoordInputData = .TRUE.
826     IF ( delR(K) .NE. UNSET_RL ) rCoordInputData = .TRUE.
827     IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delZ(K)
828     IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delP(K)
829 adcroft 1.39 IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delRDefault(K)
830 jmc 1.78 IF (.NOT.setCenterDr .AND. delR(K).EQ.delRDefault(K) ) THEN
831 adcroft 1.41 WRITE(msgBuf,'(A,I4)')
832     & 'S/R INI_PARMS: No value for delZ/delP/delR at K = ',K
833 jmc 1.78 CALL PRINT_ERROR( msgBuf , 1)
834     STOP 'ABNORMAL END: S/R INI_PARMS'
835     ELSEIF ( setCenterDr .AND. delR(K).NE.delRDefault(K) ) THEN
836     WRITE(msgBuf,'(2A,I4)') 'S/R INI_PARMS:',
837     & ' Cannot specify both delRc and delZ/delP/delR at K=', K
838 adcroft 1.41 CALL PRINT_ERROR( msgBuf , 1)
839     STOP 'ABNORMAL END: S/R INI_PARMS'
840     ENDIF
841 cnh 1.28 ENDDO
842     C Check for multiple coordinate systems
843 adcroft 1.39 CoordsSet = 0
844 cnh 1.28 IF ( zCoordInputData ) coordsSet = coordsSet + 1
845     IF ( pCoordInputData ) coordsSet = coordsSet + 1
846     IF ( rCoordInputData ) coordsSet = coordsSet + 1
847     IF ( coordsSet .GT. 1 ) THEN
848     WRITE(msgBuf,'(A)')
849     & 'S/R INI_PARMS: Cannot mix z, p and r in the input data.'
850     CALL PRINT_ERROR( msgBuf , myThid)
851     STOP 'ABNORMAL END: S/R INI_PARMS'
852     ENDIF
853 jmc 1.92
854     C-- When using the dynamical pressure in EOS (with Z-coord.),
855     C needs to activate specific part of the code (restart & exchange)
856     c useDynP_inEos_Zc = .FALSE.
857     useDynP_inEos_Zc = ( buoyancyRelation .EQ. 'OCEANIC'
858     & .AND. ( eosType .EQ. 'JMD95P' .OR.
859     & eosType .EQ. 'UNESCO' .OR.
860     & eosType .EQ. 'MDJWF' ) )
861 cnh 1.15
862     C-- Input files
863 adcroft 1.41 READ(UNIT=iUnit,NML=PARM05) !,IOSTAT=errIO)
864 cnh 1.35 IF ( errIO .LT. 0 ) THEN
865 cnh 1.15 WRITE(msgBuf,'(A)')
866     & 'Error reading numerical model '
867     CALL PRINT_ERROR( msgBuf , 1)
868     WRITE(msgBuf,'(A)')
869     & 'parameter file "data"'
870     CALL PRINT_ERROR( msgBuf , 1)
871     WRITE(msgBuf,'(A)')
872     & 'Problem in namelist PARM05'
873     CALL PRINT_ERROR( msgBuf , 1)
874     CALL MODELDATA_EXAMPLE( myThid )
875     STOP 'ABNORMAL END: S/R INI_PARMS'
876 jmc 1.72 ELSE
877     WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM05 : OK'
878     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
879     & SQUEEZE_RIGHT , 1)
880 cnh 1.35 ENDIF
881 cnh 1.25
882 cnh 1.30 C-- Set factors required for mixing pressure and meters as vertical coordinate.
883     C rkFac is a "sign" parameter which is used where the orientation of the vertical
884     C coordinate (pressure or meters) relative to the vertical index (K) is important.
885     C rkFac = 1 applies when K and the coordinate are in the opposite sense.
886     C rkFac = -1 applies when K and the coordinate are in the same sense.
887     C horiVertRatio is a parameter that maps horizontal units to vertical units.
888     C It is used in certain special cases where lateral and vertical terms are
889     C being combined and a single frame of reference is needed.
890 adcroft 1.41 IF ( zCoordInputData .AND. rkFac .EQ. UNSET_RS ) THEN
891 cnh 1.30 rkFac = 1.D0
892     horiVertRatio = 1.D0
893     ENDIF
894 adcroft 1.41 IF ( pCoordInputData .AND. rkFac .EQ. UNSET_RS ) THEN
895 jmc 1.89 C- jmc: any time P-coordinate is used (ocean,atmos), it requires rkFac=1
896     c rkFac = -1.D0
897 cnh 1.30 horiVertRatio = Gravity * rhoConst
898     ENDIF
899 adcroft 1.41 IF ( rCoordInputData .AND. rkFac .EQ. UNSET_RS ) THEN
900 cnh 1.30 rkFac = 1.D0
901     horiVertRatio = 1.D0
902     ENDIF
903 jmc 1.85 convertEmP2rUnit = 1. _d 0
904 adcroft 1.53 IF (buoyancyRelation.EQ.'ATMOSPHERIC')
905 jmc 1.85 & horiVertRatio = Gravity * rhoConst
906     IF (buoyancyRelation.EQ.'OCEANICP') THEN
907     horiVertRatio = Gravity * rhoConst
908     convertEmP2rUnit = Gravity * rhoConstFresh
909     ENDIF
910 adcroft 1.41 IF ( rkFac .EQ. UNSET_RS ) rkFac=rkFacDefault
911 cnh 1.28 recip_rkFac = 1.D0 / rkFac
912 cnh 1.32 recip_horiVertRatio = 1./horiVertRatio
913 cnh 1.29 IF ( zCoordInputData ) usingZCoords = .TRUE.
914     IF ( pCoordInputData ) usingPCoords = .TRUE.
915 adcroft 1.37
916 cnh 1.25 C
917     CLOSE(iUnit)
918 cnh 1.75
919     C-- Check whether any retired parameters were found.
920     C-- Stop if they were
921     IF ( nRetired .GT. 0 ) THEN
922     WRITE(msgBuf,'(A)')
923     & 'Error reading '
924     CALL PRINT_ERROR( msgBuf , 1)
925     WRITE(msgBuf,'(A)')
926     & 'parameter file "data"'
927     CALL PRINT_ERROR( msgBuf , 1)
928     WRITE(msgBuf,'(A)')
929     & 'some out of date parameters were found in the namelist'
930     CALL PRINT_ERROR( msgBuf , 1)
931     STOP 'ABNORMAL END: S/R INI_PARMS'
932     ENDIF
933 cnh 1.1
934     _END_MASTER(myThid)
935    
936     C-- Everyone else must wait for the parameters to be loaded
937     _BARRIER
938     C
939     RETURN
940     END
941    

  ViewVC Help
Powered by ViewVC 1.1.22