/[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.28 by cnh, Sat Sep 5 17:52:13 1998 UTC
# Line 19  C     === Global variables === Line 19  C     === Global variables ===
19  #include "SIZE.h"  #include "SIZE.h"
20  #include "EEPARAMS.h"  #include "EEPARAMS.h"
21  #include "PARAMS.h"  #include "PARAMS.h"
22    #include "GRID.h"
23  #include "CG2D.h"  #include "CG2D.h"
24    
25  C     === Routine arguments ===  C     === Routine arguments ===
# Line 37  C     errIO     - IO error flag Line 38  C     errIO     - IO error flag
38  C     iUnit - Work variable for IO unit number  C     iUnit - Work variable for IO unit number
39  C     record - Work variable for IO buffer  C     record - Work variable for IO buffer
40  C     K, I, J - Loop counters  C     K, I, J - Loop counters
41        REAL dxSpacing  C     xxxDefault - Default value for variable xxx
42        REAL dySpacing        _RL  dxSpacing
43          _RL  dySpacing
44        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
45        CHARACTER*(MAX_LEN_PREC) record        CHARACTER*(MAX_LEN_PREC) record
46        INTEGER goptCount        INTEGER goptCount
# Line 48  C     K, I, J - Loop counters Line 50  C     K, I, J - Loop counters
50        EXTERNAL IFNBLNK        EXTERNAL IFNBLNK
51        INTEGER  ILNBLNK        INTEGER  ILNBLNK
52        EXTERNAL ILNBLNK        EXTERNAL ILNBLNK
53    C     Default values for variables which have vertical coordinate system
54    C     dependency.
55          _RL viscArDefault
56          _RL diffKrTDefault
57          _RL diffKrSDefault
58          _RL hFacMinDrDefault
59          _RL delRDefault
60    C     zCoordInputData - These are used to select between different coordinate systems.
61    C     pCoordInputData   The vertical coordinate system in the rest of the model is
62    C     rCoordInputData   written in terms of r. In the model "data" file input data can
63    C     coordsSet         be interms of z, p or r.
64    C                       e.g. delZ or delP or delR for the vertical grid spacing.
65    C                       The following rules apply:
66    C                       All parameters must use the same vertical coordinate system.
67    C                       e.g. delZ and viscAz is legal but
68    C                            delZ and viscAr is an error.
69    C                       Similarly specifyinh delZ and delP is an error.
70    C                       zCoord..., pCoord..., rCoord... are used to flag when z, p or r are
71    C                       used. coordsSet counts how many vertical coordinate systems have been
72    C                       used to specify variables. coordsSet > 1 is an error.
73    C
74          LOGICAL zCoordInputData
75          LOGICAL pCoordInputData
76          LOGICAL rCoordInputData
77          INTEGER coordsSet
78    
79  C--   Continuous equation parameters  C--   Continuous equation parameters
80        NAMELIST /PARM01/        NAMELIST /PARM01/
# Line 64  C--   Continuous equation parameters Line 91  C--   Continuous equation parameters
91       & implicitFreeSurface, rigidLid, freeSurfFac, hFacMin, hFacMinDz,       & implicitFreeSurface, rigidLid, freeSurfFac, hFacMin, hFacMinDz,
92       & tempStepping, saltStepping, momStepping, implicitDiffusion,       & tempStepping, saltStepping, momStepping, implicitDiffusion,
93       & viscAr, diffKrT, diffKrS, hFacMinDr,       & viscAr, diffKrT, diffKrS, hFacMinDr,
94       & rhoConst       & rhoConst, buoyancyRelation
95    
96  C--   Elliptic solver parameters  C--   Elliptic solver parameters
97        NAMELIST /PARM02/        NAMELIST /PARM02/
# Line 81  C--   Gridding parameters Line 108  C--   Gridding parameters
108        NAMELIST /PARM04/        NAMELIST /PARM04/
109       & usingCartesianGrid, delZ, dxSpacing, dySpacing, delX, delY,       & usingCartesianGrid, delZ, dxSpacing, dySpacing, delX, delY,
110       & usingSphericalPolarGrid, phiMin, thetaMin, rSphere,       & usingSphericalPolarGrid, phiMin, thetaMin, rSphere,
111       & l, m, n       & l, m, n, delP, delR, rkFac
112    
113  C--   Input files  C--   Input files
114        NAMELIST /PARM05/        NAMELIST /PARM05/
# Line 89  C--   Input files Line 116  C--   Input files
116       & zonalWindFile, meridWindFile, thetaClimFile,       & zonalWindFile, meridWindFile, thetaClimFile,
117       & saltClimFile       & saltClimFile
118    
119    
120  C  C
121        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
122    
123    C--   Initialise "which vertical coordinate system used" flags.
124          zCoordInputData = .FALSE.
125          pCoordInputData = .FALSE.
126          rCoordInputData = .FALSE.
127          coordsSet       = 0
128    
129  C--   Open the parameter file  C--   Open the parameter file
130        OPEN(UNIT=scrUnit1,STATUS='SCRATCH')        OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
131        OPEN(UNIT=scrUnit2,STATUS='SCRATCH')        OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
# Line 152  C--   Read settings from model parameter Line 186  C--   Read settings from model parameter
186    
187  C--   Set default "physical" parameters  C--   Set default "physical" parameters
188        DO K =1,Nr        DO K =1,Nr
189         tRef(K) = 30.D0 - FLOAT(K)         tRef(K) = 30.D0 - FLOAT( K )
190        ENDDO        ENDDO
191        gravity =   9.81 D0        gravity  =   9.81D0
192        gBaro   = gravity        gBaro    = gravity
193        rhoNil   = 999.8 D0        rhoNil   = 999.8D0
194        rhoConst = 999.8 D0        rhoConst = 999.8D0
195        f0     = 1.D-4        f0       = 1.D-4
196        beta   = 1. _d -11        beta     = 1.D-11
197        viscAh = 1.d3        viscAh   = 1.D3
198        diffKhT= 1.0d3        diffKhT  = 1.D3
199        diffKhS= 1.0d3        diffKhS  = 1.D3
200        viscAr = 1.d-3        viscArDefault = 1.D-3
201        diffKrT= 1.d-5        viscAz   = UNSET_RL    
202        diffKrS= 1.d-5        viscAr   = UNSET_RL
203        viscA4 = 0.        viscAp   = UNSET_RL
204        diffK4T= 0.        diffKrTDefault = 1.D-5
205        diffK4S= 0.        diffKzT  = UNSET_RL
206        GMmaxslope   = 1.d-2        diffKpT  = UNSET_RL
207        GMlength     = 200.d3        diffKrT  = UNSET_RL
208        GMalpha      = 0.        diffKrSDefault = 1.D-5
209        GMdepth      = 1000.        diffKzS  = UNSET_RL
210        GMkbackground= 0.        diffKpS  = UNSET_RL
211        GMmaxval     = 2500.d0        diffKrS  = UNSET_RL
212        tAlpha=2.d-4        viscA4   = 0.
213        sBeta=7.4d-4        diffK4T  = 0.
214        eosType='LINEAR'        diffK4S  = 0.
215        buoyancyRelation='OCEANIC'        GMmaxslope   =   1.D-2
216          GMlength     = 200.D3
217          GMalpha      = 0.D0
218          GMdepth      = 1000.D0
219          GMkbackground= 0.D0
220          GMmaxval     = 2500.D0
221          tAlpha       = 2.D-4
222          sBeta        = 7.4D-4
223          eosType      = 'LINEAR'
224          buoyancyRelation    = 'OCEANIC'
225        implicitFreeSurface = .TRUE.        implicitFreeSurface = .TRUE.
226        rigidLid            = .FALSE.        rigidLid            = .FALSE.
227        freeSurfFac         = 1. _d 0        freeSurfFac         = 1.D0
228        hFacMin             = 0. _d 0        hFacMin             = 0.D0
229        hFacMinDr           = 0. _d 0        hFacMinDrDefault    = 0.D0
230          hFacMinDr           = UNSET_RL
231          hFacMinDz           = UNSET_RL
232          hFacMinDp           = UNSET_RL
233        momViscosity        = .TRUE.        momViscosity        = .TRUE.
234        momAdvection        = .TRUE.        momAdvection        = .TRUE.
235        momForcing          = .TRUE.        momForcing          = .TRUE.
# Line 212  C--   Set default "physical" parameters Line 258  C--   Set default "physical" parameters
258         CALL MODELDATA_EXAMPLE( myThid )         CALL MODELDATA_EXAMPLE( myThid )
259         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
260     4  CONTINUE     4  CONTINUE
261        IF ( implicitFreeSurface ) freeSurfFac = 1. _d 0        IF ( implicitFreeSurface ) freeSurfFac = 1.D0
262        IF ( rigidLid            ) freeSurfFac = 0. _d 0        IF ( rigidLid            ) freeSurfFac = 0.D0
263    C--   Momentum viscosity on/off flag.
264        IF ( momViscosity        ) THEN        IF ( momViscosity        ) THEN
265         vfFacMom = 1. _d 0         vfFacMom = 1.D0
266        ELSE        ELSE
267         vfFacMom = 0. _d 0         vfFacMom = 0.D0
268        ENDIF        ENDIF
269    C--   Momentum advection on/off flag.
270        IF ( momAdvection        ) THEN        IF ( momAdvection        ) THEN
271         afFacMom = 1. _d 0         afFacMom = 1.D0
272        ELSE        ELSE
273         afFacMom = 0. _d 0         afFacMom = 0.D0
274        ENDIF        ENDIF
275    C--   Momentum forcing on/off flag.
276        IF ( momForcing ) THEN        IF ( momForcing ) THEN
277         foFacMom = 1. _d 0         foFacMom = 1.D0
278        ELSE        ELSE
279         foFacMom = 0. _d 0         foFacMom = 0.D0
280        ENDIF        ENDIF
281    C--   Coriolis term on/off flag.
282        IF ( useCoriolis ) THEN        IF ( useCoriolis ) THEN
283         cfFacMom = 1. _d 0         cfFacMom = 1.D0
284        ELSE        ELSE
285         cfFacMom = 0. _d 0         cfFacMom = 0.D0
286        ENDIF        ENDIF
287    C--   Pressure term on/off flag.
288        IF ( momPressureForcing ) THEN        IF ( momPressureForcing ) THEN
289         pfFacMom = 1. _d 0         pfFacMom = 1.D0
290        ELSE        ELSE
291         pfFacMom = 0. _d 0         pfFacMom = 0.D0
292        ENDIF        ENDIF
293    C--   Metric terms on/off flag.
294        IF ( metricTerms ) THEN        IF ( metricTerms ) THEN
295         mTFacMom = 1. _d 0         mTFacMom = 1.D0
296        ELSE        ELSE
297         mTFacMom = 1. _d 0         mTFacMom = 1.D0
298        ENDIF        ENDIF
299    C--   z,p,r coord input switching.
300          IF ( viscAz .NE. UNSET_RL ) zCoordInputData = .TRUE.
301          IF ( viscAp .NE. UNSET_RL ) pCoordInputData = .TRUE.
302          IF ( viscAr .NE. UNSET_RL ) rCoordInputData = .TRUE.
303          IF ( viscAr .EQ. UNSET_RL )          viscAr = viscAz
304          IF ( viscAr .EQ. UNSET_RL )          viscAr = viscAp
305          IF ( viscAr .EQ. UNSET_RL )          viscAr = viscArDefault
306    
307          IF ( diffKzT .NE. UNSET_RL ) zCoordInputData  = .TRUE.
308          IF ( diffKpT .NE. UNSET_RL ) pCoordInputData  = .TRUE.
309          IF ( diffKrT .NE. UNSET_RL ) rCoordInputData  = .TRUE.
310          IF ( diffKrT .EQ. UNSET_RL )          diffKrT = diffKzT
311          IF ( diffKrT .EQ. UNSET_RL )          diffKrT = diffKpT
312          IF ( diffKrT .EQ. UNSET_RL )          diffKrT = diffKrTDefault
313    
314          IF ( diffKzS .NE. UNSET_RL ) zCoordInputData  = .TRUE.
315          IF ( diffKpS .NE. UNSET_RL ) pCoordInputData  = .TRUE.
316          IF ( diffKrS .NE. UNSET_RL ) rCoordInputData  = .TRUE.
317          IF ( diffKrS .EQ. UNSET_RL )          diffKrS = diffKzS
318          IF ( diffKrS .EQ. UNSET_RL )          diffKrS = diffKpS
319          IF ( diffKrS .EQ. UNSET_RL )          diffKrS = diffKrSDefault
320    
321          IF ( hFacMinDz .NE. UNSET_RL ) zCoordInputData = .TRUE.
322          IF ( hFacMinDp .NE. UNSET_RL ) pCoordInputData = .TRUE.
323          IF ( hFacMinDr .NE. UNSET_RL ) rCoordInputData = .TRUE.
324          IF ( hFacMinDz .EQ. UNSET_RL ) hFacMinDr       = hFacMinDz
325          IF ( hFacMinDp .EQ. UNSET_RL ) hFacMinDr       = hFacMinDp
326          IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr       = hFacMinDrDefault
327    
328        IF ( implicitFreeSurface .AND.  rigidLid ) THEN        IF ( implicitFreeSurface .AND.  rigidLid ) THEN
329         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
330       &  'S/R INI_PARMS: Cannot select implicitFreeSurface and rigidLid.'       &  'S/R INI_PARMS: Cannot select both implicitFreeSurface and rigidLid.'
331           CALL PRINT_ERROR( msgBuf , myThid)
332           STOP 'ABNORMAL END: S/R INI_PARMS'
333          ENDIF
334          coordsSet = 0
335          IF ( zCoordInputData ) coordsSet = coordsSet + 1
336          IF ( pCoordInputData ) coordsSet = coordsSet + 1
337          IF ( rCoordInputData ) coordsSet = coordsSet + 1
338          IF ( coordsSet .GT. 1 ) THEN
339           WRITE(msgBuf,'(A)')
340         &  'S/R INI_PARMS: Cannot mix z, p and r in the input data.'
341         CALL PRINT_ERROR( msgBuf , myThid)         CALL PRINT_ERROR( msgBuf , myThid)
342         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
343        ENDIF        ENDIF
344          IF ( rhoConst .LE. 0. ) THEN
345           WRITE(msgBuf,'(A)')
346         &  'S/R INI_PARMS: rhoConst must be greater than 0.'
347           CALL PRINT_ERROR( msgBuf , myThid)
348           STOP 'ABNORMAL END: S/R INI_PARMS'
349          ELSE
350           recip_rhoConst = 1.D0 / rhoConst
351          ENDIF
352    
353  C--   Elliptic solver parameters  C--   Elliptic solver parameters
354        cg2dMaxIters   = 150        cg2dMaxIters       = 150
355        cg2dTargetResidual = 1. _d -7        cg2dTargetResidual = 1.D-7
356        cg2dChkResFreq = 1        cg2dChkResFreq     = 1
357        cg2dpcOffDFac  = 0.51 _d 0        cg2dpcOffDFac      = 0.51D0
358        READ(UNIT=iUnit,NML=PARM02,IOSTAT=errIO,err=5)        READ(UNIT=iUnit,NML=PARM02,IOSTAT=errIO,err=5)
359        IF ( errIO .GE. 0 ) GOTO 6        IF ( errIO .GE. 0 ) GOTO 6
360      5 CONTINUE      5 CONTINUE
# Line 277  C--   Elliptic solver parameters Line 375  C--   Elliptic solver parameters
375     6  CONTINUE     6  CONTINUE
376    
377  C--   Time stepping parameters  C--   Time stepping parameters
378        startTime      = 0.        startTime         = 0.
379        nTimeSteps     = 0        nTimeSteps        = 0
380        endTime        = 0.        endTime           = 0.
381        nIter0         = 0        nIter0            = 0
382        deltaT         = 0.        deltaT            = 0.
383        deltaTClock    = 0.        deltaTClock       = 0.
384        deltaTtracer   = 0.        deltaTtracer      = 0.
385        deltaTMom      = 0.        deltaTMom         = 0.
386        abEps          = 0.01        abEps             = 0.01
387        pchkPtFreq     = 0.        pchkPtFreq        = 0.
388        chkPtFreq      = 3600.*25        chkPtFreq         = 3600.*25
389        dumpFreq       = 3600.*100        dumpFreq          = 3600.*100
390        taveFreq       = 0.        taveFreq          = 0.
391        writeStatePrec = precFloat32        writeStatePrec    = precFloat32
392        nCheckLev      = 1        nCheckLev         = 1
393        checkPtSuff(1) = 'ckptA'        checkPtSuff(1)    = 'ckptA'
394        checkPtSuff(2) = 'ckptB'        checkPtSuff(2)    = 'ckptB'
395        cAdjFreq       = -1. _d 0        cAdjFreq          = -1.D0
396        rCD            = -1. _d 0        rCD               = -1.D0
397        tauCD          = 0. _d 0        tauCD             =  0.D0
398        tauThetaClimRelax = 0. _d 0        tauThetaClimRelax =  0.D0
399        doThetaClimRelax  = .FALSE.        doThetaClimRelax  = .FALSE.
400        tauSaltClimRelax  = 0. _d 0        tauSaltClimRelax  =  0.D0
401        doSaltClimRelax   = .FALSE.        doSaltClimRelax   = .FALSE.
402        periodicExternalForcing = .FALSE.        periodicExternalForcing = .FALSE.
403        externForcingPeriod = 0.        externForcingPeriod     = 0.
404        externForcingCycle = 0.        externForcingCycle      = 0.
405        READ(UNIT=iUnit,NML=PARM03,IOSTAT=errIO,err=7)        READ(UNIT=iUnit,NML=PARM03,IOSTAT=errIO,err=7)
406        IF ( errIO .GE. 0 ) GOTO 8        IF ( errIO .GE. 0 ) GOTO 8
407      7 CONTINUE      7 CONTINUE
# Line 361  C     o Convection frequency Line 459  C     o Convection frequency
459         cAdjFreq = deltaTClock         cAdjFreq = deltaTClock
460        ENDIF        ENDIF
461  C     o CD coupling  C     o CD coupling
462        IF ( tauCD .EQ. 0. _d 0 ) THEN        IF ( tauCD .EQ. 0.D0 ) THEN
463          tauCD = deltaTmom          tauCD = deltaTmom
464        ENDIF        ENDIF
465        IF ( rCD .LT. 0. ) THEN        IF ( rCD .LT. 0. ) THEN
466         rCD = 1. - deltaTMom/tauCD         rCD = 1. - deltaTMom/tauCD
467        ENDIF        ENDIF
468  C     o Temperature climatology relaxation time scale  C     o Temperature climatology relaxation time scale
469        IF ( tauThetaClimRelax .EQ. 0. _d 0 ) THEN        IF ( tauThetaClimRelax .EQ. 0.D0 ) THEN
470         doThetaClimRelax     = .FALSE.         doThetaClimRelax     = .FALSE.
471         lambdaThetaClimRelax = 0. _d 0         lambdaThetaClimRelax = 0.D0
472        ELSE        ELSE
473         doThetaClimRelax     = .TRUE.         doThetaClimRelax     = .TRUE.
474         lambdaThetaClimRelax = 1./tauThetaClimRelax         lambdaThetaClimRelax = 1./tauThetaClimRelax
475        ENDIF        ENDIF
476  C     o Salinity climatology relaxation time scale  C     o Salinity climatology relaxation time scale
477        IF ( tauSaltClimRelax .EQ. 0. _d 0 ) THEN        IF ( tauSaltClimRelax .EQ. 0.D0 ) THEN
478         doSaltClimRelax     = .FALSE.         doSaltClimRelax     = .FALSE.
479         lambdaSaltClimRelax = 0. _d 0         lambdaSaltClimRelax = 0.D0
480        ELSE        ELSE
481         doSaltClimRelax     = .TRUE.         doSaltClimRelax     = .TRUE.
482         lambdaSaltClimRelax = 1./tauSaltClimRelax         lambdaSaltClimRelax = 1./tauSaltClimRelax
# Line 410  C       code is being compiled Line 508  C       code is being compiled
508    
509  C--   Grid parameters  C--   Grid parameters
510  C     In cartesian coords distances are in metres  C     In cartesian coords distances are in metres
511          rkFac = UNSET_I
512        usingCartesianGrid = .TRUE.        usingCartesianGrid = .TRUE.
513          delRDefault =  1.D2
514        DO K =1,Nr        DO K =1,Nr
515         delZ(K) = 100. _d 0         delZ(K) = UNSET_RL
516           delP(K) = UNSET_RL
517           delR(K) = UNSET_RL
518        ENDDO        ENDDO
519        dxSpacing = 20. _d 0 * 1000. _d 0        dxSpacing = 20.D0 * 1000.D0
520        dySpacing = 20. _d 0 * 1000. _d 0        dySpacing = 20.D0 * 1000.D0
521        DO i=1,Nx        DO i=1,Nx
522         delX(i) = dxSpacing         delX(i) = dxSpacing
523        ENDDO        ENDDO
# Line 426  C     In spherical polar distances are i Line 528  C     In spherical polar distances are i
528        usingSphericalPolarGrid = .FALSE.        usingSphericalPolarGrid = .FALSE.
529        phiMin    = -5.0        phiMin    = -5.0
530        thetaMin  = 0.        thetaMin  = 0.
531        rSphere   = 6370. * 1. _d 3        rSphere   = 6370. * 1.D3
532        recip_rSphere  = 1. _d 0/rSphere        recip_rSphere  = 1.D0/rSphere
533        IF ( usingSphericalPolarGrid ) THEN        IF ( usingSphericalPolarGrid ) THEN
534         dxSpacing = 1.         dxSpacing = 1.
535         dySpacing = 1.         dySpacing = 1.
# Line 457  C     In spherical polar distances are i Line 559  C     In spherical polar distances are i
559         CALL MODELDATA_EXAMPLE( myThid )         CALL MODELDATA_EXAMPLE( myThid )
560         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
561    10  CONTINUE    10  CONTINUE
562    C
563        IF ( rSphere .NE. 0 ) THEN        IF ( rSphere .NE. 0 ) THEN
564         recip_rSphere = 1. _d 0/rSphere         recip_rSphere = 1.D0/rSphere
565        ELSE        ELSE
566         recip_rSphere = 0.         recip_rSphere = 0.
567        ENDIF        ENDIF
568    C--   Initialize EOS coefficients (3rd order polynomial)
 C     Initialize EOS coefficients (3rd order polynomial)  
569        IF (eostype.eq.'POLY3') THEN        IF (eostype.eq.'POLY3') THEN
570         OPEN(37,FILE='POLY3.COEFFS',STATUS='OLD',FORM='FORMATTED')         OPEN(37,FILE='POLY3.COEFFS',STATUS='OLD',FORM='FORMATTED')
571         READ(37,*) I         READ(37,*) I
572         IF (I.NE.Nr) THEN         IF (I.NE.Nr) THEN
573          WRITE(0,*) 'ini_parms: attempt to read POLY3.COEFFS failed'          WRITE(msgBuf,'(A)')
574          WRITE(0,*) '           because bad # of levels in data'       &  'ini_parms: attempt to read POLY3.COEFFS failed'
575            CALL PRINT_ERROR( msgBuf , 1)
576            WRITE(msgBuf,'(A)')
577         &  '           because bad # of levels in data'
578            CALL PRINT_ERROR( msgBuf , 1)
579          STOP 'Bad data in POLY3.COEFFS'          STOP 'Bad data in POLY3.COEFFS'
580         ENDIF         ENDIF
581         READ(37,*) (eosRefT(K),eosRefS(K),eosSig0(K),K=1,Nr)         READ(37,*) (eosRefT(K),eosRefS(K),eosSig0(K),K=1,Nr)
582         DO K=1,Nr         DO K=1,Nr
583          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)  
584         ENDDO         ENDDO
585         CLOSE(37)         CLOSE(37)
586        ENDIF        ENDIF
587    C--   Check for conflicting grid definitions.
588        goptCount = 0        goptCount = 0
589        IF ( usingCartesianGrid )      goptCount = goptCount+1        IF ( usingCartesianGrid )      goptCount = goptCount+1
590        IF ( usingSphericalPolarGrid ) goptCount = goptCount+1        IF ( usingSphericalPolarGrid ) goptCount = goptCount+1
# Line 491  C     Initialize EOS coefficients (3rd o Line 594  C     Initialize EOS coefficients (3rd o
594         CALL PRINT_ERROR( msgBuf , myThid)         CALL PRINT_ERROR( msgBuf , myThid)
595         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
596        ENDIF        ENDIF
597    C--   Make metric term settings consistent with underlying grid.
598        IF ( usingCartesianGrid ) THEN        IF ( usingCartesianGrid ) THEN
599         usingSphericalPolarMterms = .FALSE.         usingSphericalPolarMterms = .FALSE.
600         metricTerms = .FALSE.         metricTerms = .FALSE.
# Line 502  C     Initialize EOS coefficients (3rd o Line 605  C     Initialize EOS coefficients (3rd o
605         useConstantF  = .FALSE.         useConstantF  = .FALSE.
606         useBetaPlaneF = .FALSE.         useBetaPlaneF = .FALSE.
607         useSphereF    = .TRUE.         useSphereF    = .TRUE.
608         omega         = 2. _d 0 * PI / ( 3600. _d 0 * 24. _d 0 )         omega         = 2.D0 * PI / ( 3600.D0 * 24.D0 )
609         usingSphericalPolarMterms = .TRUE.         usingSphericalPolarMterms = .TRUE.
610         metricTerms = .TRUE.         metricTerms = .TRUE.
611         mTFacMom = 1         mTFacMom = 1
612        ENDIF        ENDIF
613    C--   p, z, r coord parameters
614          DO K = 1, Nr
615           IF ( delZ(K) .NE. UNSET_RL ) zCoordInputData = .TRUE.
616           IF ( delP(K) .NE. UNSET_RL ) pCoordInputData = .TRUE.
617           IF ( delR(K) .NE. UNSET_RL ) rCoordInputData = .TRUE.
618           IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delZ(K)
619           IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delP(K)
620           IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delRDefault
621          ENDDO
622    C     Check for multiple coordinate systems
623          coordsSet = 0
624          IF ( zCoordInputData ) coordsSet = coordsSet + 1
625          IF ( pCoordInputData ) coordsSet = coordsSet + 1
626          IF ( rCoordInputData ) coordsSet = coordsSet + 1
627          IF ( coordsSet .GT. 1 ) THEN
628           WRITE(msgBuf,'(A)')
629         &  'S/R INI_PARMS: Cannot mix z, p and r in the input data.'
630           CALL PRINT_ERROR( msgBuf , myThid)
631           STOP 'ABNORMAL END: S/R INI_PARMS'
632          ENDIF
633    
634  C--   Input files  C--   Input files
635        bathyFile       = ' '        bathyFile       = ' '
# Line 536  C--   Input files Line 659  C--   Input files
659    12  CONTINUE    12  CONTINUE
660    
661  C  C
662          IF ( zCoordInputData .AND. rkFac .EQ. UNSET_I ) rkFac =  1.D0
663          IF ( pCoordInputData .AND. rkFac .EQ. UNSET_I ) rkFac = -1.D0
664          IF ( rCoordInputData .AND. rkFac .EQ. UNSET_I ) rkFac =  1.D0
665          recip_rkFac = 1.D0 / rkFac
666    C
667        CLOSE(iUnit)        CLOSE(iUnit)
668    
669        _END_MASTER(myThid)        _END_MASTER(myThid)

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

  ViewVC Help
Powered by ViewVC 1.1.22