/[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.148 - (hide annotations) (download)
Mon Feb 28 17:37:31 2005 UTC (19 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57e_post
Changes since 1.147: +2 -1 lines
Adding eddy stress controls a la Ferreira et al.

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

  ViewVC Help
Powered by ViewVC 1.1.22