/[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.64 by heimbach, Fri Jul 13 14:26:57 2001 UTC revision 1.83 by adcroft, Thu Aug 15 17:25:31 2002 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6    CBOP
7    C     !ROUTINE: INI_PARMS
8    C     !INTERFACE:
9        SUBROUTINE INI_PARMS( myThid )        SUBROUTINE INI_PARMS( myThid )
10  C     /==========================================================\  C     !DESCRIPTION: \bv
11  C     | SUBROUTINE INI_PARMS                                     |  C     *==========================================================*
12  C     | o Routine to set model "parameters"                      |  C     | SUBROUTINE INI_PARMS                                      
13  C     |==========================================================|  C     | o Routine to set model "parameters"                      
14  C     | Notes:                                                   |  C     *==========================================================*
15  C     | ======                                                   |  C     | Notes:                                                    
16  C     | The present version of this routine is a place-holder.   |  C     | ======                                                    
17  C     | A production version needs to handle parameters from an  |  C     | The present version of this routine is a place-holder.    
18  C     | external file and possibly reading in some initial field |  C     | A production version needs to handle parameters from an  
19  C     | values.                                                  |  C     | external file and possibly reading in some initial field  
20  C     \==========================================================/  C     | values.                                                  
21        IMPLICIT NONE  C     *==========================================================*
22    C     \ev
23    
24    C     !USES:
25          IMPLICIT NONE
26  C     === Global variables ===  C     === Global variables ===
27  #include "SIZE.h"  #include "SIZE.h"
28  #include "EEPARAMS.h"  #include "EEPARAMS.h"
29  #include "PARAMS.h"  #include "PARAMS.h"
30  #include "GRID.h"  #include "GRID.h"
31    #include "EOS.h"
32    
33    C     !INPUT/OUTPUT PARAMETERS:
34  C     === Routine arguments ===  C     === Routine arguments ===
35  C     myThid - Number of this instance of INI_PARMS  C     myThid - Number of this instance of INI_PARMS
36        INTEGER myThid        INTEGER myThid
37    
38    C     !LOCAL VARIABLES:
39  C     === Local variables ===  C     === Local variables ===
40  C     dxSpacing, dySpacing - Default spacing in X and Y.  C     dxSpacing, dySpacing - Default spacing in X and Y.
41  C                            Units are that of coordinate system  C                            Units are that of coordinate system
# Line 47  C     xxxDefault - Default value for var Line 56  C     xxxDefault - Default value for var
56        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
57        CHARACTER*(MAX_LEN_PREC) record        CHARACTER*(MAX_LEN_PREC) record
58        INTEGER goptCount        INTEGER goptCount
59        INTEGER K, I, J, IL, iUnit        INTEGER K, I, IL, iUnit
60        INTEGER errIO        INTEGER errIO
61        INTEGER  IFNBLNK        INTEGER  IFNBLNK
62        EXTERNAL IFNBLNK        EXTERNAL IFNBLNK
# Line 61  C     dependency. Line 70  C     dependency.
70        _RL hFacMinDrDefault        _RL hFacMinDrDefault
71        _RL delRDefault(Nr)        _RL delRDefault(Nr)
72        _RS rkFacDefault        _RS rkFacDefault
73  C     zCoordInputData - These are used to select between different coordinate systems.  C     zCoordInputData :: Variables used to select between different coordinate systems.
74  C     pCoordInputData   The vertical coordinate system in the rest of the model is  C     pCoordInputData :: The vertical coordinate system in the rest of the model is
75  C     rCoordInputData   written in terms of r. In the model "data" file input data can  C     rCoordInputData :: written in terms of r. In the model "data" file input data can
76  C     coordsSet         be interms of z, p or r.  C     coordsSet       :: be interms of z, p or r.
77  C                       e.g. delZ or delP or delR for the vertical grid spacing.  C                     :: e.g. delZ or delP or delR for the vertical grid spacing.
78  C                       The following rules apply:  C                     :: The following rules apply:
79  C                       All parameters must use the same vertical coordinate system.  C                     :: All parameters must use the same vertical coordinate system.
80  C                       e.g. delZ and viscAz is legal but  C                     ::  e.g. delZ and viscAz is legal but
81  C                            delZ and viscAr is an error.  C                     ::       delZ and viscAr is an error.
82  C                       Similarly specifyinh delZ and delP is an error.  C                     :: Similarly specifyinh delZ and delP is an error.
83  C                       zCoord..., pCoord..., rCoord... are used to flag when z, p or r are  C                     :: zCoord..., pCoord..., rCoord... are used to flag when z, p or r are
84  C                       used. coordsSet counts how many vertical coordinate systems have been  C                     :: used. coordsSet counts how many vertical coordinate systems have been
85  C                       used to specify variables. coordsSet > 1 is an error.  C                        used to specify variables. coordsSet > 1 is an error.
86  C  C
87        LOGICAL zCoordInputData        LOGICAL zCoordInputData
88        LOGICAL pCoordInputData        LOGICAL pCoordInputData
89        LOGICAL rCoordInputData        LOGICAL rCoordInputData
90        INTEGER coordsSet        INTEGER coordsSet
91    
92    C     Retired main data file parameters. Kept here to trap use of old data files.
93    C     zonal_filt_lat  - Moved to package "zonal_filt"
94    C     nRetired :: Counter used to trap gracefully namelists containing "retired"
95    C              :: parameters. These are parameters that are either no-longer used
96    C                 or that have moved to a different input file and/or namelist.
97          _RL zonal_filt_lat
98          INTEGER nRetired
99    CEOP
100    
101  C--   Continuous equation parameters  C--   Continuous equation parameters
102        NAMELIST /PARM01/        NAMELIST /PARM01/
103         & gravitySign,
104       & gravity, gBaro, rhonil, tAlpha, sBeta, f0, beta, omega,       & gravity, gBaro, rhonil, tAlpha, sBeta, f0, beta, omega,
105       & viscAh,  viscAz,  viscA4, cosPower,       & viscAh,  viscAz,  viscA4, cosPower, viscAstrain, viscAtension,
106       & diffKhT, diffKzT, diffK4T,       & diffKhT, diffKzT, diffK4T,
107       & diffKhS, diffKzS, diffK4S,       & diffKhS, diffKzS, diffK4S,
108       & tRef, sRef, eosType, Integr_GeoPot,       & tRef, sRef, eosType, Integr_GeoPot,
109       & no_slip_sides,no_slip_bottom,       & no_slip_sides,no_slip_bottom,
110       & momViscosity,  momAdvection, momForcing, useCoriolis,       & momViscosity,  momAdvection, momForcing, useCoriolis,
111       & momPressureForcing, metricTerms,       & momPressureForcing, metricTerms, vectorInvariantMomentum,
112       & tempDiffusion, tempAdvection, tempForcing,       & tempDiffusion, tempAdvection, tempForcing,
113       & saltDiffusion, saltAdvection, saltForcing,       & saltDiffusion, saltAdvection, saltForcing,
114       & implicSurfPress, implicDiv2DFlow,       & implicSurfPress, implicDiv2DFlow,
# Line 104  C--   Continuous equation parameters Line 123  C--   Continuous equation parameters
123       & writeBinaryPrec, readBinaryPrec, writeStatePrec,       & writeBinaryPrec, readBinaryPrec, writeStatePrec,
124       & nonHydrostatic, globalFiles,       & nonHydrostatic, globalFiles,
125       & allowFreezing, ivdc_kappa,       & allowFreezing, ivdc_kappa,
      & zonal_filt_lat, zonal_filt_sinpow, zonal_filt_cospow,  
126       & bottomDragLinear,bottomDragQuadratic,       & bottomDragLinear,bottomDragQuadratic,
127       & usePickupBeforeC35, debugMode,       & usePickupBeforeC35, debugMode,
128       & readPickupWithTracer, writePickupWithTracer       & readPickupWithTracer, writePickupWithTracer,
129         & tempAdvScheme, saltAdvScheme, tracerAdvScheme,
130         & multiDimAdvection, useEnergyConservingCoriolis,
131         & useJamartWetPoints,
132         & useRealFreshWaterFlux, convertFW2Salt,
133         & temp_EvPrRn, salt_EvPrRn, trac_EvPrRn,
134         & zonal_filt_lat
135    
136  C--   Elliptic solver parameters  C--   Elliptic solver parameters
137        NAMELIST /PARM02/        NAMELIST /PARM02/
# Line 117  C--   Elliptic solver parameters Line 141  C--   Elliptic solver parameters
141    
142  C--   Time stepping parammeters  C--   Time stepping parammeters
143        NAMELIST /PARM03/        NAMELIST /PARM03/
144       & nIter0, nTimeSteps, nEndIter, deltaT, deltaTmom, deltaTtracer,       & nIter0, nTimeSteps, nEndIter,
145       & abEps, tauCD, rCD,       & deltaT, deltaTmom, deltaTtracer, deltaTfreesurf,
146       & startTime, endTime, chkPtFreq, dumpFreq, taveFreq, deltaTClock,       & forcing_In_AB, abEps, tauCD, rCD,
147         & startTime, endTime, chkPtFreq,
148         & dumpFreq, taveFreq, deltaTClock, diagFreq,
149       & monitorFreq, pChkPtFreq, cAdjFreq,       & monitorFreq, pChkPtFreq, cAdjFreq,
150       & tauThetaClimRelax, tauSaltClimRelax, tauTr1ClimRelax,       & tauThetaClimRelax, tauSaltClimRelax, tauTr1ClimRelax,
151       & periodicExternalForcing, externForcingPeriod, externForcingCycle       & periodicExternalForcing, externForcingPeriod, externForcingCycle
# Line 128  C--   Gridding parameters Line 154  C--   Gridding parameters
154        NAMELIST /PARM04/        NAMELIST /PARM04/
155       & usingCartesianGrid, dxSpacing, dySpacing, delX, delY, delZ,       & usingCartesianGrid, dxSpacing, dySpacing, delX, delY, delZ,
156       & usingSphericalPolarGrid, phiMin, thetaMin, rSphere,       & usingSphericalPolarGrid, phiMin, thetaMin, rSphere,
157       & usingCurvilinearGrid,       & usingCurvilinearGrid, gravitySign,
158       & delP, delR, rkFac, Ro_SeaLevel, groundAtK1,       & delP, delR, rkFac, Ro_SeaLevel, groundAtK1, delRc,
159       & delXfile, delYfile       & delXfile, delYfile
160    
161  C--   Input files  C--   Input files
# Line 139  C--   Input files Line 165  C--   Input files
165       & thetaClimFile, saltClimFile,       & thetaClimFile, saltClimFile,
166       & surfQfile, EmPmRfile, surfQswfile,       & surfQfile, EmPmRfile, surfQswfile,
167       & uVelInitFile, vVelInitFile, pSurfInitFile,       & uVelInitFile, vVelInitFile, pSurfInitFile,
168       & dQdTFile       & dQdTFile, ploadFile
169    
170  C  C
171        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
# Line 158  C--   Initialise "which vertical coordin Line 184  C--   Initialise "which vertical coordin
184        usingZCoords    = .FALSE.        usingZCoords    = .FALSE.
185        coordsSet       = 0        coordsSet       = 0
186    
187    C--   Iniialise retired parameters to unlikely value
188          nRetired = 0
189          zonal_filt_lat  = UNSET_RL
190    
191  C--   Open the parameter file  C--   Open the parameter file
192        OPEN(UNIT=scrUnit1,STATUS='SCRATCH')        OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
193        OPEN(UNIT=scrUnit2,STATUS='SCRATCH')        OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
# Line 234  C--   Set default "physical" parameters Line 264  C--   Set default "physical" parameters
264        hFacMinDr           = UNSET_RL        hFacMinDr           = UNSET_RL
265        hFacMinDz           = UNSET_RL        hFacMinDz           = UNSET_RL
266        hFacMinDp           = UNSET_RL        hFacMinDp           = UNSET_RL
267          convertFW2Salt = UNSET_RL
268          tAlpha              = UNSET_RL
269          sBeta               = UNSET_RL
270        READ(UNIT=iUnit,NML=PARM01) !,IOSTAT=errIO)        READ(UNIT=iUnit,NML=PARM01) !,IOSTAT=errIO)
271        IF ( errIO .LT. 0 ) THEN        IF ( errIO .LT. 0 ) THEN
272         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
# Line 250  C--   Set default "physical" parameters Line 283  C--   Set default "physical" parameters
283         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
284         CALL MODELDATA_EXAMPLE( myThid )         CALL MODELDATA_EXAMPLE( myThid )
285         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
286          ELSE
287           WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM01 : OK'
288           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
289         &                    SQUEEZE_RIGHT , 1)
290        ENDIF        ENDIF
291        IF ( implicitFreeSurface ) freeSurfFac = 1.D0        IF ( implicitFreeSurface ) freeSurfFac = 1.D0
292        IF ( rigidLid            ) freeSurfFac = 0.D0        IF ( rigidLid            ) freeSurfFac = 0.D0
# Line 291  C--   Metric terms on/off flag. Line 328  C--   Metric terms on/off flag.
328        ELSE        ELSE
329         mTFacMom = 0.D0         mTFacMom = 0.D0
330        ENDIF        ENDIF
331    C--   Advection and Forcing for Temp and salt  on/off flags
332          tempAdvection = tempStepping .AND. tempAdvection
333          tempForcing   = tempStepping .AND. tempForcing
334          saltAdvection = saltStepping .AND. saltAdvection
335          saltForcing   = saltStepping .AND. saltForcing
336  C--   z,p,r coord input switching.  C--   z,p,r coord input switching.
337        IF ( viscAz .NE. UNSET_RL ) zCoordInputData = .TRUE.        IF ( viscAz .NE. UNSET_RL ) zCoordInputData = .TRUE.
338        IF ( viscAp .NE. UNSET_RL ) pCoordInputData = .TRUE.        IF ( viscAp .NE. UNSET_RL ) pCoordInputData = .TRUE.
# Line 320  C--   z,p,r coord input switching. Line 362  C--   z,p,r coord input switching.
362        IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr       = hFacMinDp        IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr       = hFacMinDp
363        IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr       = hFacMinDrDefault        IF ( hFacMinDr .EQ. UNSET_RL ) hFacMinDr       = hFacMinDrDefault
364    
365          IF (convertFW2Salt.EQ.UNSET_RL) THEN
366            convertFW2Salt = 35.
367            IF (useRealFreshWaterFlux) convertFW2Salt=-1
368          ENDIF
369    
370        IF ( ivdc_kappa .NE. 0. .AND. .NOT. implicitDiffusion ) THEN        IF ( ivdc_kappa .NE. 0. .AND. .NOT. implicitDiffusion ) THEN
371         WRITE(msgBuf,'(A,A)')          WRITE(msgBuf,'(A,A)')
372       &  'S/R INI_PARMS: To use ivdc_kappa you must enable implicit',       &  'S/R INI_PARMS: To use ivdc_kappa you must enable implicit',
373       &  ' vertical diffusion.'       &  ' vertical diffusion.'
374         CALL PRINT_ERROR( msgBuf , myThid)         CALL PRINT_ERROR( msgBuf , myThid)
375         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
376        ENDIF        ENDIF
377    
       IF ( implicitFreeSurface .AND.  rigidLid ) THEN  
        WRITE(msgBuf,'(A,A)')  
      & 'S/R INI_PARMS: Cannot select both implicitFreeSurface',  
      & ' and rigidLid.'  
        CALL PRINT_ERROR( msgBuf , myThid)  
        STOP 'ABNORMAL END: S/R INI_PARMS'  
       ENDIF  
       IF ( (implicSurfPress.NE.1. .OR. implicDiv2DFlow.NE.1.)  
      &    .AND. nonHydrostatic ) THEN  
        WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: nonHydrostatic',  
      & ' NOT SAFE with non-fully implicit Barotropic solver'  
        CALL PRINT_ERROR( msgBuf , myThid)  
        WRITE(msgBuf,'(A,A)') 'S/R INI_PARMS: To by-pass this',  
      &    'STOP, comment this test and re-compile ini_params'  
        CALL PRINT_ERROR( msgBuf , myThid)  
        STOP 'ABNORMAL END: S/R INI_PARMS'  
       ENDIF  
   
378        coordsSet = 0        coordsSet = 0
379        IF ( zCoordInputData ) coordsSet = coordsSet + 1        IF ( zCoordInputData ) coordsSet = coordsSet + 1
380        IF ( pCoordInputData ) coordsSet = coordsSet + 1        IF ( pCoordInputData ) coordsSet = coordsSet + 1
# Line 395  C     Set globalFiles flag for READ_WRIT Line 424  C     Set globalFiles flag for READ_WRIT
424  C     Set globalFiles flag for READ_WRITE_REC package  C     Set globalFiles flag for READ_WRITE_REC package
425        CALL SET_WRITE_GLOBAL_PICKUP( globalFiles )        CALL SET_WRITE_GLOBAL_PICKUP( globalFiles )
426    
427    C     Check for retired parameters still being used
428          nRetired = 0
429          IF ( zonal_filt_lat .NE. UNSET_RL ) THEN
430           nRetired = nRetired+1
431           WRITE(msgBuf,'(A,A)')
432         &  'S/R INI_PARMS: Paramater "zonal_filt_lat" is',
433         &  ' no longer allowed in file "data".'
434           CALL PRINT_ERROR( msgBuf , myThid)
435           WRITE(msgBuf,'(A,A)')
436         &  'S/R INI_PARMS: Paramater "zonal_filt_lat" is',
437         &  ' now read from file "data.zonfilt".'
438           CALL PRINT_ERROR( msgBuf , myThid)
439          ENDIF
440    
441  C--   Elliptic solver parameters  C--   Elliptic solver parameters
442        READ(UNIT=iUnit,NML=PARM02) !,IOSTAT=errIO)        READ(UNIT=iUnit,NML=PARM02) !,IOSTAT=errIO)
443        IF ( errIO .LT. 0 ) THEN        IF ( errIO .LT. 0 ) THEN
# Line 412  C--   Elliptic solver parameters Line 455  C--   Elliptic solver parameters
455         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
456         CALL MODELDATA_EXAMPLE( myThid )         CALL MODELDATA_EXAMPLE( myThid )
457         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
458          ELSE
459           WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM02 : OK'
460           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
461         &                    SQUEEZE_RIGHT , 1)
462        ENDIF            ENDIF    
463    
464  C--   Time stepping parameters  C--   Time stepping parameters
# Line 432  C--   Time stepping parameters Line 479  C--   Time stepping parameters
479         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
480         CALL MODELDATA_EXAMPLE( myThid )         CALL MODELDATA_EXAMPLE( myThid )
481         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
482          ELSE
483           WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM03 : OK'
484           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
485         &                    SQUEEZE_RIGHT , 1)
486        ENDIF          ENDIF  
487  C     Process "timestepping" params  C     Process "timestepping" params
488  C     o Time step size  C     o Time step size
# Line 440  C     o Time step size Line 491  C     o Time step size
491        IF ( deltaTmom    .EQ. 0. ) deltaTmom    = deltaT        IF ( deltaTmom    .EQ. 0. ) deltaTmom    = deltaT
492        IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT        IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT
493        IF ( deltaTClock  .EQ. 0. ) deltaTClock  = deltaT        IF ( deltaTClock  .EQ. 0. ) deltaTClock  = deltaT
494    C Note that this line should set deltaTreesurf=deltaTmom
495    C but this would change a lot of existing set-ups so we are
496    C obliged to set the default inappropriately.
497    C Be advised that when using asynchronous time stepping
498    C it is better to set deltaTreesurf=deltaTtracer
499          IF ( deltaTfreesurf .EQ. 0. ) deltaTfreesurf  = deltaTmom
500        IF ( periodicExternalForcing ) THEN        IF ( periodicExternalForcing ) THEN
501         IF ( externForcingCycle*externForcingPeriod .EQ. 0. ) THEN         IF ( externForcingCycle*externForcingPeriod .EQ. 0. ) THEN
502          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 561  C     o Monitor (should also add CPP fla Line 618  C     o Monitor (should also add CPP fla
618        IF (monitorFreq.LT.0.) THEN        IF (monitorFreq.LT.0.) THEN
619         monitorFreq=0.         monitorFreq=0.
620         IF (dumpFreq.NE.0.) monitorFreq=dumpFreq         IF (dumpFreq.NE.0.) monitorFreq=dumpFreq
621           IF (diagFreq.NE.0..AND.diagFreq.LT.monitorFreq)
622         &         monitorFreq=diagFreq
623         IF (taveFreq.NE.0..AND.taveFreq.LT.monitorFreq)         IF (taveFreq.NE.0..AND.taveFreq.LT.monitorFreq)
624       &         monitorFreq=taveFreq       &         monitorFreq=taveFreq
625         IF (chkPtFreq.NE.0..AND.chkPtFreq.LT.monitorFreq)         IF (chkPtFreq.NE.0..AND.chkPtFreq.LT.monitorFreq)
# Line 602  C     In spherical polar distances are i Line 661  C     In spherical polar distances are i
661        dySpacing = UNSET_RL        dySpacing = UNSET_RL
662        delXfile = ' '        delXfile = ' '
663        delYfile = ' '        delYfile = ' '
664        READ(UNIT=iUnit,NML=PARM04) !,IOSTAT=errIO)        READ(UNIT=iUnit,NML=PARM04,IOSTAT=errIO)
665        IF ( errIO .LT. 0 ) THEN        IF ( errIO .LT. 0 ) THEN
666         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
667       &  'S/R INI_PARMS'       &  'S/R INI_PARMS'
# Line 618  C     In spherical polar distances are i Line 677  C     In spherical polar distances are i
677         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
678         CALL MODELDATA_EXAMPLE( myThid )         CALL MODELDATA_EXAMPLE( myThid )
679         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
680          ELSE
681           WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM04 : OK'
682           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
683         &                    SQUEEZE_RIGHT , 1)
684        ENDIF            ENDIF    
685    
686  C     X coordinate  C     X coordinate
# Line 694  C Line 757  C
757        ELSE        ELSE
758         recip_rSphere = 0.         recip_rSphere = 0.
759        ENDIF        ENDIF
 C--   Initialize EOS coefficients (3rd order polynomial)  
       IF (eostype.eq.'POLY3') THEN  
        OPEN(37,FILE='POLY3.COEFFS',STATUS='OLD',FORM='FORMATTED')  
        READ(37,*) I  
        IF (I.NE.Nr) THEN  
         WRITE(msgBuf,'(A)')  
      &  'ini_parms: attempt to read POLY3.COEFFS failed'  
         CALL PRINT_ERROR( msgBuf , 1)  
         WRITE(msgBuf,'(A)')  
      &  '           because bad # of levels in data'  
         CALL PRINT_ERROR( msgBuf , 1)  
         STOP 'Bad data in POLY3.COEFFS'  
        ENDIF  
        READ(37,*) (eosRefT(K),eosRefS(K),eosSig0(K),K=1,Nr)  
        DO K=1,Nr  
         READ(37,*) (eosC(I,K),I=1,9)  
        ENDDO  
        CLOSE(37)  
       ENDIF  
760  C--   Check for conflicting grid definitions.  C--   Check for conflicting grid definitions.
761        goptCount = 0        goptCount = 0
762        IF ( usingCartesianGrid )      goptCount = goptCount+1        IF ( usingCartesianGrid )      goptCount = goptCount+1
# Line 746  C--   Make metric term settings consiste Line 790  C--   Make metric term settings consiste
790        IF ( usingCurvilinearGrid ) THEN        IF ( usingCurvilinearGrid ) THEN
791         useSphereF    = .TRUE.         useSphereF    = .TRUE.
792        ENDIF        ENDIF
793    C--   set cell Center depth and put Interface at the middle between 2 C
794          setCenterDr = .FALSE.
795          IF (delRc(1).NE.UNSET_RL) setCenterDr=.TRUE.
796          DO K=1,Nr+1
797            IF (delRc(K).EQ.UNSET_RL) setCenterDr = .FALSE.
798          ENDDO
799  C--   p, z, r coord parameters  C--   p, z, r coord parameters
800        DO K = 1, Nr        DO K = 1, Nr
801         IF ( delZ(K) .NE. UNSET_RL ) zCoordInputData = .TRUE.         IF ( delZ(K) .NE. UNSET_RL ) zCoordInputData = .TRUE.
# Line 754  C--   p, z, r coord parameters Line 804  C--   p, z, r coord parameters
804         IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delZ(K)         IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delZ(K)
805         IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delP(K)         IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delP(K)
806         IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delRDefault(K)         IF ( delR(K) .EQ. UNSET_RL ) delR(K) = delRDefault(K)
807         IF ( delR(K) .EQ. 0. ) THEN         IF (.NOT.setCenterDr .AND. delR(K).EQ.delRDefault(K) ) THEN
808           WRITE(msgBuf,'(A,I4)')           WRITE(msgBuf,'(A,I4)')
809       &  'S/R INI_PARMS: No value for delZ/delP/delR at K = ',K       &  'S/R INI_PARMS: No value for delZ/delP/delR at K = ',K
810           CALL PRINT_ERROR( msgBuf , 1)           CALL PRINT_ERROR( msgBuf , 1)
811           STOP 'ABNORMAL END: S/R INI_PARMS'           STOP 'ABNORMAL END: S/R INI_PARMS'
812           ELSEIF ( setCenterDr .AND. delR(K).NE.delRDefault(K) ) THEN
813             WRITE(msgBuf,'(2A,I4)') 'S/R INI_PARMS:',
814         &    ' Cannot specify both delRc and delZ/delP/delR at K=', K
815             CALL PRINT_ERROR( msgBuf , 1)
816             STOP 'ABNORMAL END: S/R INI_PARMS'
817         ENDIF         ENDIF
818        ENDDO        ENDDO
819  C     Check for multiple coordinate systems  C     Check for multiple coordinate systems
# Line 787  C--   Input files Line 842  C--   Input files
842         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
843         CALL MODELDATA_EXAMPLE( myThid )         CALL MODELDATA_EXAMPLE( myThid )
844         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
845          ELSE
846           WRITE(msgBuf,'(A)') 'S/R INI_PARMS ; read PARM05 : OK'
847           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
848         &                    SQUEEZE_RIGHT , 1)
849        ENDIF              ENDIF      
850    C     o If pLoadFile is set, then we should make sure the corresponing
851    C       code is being compiled
852    #ifndef ATMOSPHERIC_LOADING
853          IF (pLoadFile.NE.' ') THEN
854            WRITE(msgBuf,'(A)')
855         &  'S/R INI_PARMS: pLoadFile is set but you have not'
856            CALL PRINT_ERROR( msgBuf , 1)
857            WRITE(msgBuf,'(A)')
858         &  'compiled the model with the pressure loading code.'
859            CALL PRINT_ERROR( msgBuf , 1)
860            WRITE(msgBuf,'(A,A)')
861         &  'Re-compile with:  #define ATMOSPHERIC_LOADING',
862         &  '              or  -DATMOSPHERIC_LOADING'
863            CALL PRINT_ERROR( msgBuf , 1)
864            STOP 'ABNORMAL END: S/R INI_PARMS'
865          ENDIF
866    #endif
867    
868  C  C
869  C--   Set factors required for mixing pressure and meters as vertical coordinate.  C--   Set factors required for mixing pressure and meters as vertical coordinate.
# Line 812  C     being combined and a single frame Line 888  C     being combined and a single frame
888        ENDIF        ENDIF
889        IF (buoyancyRelation.EQ.'ATMOSPHERIC')        IF (buoyancyRelation.EQ.'ATMOSPHERIC')
890       &   horiVertRatio = Gravity * rhoConst                                           &   horiVertRatio = Gravity * rhoConst                                    
891          IF (buoyancyRelation.EQ.'OCEANICP')
892         &   horiVertRatio = Gravity * rhoConst                                    
893        IF ( rkFac .EQ. UNSET_RS ) rkFac=rkFacDefault        IF ( rkFac .EQ. UNSET_RS ) rkFac=rkFacDefault
894        recip_rkFac = 1.D0 / rkFac        recip_rkFac = 1.D0 / rkFac
895        recip_horiVertRatio = 1./horiVertRatio        recip_horiVertRatio = 1./horiVertRatio
# Line 821  C     being combined and a single frame Line 899  C     being combined and a single frame
899  C  C
900        CLOSE(iUnit)        CLOSE(iUnit)
901    
902    C--   Check whether any retired parameters were found.
903    C--   Stop if they were
904          IF ( nRetired .GT. 0 ) THEN    
905           WRITE(msgBuf,'(A)')
906         &  'Error reading '
907           CALL PRINT_ERROR( msgBuf , 1)
908           WRITE(msgBuf,'(A)')
909         &  'parameter file "data"'
910           CALL PRINT_ERROR( msgBuf , 1)
911           WRITE(msgBuf,'(A)')
912         &  'some out of date parameters were found in the namelist'
913           CALL PRINT_ERROR( msgBuf , 1)
914           STOP 'ABNORMAL END: S/R INI_PARMS'
915          ENDIF
916    
917        _END_MASTER(myThid)        _END_MASTER(myThid)
918    
919  C--   Everyone else must wait for the parameters to be loaded  C--   Everyone else must wait for the parameters to be loaded
920        _BARRIER        _BARRIER
921  C  C
   
922        RETURN        RETURN
923        END        END
924    

Legend:
Removed from v.1.64  
changed lines
  Added in v.1.83

  ViewVC Help
Powered by ViewVC 1.1.22