1 |
cnh |
1.1 |
C $Header: /u/gcmpack/MITgcm/model/src/ini_parms.F,v 1.224 2009/10/15 01:06:50 jmc Exp $ |
2 |
|
|
C $Name: $ |
3 |
|
|
|
4 |
|
|
c #include "PACKAGES_CONFIG.h" |
5 |
|
|
#include "CPP_OPTIONS.h" |
6 |
|
|
|
7 |
|
|
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
8 |
|
|
CBOP |
9 |
|
|
C !ROUTINE: INI_PARMS |
10 |
|
|
C !INTERFACE: |
11 |
|
|
SUBROUTINE INI_PARMS( myThid ) |
12 |
|
|
|
13 |
|
|
C !DESCRIPTION: |
14 |
|
|
C Routine to load model "parameters" from parameter file "data" |
15 |
|
|
|
16 |
|
|
C !USES: |
17 |
|
|
IMPLICIT NONE |
18 |
|
|
#include "SIZE.h" |
19 |
|
|
#include "EEPARAMS.h" |
20 |
|
|
#include "PARAMS.h" |
21 |
|
|
c#include "GRID.h" |
22 |
|
|
#include "EOS.h" |
23 |
|
|
|
24 |
|
|
C !INPUT/OUTPUT PARAMETERS: |
25 |
|
|
C myThid :: Number of this instance of INI_PARMS |
26 |
|
|
INTEGER myThid |
27 |
|
|
|
28 |
|
|
C !FUNCTIONS: |
29 |
|
|
INTEGER IFNBLNK |
30 |
|
|
EXTERNAL IFNBLNK |
31 |
|
|
INTEGER ILNBLNK |
32 |
|
|
EXTERNAL ILNBLNK |
33 |
|
|
|
34 |
|
|
C !LOCAL VARIABLES: |
35 |
|
|
C dxSpacing, dySpacing :: Default spacing in X and Y. |
36 |
|
|
C :: Units are that of coordinate system |
37 |
|
|
C :: i.e. cartesian => metres |
38 |
|
|
C :: s. polar => degrees |
39 |
|
|
C SadournyCoriolis :: for backward compatibility |
40 |
|
|
C deltaTtracer :: Timestep for tracer equations ( s ) |
41 |
|
|
C forcing_In_AB :: flag to put all forcings (Temp,Salt,Tracers,Momentum) |
42 |
|
|
C :: contribution in (or out of) Adams-Bashforth time stepping. |
43 |
|
|
C goptCount :: Used to count the nuber of grid options (only one is allowed!) |
44 |
|
|
C msgBuf :: Informational/error meesage buffer |
45 |
|
|
C errIO :: IO error flag |
46 |
|
|
C iUnit :: Work variable for IO unit number |
47 |
|
|
C record :: Work variable for IO buffer |
48 |
|
|
C K, I, J :: Loop counters |
49 |
|
|
C xxxDefault :: Default value for variable xxx |
50 |
|
|
_RL dxSpacing |
51 |
|
|
_RL dySpacing |
52 |
|
|
_RL deltaTtracer |
53 |
|
|
CHARACTER*(MAX_LEN_MBUF) msgBuf |
54 |
|
|
CHARACTER*(MAX_LEN_PREC) record |
55 |
|
|
#if defined (TARGET_BGL) || defined (TARGET_CRAYXT) |
56 |
|
|
CHARACTER*(MAX_LEN_FNAM) scratchFile1 |
57 |
|
|
CHARACTER*(MAX_LEN_FNAM) scratchFile2 |
58 |
|
|
#endif |
59 |
|
|
LOGICAL SadournyCoriolis |
60 |
|
|
LOGICAL forcing_In_AB |
61 |
|
|
INTEGER goptCount |
62 |
|
|
INTEGER k, i, j, IL, iUnit |
63 |
|
|
INTEGER errIO |
64 |
|
|
C Default values for variables which have vertical coordinate system |
65 |
|
|
C dependency. |
66 |
|
|
_RL viscArDefault |
67 |
|
|
_RL diffKrTDefault |
68 |
|
|
_RL diffKrSDefault |
69 |
|
|
_RL hFacMinDrDefault |
70 |
|
|
_RL delRDefault(Nr) |
71 |
|
|
_RS rkFacDefault |
72 |
|
|
C zCoordInputData :: Variables used to select between different coordinate systems. |
73 |
|
|
C pCoordInputData :: The vertical coordinate system in the rest of the model is |
74 |
|
|
C rCoordInputData :: written in terms of r. In the model "data" file input data |
75 |
|
|
C coordsSet :: can be interms of z, p or r. |
76 |
|
|
C :: e.g. delZ or delP or delR for the vertical grid spacing. |
77 |
|
|
C :: The following rules apply: |
78 |
|
|
C :: All parameters must use the same vertical coordinate system. |
79 |
|
|
C :: e.g. delZ and viscAz is legal but |
80 |
|
|
C :: delZ and viscAr is an error. |
81 |
|
|
C :: Similarly specifying delZ and delP is an error. |
82 |
|
|
C :: zCoord..., pCoord..., rCoord... are used to flag when |
83 |
|
|
C :: z, p or r are used. |
84 |
|
|
C :: coordsSet counts how many vertical coordinate systems have |
85 |
|
|
C :: been used to specify variables. coordsSet > 1 is an error. |
86 |
|
|
C vertSetCount :: to count number of vertical array elements which are set. |
87 |
|
|
|
88 |
|
|
LOGICAL zCoordInputData |
89 |
|
|
LOGICAL pCoordInputData |
90 |
|
|
LOGICAL rCoordInputData |
91 |
|
|
INTEGER coordsSet |
92 |
|
|
INTEGER vertSetCount |
93 |
|
|
|
94 |
|
|
C Variables which have vertical coordinate system dependency. |
95 |
|
|
C delZ :: Vertical grid spacing ( m ). |
96 |
|
|
C delP :: Vertical grid spacing ( Pa ). |
97 |
|
|
C viscAz :: Eddy viscosity coeff. for mixing of momentum vertically ( m^2/s ) |
98 |
|
|
C viscAp :: Eddy viscosity coeff. for mixing of momentum vertically ( Pa^2/s ) |
99 |
|
|
C diffKzT :: Laplacian diffusion coeff. for mixing of heat vertically ( m^2/s ) |
100 |
|
|
C diffKpT :: Laplacian diffusion coeff. for mixing of heat vertically ( Pa^2/s ) |
101 |
|
|
C diffKzS :: Laplacian diffusion coeff. for mixing of salt vertically ( m^2/s ) |
102 |
|
|
C diffKpS :: Laplacian diffusion coeff. for mixing of salt vertically ( Pa^2/s ) |
103 |
|
|
_RL delZ(Nr) |
104 |
|
|
_RL delP(Nr) |
105 |
|
|
_RL viscAz |
106 |
|
|
_RL viscAp |
107 |
|
|
_RL viscAr |
108 |
|
|
_RL diffKzT |
109 |
|
|
_RL diffKpT |
110 |
|
|
_RL diffKrT |
111 |
|
|
_RL diffKzS |
112 |
|
|
_RL diffKpS |
113 |
|
|
_RL diffKrS |
114 |
|
|
|
115 |
|
|
C Retired main data file parameters. Kept here to trap use of old data files. |
116 |
|
|
C nRetired :: Counter used to trap gracefully namelists containing "retired" |
117 |
|
|
C :: parameters. These are parameters that are either no-longer used |
118 |
|
|
C or that have moved to a different input file and/or namelist. |
119 |
|
|
C Namelist PARM01: |
120 |
|
|
C tracerAdvScheme :: tracer advection scheme (old passive tracer code) |
121 |
|
|
C trac_EvPrRn :: tracer conc. in Rain & Evap (old passive tracer code) |
122 |
|
|
C saltDiffusion :: diffusion of salinity on/off (flag not used) |
123 |
|
|
C tempDiffusion :: diffusion of temperature on/off (flag not used) |
124 |
|
|
C zonal_filt_lat :: Moved to package "zonal_filt" |
125 |
|
|
C gravitySign :: direction of gravity relative to R direction |
126 |
|
|
C :: (removed from namelist and set according to z/p coordinate) |
127 |
|
|
C viscAstrain :: replaced by standard viscosity coeff & useStrainTensionVisc |
128 |
|
|
C viscAtension :: replaced by standard viscosity coeff & useStrainTensionVisc |
129 |
|
|
C useAnisotropicViscAgridMax :: Changed to be default behavior. Can |
130 |
|
|
C use old method by setting useAreaViscLength=.true. |
131 |
|
|
C usePickupBeforeC35 :: to restart from old-pickup files (generated with code |
132 |
|
|
C from before checkpoint-35, Feb 08, 2001): disabled (Jan 2007) |
133 |
|
|
C Namelist PARM03: |
134 |
|
|
C tauThetaClimRelax3Dim :: replaced by pkg/rbcs (3.D Relaxation B.Cs) |
135 |
|
|
C tauSaltClimRelax3Dim :: replaced by pkg/rbcs (3.D Relaxation B.Cs) |
136 |
|
|
C calendarDumps :: moved to package "cal" (calendar) |
137 |
|
|
C Namelist PARM04: |
138 |
|
|
C groundAtK1 :: put the surface(k=1) at the ground (replaced by usingPCoords) |
139 |
|
|
C rkFac :: removed from namelist ; replaced by -rkSign |
140 |
|
|
C thetaMin :: unfortunate variable name ; replaced by xgOrigin |
141 |
|
|
C phiMin :: unfortunate variable name ; replaced by ygOrigin |
142 |
|
|
C Namelist PARM05: |
143 |
|
|
C shelfIceFile :: File containing the topography of the shelfice draught |
144 |
|
|
C (replaced by SHELFICEtopoFile in SHELFICE.h) |
145 |
|
|
|
146 |
|
|
INTEGER nRetired |
147 |
|
|
LOGICAL tempDiffusion, saltDiffusion |
148 |
|
|
INTEGER tracerAdvScheme |
149 |
|
|
_RL trac_EvPrRn |
150 |
|
|
_RL zonal_filt_lat, gravitySign |
151 |
|
|
_RL viscAstrain, viscAtension |
152 |
|
|
LOGICAL useAnisotropicViscAgridMax |
153 |
|
|
LOGICAL usePickupBeforeC35 |
154 |
|
|
C- |
155 |
|
|
_RL tauThetaClimRelax3Dim, tauSaltClimRelax3Dim |
156 |
|
|
LOGICAL calendarDumps |
157 |
|
|
C- |
158 |
|
|
LOGICAL groundAtK1 |
159 |
|
|
_RL rkFac |
160 |
|
|
_RL thetaMin, phiMin |
161 |
|
|
CHARACTER*(MAX_LEN_FNAM) shelfIceFile |
162 |
|
|
|
163 |
|
|
C-- Continuous equation parameters |
164 |
|
|
NAMELIST /PARM01/ |
165 |
|
|
& gravitySign, nh_Am2, |
166 |
|
|
& gravity, gBaro, rhonil, tAlpha, sBeta, |
167 |
|
|
& f0, beta, omega, rotationPeriod, |
168 |
|
|
& viscAh, viscAhW, viscAhMax, |
169 |
|
|
& viscAhGrid, viscAhGridMax, viscAhGridMin, |
170 |
|
|
& viscC2leith, viscC4leith, |
171 |
|
|
& useFullLeith, useAnisotropicViscAgridMax, useStrainTensionVisc, |
172 |
|
|
& useAreaViscLength, |
173 |
|
|
& viscC2leithD, viscC4leithD, viscC2smag, viscC4smag, |
174 |
|
|
& viscAhD, viscAhZ, viscA4D, viscA4Z, |
175 |
|
|
& viscA4, viscA4W, |
176 |
|
|
& viscA4Max, viscA4Grid, viscA4GridMax, viscA4GridMin, |
177 |
|
|
& viscA4ReMax, viscAhReMax, |
178 |
|
|
& cosPower, viscAstrain, viscAtension, |
179 |
|
|
& diffKhT, diffK4T, diffKhS, diffK4S, |
180 |
|
|
& tRef, sRef, tRefFile, sRefFile, rhoRefFile, |
181 |
|
|
& eosType, integr_GeoPot, selectFindRoSurf, |
182 |
|
|
& atm_Cp, atm_Rd, atm_Rq, atm_Po, |
183 |
|
|
& no_slip_sides, sideDragFactor, |
184 |
|
|
& no_slip_bottom, bottomDragLinear, bottomDragQuadratic, |
185 |
|
|
& momViscosity, momAdvection, momForcing, useCoriolis, |
186 |
|
|
& useConstantF, useBetaPlaneF, useSphereF, use3dCoriolis, |
187 |
|
|
& momPressureForcing, metricTerms, vectorInvariantMomentum, |
188 |
|
|
& tempDiffusion, tempAdvection, tempForcing, |
189 |
|
|
& saltDiffusion, saltAdvection, saltForcing, |
190 |
|
|
& implicSurfPress, implicDiv2Dflow, |
191 |
|
|
& implicitFreeSurface, rigidLid, freeSurfFac, |
192 |
|
|
& hFacMin, hFacMinDz, hFacMinDp, hFacMinDr, |
193 |
|
|
& exactConserv, linFSConserveTr, uniformLin_PhiSurf, |
194 |
|
|
& nonlinFreeSurf, hFacInf, hFacSup, select_rStar, |
195 |
|
|
& implicitIntGravWave, staggerTimeStep, |
196 |
|
|
& tempStepping, saltStepping, momStepping, |
197 |
|
|
& implicitDiffusion, implicitViscosity, |
198 |
|
|
& tempImplVertAdv, saltImplVertAdv, momImplVertAdv, |
199 |
|
|
& viscAz, diffKzT, diffKzS, viscAp, diffKpT, diffKpS, |
200 |
|
|
& viscAr, diffKrT, diffKrS, viscArNr, diffKrNrT, diffKrNrS, |
201 |
|
|
& diffKrBL79surf, diffKrBL79deep, diffKrBL79scl, diffKrBL79Ho, |
202 |
|
|
& BL79LatVary, |
203 |
|
|
& diffKrBLEQsurf, diffKrBLEQdeep, diffKrBLEQscl, diffKrBLEQHo, |
204 |
|
|
& rhoConst, rhoConstFresh, buoyancyRelation, HeatCapacity_Cp, |
205 |
|
|
& writeBinaryPrec, readBinaryPrec, writeStatePrec, |
206 |
|
|
& nonHydrostatic, quasiHydrostatic, globalFiles, useSingleCpuIO, |
207 |
|
|
& allowFreezing, useOldFreezing, ivdc_kappa, |
208 |
|
|
& hMixCriteria, dRhoSmall, hMixSmooth, |
209 |
|
|
& usePickupBeforeC35, usePickupBeforeC54, debugMode, debugLevel, |
210 |
|
|
& tempAdvScheme, tempVertAdvScheme, |
211 |
|
|
& saltAdvScheme, saltVertAdvScheme, tracerAdvScheme, |
212 |
|
|
& multiDimAdvection, useEnergyConservingCoriolis, |
213 |
|
|
& useCDscheme, useJamartWetPoints, useJamartMomAdv, useNHMTerms, |
214 |
|
|
& selectVortScheme, upwindVorticity, highOrderVorticity, |
215 |
|
|
& SadournyCoriolis, useAbsVorticity, upwindShear, selectKEscheme, |
216 |
|
|
& selectAddFluid, useRealFreshWaterFlux, convertFW2Salt, |
217 |
|
|
& temp_EvPrRn, salt_EvPrRn, trac_EvPrRn, |
218 |
|
|
& zonal_filt_lat, |
219 |
|
|
& inAdExact, smoothAbsFuncRange, |
220 |
|
|
& balanceEmPmR, balanceQnet, balancePrintMean |
221 |
|
|
|
222 |
|
|
C-- Elliptic solver parameters |
223 |
|
|
NAMELIST /PARM02/ |
224 |
|
|
& cg2dMaxIters, cg2dChkResFreq, cg2dTargetResidual, |
225 |
|
|
& cg2dTargetResWunit, cg2dpcOffDFac, cg2dPreCondFreq, |
226 |
|
|
& cg3dMaxIters, cg3dChkResFreq, cg3dTargetResidual |
227 |
|
|
|
228 |
|
|
C-- Time stepping parammeters |
229 |
|
|
NAMELIST /PARM03/ |
230 |
|
|
& nIter0, nTimeSteps, nEndIter, |
231 |
|
|
& baseTime, startTime, endTime, |
232 |
|
|
& deltaT, deltaTClock, deltaTmom, |
233 |
|
|
& deltaTtracer, dTtracerLev, deltaTfreesurf, |
234 |
|
|
& forcing_In_AB, momForcingOutAB, tracForcingOutAB, |
235 |
|
|
& momDissip_In_AB, doAB_onGtGs, |
236 |
|
|
& abEps, alph_AB, beta_AB, startFromPickupAB2, |
237 |
|
|
& tauCD, rCD, cAdjFreq, |
238 |
|
|
& chkPtFreq, pChkPtFreq, pickupSuff, pickupStrictlyMatch, |
239 |
|
|
& writePickupAtEnd, |
240 |
|
|
& dumpFreq, dumpInitAndLast, adjDumpFreq, taveFreq, tave_lastIter, |
241 |
|
|
& diagFreq, monitorFreq, adjMonitorFreq, monitorSelect, |
242 |
|
|
& outputTypesInclusive, |
243 |
|
|
& tauThetaClimRelax, tauSaltClimRelax, latBandClimRelax, |
244 |
|
|
& tauThetaClimRelax3Dim, tauSaltClimRelax3Dim, |
245 |
|
|
& periodicExternalForcing, externForcingPeriod, externForcingCycle, |
246 |
|
|
& calendarDumps |
247 |
|
|
|
248 |
|
|
C-- Gridding parameters |
249 |
|
|
NAMELIST /PARM04/ |
250 |
|
|
& usingCartesianGrid, usingCylindricalGrid, |
251 |
|
|
& usingSphericalPolarGrid, usingCurvilinearGrid, |
252 |
|
|
& xgOrigin, ygOrigin, dxSpacing, dySpacing, |
253 |
|
|
& delX, delY, delXFile, delYFile, horizGridFile, |
254 |
|
|
& phiEuler, thetaEuler, psiEuler, |
255 |
|
|
& rSphere, deepAtmosphere, |
256 |
|
|
& Ro_SeaLevel, delZ, delP, delR, delRc, delRFile, delRcFile, |
257 |
|
|
& rkFac, groundAtK1, thetaMin, phiMin |
258 |
|
|
|
259 |
|
|
C-- Input files |
260 |
|
|
NAMELIST /PARM05/ |
261 |
|
|
& bathyFile, topoFile, shelfIceFile, |
262 |
|
|
& diffKrFile, |
263 |
|
|
& hydrogThetaFile, hydrogSaltFile, |
264 |
|
|
& maskIniTemp, maskIniSalt, checkIniTemp, checkIniSalt, |
265 |
|
|
& zonalWindFile, meridWindFile, |
266 |
|
|
& thetaClimFile, saltClimFile, |
267 |
|
|
& surfQfile, surfQnetFile, surfQswFile, EmPmRfile, saltFluxFile, |
268 |
|
|
& lambdaThetaFile, lambdaSaltFile, |
269 |
|
|
& uVelInitFile, vVelInitFile, pSurfInitFile, |
270 |
|
|
& dQdTFile, ploadFile,tCylIn,tCylOut, |
271 |
|
|
& eddyPsiXFile, eddyPsiYFile, |
272 |
|
|
& mdsioLocalDir, |
273 |
|
|
& the_run_name |
274 |
|
|
CEOP |
275 |
|
|
|
276 |
|
|
_BEGIN_MASTER(myThid) |
277 |
|
|
|
278 |
|
|
C Defaults values for input parameters |
279 |
|
|
CALL SET_DEFAULTS( |
280 |
|
|
O viscArDefault, diffKrTDefault, diffKrSDefault, |
281 |
|
|
O hFacMinDrDefault, delRDefault, rkFacDefault, |
282 |
|
|
I myThid ) |
283 |
|
|
SadournyCoriolis = .FALSE. |
284 |
|
|
|
285 |
|
|
C-- Initialise "which vertical coordinate system used" flags. |
286 |
|
|
zCoordInputData = .FALSE. |
287 |
|
|
pCoordInputData = .FALSE. |
288 |
|
|
rCoordInputData = .FALSE. |
289 |
|
|
coordsSet = 0 |
290 |
|
|
|
291 |
|
|
C-- Initialise retired parameters to unlikely value |
292 |
|
|
nRetired = 0 |
293 |
|
|
tempDiffusion = .TRUE. |
294 |
|
|
saltDiffusion = .TRUE. |
295 |
|
|
tracerAdvScheme = UNSET_I |
296 |
|
|
trac_EvPrRn = UNSET_RL |
297 |
|
|
zonal_filt_lat = UNSET_RL |
298 |
|
|
gravitySign = UNSET_RL |
299 |
|
|
viscAstrain = UNSET_RL |
300 |
|
|
viscAtension = UNSET_RL |
301 |
|
|
useAnisotropicViscAgridMax=.TRUE. |
302 |
|
|
usePickupBeforeC35 = .FALSE. |
303 |
|
|
tauThetaClimRelax3Dim = UNSET_RL |
304 |
|
|
tauSaltClimRelax3Dim = UNSET_RL |
305 |
|
|
calendarDumps = .FALSE. |
306 |
|
|
rkFac = UNSET_RL |
307 |
|
|
groundAtK1 = .FALSE. |
308 |
|
|
thetaMin = UNSET_RL |
309 |
|
|
phiMin = UNSET_RL |
310 |
|
|
shelfIceFile = ' ' |
311 |
|
|
|
312 |
|
|
C-- Open the parameter file |
313 |
|
|
#if defined (TARGET_BGL) || defined (TARGET_CRAYXT) |
314 |
|
|
WRITE(scratchFile1,'(A,I4.4)') 'scratch1.', myProcId |
315 |
|
|
WRITE(scratchFile2,'(A,I4.4)') 'scratch2.', myProcId |
316 |
|
|
OPEN(UNIT=scrUnit1, FILE=scratchFile1, STATUS='UNKNOWN') |
317 |
|
|
OPEN(UNIT=scrUnit2, FILE=scratchFile2, STATUS='UNKNOWN') |
318 |
|
|
#else |
319 |
|
|
OPEN(UNIT=scrUnit1,STATUS='SCRATCH') |
320 |
|
|
OPEN(UNIT=scrUnit2,STATUS='SCRATCH') |
321 |
|
|
#endif |
322 |
|
|
OPEN(UNIT=modelDataUnit,FILE='data',STATUS='OLD', |
323 |
|
|
& IOSTAT=errIO) |
324 |
|
|
IF ( errIO .LT. 0 ) THEN |
325 |
|
|
WRITE(msgBuf,'(A)') |
326 |
|
|
& 'S/R INI_PARMS' |
327 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
328 |
|
|
WRITE(msgBuf,'(A)') |
329 |
|
|
& 'Unable to open model parameter' |
330 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
331 |
|
|
WRITE(msgBuf,'(A)') |
332 |
|
|
& 'file "data"' |
333 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
334 |
|
|
CALL MODELDATA_EXAMPLE( myThid ) |
335 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
336 |
|
|
ENDIF |
337 |
|
|
|
338 |
|
|
DO WHILE ( .TRUE. ) |
339 |
|
|
READ(modelDataUnit,FMT='(A)',END=1001) RECORD |
340 |
|
|
IL = MAX(ILNBLNK(RECORD),1) |
341 |
|
|
IF ( RECORD(1:1) .NE. commentCharacter ) THEN |
342 |
|
|
CALL NML_SET_TERMINATOR( RECORD ) |
343 |
|
|
WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL) |
344 |
|
|
ENDIF |
345 |
|
|
WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL) |
346 |
|
|
ENDDO |
347 |
|
|
1001 CONTINUE |
348 |
|
|
CLOSE(modelDataUnit) |
349 |
|
|
|
350 |
|
|
C-- Report contents of model parameter file |
351 |
|
|
WRITE(msgBuf,'(A)') |
352 |
|
|
&'// =======================================================' |
353 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
354 |
|
|
& SQUEEZE_RIGHT, myThid ) |
355 |
|
|
WRITE(msgBuf,'(A)') '// Model parameter file "data"' |
356 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
357 |
|
|
& SQUEEZE_RIGHT, myThid ) |
358 |
|
|
WRITE(msgBuf,'(A)') |
359 |
|
|
&'// =======================================================' |
360 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
361 |
|
|
& SQUEEZE_RIGHT, myThid ) |
362 |
|
|
iUnit = scrUnit2 |
363 |
|
|
REWIND(iUnit) |
364 |
|
|
DO WHILE ( .TRUE. ) |
365 |
|
|
READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD |
366 |
|
|
IL = MAX(ILNBLNK(RECORD),1) |
367 |
|
|
WRITE(msgBuf,'(A,A)') '>',RECORD(:IL) |
368 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
369 |
|
|
& SQUEEZE_RIGHT, myThid ) |
370 |
|
|
ENDDO |
371 |
|
|
2001 CONTINUE |
372 |
|
|
CLOSE(iUnit) |
373 |
|
|
WRITE(msgBuf,'(A)') ' ' |
374 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
375 |
|
|
& SQUEEZE_RIGHT, myThid ) |
376 |
|
|
|
377 |
|
|
|
378 |
|
|
C-- Read settings from model parameter file "data". |
379 |
|
|
iUnit = scrUnit1 |
380 |
|
|
REWIND(iUnit) |
381 |
|
|
|
382 |
|
|
C-- Set default "physical" parameters |
383 |
|
|
viscAhW = UNSET_RL |
384 |
|
|
viscA4W = UNSET_RL |
385 |
|
|
viscAhD = UNSET_RL |
386 |
|
|
viscAhZ = UNSET_RL |
387 |
|
|
viscA4D = UNSET_RL |
388 |
|
|
viscA4Z = UNSET_RL |
389 |
|
|
viscAz = UNSET_RL |
390 |
|
|
viscAp = UNSET_RL |
391 |
|
|
viscAr = UNSET_RL |
392 |
|
|
diffKzT = UNSET_RL |
393 |
|
|
diffKpT = UNSET_RL |
394 |
|
|
diffKrT = UNSET_RL |
395 |
|
|
diffKzS = UNSET_RL |
396 |
|
|
diffKpS = UNSET_RL |
397 |
|
|
diffKrS = UNSET_RL |
398 |
|
|
DO k=1,Nr |
399 |
|
|
viscArNr(k) = UNSET_RL |
400 |
|
|
diffKrNrT(k) = UNSET_RL |
401 |
|
|
diffKrNrS(k) = UNSET_RL |
402 |
|
|
tRef(k) = UNSET_RL |
403 |
|
|
sRef(k) = UNSET_RL |
404 |
|
|
ENDDO |
405 |
|
|
gBaro = UNSET_RL |
406 |
|
|
rhoConst = UNSET_RL |
407 |
|
|
omega = UNSET_RL |
408 |
|
|
hFacMinDr = UNSET_RL |
409 |
|
|
hFacMinDz = UNSET_RL |
410 |
|
|
hFacMinDp = UNSET_RL |
411 |
|
|
rhoConstFresh = UNSET_RL |
412 |
|
|
convertFW2Salt = UNSET_RL |
413 |
|
|
tAlpha = UNSET_RL |
414 |
|
|
sBeta = UNSET_RL |
415 |
|
|
tempVertAdvScheme = 0 |
416 |
|
|
saltVertAdvScheme = 0 |
417 |
|
|
C-- z,p,r coord input switching. |
418 |
|
|
WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM01' |
419 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
420 |
|
|
& SQUEEZE_RIGHT, myThid ) |
421 |
|
|
READ(UNIT=iUnit,NML=PARM01) !,IOSTAT=errIO) |
422 |
|
|
IF ( errIO .LT. 0 ) THEN |
423 |
|
|
WRITE(msgBuf,'(A)') |
424 |
|
|
& 'S/R INI_PARMS' |
425 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
426 |
|
|
WRITE(msgBuf,'(A)') |
427 |
|
|
& 'Error reading numerical model ' |
428 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
429 |
|
|
WRITE(msgBuf,'(A)') |
430 |
|
|
& 'parameter file "data"' |
431 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
432 |
|
|
WRITE(msgBuf,'(A)') |
433 |
|
|
& 'Problem in namelist PARM01' |
434 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
435 |
|
|
CALL MODELDATA_EXAMPLE( myThid ) |
436 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
437 |
|
|
ELSE |
438 |
|
|
WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM01 : OK' |
439 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
440 |
|
|
& SQUEEZE_RIGHT, myThid ) |
441 |
|
|
ENDIF |
442 |
|
|
|
443 |
|
|
C- set the type of vertical coordinate and type of fluid |
444 |
|
|
C according to buoyancyRelation |
445 |
|
|
usingPCoords = .FALSE. |
446 |
|
|
usingZCoords = .FALSE. |
447 |
|
|
fluidIsAir = .FALSE. |
448 |
|
|
fluidIsWater = .FALSE. |
449 |
|
|
IF ( buoyancyRelation.EQ.'ATMOSPHERIC' ) THEN |
450 |
|
|
usingPCoords = .TRUE. |
451 |
|
|
fluidIsAir = .TRUE. |
452 |
|
|
ELSEIF ( buoyancyRelation.EQ.'OCEANICP') THEN |
453 |
|
|
usingPCoords = .TRUE. |
454 |
|
|
fluidIsWater = .TRUE. |
455 |
|
|
ELSEIF ( buoyancyRelation.EQ.'OCEANIC' ) THEN |
456 |
|
|
usingZCoords = .TRUE. |
457 |
|
|
fluidIsWater = .TRUE. |
458 |
|
|
ELSE |
459 |
|
|
WRITE(msgBuf,'(2A)') 'S/R INI_PARMS:', |
460 |
|
|
& ' Bad value of buoyancyRelation ' |
461 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
462 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
463 |
|
|
ENDIF |
464 |
|
|
|
465 |
|
|
IF ( .NOT.rigidLid .AND. |
466 |
|
|
& .NOT.implicitFreeSurface ) THEN |
467 |
|
|
C- No barotropic solver selected => use implicitFreeSurface as default |
468 |
|
|
WRITE(msgBuf,'(A)') |
469 |
|
|
& 'S/R INI_PARMS: No request for barotropic solver' |
470 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
471 |
|
|
& SQUEEZE_RIGHT, myThid ) |
472 |
|
|
WRITE(msgBuf,'(A)') |
473 |
|
|
& 'S/R INI_PARMS: => Use implicitFreeSurface as default' |
474 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
475 |
|
|
& SQUEEZE_RIGHT, myThid ) |
476 |
|
|
implicitFreeSurface = .TRUE. |
477 |
|
|
ENDIF |
478 |
|
|
IF ( implicitFreeSurface ) freeSurfFac = 1.D0 |
479 |
|
|
IF ( rigidLid ) freeSurfFac = 0.D0 |
480 |
|
|
IF ( gBaro .EQ. UNSET_RL ) gBaro=gravity |
481 |
|
|
IF ( rhoConst .EQ. UNSET_RL ) rhoConst=rhoNil |
482 |
|
|
IF ( rhoConstFresh .EQ. UNSET_RL ) rhoConstFresh=rhoConst |
483 |
|
|
IF ( omega .EQ. UNSET_RL ) THEN |
484 |
|
|
omega = 0. _d 0 |
485 |
|
|
IF ( rotationPeriod .NE. 0. _d 0 ) |
486 |
|
|
& omega = 2.D0 * PI / rotationPeriod |
487 |
|
|
ELSEIF ( omega .EQ. 0. _d 0 ) THEN |
488 |
|
|
rotationPeriod = 0. _d 0 |
489 |
|
|
ELSE |
490 |
|
|
rotationPeriod = 2.D0 * PI / omega |
491 |
|
|
ENDIF |
492 |
|
|
IF (atm_Rd .EQ. UNSET_RL) THEN |
493 |
|
|
atm_Rd = atm_Cp * atm_kappa |
494 |
|
|
ELSE |
495 |
|
|
atm_kappa = atm_Rd / atm_Cp |
496 |
|
|
ENDIF |
497 |
|
|
C-- Non-hydrostatic/quasi-hydrostatic |
498 |
|
|
IF (nonHydrostatic.AND.quasiHydrostatic) THEN |
499 |
|
|
WRITE(msgBuf,'(A)') |
500 |
|
|
& 'Illegal: both nonHydrostatic = quasiHydrostatic = TRUE' |
501 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
502 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
503 |
|
|
ENDIF |
504 |
|
|
C-- Advection and Forcing for Temp and salt |
505 |
|
|
IF (tempVertAdvScheme.EQ.0) tempVertAdvScheme = tempAdvScheme |
506 |
|
|
IF (saltVertAdvScheme.EQ.0) saltVertAdvScheme = saltAdvScheme |
507 |
|
|
C-- horizontal viscosity for vertical moments |
508 |
|
|
IF ( viscAhW .EQ. UNSET_RL ) viscAhW = viscAh |
509 |
|
|
IF ( viscA4W .EQ. UNSET_RL ) viscA4W = viscA4 |
510 |
|
|
C-- horizontal viscosity (acting on Divergence or Vorticity) |
511 |
|
|
IF ( viscAhD .EQ. UNSET_RL ) viscAhD = viscAh |
512 |
|
|
IF ( viscAhZ .EQ. UNSET_RL ) viscAhZ = viscAh |
513 |
|
|
IF ( viscA4D .EQ. UNSET_RL ) viscA4D = viscA4 |
514 |
|
|
IF ( viscA4Z .EQ. UNSET_RL ) viscA4Z = viscA4 |
515 |
|
|
C-- z,p,r coord input switching. |
516 |
|
|
IF ( viscAz .NE. UNSET_RL ) zCoordInputData = .TRUE. |
517 |
|
|
IF ( viscAp .NE. UNSET_RL ) pCoordInputData = .TRUE. |
518 |
|
|
IF ( viscAr .NE. UNSET_RL ) rCoordInputData = .TRUE. |
519 |
|
|
IF ( viscAr .EQ. UNSET_RL ) viscAr = viscAz |
520 |
|
|
IF ( viscAr .EQ. UNSET_RL ) viscAr = viscAp |
521 |
|
|
IF ( viscAr .EQ. UNSET_RL ) viscAr = viscArDefault |
522 |
|
|
vertSetCount = 0 |
523 |
|
|
DO k=1,Nr |
524 |
|
|
IF ( viscArNr(k).EQ.UNSET_RL ) THEN |
525 |
|
|
viscArNr(k) = viscAr |
526 |
|
|
ELSE |
527 |
|
|
vertSetCount = vertSetCount + 1 |
528 |
|
|
ENDIF |
529 |
|
|
ENDDO |
530 |
|
|
IF ( viscAr.NE.viscArDefault .AND. vertSetCount.GT.0 ) THEN |
531 |
|
|
WRITE(msgBuf,'(2A)') 'S/R INI_PARMS: Cannot set both ', |
532 |
|
|
& 'viscArNr and viscAr (or Ap,Az) in param file data' |
533 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
534 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
535 |
|
|
ELSEIF ( vertSetCount.GT.0 .AND. vertSetCount.LT.Nr ) THEN |
536 |
|
|
WRITE(msgBuf,'(A,2(I5,A))') 'S/R INI_PARMS: Partial setting (', |
537 |
|
|
& vertSetCount, ' /', Nr, ') of viscArNr is not allowed' |
538 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
539 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
540 |
|
|
ENDIF |
541 |
|
|
|
542 |
|
|
IF ( diffKzT .NE. UNSET_RL ) zCoordInputData = .TRUE. |
543 |
|
|
IF ( diffKpT .NE. UNSET_RL ) pCoordInputData = .TRUE. |
544 |
|
|
IF ( diffKrT .NE. UNSET_RL ) rCoordInputData = .TRUE. |
545 |
|
|
IF ( diffKrT .EQ. UNSET_RL ) diffKrT = diffKzT |
546 |
|
|
IF ( diffKrT .EQ. UNSET_RL ) diffKrT = diffKpT |
547 |
|
|
IF ( diffKrT .EQ. UNSET_RL ) diffKrT = diffKrTDefault |
548 |
|
|
vertSetCount = 0 |
549 |
|
|
DO k=1,Nr |
550 |
|
|
IF ( diffKrNrT(k).EQ.UNSET_RL ) THEN |
551 |
|
|
diffKrNrT(k) = diffKrT |
552 |
|
|
ELSE |
553 |
|
|
vertSetCount = vertSetCount + 1 |
554 |
|
|
ENDIF |
555 |
|
|
ENDDO |
556 |
|
|
IF ( diffKrT.NE.diffKrTDefault .AND. vertSetCount.GT.0 ) THEN |
557 |
|
|
WRITE(msgBuf,'(2A)') 'S/R INI_PARMS: Cannot set both ', |
558 |
|
|
& 'diffKrNrT and diffKrT (or Kp,Kz) in param file data' |
559 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
560 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
561 |
|
|
ELSEIF ( vertSetCount.GT.0 .AND. vertSetCount.LT.Nr ) THEN |
562 |
|
|
WRITE(msgBuf,'(A,2(I5,A))') 'S/R INI_PARMS: Partial setting (', |
563 |
|
|
& vertSetCount, ' /', Nr, ') of diffKrNrT is not allowed' |
564 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
565 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
566 |
|
|
ENDIF |
567 |
|
|
|
568 |
|
|
IF ( diffKzS .NE. UNSET_RL ) zCoordInputData = .TRUE. |
569 |
|
|
IF ( diffKpS .NE. UNSET_RL ) pCoordInputData = .TRUE. |
570 |
|
|
IF ( diffKrS .NE. UNSET_RL ) rCoordInputData = .TRUE. |
571 |
|
|
IF ( diffKrS .EQ. UNSET_RL ) diffKrS = diffKzS |
572 |
|
|
IF ( diffKrS .EQ. UNSET_RL ) diffKrS = diffKpS |
573 |
|
|
IF ( diffKrS .EQ. UNSET_RL ) diffKrS = diffKrSDefault |
574 |
|
|
vertSetCount = 0 |
575 |
|
|
DO k=1,Nr |
576 |
|
|
IF ( diffKrNrS(k).EQ.UNSET_RL ) THEN |
577 |
|
|
diffKrNrS(k) = diffKrS |
578 |
|
|
ELSE |
579 |
|
|
vertSetCount = vertSetCount + 1 |
580 |
|
|
ENDIF |
581 |
|
|
ENDDO |
582 |
|
|
IF ( diffKrS.NE.diffKrSDefault .AND. vertSetCount.GT.0 ) THEN |
583 |
|
|
WRITE(msgBuf,'(2A)') 'S/R INI_PARMS: Cannot set both ', |
584 |
|
|
& 'diffKrNrS and diffKrS (or Kp,Kz) in param file data' |
585 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
586 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
587 |
|
|
ELSEIF ( vertSetCount.GT.0 .AND. vertSetCount.LT.Nr ) THEN |
588 |
|
|
WRITE(msgBuf,'(A,2(I5,A))') 'S/R INI_PARMS: Partial setting (', |
589 |
|
|
& vertSetCount, ' /', Nr, ') of diffKrNrS is not allowed' |
590 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
591 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
592 |
|
|
ENDIF |
593 |
|
|
|
594 |
|
|
IF (diffKrBLEQsurf .EQ. UNSET_RL) diffKrBLEQsurf = diffKrBL79surf |
595 |
|
|
IF (diffKrBLEQdeep .EQ. UNSET_RL) diffKrBLEQdeep = diffKrBL79deep |
596 |
|
|
IF (diffKrBLEQscl .EQ. UNSET_RL) diffKrBLEQscl = diffKrBL79scl |
597 |
|
|
IF (diffKrBLEQHo .EQ. UNSET_RL) diffKrBLEQHo = diffKrBL79Ho |
598 |
|
|
|
599 |
|
|
IF ( hFacMinDz .NE. UNSET_RL ) zCoordInputData = .TRUE. |
600 |
|
|
IF ( hFacMinDp .NE. UNSET_RL ) pCoordInputData = .TRUE. |
601 |
|
|
IF ( hFacMinDr .NE. UNSET_RL ) rCoordInputData = .TRUE. |
602 |
|
|
IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr = hFacMinDz |
603 |
|
|
IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr = hFacMinDp |
604 |
|
|
IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr = hFacMinDrDefault |
605 |
|
|
|
606 |
|
|
IF (convertFW2Salt.EQ.UNSET_RL) THEN |
607 |
|
|
convertFW2Salt = 35. |
608 |
|
|
IF (useRealFreshWaterFlux) convertFW2Salt=-1 |
609 |
|
|
IF ( selectAddFluid.GE.1 ) convertFW2Salt=-1 |
610 |
|
|
ENDIF |
611 |
|
|
|
612 |
|
|
IF ( SadournyCoriolis ) THEN |
613 |
|
|
C-- for backward compatibility : |
614 |
|
|
IF ( selectVortScheme.EQ.UNSET_I ) selectVortScheme = 2 |
615 |
|
|
IF ( selectVortScheme.NE.2 ) THEN |
616 |
|
|
WRITE(msgBuf,'(A,I5,A)') |
617 |
|
|
& 'S/R INI_PARMS: selectVortScheme=', selectVortScheme, |
618 |
|
|
& ' conflicts with "SadournyCoriolis"' |
619 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
620 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
621 |
|
|
ENDIF |
622 |
|
|
ENDIF |
623 |
|
|
|
624 |
|
|
IF ( ivdc_kappa .NE. 0. .AND. .NOT. implicitDiffusion ) THEN |
625 |
|
|
WRITE(msgBuf,'(A,A)') |
626 |
|
|
& 'S/R INI_PARMS: To use ivdc_kappa you must enable implicit', |
627 |
|
|
& ' vertical diffusion.' |
628 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
629 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
630 |
|
|
ENDIF |
631 |
|
|
|
632 |
|
|
coordsSet = 0 |
633 |
|
|
IF ( zCoordInputData ) coordsSet = coordsSet + 1 |
634 |
|
|
IF ( pCoordInputData ) coordsSet = coordsSet + 1 |
635 |
|
|
IF ( rCoordInputData ) coordsSet = coordsSet + 1 |
636 |
|
|
IF ( coordsSet .GT. 1 ) THEN |
637 |
|
|
WRITE(msgBuf,'(A)') |
638 |
|
|
& 'S/R INI_PARMS: Cannot mix z, p and r in the input data.' |
639 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
640 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
641 |
|
|
ENDIF |
642 |
|
|
IF ( rhoConst .LE. 0. ) THEN |
643 |
|
|
WRITE(msgBuf,'(A)') |
644 |
|
|
& 'S/R INI_PARMS: rhoConst must be greater than 0.' |
645 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
646 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
647 |
|
|
ELSE |
648 |
|
|
recip_rhoConst = 1.D0 / rhoConst |
649 |
|
|
ENDIF |
650 |
|
|
IF ( rhoNil .LE. 0. ) THEN |
651 |
|
|
WRITE(msgBuf,'(A)') |
652 |
|
|
& 'S/R INI_PARMS: rhoNil must be greater than 0.' |
653 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
654 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
655 |
|
|
ELSE |
656 |
|
|
recip_rhoNil = 1.D0 / rhoNil |
657 |
|
|
ENDIF |
658 |
|
|
IF ( HeatCapacity_Cp .LE. 0. ) THEN |
659 |
|
|
WRITE(msgBuf,'(A)') |
660 |
|
|
& 'S/R INI_PARMS: HeatCapacity_Cp must be greater than 0.' |
661 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
662 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
663 |
|
|
ELSE |
664 |
|
|
recip_Cp = 1.D0 / HeatCapacity_Cp |
665 |
|
|
ENDIF |
666 |
|
|
IF ( gravity .LE. 0. ) THEN |
667 |
|
|
WRITE(msgBuf,'(A)') |
668 |
|
|
& 'S/R INI_PARMS: gravity must be greater than 0.' |
669 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
670 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
671 |
|
|
ELSE |
672 |
|
|
recip_gravity = 1.D0 / gravity |
673 |
|
|
ENDIF |
674 |
|
|
C This flags are now passed to RW and MDSIO packages in ini_model_io.F |
675 |
|
|
C Set globalFiles flag for READ_WRITE_FLD package |
676 |
|
|
c CALL SET_WRITE_GLOBAL_FLD( globalFiles ) |
677 |
|
|
C Set globalFiles flag for READ_WRITE_REC package |
678 |
|
|
c CALL SET_WRITE_GLOBAL_REC( globalFiles ) |
679 |
|
|
C Set globalFiles flag for READ_WRITE_REC package |
680 |
|
|
c CALL SET_WRITE_GLOBAL_PICKUP( globalFiles ) |
681 |
|
|
|
682 |
|
|
C Check for retired parameters still being used |
683 |
|
|
nRetired = 0 |
684 |
|
|
IF ( zonal_filt_lat .NE. UNSET_RL ) THEN |
685 |
|
|
nRetired = nRetired+1 |
686 |
|
|
WRITE(msgBuf,'(A,A)') |
687 |
|
|
& 'S/R INI_PARMS: Paramater "zonal_filt_lat" is', |
688 |
|
|
& ' no longer allowed in file "data".' |
689 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
690 |
|
|
WRITE(msgBuf,'(A,A)') |
691 |
|
|
& 'S/R INI_PARMS: Paramater "zonal_filt_lat" is', |
692 |
|
|
& ' now read from file "data.zonfilt".' |
693 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
694 |
|
|
ENDIF |
695 |
|
|
IF ( gravitySign .NE. UNSET_RL ) THEN |
696 |
|
|
nRetired = nRetired+1 |
697 |
|
|
WRITE(msgBuf,'(A,A)') |
698 |
|
|
& 'S/R INI_PARMS: "gravitySign" is set according to vertical ', |
699 |
|
|
& ' coordinate and is no longer allowed in file "data".' |
700 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
701 |
|
|
ENDIF |
702 |
|
|
IF ( tracerAdvScheme .NE. UNSET_I ) THEN |
703 |
|
|
nRetired = nRetired+1 |
704 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "tracerAdvScheme" ', |
705 |
|
|
& '(old passive tracer code) is no longer allowed in file "data"' |
706 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
707 |
|
|
ENDIF |
708 |
|
|
IF ( trac_EvPrRn .NE. UNSET_RL ) THEN |
709 |
|
|
nRetired = nRetired+1 |
710 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "trac_EvPrRn" ', |
711 |
|
|
& '(old passive tracer code) is no longer allowed in file "data"' |
712 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
713 |
|
|
ENDIF |
714 |
|
|
IF ( .NOT. tempDiffusion ) THEN |
715 |
|
|
nRetired = nRetired+1 |
716 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "tempDiffusion" ', |
717 |
|
|
& 'is no longer allowed in file "data"' |
718 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
719 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: to turn off diffusion', |
720 |
|
|
& ' => set diffusivity to zero' |
721 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
722 |
|
|
ENDIF |
723 |
|
|
IF ( .NOT. saltDiffusion ) THEN |
724 |
|
|
nRetired = nRetired+1 |
725 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "saltDiffusion" ', |
726 |
|
|
& 'is no longer allowed in file "data"' |
727 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
728 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: to turn off diffusion', |
729 |
|
|
& ' => set diffusivity to zero' |
730 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
731 |
|
|
ENDIF |
732 |
|
|
IF ( viscAstrain .NE. UNSET_RL ) THEN |
733 |
|
|
nRetired = nRetired+1 |
734 |
|
|
WRITE(msgBuf,'(A,A)') |
735 |
|
|
& 'S/R INI_PARMS: "viscAstrain" ', |
736 |
|
|
& 'is no longer allowed in file "data"' |
737 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
738 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: to use Strain & Tension', |
739 |
|
|
& ' formulation => set useStrainTensionVisc to TRUE' |
740 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
741 |
|
|
ENDIF |
742 |
|
|
IF ( viscAtension .NE. UNSET_RL ) THEN |
743 |
|
|
nRetired = nRetired+1 |
744 |
|
|
WRITE(msgBuf,'(A,A)') |
745 |
|
|
& 'S/R INI_PARMS: "viscAtension" ', |
746 |
|
|
& 'is no longer allowed in file "data"' |
747 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
748 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: to use Strain & Tension', |
749 |
|
|
& ' formulation => set useStrainTensionVisc to TRUE' |
750 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
751 |
|
|
ENDIF |
752 |
|
|
IF ( .NOT.useAnisotropicViscAgridMax ) THEN |
753 |
|
|
nRetired = nRetired+1 |
754 |
|
|
WRITE(msgBuf,'(A,A)') |
755 |
|
|
& 'S/R INI_PARMS: "useAnisotropicViscAgridMax" ', |
756 |
|
|
& 'is not allowed in "data" substitute useAreaViscLength=true' |
757 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
758 |
|
|
ENDIF |
759 |
|
|
IF ( usePickupBeforeC35 ) THEN |
760 |
|
|
nRetired = nRetired+1 |
761 |
|
|
WRITE(msgBuf,'(A,A)') |
762 |
|
|
& 'S/R INI_PARMS: "usePickupBeforeC35" ', |
763 |
|
|
& 'is no longer supported & not longer allowed in file "data"' |
764 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
765 |
|
|
ENDIF |
766 |
|
|
|
767 |
|
|
C-- Elliptic solver parameters |
768 |
|
|
WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM02' |
769 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
770 |
|
|
& SQUEEZE_RIGHT, myThid ) |
771 |
|
|
READ(UNIT=iUnit,NML=PARM02) !,IOSTAT=errIO) |
772 |
|
|
IF ( errIO .LT. 0 ) THEN |
773 |
|
|
WRITE(msgBuf,'(A)') |
774 |
|
|
& 'S/R INI_PARMS' |
775 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
776 |
|
|
WRITE(msgBuf,'(A)') |
777 |
|
|
& 'Error reading numerical model ' |
778 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
779 |
|
|
WRITE(msgBuf,'(A)') |
780 |
|
|
& 'parameter file "data".' |
781 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
782 |
|
|
WRITE(msgBuf,'(A)') |
783 |
|
|
& 'Problem in namelist PARM02' |
784 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
785 |
|
|
CALL MODELDATA_EXAMPLE( myThid ) |
786 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
787 |
|
|
ELSE |
788 |
|
|
WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM02 : OK' |
789 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
790 |
|
|
& SQUEEZE_RIGHT, myThid ) |
791 |
|
|
ENDIF |
792 |
|
|
|
793 |
|
|
C-- Time stepping parameters |
794 |
|
|
rCD = -1.D0 |
795 |
|
|
latBandClimRelax = UNSET_RL |
796 |
|
|
deltaTtracer = 0. _d 0 |
797 |
|
|
forcing_In_AB = .TRUE. |
798 |
|
|
WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM03' |
799 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
800 |
|
|
& SQUEEZE_RIGHT, myThid ) |
801 |
|
|
READ(UNIT=iUnit,NML=PARM03) !,IOSTAT=errIO) |
802 |
|
|
IF ( errIO .LT. 0 ) THEN |
803 |
|
|
WRITE(msgBuf,'(A)') |
804 |
|
|
& 'S/R INI_PARMS' |
805 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
806 |
|
|
WRITE(msgBuf,'(A)') |
807 |
|
|
& 'Error reading numerical model ' |
808 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
809 |
|
|
WRITE(msgBuf,'(A)') |
810 |
|
|
& 'parameter file "data"' |
811 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
812 |
|
|
WRITE(msgBuf,'(A)') |
813 |
|
|
& 'Problem in namelist PARM03' |
814 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
815 |
|
|
CALL MODELDATA_EXAMPLE( myThid ) |
816 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
817 |
|
|
ELSE |
818 |
|
|
WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM03 : OK' |
819 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
820 |
|
|
& SQUEEZE_RIGHT, myThid ) |
821 |
|
|
ENDIF |
822 |
|
|
C Check for retired parameters still being used |
823 |
|
|
IF ( tauThetaClimRelax3Dim .NE. UNSET_RL ) THEN |
824 |
|
|
nRetired = nRetired+1 |
825 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "tauThetaClimRelax3Dim" ', |
826 |
|
|
& 'is no longer allowed in file "data"' |
827 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
828 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: 3-dim. relaxation code', |
829 |
|
|
& ' has moved to separate pkg/rbcs.' |
830 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
831 |
|
|
ENDIF |
832 |
|
|
IF ( tauSaltClimRelax3Dim .NE. UNSET_RL ) THEN |
833 |
|
|
nRetired = nRetired+1 |
834 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "tauSaltClimRelax3Dim" ', |
835 |
|
|
& 'is no longer allowed in file "data"' |
836 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
837 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: 3-dim. relaxation code', |
838 |
|
|
& ' has moved to separate pkg/rbcs.' |
839 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
840 |
|
|
ENDIF |
841 |
|
|
IF ( calendarDumps ) THEN |
842 |
|
|
nRetired = nRetired+1 |
843 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: "calendarDumps" ', |
844 |
|
|
& 'is no longer allowed in file "data"' |
845 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
846 |
|
|
WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: calendarDumps', |
847 |
|
|
& ' has moved to "data.cal"' |
848 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
849 |
|
|
ENDIF |
850 |
|
|
|
851 |
|
|
C Process "timestepping" params |
852 |
|
|
C o Time step size |
853 |
|
|
IF ( deltaTtracer .NE. dTtracerLev(1) .AND. |
854 |
|
|
& deltaTtracer .NE. 0. .AND. dTtracerLev(1) .NE. 0. ) THEN |
855 |
|
|
WRITE(msgBuf,'(A)') |
856 |
|
|
& 'S/R INI_PARMS: deltaTtracer & dTtracerLev(1) not equal' |
857 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
858 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
859 |
|
|
ELSEIF ( dTtracerLev(1) .NE. 0. ) THEN |
860 |
|
|
deltaTtracer = dTtracerLev(1) |
861 |
|
|
ENDIF |
862 |
|
|
IF ( deltaT .EQ. 0. ) deltaT = deltaTClock |
863 |
|
|
IF ( deltaT .EQ. 0. ) deltaT = deltaTtracer |
864 |
|
|
IF ( deltaT .EQ. 0. ) deltaT = deltaTmom |
865 |
|
|
IF ( deltaT .EQ. 0. ) deltaT = deltaTfreesurf |
866 |
|
|
IF ( deltaTmom .EQ. 0. ) deltaTmom = deltaT |
867 |
|
|
IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT |
868 |
|
|
IF ( deltaTClock .EQ. 0. ) deltaTClock = deltaT |
869 |
|
|
DO k=1,Nr |
870 |
|
|
IF (dTtracerLev(k).EQ.0.) dTtracerLev(k)= deltaTtracer |
871 |
|
|
ENDDO |
872 |
|
|
C Note that this line should set deltaFreesurf=deltaTtracer |
873 |
|
|
C but this would change a lot of existing set-ups so we are |
874 |
|
|
C obliged to set the default inappropriately. |
875 |
|
|
C Be advised that when using asynchronous time stepping |
876 |
|
|
C it is better to set deltaTreesurf=deltaTtracer |
877 |
|
|
IF ( deltaTfreesurf .EQ. 0. ) deltaTfreesurf = deltaTmom |
878 |
|
|
IF ( periodicExternalForcing ) THEN |
879 |
|
|
IF ( externForcingCycle*externForcingPeriod .EQ. 0. ) THEN |
880 |
|
|
WRITE(msgBuf,'(A)') |
881 |
|
|
& 'S/R INI_PARMS: externForcingCycle,externForcingPeriod =0' |
882 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
883 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
884 |
|
|
ENDIF |
885 |
|
|
IF ( INT(externForcingCycle/externForcingPeriod) .NE. |
886 |
|
|
& externForcingCycle/externForcingPeriod ) THEN |
887 |
|
|
WRITE(msgBuf,'(A)') |
888 |
|
|
& 'S/R INI_PARMS: externForcingCycle <> N*externForcingPeriod' |
889 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
890 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
891 |
|
|
ENDIF |
892 |
|
|
IF ( externForcingCycle.lt.externForcingPeriod ) THEN |
893 |
|
|
WRITE(msgBuf,'(A)') |
894 |
|
|
& 'S/R INI_PARMS: externForcingCycle < externForcingPeriod' |
895 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
896 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
897 |
|
|
ENDIF |
898 |
|
|
IF ( externForcingPeriod.lt.deltaTclock ) THEN |
899 |
|
|
WRITE(msgBuf,'(A)') |
900 |
|
|
& 'S/R INI_PARMS: externForcingPeriod < deltaTclock' |
901 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
902 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
903 |
|
|
ENDIF |
904 |
|
|
ENDIF |
905 |
|
|
C o Adams-Bashforth time stepping: |
906 |
|
|
IF ( momForcingOutAB .EQ. UNSET_I ) THEN |
907 |
|
|
momForcingOutAB = 1 |
908 |
|
|
IF ( forcing_In_AB ) momForcingOutAB = 0 |
909 |
|
|
ENDIF |
910 |
|
|
IF ( tracForcingOutAB .EQ. UNSET_I ) THEN |
911 |
|
|
tracForcingOutAB = 1 |
912 |
|
|
IF ( forcing_In_AB ) tracForcingOutAB = 0 |
913 |
|
|
ENDIF |
914 |
|
|
C o Convection frequency |
915 |
|
|
IF ( cAdjFreq .LT. 0. ) THEN |
916 |
|
|
cAdjFreq = deltaTClock |
917 |
|
|
ENDIF |
918 |
|
|
IF ( ivdc_kappa .NE. 0. .AND. cAdjFreq .NE. 0. ) THEN |
919 |
|
|
WRITE(msgBuf,'(A,A)') |
920 |
|
|
& 'S/R INI_PARMS: You have enabled both ivdc_kappa and', |
921 |
|
|
& ' convective adjustment.' |
922 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
923 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
924 |
|
|
ENDIF |
925 |
|
|
IF (useCDscheme) THEN |
926 |
|
|
C o CD coupling (CD scheme): |
927 |
|
|
IF ( tauCD .EQ. 0.D0 ) tauCD = deltaTmom |
928 |
|
|
IF ( rCD .LT. 0. ) rCD = 1. _d 0 - deltaTMom/tauCD |
929 |
|
|
ENDIF |
930 |
|
|
C o Temperature climatology relaxation time scale |
931 |
|
|
IF ( tauThetaClimRelax .EQ. 0.D0 ) THEN |
932 |
|
|
doThetaClimRelax = .FALSE. |
933 |
|
|
ELSE |
934 |
|
|
doThetaClimRelax = .TRUE. |
935 |
|
|
ENDIF |
936 |
|
|
C o Salinity climatology relaxation time scale |
937 |
|
|
IF ( tauSaltClimRelax .EQ. 0.D0 ) THEN |
938 |
|
|
doSaltClimRelax = .FALSE. |
939 |
|
|
ELSE |
940 |
|
|
doSaltClimRelax = .TRUE. |
941 |
|
|
ENDIF |
942 |
|
|
|
943 |
|
|
C o Base time |
944 |
|
|
IF ( nIter0.NE.0 .AND. startTime.NE.0. .AND. baseTime.EQ.0. ) |
945 |
|
|
& baseTime = startTime - deltaTClock*float(nIter0) |
946 |
|
|
C o Start time |
947 |
|
|
IF ( nIter0 .NE. 0 .AND. startTime .EQ. 0. ) |
948 |
|
|
& startTime = baseTime + deltaTClock*float(nIter0) |
949 |
|
|
C o nIter0 |
950 |
|
|
IF ( nIter0 .EQ. 0 .AND. startTime .NE. baseTime ) |
951 |
|
|
& nIter0 = NINT( (startTime-baseTime)/deltaTClock ) |
952 |
|
|
|
953 |
|
|
C o nTimeSteps 1 |
954 |
|
|
IF ( nTimeSteps .EQ. 0 .AND. nEndIter .NE. 0 ) |
955 |
|
|
& nTimeSteps = nEndIter-nIter0 |
956 |
|
|
C o nTimeSteps 2 |
957 |
|
|
IF ( nTimeSteps .EQ. 0 .AND. endTime .NE. 0. ) |
958 |
|
|
& nTimeSteps = NINT((endTime-startTime)/deltaTclock) |
959 |
|
|
C o nEndIter 1 |
960 |
|
|
IF ( nEndIter .EQ. 0 .AND. nTimeSteps .NE. 0 ) |
961 |
|
|
& nEndIter = nIter0+nTimeSteps |
962 |
|
|
C o nEndIter 2 |
963 |
|
|
IF ( nEndIter .EQ. 0 .AND. endTime .NE. 0. ) |
964 |
|
|
& nEndIter = NINT((endTime-baseTime)/deltaTclock) |
965 |
|
|
C o End Time 1 |
966 |
|
|
IF ( endTime .EQ. 0. .AND. nTimeSteps .NE. 0 ) |
967 |
|
|
& endTime = startTime + deltaTClock*float(nTimeSteps) |
968 |
|
|
C o End Time 2 |
969 |
|
|
IF ( endTime .EQ. 0. .AND. nEndIter .NE. 0 ) |
970 |
|
|
& endTime = baseTime + deltaTClock*float(nEndIter) |
971 |
|
|
|
972 |
|
|
C o Consistent? |
973 |
|
|
IF ( startTime .NE. baseTime+deltaTClock*float(nIter0) ) THEN |
974 |
|
|
WRITE(msgBuf,'(A)') |
975 |
|
|
& 'S/R INI_PARMS: startTime, baseTime and nIter0 are inconsistent' |
976 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
977 |
|
|
WRITE(msgBuf,'(A)') |
978 |
|
|
& 'S/R INI_PARMS: Perhaps more than two were set at once' |
979 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
980 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
981 |
|
|
ENDIF |
982 |
|
|
IF ( nEndIter .NE. nIter0+nTimeSteps ) THEN |
983 |
|
|
WRITE(msgBuf,'(A)') |
984 |
|
|
& 'S/R INI_PARMS: nIter0, nTimeSteps and nEndIter are inconsistent' |
985 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
986 |
|
|
WRITE(msgBuf,'(A)') |
987 |
|
|
& 'S/R INI_PARMS: Perhaps more than two were set at once' |
988 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
989 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
990 |
|
|
ENDIF |
991 |
|
|
IF ( nTimeSteps .NE. NINT((endTime-startTime)/deltaTClock) |
992 |
|
|
& ) THEN |
993 |
|
|
WRITE(msgBuf,'(A)') |
994 |
|
|
& 'S/R INI_PARMS: both endTime and nTimeSteps have been set' |
995 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
996 |
|
|
WRITE(msgBuf,'(A)') |
997 |
|
|
& 'S/R INI_PARMS: but are inconsistent' |
998 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
999 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1000 |
|
|
ENDIF |
1001 |
|
|
|
1002 |
|
|
C o Monitor (should also add CPP flag for monitor?) |
1003 |
|
|
IF (monitorFreq.LT.0.) THEN |
1004 |
|
|
monitorFreq=0. |
1005 |
|
|
IF (dumpFreq.NE.0.) monitorFreq=dumpFreq |
1006 |
|
|
IF (diagFreq.NE.0..AND.diagFreq.LT.monitorFreq) |
1007 |
|
|
& monitorFreq=diagFreq |
1008 |
|
|
IF (taveFreq.NE.0..AND.taveFreq.LT.monitorFreq) |
1009 |
|
|
& monitorFreq=taveFreq |
1010 |
|
|
IF (chkPtFreq.NE.0..AND.chkPtFreq.LT.monitorFreq) |
1011 |
|
|
& monitorFreq=chkPtFreq |
1012 |
|
|
IF (pChkPtFreq.NE.0..AND.pChkPtFreq.LT.monitorFreq) |
1013 |
|
|
& monitorFreq=pChkPtFreq |
1014 |
|
|
IF (monitorFreq.EQ.0.) monitorFreq=deltaTclock |
1015 |
|
|
ENDIF |
1016 |
|
|
IF ( monitorSelect.EQ.UNSET_I ) THEN |
1017 |
|
|
monitorSelect = 2 |
1018 |
|
|
IF ( fluidIsWater ) monitorSelect = 3 |
1019 |
|
|
ENDIF |
1020 |
|
|
|
1021 |
|
|
C-- Grid parameters |
1022 |
|
|
C In cartesian coords distances are in metres |
1023 |
|
|
DO k =1,Nr |
1024 |
|
|
delZ(k) = UNSET_RL |
1025 |
|
|
delP(k) = UNSET_RL |
1026 |
|
|
delR(k) = UNSET_RL |
1027 |
|
|
ENDDO |
1028 |
|
|
C In spherical polar distances are in degrees |
1029 |
|
|
dxSpacing = UNSET_RL |
1030 |
|
|
dySpacing = UNSET_RL |
1031 |
|
|
WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM04' |
1032 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
1033 |
|
|
& SQUEEZE_RIGHT, myThid ) |
1034 |
|
|
READ(UNIT=iUnit,NML=PARM04,IOSTAT=errIO) |
1035 |
|
|
IF ( errIO .LT. 0 ) THEN |
1036 |
|
|
WRITE(msgBuf,'(A)') |
1037 |
|
|
& 'S/R INI_PARMS' |
1038 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1039 |
|
|
WRITE(msgBuf,'(A)') |
1040 |
|
|
& 'Error reading numerical model ' |
1041 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1042 |
|
|
WRITE(msgBuf,'(A)') |
1043 |
|
|
& 'parameter file "data"' |
1044 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1045 |
|
|
WRITE(msgBuf,'(A)') |
1046 |
|
|
& 'Problem in namelist PARM04' |
1047 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1048 |
|
|
CALL MODELDATA_EXAMPLE( myThid ) |
1049 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1050 |
|
|
ELSE |
1051 |
|
|
WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM04 : OK' |
1052 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
1053 |
|
|
& SQUEEZE_RIGHT, myThid ) |
1054 |
|
|
ENDIF |
1055 |
|
|
|
1056 |
|
|
C Check for retired parameters still being used |
1057 |
|
|
IF ( rkFac .NE. UNSET_RL ) THEN |
1058 |
|
|
nRetired = nRetired+1 |
1059 |
|
|
WRITE(msgBuf,'(A,A)') |
1060 |
|
|
& 'S/R INI_PARMS: "rkFac" has been replaced by -rkSign ', |
1061 |
|
|
& ' and is no longer allowed in file "data".' |
1062 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1063 |
|
|
ENDIF |
1064 |
|
|
IF ( groundAtK1 ) THEN |
1065 |
|
|
c nRetired = nRetired+1 |
1066 |
|
|
WRITE(msgBuf,'(A,A)') |
1067 |
|
|
& 'S/R INI_PARMS: "groundAtK1" is set according to vertical ', |
1068 |
|
|
& ' coordinate and is no longer allowed in file "data".' |
1069 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1070 |
|
|
ENDIF |
1071 |
|
|
IF ( thetaMin .NE. UNSET_RL ) THEN |
1072 |
|
|
nRetired = nRetired+1 |
1073 |
|
|
WRITE(msgBuf,'(A,A)') |
1074 |
|
|
& 'S/R INI_PARMS: "thetaMin" no longer allowed,', |
1075 |
|
|
& ' has been replaced by "xgOrigin"' |
1076 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1077 |
|
|
ENDIF |
1078 |
|
|
IF ( phiMin .NE. UNSET_RL ) THEN |
1079 |
|
|
nRetired = nRetired+1 |
1080 |
|
|
WRITE(msgBuf,'(A,A)') |
1081 |
|
|
& 'S/R INI_PARMS: "phiMin" no longer allowed,', |
1082 |
|
|
& ' has been replaced by "ygOrigin"' |
1083 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1084 |
|
|
ENDIF |
1085 |
|
|
|
1086 |
|
|
C X coordinate : Check for multiple definitions |
1087 |
|
|
goptCount = 0 |
1088 |
|
|
IF ( delX(1) .NE. UNSET_RL ) goptCount = goptCount + 1 |
1089 |
|
|
IF ( dxSpacing .NE. UNSET_RL ) goptCount = goptCount + 1 |
1090 |
|
|
IF ( delXFile .NE. ' ' ) goptCount = goptCount + 1 |
1091 |
|
|
IF ( goptCount.GT.1 ) THEN |
1092 |
|
|
WRITE(msgBuf,'(A,A)') 'Too many specifications for delX:', |
1093 |
|
|
& 'Specify only one of delX, dxSpacing or delXfile' |
1094 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1095 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1096 |
|
|
ENDIF |
1097 |
|
|
IF ( dxSpacing .NE. UNSET_RL ) THEN |
1098 |
|
|
DO i=1,Nx |
1099 |
|
|
delX(i) = dxSpacing |
1100 |
|
|
ENDDO |
1101 |
|
|
ENDIF |
1102 |
|
|
C Y coordinate : Check for multiple definitions |
1103 |
|
|
goptCount = 0 |
1104 |
|
|
IF ( delY(1) .NE. UNSET_RL ) goptCount = goptCount + 1 |
1105 |
|
|
IF ( dySpacing .NE. UNSET_RL ) goptCount = goptCount + 1 |
1106 |
|
|
IF ( delYFile .NE. ' ' ) goptCount = goptCount + 1 |
1107 |
|
|
IF ( goptCount.GT.1 ) THEN |
1108 |
|
|
WRITE(msgBuf,'(A,A)') 'Too many specifications for delY:', |
1109 |
|
|
& 'Specify only one of delY, dySpacing or delYfile' |
1110 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1111 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1112 |
|
|
ENDIF |
1113 |
|
|
IF ( dySpacing .NE. UNSET_RL ) THEN |
1114 |
|
|
DO j=1,Ny |
1115 |
|
|
delY(j) = dySpacing |
1116 |
|
|
ENDDO |
1117 |
|
|
ENDIF |
1118 |
|
|
C |
1119 |
|
|
IF ( rSphere .NE. 0. ) THEN |
1120 |
|
|
recip_rSphere = 1. _d 0/rSphere |
1121 |
|
|
ELSE |
1122 |
|
|
recip_rSphere = 0. |
1123 |
|
|
ENDIF |
1124 |
|
|
C-- Check for conflicting grid definitions. |
1125 |
|
|
goptCount = 0 |
1126 |
|
|
IF ( usingCartesianGrid ) goptCount = goptCount+1 |
1127 |
|
|
IF ( usingSphericalPolarGrid ) goptCount = goptCount+1 |
1128 |
|
|
IF ( usingCurvilinearGrid ) goptCount = goptCount+1 |
1129 |
|
|
IF ( usingCylindricalGrid ) goptCount = goptCount+1 |
1130 |
|
|
IF ( goptCount .GT. 1 ) THEN |
1131 |
|
|
WRITE(msgBuf,'(A)') |
1132 |
|
|
& 'S/R INI_PARMS: More than one coordinate system requested' |
1133 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1134 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1135 |
|
|
ENDIF |
1136 |
|
|
IF ( goptCount .LT. 1 ) THEN |
1137 |
|
|
C- No horizontal grid is specified => use Cartesian grid as default: |
1138 |
|
|
WRITE(msgBuf,'(A)') |
1139 |
|
|
& 'S/R INI_PARMS: No horizontal grid requested' |
1140 |
|
|
CALL PRINT_MESSAGE( msgBuf, errorMessageUnit, |
1141 |
|
|
& SQUEEZE_RIGHT, myThid ) |
1142 |
|
|
WRITE(msgBuf,'(A)') |
1143 |
|
|
& 'S/R INI_PARMS: => Use Cartesian Grid as default' |
1144 |
|
|
CALL PRINT_MESSAGE( msgBuf, errorMessageUnit, |
1145 |
|
|
& SQUEEZE_RIGHT, myThid ) |
1146 |
|
|
usingCartesianGrid = .TRUE. |
1147 |
|
|
ENDIF |
1148 |
|
|
C-- Default origin for X & Y axis (longitude & latitude origin): |
1149 |
|
|
IF ( xgOrigin .EQ. UNSET_RL ) xgOrigin = 0. |
1150 |
|
|
IF ( ygOrigin .EQ. UNSET_RL ) THEN |
1151 |
|
|
IF ( usingSphericalPolarGrid ) THEN |
1152 |
|
|
ygOrigin = 0. |
1153 |
|
|
ELSEIF ( usingCartesianGrid ) THEN |
1154 |
|
|
ygOrigin = 0. |
1155 |
|
|
ELSEIF ( usingCylindricalGrid ) THEN |
1156 |
|
|
ygOrigin = 0. |
1157 |
|
|
ELSEIF ( usingCurvilinearGrid ) THEN |
1158 |
|
|
ygOrigin = 0. |
1159 |
|
|
ELSE |
1160 |
|
|
WRITE(msgBuf,'(A)') |
1161 |
|
|
& 'S/R INI_PARMS: found no coordinate system to set ygOrigin' |
1162 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1163 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1164 |
|
|
ENDIF |
1165 |
|
|
ENDIF |
1166 |
|
|
C-- Make metric term & Coriolis settings consistent with underlying grid. |
1167 |
|
|
IF ( usingCartesianGrid ) THEN |
1168 |
|
|
metricTerms = .FALSE. |
1169 |
|
|
useNHMTerms = .FALSE. |
1170 |
|
|
useBetaPlaneF = .TRUE. |
1171 |
|
|
ENDIF |
1172 |
|
|
IF ( usingCylindricalGrid ) THEN |
1173 |
|
|
useNHMTerms = .FALSE. |
1174 |
|
|
useBetaPlaneF = .TRUE. |
1175 |
|
|
WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; Cylinder OK' |
1176 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
1177 |
|
|
& SQUEEZE_RIGHT, myThid ) |
1178 |
|
|
ENDIF |
1179 |
|
|
IF ( usingCurvilinearGrid ) THEN |
1180 |
|
|
metricTerms = .FALSE. |
1181 |
|
|
ENDIF |
1182 |
|
|
IF ( useConstantF ) useBetaPlaneF = .FALSE. |
1183 |
|
|
IF ( useConstantF ) useSphereF = .FALSE. |
1184 |
|
|
IF ( useBetaPlaneF ) useSphereF = .FALSE. |
1185 |
|
|
IF ( usingCartesianGrid .OR. usingCylindricalGrid |
1186 |
|
|
& .OR. .NOT.(nonHydrostatic.OR.quasiHydrostatic) ) |
1187 |
|
|
& use3dCoriolis = .FALSE. |
1188 |
|
|
|
1189 |
|
|
C-- Grid rotation |
1190 |
|
|
IF ( phiEuler .NE. 0. _d 0 .OR. thetaEuler .NE. 0. _d 0 |
1191 |
|
|
& .OR. psiEuler .NE. 0. _d 0 ) rotateGrid = .TRUE. |
1192 |
|
|
|
1193 |
|
|
C-- Set default for latitude-band where relaxation to climatology applies |
1194 |
|
|
C note: done later (once domain size is known) if using CartesianGrid |
1195 |
|
|
IF ( latBandClimRelax .EQ. UNSET_RL) THEN |
1196 |
|
|
IF ( usingSphericalPolarGrid ) latBandClimRelax= 180. _d 0 |
1197 |
|
|
IF ( usingCurvilinearGrid ) latBandClimRelax= 180. _d 0 |
1198 |
|
|
ENDIF |
1199 |
|
|
C-- set cell Center depth and put Interface at the middle between 2 C |
1200 |
|
|
setCenterDr = .FALSE. |
1201 |
|
|
DO k=1,Nr+1 |
1202 |
|
|
IF ( delRc(k).EQ.UNSET_RL ) THEN |
1203 |
|
|
IF ( setCenterDr ) THEN |
1204 |
|
|
WRITE(msgBuf,'(A,I4)') |
1205 |
|
|
& 'S/R INI_PARMS: No value for delRc at k =', k |
1206 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1207 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1208 |
|
|
ENDIF |
1209 |
|
|
ELSE |
1210 |
|
|
IF ( k.EQ.1 ) setCenterDr = .TRUE. |
1211 |
|
|
IF ( .NOT.setCenterDr ) THEN |
1212 |
|
|
WRITE(msgBuf,'(A,I4)') |
1213 |
|
|
& 'S/R INI_PARMS: No value for delRc at k <', k |
1214 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1215 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1216 |
|
|
ENDIF |
1217 |
|
|
ENDIF |
1218 |
|
|
ENDDO |
1219 |
|
|
IF ( setCenterDr ) rCoordInputData = .TRUE. |
1220 |
|
|
C-- p, z, r coord parameters |
1221 |
|
|
setInterFDr = .FALSE. |
1222 |
|
|
DO k = 1, Nr |
1223 |
|
|
IF ( delZ(k) .NE. UNSET_RL ) zCoordInputData = .TRUE. |
1224 |
|
|
IF ( delP(k) .NE. UNSET_RL ) pCoordInputData = .TRUE. |
1225 |
|
|
IF ( delR(k) .NE. UNSET_RL ) rCoordInputData = .TRUE. |
1226 |
|
|
IF ( delR(k) .EQ. UNSET_RL ) delR(k) = delZ(k) |
1227 |
|
|
IF ( delR(k) .EQ. UNSET_RL ) delR(k) = delP(k) |
1228 |
|
|
IF ( delR(k) .EQ. UNSET_RL ) THEN |
1229 |
|
|
IF ( setInterFDr ) THEN |
1230 |
|
|
WRITE(msgBuf,'(A,I4)') |
1231 |
|
|
& 'S/R INI_PARMS: No value for delZ/delP/delR at k =', k |
1232 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1233 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1234 |
|
|
ENDIF |
1235 |
|
|
ELSE |
1236 |
|
|
IF ( k.EQ.1 ) setInterFDr = .TRUE. |
1237 |
|
|
IF ( .NOT.setInterFDr ) THEN |
1238 |
|
|
WRITE(msgBuf,'(A,I4)') |
1239 |
|
|
& 'S/R INI_PARMS: No value for delZ/delP/delR at k <', k |
1240 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1241 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1242 |
|
|
ENDIF |
1243 |
|
|
ENDIF |
1244 |
|
|
ENDDO |
1245 |
|
|
C Check for multiple coordinate systems |
1246 |
|
|
coordsSet = 0 |
1247 |
|
|
IF ( zCoordInputData ) coordsSet = coordsSet + 1 |
1248 |
|
|
IF ( pCoordInputData ) coordsSet = coordsSet + 1 |
1249 |
|
|
IF ( rCoordInputData ) coordsSet = coordsSet + 1 |
1250 |
|
|
IF ( coordsSet .GT. 1 ) THEN |
1251 |
|
|
WRITE(msgBuf,'(A)') |
1252 |
|
|
& 'S/R INI_PARMS: Cannot mix z, p and r in the input data.' |
1253 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1254 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1255 |
|
|
ENDIF |
1256 |
|
|
C- Check for double definition (file & namelist) |
1257 |
|
|
IF ( delRcFile.NE.' ' ) THEN |
1258 |
|
|
IF ( setCenterDr ) THEN |
1259 |
|
|
WRITE(msgBuf,'(A)') |
1260 |
|
|
& 'S/R INI_PARMS: Cannot set both delRc and delRcFile' |
1261 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1262 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1263 |
|
|
ENDIF |
1264 |
|
|
setCenterDr = .TRUE. |
1265 |
|
|
ENDIF |
1266 |
|
|
IF ( delRFile.NE.' ' ) THEN |
1267 |
|
|
IF ( setInterFDr ) THEN |
1268 |
|
|
WRITE(msgBuf,'(A)') |
1269 |
|
|
& 'S/R INI_PARMS: Cannot set both delR and delRFile' |
1270 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1271 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1272 |
|
|
ENDIF |
1273 |
|
|
setInterFDr = .TRUE. |
1274 |
|
|
ENDIF |
1275 |
|
|
c IF ( setInterFDr .AND. setCenterDr ) THEN |
1276 |
|
|
c WRITE(msgBuf,'(2A)') 'S/R INI_PARMS:', |
1277 |
|
|
c & ' Cannot specify both delRc and delZ/delP/delR' |
1278 |
|
|
c CALL PRINT_ERROR( msgBuf, myThid ) |
1279 |
|
|
c STOP 'ABNORMAL END: S/R INI_PARMS' |
1280 |
|
|
c ENDIF |
1281 |
|
|
|
1282 |
|
|
C-- Input files |
1283 |
|
|
WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; starts to read PARM05' |
1284 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
1285 |
|
|
& SQUEEZE_RIGHT, myThid ) |
1286 |
|
|
READ(UNIT=iUnit,NML=PARM05) !,IOSTAT=errIO) |
1287 |
|
|
IF ( errIO .LT. 0 ) THEN |
1288 |
|
|
WRITE(msgBuf,'(A)') |
1289 |
|
|
& 'Error reading numerical model ' |
1290 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1291 |
|
|
WRITE(msgBuf,'(A)') |
1292 |
|
|
& 'parameter file "data"' |
1293 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1294 |
|
|
WRITE(msgBuf,'(A)') |
1295 |
|
|
& 'Problem in namelist PARM05' |
1296 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1297 |
|
|
CALL MODELDATA_EXAMPLE( myThid ) |
1298 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1299 |
|
|
ELSE |
1300 |
|
|
WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM05 : OK' |
1301 |
|
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
1302 |
|
|
& SQUEEZE_RIGHT, myThid ) |
1303 |
|
|
ENDIF |
1304 |
|
|
C Check for retired parameters still being used |
1305 |
|
|
IF ( shelfIceFile .NE. ' ' ) THEN |
1306 |
|
|
nRetired = nRetired+1 |
1307 |
|
|
WRITE(msgBuf,'(A,A)') |
1308 |
|
|
& 'S/R INI_PARMS: "shelfIceFile" is not allowed in "data", ', |
1309 |
|
|
& 'substitute "SHELFICEtopoFile" in data.shelfice' |
1310 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1311 |
|
|
ENDIF |
1312 |
|
|
|
1313 |
|
|
C-- Set Units conversion factor required to incorporate |
1314 |
|
|
C surface forcing into z-p isomorphic equations: |
1315 |
|
|
C mass2rUnit: from mass per unit area [kg/m2] to r-coordinate (z:=1/rho;p:=g) |
1316 |
|
|
C rUnit2mass: from r-coordinate to mass per unit area [kg/m2] (z:=rho;p:=1/g) |
1317 |
|
|
IF ( usingPCoords ) THEN |
1318 |
|
|
mass2rUnit = gravity |
1319 |
|
|
rUnit2mass = recip_gravity |
1320 |
|
|
ELSE |
1321 |
|
|
mass2rUnit = recip_rhoConst |
1322 |
|
|
rUnit2mass = rhoConst |
1323 |
|
|
ENDIF |
1324 |
|
|
|
1325 |
|
|
c-- gradually replacing debugMode by debugLevel |
1326 |
|
|
IF ( debugMode ) debugLevel = debLevB |
1327 |
|
|
IF ( debugLevel .GE. debLevB ) debugMode = .TRUE. |
1328 |
|
|
|
1329 |
|
|
c-- flag for approximate adjoint |
1330 |
|
|
IF ( inAdExact ) THEN |
1331 |
|
|
inAdTrue = .FALSE. |
1332 |
|
|
inAdFALSE = .FALSE. |
1333 |
|
|
ELSE |
1334 |
|
|
inAdTrue = .TRUE. |
1335 |
|
|
inAdFALSE = .FALSE. |
1336 |
|
|
ENDIF |
1337 |
|
|
C |
1338 |
|
|
CLOSE(iUnit) |
1339 |
|
|
|
1340 |
|
|
C-- Check whether any retired parameters were found. |
1341 |
|
|
C-- Stop if they were |
1342 |
|
|
IF ( nRetired .GT. 0 ) THEN |
1343 |
|
|
WRITE(msgBuf,'(A)') |
1344 |
|
|
& 'Error reading parameter file "data"' |
1345 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1346 |
|
|
WRITE(msgBuf,'(A)') |
1347 |
|
|
& 'some out of date parameters were found in the namelist' |
1348 |
|
|
CALL PRINT_ERROR( msgBuf, myThid ) |
1349 |
|
|
STOP 'ABNORMAL END: S/R INI_PARMS' |
1350 |
|
|
ENDIF |
1351 |
|
|
|
1352 |
|
|
CcnhSigmaTestingBegin |
1353 |
|
|
CALL SIGMA_TESTING_READPARMS( myThid ) |
1354 |
|
|
CcnhSigmaTestingEnd |
1355 |
|
|
|
1356 |
|
|
_END_MASTER(myThid) |
1357 |
|
|
|
1358 |
|
|
C-- Everyone else must wait for the parameters to be loaded |
1359 |
|
|
_BARRIER |
1360 |
|
|
C |
1361 |
|
|
RETURN |
1362 |
|
|
END |