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

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

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

revision 1.27 by cnh, Mon Aug 24 02:25:01 1998 UTC revision 1.57 by heimbach, Sun Mar 25 22:33:52 2001 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5    
# Line 14  C     | A production version needs to ha Line 15  C     | A production version needs to ha
15  C     | external file and possibly reading in some initial field |  C     | external file and possibly reading in some initial field |
16  C     | values.                                                  |  C     | values.                                                  |
17  C     \==========================================================/  C     \==========================================================/
18          IMPLICIT NONE
19    
20  C     === Global variables ===  C     === Global variables ===
21  #include "SIZE.h"  #include "SIZE.h"
22  #include "EEPARAMS.h"  #include "EEPARAMS.h"
23  #include "PARAMS.h"  #include "PARAMS.h"
24  #include "CG2D.h"  #include "GRID.h"
25    
26  C     === Routine arguments ===  C     === Routine arguments ===
27  C     myThid - Number of this instance of INI_PARMS  C     myThid - Number of this instance of INI_PARMS
# Line 37  C     errIO     - IO error flag Line 39  C     errIO     - IO error flag
39  C     iUnit - Work variable for IO unit number  C     iUnit - Work variable for IO unit number
40  C     record - Work variable for IO buffer  C     record - Work variable for IO buffer
41  C     K, I, J - Loop counters  C     K, I, J - Loop counters
42        REAL dxSpacing  C     xxxDefault - Default value for variable xxx
43        REAL dySpacing        _RL  dxSpacing
44          _RL  dySpacing
45          CHARACTER*(MAX_LEN_FNAM) delXfile
46          CHARACTER*(MAX_LEN_FNAM) delYfile
47        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
48        CHARACTER*(MAX_LEN_PREC) record        CHARACTER*(MAX_LEN_PREC) record
49        INTEGER goptCount        INTEGER goptCount
# Line 48  C     K, I, J - Loop counters Line 53  C     K, I, J - Loop counters
53        EXTERNAL IFNBLNK        EXTERNAL IFNBLNK
54        INTEGER  ILNBLNK        INTEGER  ILNBLNK
55        EXTERNAL ILNBLNK        EXTERNAL ILNBLNK
56    C     Default values for variables which have vertical coordinate system
57    C     dependency.
58          _RL viscArDefault
59          _RL diffKrTDefault
60          _RL diffKrSDefault
61          _RL hFacMinDrDefault
62          _RL delRDefault(Nr)
63          _RS rkFacDefault
64    C     zCoordInputData - These are used to select between different coordinate systems.
65    C     pCoordInputData   The vertical coordinate system in the rest of the model is
66    C     rCoordInputData   written in terms of r. In the model "data" file input data can
67    C     coordsSet         be interms of z, p or r.
68    C                       e.g. delZ or delP or delR for the vertical grid spacing.
69    C                       The following rules apply:
70    C                       All parameters must use the same vertical coordinate system.
71    C                       e.g. delZ and viscAz is legal but
72    C                            delZ and viscAr is an error.
73    C                       Similarly specifyinh delZ and delP is an error.
74    C                       zCoord..., pCoord..., rCoord... are used to flag when z, p or r are
75    C                       used. coordsSet counts how many vertical coordinate systems have been
76    C                       used to specify variables. coordsSet > 1 is an error.
77    C
78          LOGICAL zCoordInputData
79          LOGICAL pCoordInputData
80          LOGICAL rCoordInputData
81          INTEGER coordsSet
82    
83  C--   Continuous equation parameters  C--   Continuous equation parameters
84        NAMELIST /PARM01/        NAMELIST /PARM01/
85       & gravity, gBaro, rhonil, tAlpha, sBeta, f0, beta,       & gravity, gBaro, rhonil, tAlpha, sBeta, f0, beta,
86       &   viscAh,  viscAz,  viscA4,       & viscAh,  viscAz,  viscA4, cosPower,
87       &  diffKhT, diffKzT, diffK4T,       & diffKhT, diffKzT, diffK4T,
88       &  diffKhS, diffKzS, diffK4S,       & diffKhS, diffKzS, diffK4S,
89       &  GMmaxslope,GMlength,GMalpha,GMdepth,GMkbackground,GMmaxval,       & tRef, sRef, eosType,
90       &  tRef, sRef, eosType,       & no_slip_sides,no_slip_bottom,
91       & momViscosity,  momAdvection, momForcing, useCoriolis,       & momViscosity,  momAdvection, momForcing, useCoriolis,
92       & momPressureForcing, metricTerms,       & momPressureForcing, metricTerms,
93       & tempDiffusion, tempAdvection, tempForcing,       & tempDiffusion, tempAdvection, tempForcing,
94       & saltDiffusion, saltAdvection, saltForcing,       & saltDiffusion, saltAdvection, saltForcing,
95         & implicSurfPress, implicDiv2DFlow,
96       & implicitFreeSurface, rigidLid, freeSurfFac, hFacMin, hFacMinDz,       & implicitFreeSurface, rigidLid, freeSurfFac, hFacMin, hFacMinDz,
97       & tempStepping, saltStepping, momStepping, implicitDiffusion,       & staggerTimeStep,
98         & tempStepping, saltStepping, momStepping,
99         & implicitDiffusion, implicitViscosity,
100       & viscAr, diffKrT, diffKrS, hFacMinDr,       & viscAr, diffKrT, diffKrS, hFacMinDr,
101       & rhoConst       & viscAp, diffKpT, diffKpS, hFacMinDp,
102         & rhoConst, buoyancyRelation, HeatCapacity_Cp,
103         & writeBinaryPrec, readBinaryPrec, writeStatePrec,
104         & nonHydrostatic, globalFiles,
105         & allowFreezing, ivdc_kappa,
106         & nShap, zonal_filt_lat, zonal_filt_sinpow, zonal_filt_cospow,
107         & bottomDragLinear,bottomDragQuadratic
108    
109  C--   Elliptic solver parameters  C--   Elliptic solver parameters
110        NAMELIST /PARM02/        NAMELIST /PARM02/
111       & cg2dMaxIters, cg2dChkResFreq, cg2dTargetResidual, cg2dpcOffDFac       & cg2dMaxIters, cg2dChkResFreq, cg2dTargetResidual, cg2dpcOffDFac,
112         & cg3dMaxIters, cg3dChkResFreq, cg3dTargetResidual
113    
114  C--   Time stepping parammeters  C--   Time stepping parammeters
115        NAMELIST /PARM03/        NAMELIST /PARM03/
116       & nIter0, nTimeSteps, deltaT, deltaTmom, deltaTtracer, abEps, tauCD, rCD,       & nIter0, nTimeSteps, nEndIter, deltaT, deltaTmom, deltaTtracer,
117         & abEps, tauCD, rCD,
118       & startTime, endTime, chkPtFreq, dumpFreq, taveFreq, deltaTClock,       & startTime, endTime, chkPtFreq, dumpFreq, taveFreq, deltaTClock,
119       & pChkPtFreq, cAdjFreq, tauThetaClimRelax, tauSaltClimRelax,       & pChkPtFreq, cAdjFreq, tauThetaClimRelax, tauSaltClimRelax,
120       & periodicExternalForcing, externForcingPeriod, externForcingCycle       & periodicExternalForcing, externForcingPeriod, externForcingCycle
121    
122  C--   Gridding parameters  C--   Gridding parameters
123        NAMELIST /PARM04/        NAMELIST /PARM04/
124       & usingCartesianGrid, delZ, dxSpacing, dySpacing, delX, delY,       & usingCartesianGrid, dxSpacing, dySpacing, delX, delY, delZ,
125       & usingSphericalPolarGrid, phiMin, thetaMin, rSphere,       & usingSphericalPolarGrid, phiMin, thetaMin, rSphere,
126       & l, m, n       & delP, delR, rkFac, Ro_SeaLevel, groundAtK1,
127         & delXfile, delYfile
128    
129  C--   Input files  C--   Input files
130        NAMELIST /PARM05/        NAMELIST /PARM05/
131       & bathyFile, hydrogThetaFile, hydrogSaltFile,       & bathyFile, hydrogThetaFile, hydrogSaltFile,
132       & zonalWindFile, meridWindFile, thetaClimFile,       & zonalWindFile, meridWindFile,
133       & saltClimFile       & thetaClimFile, saltClimFile,
134         & surfQfile, EmPmRfile, surfQswfile,
135         & uVelInitFile, vVelInitFile, pSurfInitFile,
136         & dQdTFile
137    
138  C  C
139        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
140    
141    C     Defaults values for input parameters
142          CALL SET_DEFAULTS(
143         O   viscArDefault, diffKrTDefault, diffKrSDefault,
144         O   hFacMinDrDefault, delRdefault, rkFacDefault,
145         I   myThid )
146    
147    C--   Initialise "which vertical coordinate system used" flags.
148          zCoordInputData = .FALSE.
149          pCoordInputData = .FALSE.
150          rCoordInputData = .FALSE.
151          usingPCoords    = .FALSE.
152          usingZCoords    = .FALSE.
153          coordsSet       = 0
154    
155  C--   Open the parameter file  C--   Open the parameter file
156        OPEN(UNIT=scrUnit1,STATUS='SCRATCH')        OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
157        OPEN(UNIT=scrUnit2,STATUS='SCRATCH')        OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
158        OPEN(UNIT=modelDataUnit,FILE='data',STATUS='OLD',err=1,IOSTAT=errIO)        OPEN(UNIT=modelDataUnit,FILE='data',STATUS='OLD',
159        IF ( errIO .GE. 0 ) GOTO 2       &     IOSTAT=errIO)
160      1 CONTINUE        IF ( errIO .LT. 0 ) THEN
161         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
162       &  'S/R INI_PARMS'       &  'S/R INI_PARMS'
163         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
# Line 109  C--   Open the parameter file Line 169  C--   Open the parameter file
169         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
170         CALL MODELDATA_EXAMPLE( myThid )         CALL MODELDATA_EXAMPLE( myThid )
171         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
172      2 CONTINUE        ENDIF    
173    
174   1000 CONTINUE        DO WHILE ( .TRUE. )
175        READ(modelDataUnit,FMT='(A)',END=1001) RECORD         READ(modelDataUnit,FMT='(A)',END=1001) RECORD
176        IL = MAX(ILNBLNK(RECORD),1)         IL = MAX(ILNBLNK(RECORD),1)
177        IF ( RECORD(1:1) .NE. commentCharacter )         IF ( RECORD(1:1) .NE. commentCharacter )
178       &    WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)       &     WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
179         WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)          WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
180        GOTO 1000        ENDDO
181   1001 CONTINUE   1001 CONTINUE
182        CLOSE(modelDataUnit)        CLOSE(modelDataUnit)
183    
184  C--   Report contents of model parameter file  C--   Report contents of model parameter file
185        WRITE(msgBuf,'(A)')        WRITE(msgBuf,'(A)')
186       &'// ======================================================='       &'// ======================================================='
187        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
188         &                    SQUEEZE_RIGHT , 1)
189        WRITE(msgBuf,'(A)') '// Model parameter file "data"'        WRITE(msgBuf,'(A)') '// Model parameter file "data"'
190        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
191         &                    SQUEEZE_RIGHT , 1)
192        WRITE(msgBuf,'(A)')        WRITE(msgBuf,'(A)')
193       &'// ======================================================='       &'// ======================================================='
194        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
195       &  SQUEEZE_RIGHT , 1)       &  SQUEEZE_RIGHT , 1)
196        iUnit = scrUnit2        iUnit = scrUnit2
197        REWIND(iUnit)        REWIND(iUnit)
198   2000 CONTINUE        DO WHILE ( .TRUE. )
199         READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD         READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
200         IL = MAX(ILNBLNK(RECORD),1)         IL = MAX(ILNBLNK(RECORD),1)
201         WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)         WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
202         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
203        GOTO 2000       &                    SQUEEZE_RIGHT , 1)
204          ENDDO
205   2001 CONTINUE   2001 CONTINUE
206        CLOSE(iUnit)        CLOSE(iUnit)
207        WRITE(msgBuf,'(A)') ' '        WRITE(msgBuf,'(A)') ' '
# Line 151  C--   Read settings from model parameter Line 214  C--   Read settings from model parameter
214        REWIND(iUnit)        REWIND(iUnit)
215    
216  C--   Set default "physical" parameters  C--   Set default "physical" parameters
217        DO K =1,Nr        viscAz   = UNSET_RL    
218         tRef(K) = 30.D0 - FLOAT(K)        viscAr   = UNSET_RL
219        ENDDO        viscAp   = UNSET_RL
220        gravity =   9.81 D0        diffKzT  = UNSET_RL
221        gBaro   = gravity        diffKpT  = UNSET_RL
222        rhoNil   = 999.8 D0        diffKrT  = UNSET_RL
223        rhoConst = 999.8 D0        diffKzS  = UNSET_RL
224        f0     = 1.D-4        diffKpS  = UNSET_RL
225        beta   = 1. _d -11        diffKrS  = UNSET_RL
226        viscAh = 1.d3        gBaro    = UNSET_RL
227        diffKhT= 1.0d3        rhoConst = UNSET_RL
228        diffKhS= 1.0d3        hFacMinDr           = UNSET_RL
229        viscAr = 1.d-3        hFacMinDz           = UNSET_RL
230        diffKrT= 1.d-5        hFacMinDp           = UNSET_RL
231        diffKrS= 1.d-5        READ(UNIT=iUnit,NML=PARM01) !,IOSTAT=errIO)
232        viscA4 = 0.        IF ( errIO .LT. 0 ) THEN
       diffK4T= 0.  
       diffK4S= 0.  
       GMmaxslope   = 1.d-2  
       GMlength     = 200.d3  
       GMalpha      = 0.  
       GMdepth      = 1000.  
       GMkbackground= 0.  
       GMmaxval     = 2500.d0  
       tAlpha=2.d-4  
       sBeta=7.4d-4  
       eosType='LINEAR'  
       buoyancyRelation='OCEANIC'  
       implicitFreeSurface = .TRUE.  
       rigidLid            = .FALSE.  
       freeSurfFac         = 1. _d 0  
       hFacMin             = 0. _d 0  
       hFacMinDr           = 0. _d 0  
       momViscosity        = .TRUE.  
       momAdvection        = .TRUE.  
       momForcing          = .TRUE.  
       useCoriolis         = .TRUE.  
       momPressureForcing  = .TRUE.  
       momStepping         = .TRUE.  
       tempStepping        = .TRUE.  
       saltStepping        = .TRUE.  
       metricTerms         = .TRUE.  
       implicitDiffusion   = .FALSE.  
       READ(UNIT=iUnit,NML=PARM01,IOSTAT=errIO,err=3)  
       IF ( errIO .GE. 0 ) GOTO 4  
     3 CONTINUE  
233         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
234       &  'S/R INI_PARMS'       &  'S/R INI_PARMS'
235         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
# Line 211  C--   Set default "physical" parameters Line 244  C--   Set default "physical" parameters
244         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
245         CALL MODELDATA_EXAMPLE( myThid )         CALL MODELDATA_EXAMPLE( myThid )
246         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
247     4  CONTINUE        ENDIF
248        IF ( implicitFreeSurface ) freeSurfFac = 1. _d 0        IF ( implicitFreeSurface ) freeSurfFac = 1.D0
249        IF ( rigidLid            ) freeSurfFac = 0. _d 0        IF ( rigidLid            ) freeSurfFac = 0.D0
250          IF ( gBaro .EQ. UNSET_RL ) gBaro=gravity
251          IF ( rhoConst .EQ. UNSET_RL ) rhoConst=rhoNil
252    C--   Momentum viscosity on/off flag.
253        IF ( momViscosity        ) THEN        IF ( momViscosity        ) THEN
254         vfFacMom = 1. _d 0         vfFacMom = 1.D0
255        ELSE        ELSE
256         vfFacMom = 0. _d 0         vfFacMom = 0.D0
257        ENDIF        ENDIF
258    C--   Momentum advection on/off flag.
259        IF ( momAdvection        ) THEN        IF ( momAdvection        ) THEN
260         afFacMom = 1. _d 0         afFacMom = 1.D0
261        ELSE        ELSE
262         afFacMom = 0. _d 0         afFacMom = 0.D0
263        ENDIF        ENDIF
264    C--   Momentum forcing on/off flag.
265        IF ( momForcing ) THEN        IF ( momForcing ) THEN
266         foFacMom = 1. _d 0         foFacMom = 1.D0
267        ELSE        ELSE
268         foFacMom = 0. _d 0         foFacMom = 0.D0
269        ENDIF        ENDIF
270    C--   Coriolis term on/off flag.
271        IF ( useCoriolis ) THEN        IF ( useCoriolis ) THEN
272         cfFacMom = 1. _d 0         cfFacMom = 1.D0
273        ELSE        ELSE
274         cfFacMom = 0. _d 0         cfFacMom = 0.D0
275        ENDIF        ENDIF
276    C--   Pressure term on/off flag.
277        IF ( momPressureForcing ) THEN        IF ( momPressureForcing ) THEN
278         pfFacMom = 1. _d 0         pfFacMom = 1.D0
279        ELSE        ELSE
280         pfFacMom = 0. _d 0         pfFacMom = 0.D0
281        ENDIF        ENDIF
282    C--   Metric terms on/off flag.
283        IF ( metricTerms ) THEN        IF ( metricTerms ) THEN
284         mTFacMom = 1. _d 0         mTFacMom = 1.D0
285        ELSE        ELSE
286         mTFacMom = 1. _d 0         mTFacMom = 0.D0
287          ENDIF
288    C--   z,p,r coord input switching.
289          IF ( viscAz .NE. UNSET_RL ) zCoordInputData = .TRUE.
290          IF ( viscAp .NE. UNSET_RL ) pCoordInputData = .TRUE.
291          IF ( viscAr .NE. UNSET_RL ) rCoordInputData = .TRUE.
292          IF ( viscAr .EQ. UNSET_RL )          viscAr = viscAz
293          IF ( viscAr .EQ. UNSET_RL )          viscAr = viscAp
294          IF ( viscAr .EQ. UNSET_RL )          viscAr = viscArDefault
295    
296          IF ( diffKzT .NE. UNSET_RL ) zCoordInputData  = .TRUE.
297          IF ( diffKpT .NE. UNSET_RL ) pCoordInputData  = .TRUE.
298          IF ( diffKrT .NE. UNSET_RL ) rCoordInputData  = .TRUE.
299          IF ( diffKrT .EQ. UNSET_RL )          diffKrT = diffKzT
300          IF ( diffKrT .EQ. UNSET_RL )          diffKrT = diffKpT
301          IF ( diffKrT .EQ. UNSET_RL )          diffKrT = diffKrTDefault
302    
303          IF ( diffKzS .NE. UNSET_RL ) zCoordInputData  = .TRUE.
304          IF ( diffKpS .NE. UNSET_RL ) pCoordInputData  = .TRUE.
305          IF ( diffKrS .NE. UNSET_RL ) rCoordInputData  = .TRUE.
306          IF ( diffKrS .EQ. UNSET_RL )          diffKrS = diffKzS
307          IF ( diffKrS .EQ. UNSET_RL )          diffKrS = diffKpS
308          IF ( diffKrS .EQ. UNSET_RL )          diffKrS = diffKrSDefault
309    
310          IF ( hFacMinDz .NE. UNSET_RL ) zCoordInputData = .TRUE.
311          IF ( hFacMinDp .NE. UNSET_RL ) pCoordInputData = .TRUE.
312          IF ( hFacMinDr .NE. UNSET_RL ) rCoordInputData = .TRUE.
313          IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr       = hFacMinDz
314          IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr       = hFacMinDp
315          IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr       = hFacMinDrDefault
316    
317          IF ( ivdc_kappa .NE. 0. .AND. .NOT. implicitDiffusion ) THEN
318           WRITE(msgBuf,'(A,A)')
319         &  'S/R INI_PARMS: To use ivdc_kappa you must enable implicit',
320         &  ' vertical diffusion.'
321           CALL PRINT_ERROR( msgBuf , myThid)
322           STOP 'ABNORMAL END: S/R INI_PARMS'
323        ENDIF        ENDIF
324    
325        IF ( implicitFreeSurface .AND.  rigidLid ) THEN        IF ( implicitFreeSurface .AND.  rigidLid ) THEN
326           WRITE(msgBuf,'(A,A)')
327         & 'S/R INI_PARMS: Cannot select both implicitFreeSurface',
328         & ' and rigidLid.'
329           CALL PRINT_ERROR( msgBuf , myThid)
330           STOP 'ABNORMAL END: S/R INI_PARMS'
331          ENDIF
332          IF ( (implicSurfPress.NE.1. .OR. implicDiv2DFlow.NE.1.)
333         &    .AND. nonHydrostatic ) THEN
334           WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: nonHydrostatic',
335         & ' NOT SAFE with non-fully implicit Barotropic solver'
336           CALL PRINT_ERROR( msgBuf , myThid)
337           WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: To by-pass this',
338         &    'STOP, comment this test and re-compile ini_params'
339           CALL PRINT_ERROR( msgBuf , myThid)
340           STOP 'ABNORMAL END: S/R INI_PARMS'
341          ENDIF
342    
343          coordsSet = 0
344          IF ( zCoordInputData ) coordsSet = coordsSet + 1
345          IF ( pCoordInputData ) coordsSet = coordsSet + 1
346          IF ( rCoordInputData ) coordsSet = coordsSet + 1
347          IF ( coordsSet .GT. 1 ) THEN
348         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
349       &  'S/R INI_PARMS: Cannot select implicitFreeSurface and rigidLid.'       &  'S/R INI_PARMS: Cannot mix z, p and r in the input data.'
350         CALL PRINT_ERROR( msgBuf , myThid)         CALL PRINT_ERROR( msgBuf , myThid)
351         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
352        ENDIF        ENDIF
353          IF ( rhoConst .LE. 0. ) THEN
354           WRITE(msgBuf,'(A)')
355         &  'S/R INI_PARMS: rhoConst must be greater than 0.'
356           CALL PRINT_ERROR( msgBuf , myThid)
357           STOP 'ABNORMAL END: S/R INI_PARMS'
358          ELSE
359           recip_rhoConst = 1.D0 / rhoConst
360          ENDIF
361          IF ( rhoNil .LE. 0. ) THEN
362           WRITE(msgBuf,'(A)')
363         &  'S/R INI_PARMS: rhoNil must be greater than 0.'
364           CALL PRINT_ERROR( msgBuf , myThid)
365           STOP 'ABNORMAL END: S/R INI_PARMS'
366          ELSE
367           recip_rhoNil = 1.D0 / rhoNil
368          ENDIF
369          IF ( HeatCapacity_Cp .LE. 0. ) THEN
370           WRITE(msgBuf,'(A)')
371         &  'S/R INI_PARMS: HeatCapacity_Cp must be greater than 0.'
372           CALL PRINT_ERROR( msgBuf , myThid)
373           STOP 'ABNORMAL END: S/R INI_PARMS'
374          ELSE
375           recip_Cp = 1.D0 / HeatCapacity_Cp
376          ENDIF
377          IF ( gravity .LE. 0. ) THEN
378           WRITE(msgBuf,'(A)')
379         &  'S/R INI_PARMS: gravity must be greater than 0.'
380           CALL PRINT_ERROR( msgBuf , myThid)
381           STOP 'ABNORMAL END: S/R INI_PARMS'
382          ELSE
383           recip_gravity = 1.D0 / gravity
384          ENDIF
385    C     Set globalFiles flag for READ_WRITE_FLD package
386          CALL SET_WRITE_GLOBAL_FLD( globalFiles )
387    C     Set globalFiles flag for READ_WRITE_REC package
388          CALL SET_WRITE_GLOBAL_REC( globalFiles )
389    C     Set globalFiles flag for READ_WRITE_REC package
390          CALL SET_WRITE_GLOBAL_PICKUP( globalFiles )
391    
392  C--   Elliptic solver parameters  C--   Elliptic solver parameters
393        cg2dMaxIters   = 150        READ(UNIT=iUnit,NML=PARM02) !,IOSTAT=errIO)
394        cg2dTargetResidual = 1. _d -7        IF ( errIO .LT. 0 ) THEN
       cg2dChkResFreq = 1  
       cg2dpcOffDFac  = 0.51 _d 0  
       READ(UNIT=iUnit,NML=PARM02,IOSTAT=errIO,err=5)  
       IF ( errIO .GE. 0 ) GOTO 6  
     5 CONTINUE  
395         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
396       &  'S/R INI_PARMS'       &  'S/R INI_PARMS'
397         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
# Line 274  C--   Elliptic solver parameters Line 406  C--   Elliptic solver parameters
406         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
407         CALL MODELDATA_EXAMPLE( myThid )         CALL MODELDATA_EXAMPLE( myThid )
408         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
409     6  CONTINUE        ENDIF    
410    
411  C--   Time stepping parameters  C--   Time stepping parameters
412        startTime      = 0.        rCD               = -1.D0
413        nTimeSteps     = 0        READ(UNIT=iUnit,NML=PARM03) !,IOSTAT=errIO)
414        endTime        = 0.        IF ( errIO .LT. 0 ) THEN
       nIter0         = 0  
       deltaT         = 0.  
       deltaTClock    = 0.  
       deltaTtracer   = 0.  
       deltaTMom      = 0.  
       abEps          = 0.01  
       pchkPtFreq     = 0.  
       chkPtFreq      = 3600.*25  
       dumpFreq       = 3600.*100  
       taveFreq       = 0.  
       writeStatePrec = precFloat32  
       nCheckLev      = 1  
       checkPtSuff(1) = 'ckptA'  
       checkPtSuff(2) = 'ckptB'  
       cAdjFreq       = -1. _d 0  
       rCD            = -1. _d 0  
       tauCD          = 0. _d 0  
       tauThetaClimRelax = 0. _d 0  
       doThetaClimRelax  = .FALSE.  
       tauSaltClimRelax  = 0. _d 0  
       doSaltClimRelax   = .FALSE.  
       periodicExternalForcing = .FALSE.  
       externForcingPeriod = 0.  
       externForcingCycle = 0.  
       READ(UNIT=iUnit,NML=PARM03,IOSTAT=errIO,err=7)  
       IF ( errIO .GE. 0 ) GOTO 8  
     7 CONTINUE  
415         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
416       &  'S/R INI_PARMS'       &  'S/R INI_PARMS'
417         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
# Line 321  C--   Time stepping parameters Line 426  C--   Time stepping parameters
426         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
427         CALL MODELDATA_EXAMPLE( myThid )         CALL MODELDATA_EXAMPLE( myThid )
428         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
429     8  CONTINUE        ENDIF  
430  C     Process "timestepping" params  C     Process "timestepping" params
431  C     o Time step size  C     o Time step size
432        IF ( deltaT       .EQ. 0. ) deltaT       = deltaTmom        IF ( deltaT       .EQ. 0. ) deltaT       = deltaTmom
# Line 360  C     o Convection frequency Line 465  C     o Convection frequency
465        IF ( cAdjFreq .LT. 0. ) THEN        IF ( cAdjFreq .LT. 0. ) THEN
466         cAdjFreq = deltaTClock         cAdjFreq = deltaTClock
467        ENDIF        ENDIF
468          IF ( ivdc_kappa .NE. 0. .AND. cAdjFreq .NE. 0. ) THEN
469           WRITE(msgBuf,'(A,A)')
470         &  'S/R INI_PARMS: You have enabled both ivdc_kappa and',
471         &  ' convective adjustment.'
472           CALL PRINT_ERROR( msgBuf , myThid)
473           STOP 'ABNORMAL END: S/R INI_PARMS'
474          ENDIF
475  C     o CD coupling  C     o CD coupling
476        IF ( tauCD .EQ. 0. _d 0 ) THEN        IF ( tauCD .EQ. 0.D0 ) THEN
477          tauCD = deltaTmom          tauCD = deltaTmom
478        ENDIF        ENDIF
479        IF ( rCD .LT. 0. ) THEN        IF ( rCD .LT. 0. ) THEN
480         rCD = 1. - deltaTMom/tauCD         rCD = 1. - deltaTMom/tauCD
481        ENDIF        ENDIF
482  C     o Temperature climatology relaxation time scale  C     o Temperature climatology relaxation time scale
483        IF ( tauThetaClimRelax .EQ. 0. _d 0 ) THEN        IF ( tauThetaClimRelax .EQ. 0.D0 ) THEN
484         doThetaClimRelax     = .FALSE.         doThetaClimRelax     = .FALSE.
485         lambdaThetaClimRelax = 0. _d 0         lambdaThetaClimRelax = 0.D0
486        ELSE        ELSE
487         doThetaClimRelax     = .TRUE.         doThetaClimRelax     = .TRUE.
488         lambdaThetaClimRelax = 1./tauThetaClimRelax         lambdaThetaClimRelax = 1./tauThetaClimRelax
489        ENDIF        ENDIF
490  C     o Salinity climatology relaxation time scale  C     o Salinity climatology relaxation time scale
491        IF ( tauSaltClimRelax .EQ. 0. _d 0 ) THEN        IF ( tauSaltClimRelax .EQ. 0.D0 ) THEN
492         doSaltClimRelax     = .FALSE.         doSaltClimRelax     = .FALSE.
493         lambdaSaltClimRelax = 0. _d 0         lambdaSaltClimRelax = 0.D0
494        ELSE        ELSE
495         doSaltClimRelax     = .TRUE.         doSaltClimRelax     = .TRUE.
496         lambdaSaltClimRelax = 1./tauSaltClimRelax         lambdaSaltClimRelax = 1./tauSaltClimRelax
497        ENDIF        ENDIF
498  C     o Time step count  
499        IF ( endTime .NE. 0 ) THEN  C     o Start time
500         IF ( deltaTClock .NE. 0 ) nTimeSteps =        IF ( nIter0 .NE. 0 .AND. startTime .EQ. 0. )
501       &  INT((endTime-startTime)/deltaTClock)       &   startTime = deltaTClock*float(nIter0)
502    C     o nIter0
503          IF ( nIter0 .EQ. 0 .AND. startTime .NE. 0. )
504         &   nIter0 = INT( startTime/deltaTClock )
505    
506    C     o nTimeSteps 1
507          IF ( nTimeSteps .EQ. 0 .AND. nEndIter .NE. 0 )
508         &     nTimeSteps = nEndIter-nIter0
509    C     o nTimeSteps 2
510          IF ( nTimeSteps .EQ. 0 .AND. endTime .NE. 0. )
511         &     nTimeSteps = int(0.5+(endTime-startTime)/deltaTclock)
512    C     o nEndIter 1
513          IF ( nEndIter .EQ. 0 .AND. nTimeSteps .NE. 0 )
514         &     nEndIter = nIter0+nTimeSteps
515    C     o nEndIter 2
516          IF ( nEndIter .EQ. 0 .AND. endTime .NE. 0. )
517         &     nEndIter = int(0.5+endTime/deltaTclock)
518    C     o End Time 1
519          IF ( endTime .EQ. 0. .AND. nTimeSteps .NE. 0 )
520         &     endTime = startTime + deltaTClock*float(nTimeSteps)
521    C     o End Time 2
522          IF ( endTime .EQ. 0. .AND. nEndIter .NE. 0 )
523         &     endTime = deltaTClock*float(nEndIter)
524    
525    C     o Consistent?
526          IF ( nEndIter .NE. nIter0+nTimeSteps ) THEN
527           WRITE(msgBuf,'(A)')
528         & 'S/R INI_PARMS: nIter0, nTimeSteps and nEndIter are inconsistent'
529           CALL PRINT_ERROR( msgBuf , 1)
530           WRITE(msgBuf,'(A)')
531         & 'S/R INI_PARMS: Perhaps more than two were set at once'
532           CALL PRINT_ERROR( msgBuf , 1)
533           STOP 'ABNORMAL END: S/R INI_PARMS'
534          ENDIF
535          IF ( nTimeSteps .NE. int(0.5+(endTime-startTime)/deltaTClock) )
536         & THEN
537            WRITE(msgBuf,'(A)')
538         &  'S/R INI_PARMS: both endTime and nTimeSteps have been set'
539            CALL PRINT_ERROR( msgBuf , 1)
540            WRITE(msgBuf,'(A)')
541         &  'S/R INI_PARMS: but are inconsistent'
542            CALL PRINT_ERROR( msgBuf , 1)
543            STOP 'ABNORMAL END: S/R INI_PARMS'
544        ENDIF        ENDIF
 C     o Finish time  
       IF ( endTime .EQ. 0. ) endTime = FLOAT(nTimeSteps)*deltaTClock  
545    
546  C     o If taveFreq is finite, then we must make sure the diagnostics  C     o If taveFreq is finite, then we must make sure the diagnostics
547  C       code is being compiled  C       code is being compiled
548  #ifndef ALLOW_DIAGNOSTICS  #ifndef ALLOW_TIMEAVE
549        IF (taveFreq.NE.0.) THEN        IF (taveFreq.NE.0.) THEN
550          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
551       &  'S/R INI_PARMS: taveFreq <> 0  but you have'       &  'S/R INI_PARMS: taveFreq <> 0  but you have'
# Line 401  C       code is being compiled Line 553  C       code is being compiled
553          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
554       &  'not compiled the model with the diagnostics routines.'       &  'not compiled the model with the diagnostics routines.'
555          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
556          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A,A)')
557       &  'Re-compile with:  #define ALLOW_DIAGNOSTICS  or  -DALLOW_DIAGNOSTICS'       &  'Re-compile with:  #define ALLOW_TIMEAVE',
558         &  '              or  -DALLOW_TIMEAVE'
559          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
560          STOP 'ABNORMAL END: S/R INI_PARMS'          STOP 'ABNORMAL END: S/R INI_PARMS'
561        ENDIF        ENDIF
# Line 410  C       code is being compiled Line 563  C       code is being compiled
563    
564  C--   Grid parameters  C--   Grid parameters
565  C     In cartesian coords distances are in metres  C     In cartesian coords distances are in metres
566        usingCartesianGrid = .TRUE.        rkFac = UNSET_RS
567        DO K =1,Nr        DO K =1,Nr
568         delZ(K) = 100. _d 0         delZ(K) = UNSET_RL
569        ENDDO         delP(K) = UNSET_RL
570        dxSpacing = 20. _d 0 * 1000. _d 0         delR(K) = UNSET_RL
       dySpacing = 20. _d 0 * 1000. _d 0  
       DO i=1,Nx  
        delX(i) = dxSpacing  
       ENDDO  
       DO j=1,Ny  
        delY(j) = dySpacing  
571        ENDDO        ENDDO
572  C     In spherical polar distances are in degrees  C     In spherical polar distances are in degrees
573        usingSphericalPolarGrid = .FALSE.        recip_rSphere  = 1.D0/rSphere
574        phiMin    = -5.0        dxSpacing = UNSET_RL
575        thetaMin  = 0.        dySpacing = UNSET_RL
576        rSphere   = 6370. * 1. _d 3        delXfile = ' '
577        recip_rSphere  = 1. _d 0/rSphere        delYfile = ' '
578        IF ( usingSphericalPolarGrid ) THEN        READ(UNIT=iUnit,NML=PARM04) !,IOSTAT=errIO)
579         dxSpacing = 1.        IF ( errIO .LT. 0 ) THEN
        dySpacing = 1.  
        DO I=1,Nx  
         delX(I) = dxSpacing  
        ENDDO  
        DO J=1,Ny  
         delY(J) = dySpacing  
        ENDDO  
       ENDIF  
   
       READ(UNIT=iUnit,NML=PARM04,IOSTAT=errIO,err=9)  
       IF ( errIO .GE. 0 ) GOTO 10  
     9 CONTINUE  
580         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
581       &  'S/R INI_PARMS'       &  'S/R INI_PARMS'
582         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
# Line 456  C     In spherical polar distances are i Line 591  C     In spherical polar distances are i
591         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
592         CALL MODELDATA_EXAMPLE( myThid )         CALL MODELDATA_EXAMPLE( myThid )
593         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
594    10  CONTINUE        ENDIF    
595    
596    C     X coordinate
597          IF ( delXfile .NE. ' ' ) THEN
598           IF ( delX(1) .NE. UNSET_RL .OR. dxSpacing .NE. UNSET_RL ) THEN
599             WRITE(msgBuf,'(A,A)') 'Too many specifications for delX:',
600         &   'Specify only one of delX, dxSpacing or delXfile'
601            CALL PRINT_ERROR( msgBuf , 1)
602            STOP 'ABNORMAL END: S/R INI_PARMS'
603           ELSE
604            _BEGIN_MASTER( myThid )
605            IF (readBinaryPrec.EQ.precFloat32) THEN
606             OPEN(37,FILE=delXfile,STATUS='OLD',FORM='UNFORMATTED',
607         &        ACCESS='DIRECT',RECL=WORDLENGTH*Nx)
608             READ(37,rec=1) delX
609    #ifdef _BYTESWAPIO
610                call MDS_BYTESWAPR4( Nx, delX )
611    #endif
612             CLOSE(37)
613            ELSEIF (readBinaryPrec.EQ.precFloat64) THEN
614             OPEN(37,FILE=delXfile,STATUS='OLD',FORM='UNFORMATTED',
615         &        ACCESS='DIRECT',RECL=WORDLENGTH*2*Nx)
616             READ(37,rec=1) delX
617    #ifdef _BYTESWAPIO
618                call MDS_BYTESWAPR8( Nx, delX )
619    #endif
620             CLOSE(37)
621            ENDIF
622            _END_MASTER(myThid)
623           ENDIF
624          ENDIF
625          IF ( dxSpacing .NE. UNSET_RL ) THEN
626           DO i=1,Nx
627            delX(i) = dxSpacing
628           ENDDO
629          ENDIF
630    C     Y coordinate
631          IF ( delYfile .NE. ' ' ) THEN
632           IF ( delY(1) .NE. UNSET_RL .OR. dySpacing .NE. UNSET_RL ) THEN
633             WRITE(msgBuf,'(A,A)') 'Too many specifications for delY:',
634         &   'Specify only one of delY, dySpacing or delYfile'
635            CALL PRINT_ERROR( msgBuf , 1)
636            STOP 'ABNORMAL END: S/R INI_PARMS'
637           ELSE
638            _BEGIN_MASTER( myThid )
639            IF (readBinaryPrec.EQ.precFloat32) THEN
640             OPEN(37,FILE=delYfile,STATUS='OLD',FORM='UNFORMATTED',
641         &        ACCESS='DIRECT',RECL=WORDLENGTH*Ny)
642             READ(37,rec=1) delY
643    #ifdef _BYTESWAPIO
644                call MDS_BYTESWAPR4( Ny, delY )
645    #endif
646             CLOSE(37)
647            ELSEIF (readBinaryPrec.EQ.precFloat64) THEN
648             OPEN(37,FILE=delYfile,STATUS='OLD',FORM='UNFORMATTED',
649         &        ACCESS='DIRECT',RECL=WORDLENGTH*2*Ny)
650             READ(37,rec=1) delY
651    #ifdef _BYTESWAPIO
652                call MDS_BYTESWAPR8( Ny, delY )
653    #endif
654             CLOSE(37)
655            ENDIF
656            _END_MASTER(myThid)
657           ENDIF
658          ENDIF
659          IF ( dySpacing .NE. UNSET_RL ) THEN
660           DO i=1,Ny
661            delY(i) = dySpacing
662           ENDDO
663          ENDIF
664    C
665        IF ( rSphere .NE. 0 ) THEN        IF ( rSphere .NE. 0 ) THEN
666         recip_rSphere = 1. _d 0/rSphere         recip_rSphere = 1.D0/rSphere
667        ELSE        ELSE
668         recip_rSphere = 0.         recip_rSphere = 0.
669        ENDIF        ENDIF
670    C--   Initialize EOS coefficients (3rd order polynomial)
 C     Initialize EOS coefficients (3rd order polynomial)  
671        IF (eostype.eq.'POLY3') THEN        IF (eostype.eq.'POLY3') THEN
672         OPEN(37,FILE='POLY3.COEFFS',STATUS='OLD',FORM='FORMATTED')         OPEN(37,FILE='POLY3.COEFFS',STATUS='OLD',FORM='FORMATTED')
673         READ(37,*) I         READ(37,*) I
674         IF (I.NE.Nr) THEN         IF (I.NE.Nr) THEN
675          WRITE(0,*) 'ini_parms: attempt to read POLY3.COEFFS failed'          WRITE(msgBuf,'(A)')
676          WRITE(0,*) '           because bad # of levels in data'       &  'ini_parms: attempt to read POLY3.COEFFS failed'
677            CALL PRINT_ERROR( msgBuf , 1)
678            WRITE(msgBuf,'(A)')
679         &  '           because bad # of levels in data'
680            CALL PRINT_ERROR( msgBuf , 1)
681          STOP 'Bad data in POLY3.COEFFS'          STOP 'Bad data in POLY3.COEFFS'
682         ENDIF         ENDIF
683         READ(37,*) (eosRefT(K),eosRefS(K),eosSig0(K),K=1,Nr)         READ(37,*) (eosRefT(K),eosRefS(K),eosSig0(K),K=1,Nr)
684         DO K=1,Nr         DO K=1,Nr
685          READ(37,*) (eosC(I,K),I=1,9)          READ(37,*) (eosC(I,K),I=1,9)
         write(0,'(i3,13f8.3)') K,eosRefT(K),eosRefS(K),eosSig0(K),  
      &                (eosC(I,K),I=1,9)  
686         ENDDO         ENDDO
687         CLOSE(37)         CLOSE(37)
688        ENDIF        ENDIF
689    C--   Check for conflicting grid definitions.
690        goptCount = 0        goptCount = 0
691        IF ( usingCartesianGrid )      goptCount = goptCount+1        IF ( usingCartesianGrid )      goptCount = goptCount+1
692        IF ( usingSphericalPolarGrid ) goptCount = goptCount+1        IF ( usingSphericalPolarGrid ) goptCount = goptCount+1
# Line 491  C     Initialize EOS coefficients (3rd o Line 696  C     Initialize EOS coefficients (3rd o
696         CALL PRINT_ERROR( msgBuf , myThid)         CALL PRINT_ERROR( msgBuf , myThid)
697         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
698        ENDIF        ENDIF
699    C--   Make metric term settings consistent with underlying grid.
700        IF ( usingCartesianGrid ) THEN        IF ( usingCartesianGrid ) THEN
701         usingSphericalPolarMterms = .FALSE.         usingSphericalPolarMterms = .FALSE.
702         metricTerms = .FALSE.         metricTerms = .FALSE.
703         mTFacMom = 0         mTFacMom = 0.
704         useBetaPlaneF = .TRUE.         useBetaPlaneF = .TRUE.
705        ENDIF        ENDIF
706        IF ( usingSphericalPolarGrid ) THEN        IF ( usingSphericalPolarGrid ) THEN
707         useConstantF  = .FALSE.         useConstantF  = .FALSE.
708         useBetaPlaneF = .FALSE.         useBetaPlaneF = .FALSE.
709         useSphereF    = .TRUE.         useSphereF    = .TRUE.
710         omega         = 2. _d 0 * PI / ( 3600. _d 0 * 24. _d 0 )         omega         = 2.D0 * PI / ( 3600.D0 * 24.D0 )
711         usingSphericalPolarMterms = .TRUE.         usingSphericalPolarMterms = metricTerms
712         metricTerms = .TRUE.        ENDIF
713         mTFacMom = 1  C--   p, z, r coord parameters
714          DO K = 1, Nr
715           IF ( delZ(K) .NE. UNSET_RL ) zCoordInputData = .TRUE.
716           IF ( delP(K) .NE. UNSET_RL ) pCoordInputData = .TRUE.
717           IF ( delR(K) .NE. UNSET_RL ) rCoordInputData = .TRUE.
718           IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delZ(K)
719           IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delP(K)
720           IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delRDefault(K)
721           IF ( delR(K) .EQ. 0. ) THEN
722             WRITE(msgBuf,'(A,I4)')
723         &  'S/R INI_PARMS: No value for delZ/delP/delR at K = ',K
724             CALL PRINT_ERROR( msgBuf , 1)
725             STOP 'ABNORMAL END: S/R INI_PARMS'
726           ENDIF
727          ENDDO
728    C     Check for multiple coordinate systems
729          CoordsSet = 0
730          IF ( zCoordInputData ) coordsSet = coordsSet + 1
731          IF ( pCoordInputData ) coordsSet = coordsSet + 1
732          IF ( rCoordInputData ) coordsSet = coordsSet + 1
733          IF ( coordsSet .GT. 1 ) THEN
734           WRITE(msgBuf,'(A)')
735         &  'S/R INI_PARMS: Cannot mix z, p and r in the input data.'
736           CALL PRINT_ERROR( msgBuf , myThid)
737           STOP 'ABNORMAL END: S/R INI_PARMS'
738        ENDIF        ENDIF
739    
740  C--   Input files  C--   Input files
741        bathyFile       = ' '        READ(UNIT=iUnit,NML=PARM05) !,IOSTAT=errIO)
742        hydrogSaltFile  = ' '        IF ( errIO .LT. 0 ) THEN    
       hydrogThetaFile = ' '  
       zonalWindFile   = ' '  
       meridWindFile   = ' '  
       thetaClimFile   = ' '  
       saltClimFile    = ' '  
       READ(UNIT=iUnit,NML=PARM05,IOSTAT=errIO,err=11)  
       IF ( errIO .GE. 0 ) GOTO 12  
    11 CONTINUE  
        WRITE(msgBuf,'(A)')  
      &  'S/R INI_PARMS'  
        CALL PRINT_ERROR( msgBuf , 1)  
743         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
744       &  'Error reading numerical model '       &  'Error reading numerical model '
745         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
# Line 533  C--   Input files Line 751  C--   Input files
751         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
752         CALL MODELDATA_EXAMPLE( myThid )         CALL MODELDATA_EXAMPLE( myThid )
753         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
754    12  CONTINUE        ENDIF      
755    
756    C
757    C--   Set factors required for mixing pressure and meters as vertical coordinate.
758    C     rkFac is a "sign" parameter which is used where the orientation of the vertical
759    C     coordinate (pressure or meters) relative to the vertical index (K) is important.
760    C     rkFac =  1 applies when K and the coordinate are in the opposite sense.
761    C     rkFac = -1 applies when K and the coordinate are in the same sense.
762    C     horiVertRatio is a parameter that maps horizontal units to vertical units.
763    C     It is used in certain special cases where lateral and vertical terms are
764    C     being combined and a single frame of reference is needed.
765          IF ( zCoordInputData .AND. rkFac .EQ. UNSET_RS ) THEN
766           rkFac       = 1.D0
767           horiVertRatio = 1.D0
768          ENDIF
769          IF ( pCoordInputData .AND. rkFac .EQ. UNSET_RS ) THEN
770           rkFac = -1.D0
771           horiVertRatio = Gravity * rhoConst
772          ENDIF
773          IF ( rCoordInputData .AND. rkFac .EQ. UNSET_RS ) THEN
774           rkFac =  1.D0
775           horiVertRatio = 1.D0
776          ENDIF
777          IF (buoyancyRelation.EQ.'ATMOSPHERIC')
778         &   horiVertRatio = Gravity * rhoConst                                    
779          IF ( rkFac .EQ. UNSET_RS ) rkFac=rkFacDefault
780          recip_rkFac = 1.D0 / rkFac
781          recip_horiVertRatio = 1./horiVertRatio
782          IF ( zCoordInputData ) usingZCoords = .TRUE.
783          IF ( pCoordInputData ) usingPCoords = .TRUE.
784    
785  C  C
786        CLOSE(iUnit)        CLOSE(iUnit)

Legend:
Removed from v.1.27  
changed lines
  Added in v.1.57

  ViewVC Help
Powered by ViewVC 1.1.22