/[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.170 - (hide annotations) (download)
Wed Sep 28 01:34:43 2005 UTC (18 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpint57u_post
Changes since 1.169: +2 -2 lines
add KEscheme selector.

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

  ViewVC Help
Powered by ViewVC 1.1.22