/[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.110 - (hide annotations) (download)
Wed May 26 14:50:10 2004 UTC (20 years ago) by adcroft
Branch: MAIN
Changes since 1.109: +3 -3 lines
Added variable viscosity for the vector invariant equations
based on Leith, 1968, Phys. Fluids (10) 1409-1416
 - the use of the variable viscosty in the no-slip boundary conditions
   has not been implemented (but should be)
 - new parameters viscC2leith and viscC4leith are non-dimensional
 - I decided to modulate the variable viscosuty with the same viscAhMax
   and viscA4max; ideally we should have another maximum based on dx^2/dt etc.

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

  ViewVC Help
Powered by ViewVC 1.1.22