/[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.147 - (hide annotations) (download)
Sun Feb 20 11:46:24 2005 UTC (19 years, 3 months ago) by dimitri
Branch: MAIN
CVS Tags: eckpoint57e_pre
Changes since 1.146: +3 -2 lines
o parameter calendarDumps: when set, approximate months (30-31 days) and years
  (360-372 days) for parameters chkPtFreq, pChkPtFreq, taveFreq, SEAICE_taveFreq,
  KPP_taveFreq, and freq in pkg/diagnostics are converted to exact calendar
  months and years.  Requires pkg/cal.

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

  ViewVC Help
Powered by ViewVC 1.1.22