/[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.17 by cnh, Fri Jun 12 19:33:33 1998 UTC revision 1.27 by cnh, Mon Aug 24 02:25:01 1998 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    
3  #include "CPP_EEOPTIONS.h"  #include "CPP_OPTIONS.h"
4    
5        SUBROUTINE INI_PARMS( myThid )        SUBROUTINE INI_PARMS( myThid )
6  C     /==========================================================\  C     /==========================================================\
# Line 53  C--   Continuous equation parameters Line 53  C--   Continuous equation parameters
53        NAMELIST /PARM01/        NAMELIST /PARM01/
54       & gravity, gBaro, rhonil, tAlpha, sBeta, f0, beta,       & gravity, gBaro, rhonil, tAlpha, sBeta, f0, beta,
55       &   viscAh,  viscAz,  viscA4,       &   viscAh,  viscAz,  viscA4,
56       &  diffKhT, diffKzT, diffK4T,       &  diffKhT, diffKzT, diffK4T,
57       &  diffKhS, diffKzS, diffK4S,       &  diffKhS, diffKzS, diffK4S,
58       &  GMmaxslope,GMlength,GMalpha,GMdepth,GMkbackground,       &  GMmaxslope,GMlength,GMalpha,GMdepth,GMkbackground,GMmaxval,
59       &  tRef, sRef, eosType,       &  tRef, sRef, eosType,
60       & momViscosity,  momAdvection, momForcing, useCoriolis,       & momViscosity,  momAdvection, momForcing, useCoriolis,
61       & momPressureForcing, metricTerms,       & momPressureForcing, metricTerms,
62       & tempDiffusion, tempAdvection, tempForcing,       & tempDiffusion, tempAdvection, tempForcing,
63       & saltDiffusion, saltAdvection, saltForcing,       & saltDiffusion, saltAdvection, saltForcing,
64       & implicitFreeSurface, rigidLid, freeSurfFac,       & implicitFreeSurface, rigidLid, freeSurfFac, hFacMin, hFacMinDz,
65       & tempStepping, saltStepping, momStepping, implicitDiffusion       & tempStepping, saltStepping, momStepping, implicitDiffusion,
66         & viscAr, diffKrT, diffKrS, hFacMinDr,
67         & rhoConst
68    
69  C--   Elliptic solver parameters  C--   Elliptic solver parameters
70        NAMELIST /PARM02/        NAMELIST /PARM02/
# Line 71  C--   Elliptic solver parameters Line 73  C--   Elliptic solver parameters
73  C--   Time stepping parammeters  C--   Time stepping parammeters
74        NAMELIST /PARM03/        NAMELIST /PARM03/
75       & nIter0, nTimeSteps, deltaT, deltaTmom, deltaTtracer, abEps, tauCD, rCD,       & nIter0, nTimeSteps, deltaT, deltaTmom, deltaTtracer, abEps, tauCD, rCD,
76       & startTime, endTime, chkPtFreq, dumpFreq, deltaTClock, pChkPtFreq,       & startTime, endTime, chkPtFreq, dumpFreq, taveFreq, deltaTClock,
77       & cAdjFreq       & pChkPtFreq, cAdjFreq, tauThetaClimRelax, tauSaltClimRelax,
78         & periodicExternalForcing, externForcingPeriod, externForcingCycle
79    
80  C--   Gridding parameters  C--   Gridding parameters
81        NAMELIST /PARM04/        NAMELIST /PARM04/
# Line 83  C--   Gridding parameters Line 86  C--   Gridding parameters
86  C--   Input files  C--   Input files
87        NAMELIST /PARM05/        NAMELIST /PARM05/
88       & bathyFile, hydrogThetaFile, hydrogSaltFile,       & bathyFile, hydrogThetaFile, hydrogSaltFile,
89       & zonalWindFile, meridWindFile       & zonalWindFile, meridWindFile, thetaClimFile,
90         & saltClimFile
91    
92  C  C
93        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
# Line 147  C--   Read settings from model parameter Line 151  C--   Read settings from model parameter
151        REWIND(iUnit)        REWIND(iUnit)
152    
153  C--   Set default "physical" parameters  C--   Set default "physical" parameters
154        DO K =1,Nz        DO K =1,Nr
155         tRef(K) = 30.D0 - FLOAT(K)         tRef(K) = 30.D0 - FLOAT(K)
156        ENDDO        ENDDO
157        gravity =   9.81 D0        gravity =   9.81 D0
158        gBaro   = gravity        gBaro   = gravity
159        rhoNil   = 999.8 D0        rhoNil   = 999.8 D0
160        f0=1.D-4        rhoConst = 999.8 D0
161        beta = 1. _d -11        f0     = 1.D-4
162        viscAh=1.d3        beta   = 1. _d -11
163        diffKhT=1.0d3        viscAh = 1.d3
164        diffKhS=1.0d3        diffKhT= 1.0d3
165        viscAz=1.d-3        diffKhS= 1.0d3
166        diffKzT=1.d-5        viscAr = 1.d-3
167        diffKzS=1.d-5        diffKrT= 1.d-5
168        viscA4=0.        diffKrS= 1.d-5
169        diffK4T=0.        viscA4 = 0.
170        diffK4S=0.        diffK4T= 0.
171        GMmaxslope=1.d-2        diffK4S= 0.
172        GMlength=200.d3        GMmaxslope   = 1.d-2
173        GMalpha=0.        GMlength     = 200.d3
174        GMdepth=1000.        GMalpha      = 0.
175        GMkbackground=0.        GMdepth      = 1000.
176          GMkbackground= 0.
177          GMmaxval     = 2500.d0
178        tAlpha=2.d-4        tAlpha=2.d-4
179        sBeta=1.d-5        sBeta=7.4d-4
180        eosType='LINEAR'        eosType='LINEAR'
181          buoyancyRelation='OCEANIC'
182        implicitFreeSurface = .TRUE.        implicitFreeSurface = .TRUE.
183        rigidLid            = .FALSE.        rigidLid            = .FALSE.
184        freeSurfFac         = 1. _d 0        freeSurfFac         = 1. _d 0
185          hFacMin             = 0. _d 0
186          hFacMinDr           = 0. _d 0
187        momViscosity        = .TRUE.        momViscosity        = .TRUE.
188        momAdvection        = .TRUE.        momAdvection        = .TRUE.
189        momForcing          = .TRUE.        momForcing          = .TRUE.
# Line 280  C--   Time stepping parameters Line 289  C--   Time stepping parameters
289        pchkPtFreq     = 0.        pchkPtFreq     = 0.
290        chkPtFreq      = 3600.*25        chkPtFreq      = 3600.*25
291        dumpFreq       = 3600.*100        dumpFreq       = 3600.*100
292          taveFreq       = 0.
293        writeStatePrec = precFloat32        writeStatePrec = precFloat32
294        nCheckLev      = 1        nCheckLev      = 1
295        checkPtSuff(1) = 'ckptA'        checkPtSuff(1) = 'ckptA'
# Line 287  C--   Time stepping parameters Line 297  C--   Time stepping parameters
297        cAdjFreq       = -1. _d 0        cAdjFreq       = -1. _d 0
298        rCD            = -1. _d 0        rCD            = -1. _d 0
299        tauCD          = 0. _d 0        tauCD          = 0. _d 0
300          tauThetaClimRelax = 0. _d 0
301          doThetaClimRelax  = .FALSE.
302          tauSaltClimRelax  = 0. _d 0
303          doSaltClimRelax   = .FALSE.
304          periodicExternalForcing = .FALSE.
305          externForcingPeriod = 0.
306          externForcingCycle = 0.
307        READ(UNIT=iUnit,NML=PARM03,IOSTAT=errIO,err=7)        READ(UNIT=iUnit,NML=PARM03,IOSTAT=errIO,err=7)
308        IF ( errIO .GE. 0 ) GOTO 8        IF ( errIO .GE. 0 ) GOTO 8
309      7 CONTINUE      7 CONTINUE
# Line 312  C     o Time step size Line 329  C     o Time step size
329        IF ( deltaTmom    .EQ. 0. ) deltaTmom    = deltaT        IF ( deltaTmom    .EQ. 0. ) deltaTmom    = deltaT
330        IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT        IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT
331        IF ( deltaTClock  .EQ. 0. ) deltaTClock  = deltaT        IF ( deltaTClock  .EQ. 0. ) deltaTClock  = deltaT
332          IF ( periodicExternalForcing ) THEN
333           IF ( externForcingCycle*externForcingPeriod .EQ. 0. ) THEN
334            WRITE(msgBuf,'(A)')
335         &   'S/R INI_PARMS: externForcingCycle,externForcingPeriod =0'
336            CALL PRINT_ERROR( msgBuf , 1)
337            STOP 'ABNORMAL END: S/R INI_PARMS'
338           ENDIF
339           IF ( INT(externForcingCycle/externForcingPeriod) .NE.
340         &          externForcingCycle/externForcingPeriod ) THEN
341            WRITE(msgBuf,'(A)')
342         &   'S/R INI_PARMS: externForcingCycle <> N*externForcingPeriod'
343            CALL PRINT_ERROR( msgBuf , 1)
344            STOP 'ABNORMAL END: S/R INI_PARMS'
345           ENDIF
346           IF ( externForcingCycle.le.externForcingPeriod ) THEN
347            WRITE(msgBuf,'(A)')
348         &   'S/R INI_PARMS: externForcingCycle < externForcingPeriod'
349            CALL PRINT_ERROR( msgBuf , 1)
350            STOP 'ABNORMAL END: S/R INI_PARMS'
351           ENDIF
352           IF ( externForcingPeriod.lt.deltaTclock ) THEN
353            WRITE(msgBuf,'(A)')
354         &   'S/R INI_PARMS: externForcingPeriod < deltaTclock'
355            CALL PRINT_ERROR( msgBuf , 1)
356            STOP 'ABNORMAL END: S/R INI_PARMS'
357           ENDIF
358          ENDIF
359  C     o Convection frequency  C     o Convection frequency
360        IF ( cAdjFreq .LT. 0. ) THEN        IF ( cAdjFreq .LT. 0. ) THEN
361         cAdjFreq = deltaTClock         cAdjFreq = deltaTClock
# Line 323  C     o CD coupling Line 367  C     o CD coupling
367        IF ( rCD .LT. 0. ) THEN        IF ( rCD .LT. 0. ) THEN
368         rCD = 1. - deltaTMom/tauCD         rCD = 1. - deltaTMom/tauCD
369        ENDIF        ENDIF
370    C     o Temperature climatology relaxation time scale
371          IF ( tauThetaClimRelax .EQ. 0. _d 0 ) THEN
372           doThetaClimRelax     = .FALSE.
373           lambdaThetaClimRelax = 0. _d 0
374          ELSE
375           doThetaClimRelax     = .TRUE.
376           lambdaThetaClimRelax = 1./tauThetaClimRelax
377          ENDIF
378    C     o Salinity climatology relaxation time scale
379          IF ( tauSaltClimRelax .EQ. 0. _d 0 ) THEN
380           doSaltClimRelax     = .FALSE.
381           lambdaSaltClimRelax = 0. _d 0
382          ELSE
383           doSaltClimRelax     = .TRUE.
384           lambdaSaltClimRelax = 1./tauSaltClimRelax
385          ENDIF
386  C     o Time step count  C     o Time step count
387        IF ( endTime .NE. 0 ) THEN        IF ( endTime .NE. 0 ) THEN
388         IF ( deltaTClock .NE. 0 ) nTimeSteps =         IF ( deltaTClock .NE. 0 ) nTimeSteps =
# Line 330  C     o Time step count Line 390  C     o Time step count
390        ENDIF        ENDIF
391  C     o Finish time  C     o Finish time
392        IF ( endTime .EQ. 0. ) endTime = FLOAT(nTimeSteps)*deltaTClock        IF ( endTime .EQ. 0. ) endTime = FLOAT(nTimeSteps)*deltaTClock
393    
394    C     o If taveFreq is finite, then we must make sure the diagnostics
395    C       code is being compiled
396    #ifndef ALLOW_DIAGNOSTICS
397          IF (taveFreq.NE.0.) THEN
398            WRITE(msgBuf,'(A)')
399         &  'S/R INI_PARMS: taveFreq <> 0  but you have'
400            CALL PRINT_ERROR( msgBuf , 1)
401            WRITE(msgBuf,'(A)')
402         &  'not compiled the model with the diagnostics routines.'
403            CALL PRINT_ERROR( msgBuf , 1)
404            WRITE(msgBuf,'(A)')
405         &  'Re-compile with:  #define ALLOW_DIAGNOSTICS  or  -DALLOW_DIAGNOSTICS'
406            CALL PRINT_ERROR( msgBuf , 1)
407            STOP 'ABNORMAL END: S/R INI_PARMS'
408          ENDIF
409    #endif
410    
411  C--   Grid parameters  C--   Grid parameters
412  C     In cartesian coords distances are in metres  C     In cartesian coords distances are in metres
413        usingCartesianGrid = .TRUE.        usingCartesianGrid = .TRUE.
414        DO K =1,Nz        DO K =1,Nr
415         delZ(K) = 100. _d 0         delZ(K) = 100. _d 0
416        ENDDO        ENDDO
417        dxSpacing = 20. _d 0 * 1000. _d 0        dxSpacing = 20. _d 0 * 1000. _d 0
# Line 350  C     In spherical polar distances are i Line 427  C     In spherical polar distances are i
427        phiMin    = -5.0        phiMin    = -5.0
428        thetaMin  = 0.        thetaMin  = 0.
429        rSphere   = 6370. * 1. _d 3        rSphere   = 6370. * 1. _d 3
430        rRsphere  = 1. _d 0/rSphere        recip_rSphere  = 1. _d 0/rSphere
431        IF ( usingSphericalPolarGrid ) THEN        IF ( usingSphericalPolarGrid ) THEN
432         dxSpacing = 1.         dxSpacing = 1.
433         dySpacing = 1.         dySpacing = 1.
# Line 382  C     In spherical polar distances are i Line 459  C     In spherical polar distances are i
459    10  CONTINUE    10  CONTINUE
460    
461        IF ( rSphere .NE. 0 ) THEN        IF ( rSphere .NE. 0 ) THEN
462         rRSphere = 1. _d 0/rSphere         recip_rSphere = 1. _d 0/rSphere
463        ELSE        ELSE
464         rRSphere = 0.         recip_rSphere = 0.
465        ENDIF        ENDIF
466    
467  C     Initialize EOS coefficients (3rd order polynomial)  C     Initialize EOS coefficients (3rd order polynomial)
468        IF (eostype.eq.'POLY3') THEN        IF (eostype.eq.'POLY3') THEN
469         OPEN(37,FILE='POLY3.COEFFS',STATUS='OLD',FORM='FORMATTED')         OPEN(37,FILE='POLY3.COEFFS',STATUS='OLD',FORM='FORMATTED')
470         READ(37,*) I         READ(37,*) I
471         IF (I.NE.Nz) THEN         IF (I.NE.Nr) THEN
472          WRITE(0,*) 'ini_parms: attempt to read POLY3.COEFFS failed'          WRITE(0,*) 'ini_parms: attempt to read POLY3.COEFFS failed'
473          WRITE(0,*) '           because bad # of levels in data'          WRITE(0,*) '           because bad # of levels in data'
474          STOP 'Bad data in POLY3.COEFFS'          STOP 'Bad data in POLY3.COEFFS'
475         ENDIF         ENDIF
476         READ(37,*) (eosRefT(K),eosRefS(K),eosSig0(K),K=1,Nz)         READ(37,*) (eosRefT(K),eosRefS(K),eosSig0(K),K=1,Nr)
477         DO K=1,Nz         DO K=1,Nr
478          READ(37,*) (eosC(I,K),I=1,9)          READ(37,*) (eosC(I,K),I=1,9)
479          write(0,'(i3,13f8.3)') K,eosRefT(K),eosRefS(K),eosSig0(K),          write(0,'(i3,13f8.3)') K,eosRefT(K),eosRefS(K),eosSig0(K),
480       &                (eosC(I,K),I=1,9)       &                (eosC(I,K),I=1,9)
# Line 419  C     Initialize EOS coefficients (3rd o Line 496  C     Initialize EOS coefficients (3rd o
496         usingSphericalPolarMterms = .FALSE.         usingSphericalPolarMterms = .FALSE.
497         metricTerms = .FALSE.         metricTerms = .FALSE.
498         mTFacMom = 0         mTFacMom = 0
499           useBetaPlaneF = .TRUE.
        useConstantF  = .FALSE.  
        useBetaPlaneF = .FALSE.  
        useSphereF    = .TRUE.  
        omega         = 2. _d 0 * PI / ( 3600. _d 0 * 24. _d 0 )  
        usingSphericalPolarMterms = .TRUE.  
        metricTerms = .TRUE.  
        mTFacMom = 1  
500        ENDIF        ENDIF
501        IF ( usingSphericalPolarGrid ) THEN        IF ( usingSphericalPolarGrid ) THEN
502         useConstantF  = .FALSE.         useConstantF  = .FALSE.
# Line 436  C     Initialize EOS coefficients (3rd o Line 506  C     Initialize EOS coefficients (3rd o
506         usingSphericalPolarMterms = .TRUE.         usingSphericalPolarMterms = .TRUE.
507         metricTerms = .TRUE.         metricTerms = .TRUE.
508         mTFacMom = 1         mTFacMom = 1
   
509        ENDIF        ENDIF
510    
511  C--   Input files  C--   Input files
# Line 445  C--   Input files Line 514  C--   Input files
514        hydrogThetaFile = ' '        hydrogThetaFile = ' '
515        zonalWindFile   = ' '        zonalWindFile   = ' '
516        meridWindFile   = ' '        meridWindFile   = ' '
517          thetaClimFile   = ' '
518          saltClimFile    = ' '
519        READ(UNIT=iUnit,NML=PARM05,IOSTAT=errIO,err=11)        READ(UNIT=iUnit,NML=PARM05,IOSTAT=errIO,err=11)
520        IF ( errIO .GE. 0 ) GOTO 12        IF ( errIO .GE. 0 ) GOTO 12
521     11 CONTINUE     11 CONTINUE
# Line 464  C--   Input files Line 535  C--   Input files
535         STOP 'ABNORMAL END: S/R INI_PARMS'         STOP 'ABNORMAL END: S/R INI_PARMS'
536    12  CONTINUE    12  CONTINUE
537    
538    C
539          CLOSE(iUnit)
540    
541        _END_MASTER(myThid)        _END_MASTER(myThid)
542    
543  C--   Everyone else must wait for the parameters to be loaded  C--   Everyone else must wait for the parameters to be loaded

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

  ViewVC Help
Powered by ViewVC 1.1.22