/[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.154 - (hide annotations) (download)
Fri Apr 15 14:02:07 2005 UTC (19 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57g_post
Changes since 1.153: +3 -3 lines
add parameters for AB-3 ; remove readPickupWithTracer & writePickupWithTracer

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

  ViewVC Help
Powered by ViewVC 1.1.22