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

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

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


Revision 1.91 - (hide annotations) (download)
Tue Feb 18 05:33:54 2003 UTC (21 years, 3 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint48f_post
Changes since 1.90: +2 -2 lines
Merging from release1_p12:
o Modifications for using pkg/exf with pkg/seaice
  - improved description of the various forcing configurations
  - added basic radiation bulk formulae to pkg/exf
  - units/sign fix for evap computation in exf_getffields.F
  - updated verification/global_with_exf/results/output.txt
o Added pkg/sbo for computing IERS Special Bureau for the Oceans
  (SBO) core products, including oceanic mass, center-of-mass,
  angular, and bottom pressure (see pkg/sbo/README.sbo).
o Lower bound for viscosity/diffusivity in pkg/kpp/kpp_routines.F
  to avoid negative values in shallow regions.
  - updated verification/natl_box/results/output.txt
  - updated verification/lab_sea/results/output.txt
o MPI gather, scatter: eesupp/src/gather_2d.F and scatter_2d.F
o Added useSingleCpuIO option (see PARAMS.h).
o Updated useSingleCpuIO option in mdsio_writefield.F to
  work with multi-field files, e.g., for single-file pickup.
o pkg/seaice:
  - bug fix in growth.F: QNET for no shortwave case
  - added HeffFile for specifying initial sea-ice thickness
  - changed SEAICE_EXTERNAL_FLUXES wind stress implementation
o Added missing /* */ to CPP comments in pkg/seaice, pkg/exf,
  kpp_transport_t.F, forward_step.F, and the_main_loop.F
o pkg/seaice:
  - adjoint-friendly modifications
  - added a SEAICE_WRITE_PICKUP at end of the_model_main.F

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

  ViewVC Help
Powered by ViewVC 1.1.22