/[MITgcm]/MITgcm/model/src/ini_parms.F
ViewVC logotype

Contents of /MITgcm/model/src/ini_parms.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.100 - (show annotations) (download)
Wed Oct 29 00:19:22 2003 UTC (20 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52, checkpoint51t_post, checkpoint51s_post, checkpoint51q_post, checkpoint51r_post, checkpoint52a_pre, ecco_c52_e35, checkpoint51p_post, checkpoint51u_post
Branch point for: branch-nonh
Changes since 1.99: +26 -1 lines
delp,delz viscAz,viscAp ... are only local variables (and no longer in
 a common bloc).

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

  ViewVC Help
Powered by ViewVC 1.1.22