/[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.123 - (hide annotations) (download)
Fri Sep 17 22:57:11 2004 UTC (19 years, 8 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint55, checkpoint55a_post
Changes since 1.122: +2 -2 lines
o remove all tr1-related code (ALLOW_PASSIVE_TRACER)
  (adjoint stuff still has some tr1 names, but all use ptracer arrays)

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

  ViewVC Help
Powered by ViewVC 1.1.22