/[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.88 by adcroft, Thu Nov 7 21:51:15 2002 UTC revision 1.89 by jmc, Tue Dec 10 02:55:47 2002 UTC
# Line 41  C     dxSpacing, dySpacing - Default spa Line 41  C     dxSpacing, dySpacing - Default spa
41  C                            Units are that of coordinate system  C                            Units are that of coordinate system
42  C                            i.e. cartesian => metres  C                            i.e. cartesian => metres
43  C                                  s. polar => degrees  C                                  s. polar => degrees
44    C     tmp4delX,tmp8delX - temporary arrays to read in delX
45    C     tmp4delY,tmp8delY - temporary arrays to read in delY
46  C     goptCount - Used to count the nuber of grid options  C     goptCount - Used to count the nuber of grid options
47  C                 (only one is allowed! )  C                 (only one is allowed! )
48  C     msgBuf    - Informational/error meesage buffer  C     msgBuf    - Informational/error meesage buffer
# Line 51  C     K, I, J - Loop counters Line 53  C     K, I, J - Loop counters
53  C     xxxDefault - Default value for variable xxx  C     xxxDefault - Default value for variable xxx
54        _RL  dxSpacing        _RL  dxSpacing
55        _RL  dySpacing        _RL  dySpacing
56          REAL*4 tmp4delX(Nx), tmp4delY(Ny)
57          REAL*8 tmp8delX(Nx), tmp8delY(Ny)
58        CHARACTER*(MAX_LEN_FNAM) delXfile        CHARACTER*(MAX_LEN_FNAM) delXfile
59        CHARACTER*(MAX_LEN_FNAM) delYfile        CHARACTER*(MAX_LEN_FNAM) delYfile
60        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
61        CHARACTER*(MAX_LEN_PREC) record        CHARACTER*(MAX_LEN_PREC) record
62        INTEGER goptCount        INTEGER goptCount
63        INTEGER K, I, IL, iUnit        INTEGER K, i, j, IL, iUnit
64        INTEGER errIO        INTEGER errIO
65        INTEGER  IFNBLNK        INTEGER  IFNBLNK
66        EXTERNAL IFNBLNK        EXTERNAL IFNBLNK
# Line 105  C--   Continuous equation parameters Line 109  C--   Continuous equation parameters
109       & viscAh,  viscAz,  viscA4, cosPower, viscAstrain, viscAtension,       & viscAh,  viscAz,  viscA4, cosPower, viscAstrain, viscAtension,
110       & diffKhT, diffKzT, diffK4T,       & diffKhT, diffKzT, diffK4T,
111       & diffKhS, diffKzS, diffK4S,       & diffKhS, diffKzS, diffK4S,
112       & tRef, sRef, eosType, Integr_GeoPot,       & tRef, sRef, eosType, integr_GeoPot, selectFindRoSurf,
113         & atm_Cp, atm_Rd,
114       & no_slip_sides,no_slip_bottom,       & no_slip_sides,no_slip_bottom,
115       & momViscosity,  momAdvection, momForcing, useCoriolis,       & momViscosity,  momAdvection, momForcing, useCoriolis,
116       & momPressureForcing, metricTerms, vectorInvariantMomentum,       & momPressureForcing, metricTerms, vectorInvariantMomentum,
# Line 288  C--   Set default "physical" parameters Line 293  C--   Set default "physical" parameters
293         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
294       &                    SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , 1)
295        ENDIF        ENDIF
296    
297        IF ( implicitFreeSurface ) freeSurfFac = 1.D0        IF ( implicitFreeSurface ) freeSurfFac = 1.D0
298        IF ( rigidLid            ) freeSurfFac = 0.D0        IF ( rigidLid            ) freeSurfFac = 0.D0
299        IF ( gBaro .EQ. UNSET_RL ) gBaro=gravity        IF ( gBaro .EQ. UNSET_RL ) gBaro=gravity
300        IF ( rhoConst .EQ. UNSET_RL ) rhoConst=rhoNil        IF ( rhoConst .EQ. UNSET_RL ) rhoConst=rhoNil
301          IF (atm_Rd .EQ. UNSET_RL) THEN
302            atm_Rd = atm_Cp * atm_kappa
303          ELSE
304            atm_kappa = atm_Rd / atm_Cp
305          ENDIF
306  C--   Momentum viscosity on/off flag.  C--   Momentum viscosity on/off flag.
307        IF ( momViscosity        ) THEN        IF ( momViscosity        ) THEN
308         vfFacMom = 1.D0         vfFacMom = 1.D0
# Line 498  C     o Time step size Line 509  C     o Time step size
509        IF ( deltaTmom    .EQ. 0. ) deltaTmom    = deltaT        IF ( deltaTmom    .EQ. 0. ) deltaTmom    = deltaT
510        IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT        IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT
511        IF ( deltaTClock  .EQ. 0. ) deltaTClock  = deltaT        IF ( deltaTClock  .EQ. 0. ) deltaTClock  = deltaT
512  C Note that this line should set deltaTreesurf=deltaTmom  C Note that this line should set deltaFreesurf=deltaTmom
513  C but this would change a lot of existing set-ups so we are  C but this would change a lot of existing set-ups so we are
514  C obliged to set the default inappropriately.  C obliged to set the default inappropriately.
515  C Be advised that when using asynchronous time stepping  C Be advised that when using asynchronous time stepping
# Line 636  C     o Monitor (should also add CPP fla Line 647  C     o Monitor (should also add CPP fla
647         IF (monitorFreq.EQ.0.) monitorFreq=deltaTclock         IF (monitorFreq.EQ.0.) monitorFreq=deltaTclock
648        ENDIF        ENDIF
649    
 C     o If taveFreq is finite, then we must make sure the diagnostics  
 C       code is being compiled  
 #ifndef ALLOW_TIMEAVE  
       IF (taveFreq.NE.0.) THEN  
         WRITE(msgBuf,'(A)')  
      &  'S/R INI_PARMS: taveFreq <> 0  but you have'  
         CALL PRINT_ERROR( msgBuf , 1)  
         WRITE(msgBuf,'(A)')  
      &  'not compiled the model with the diagnostics routines.'  
         CALL PRINT_ERROR( msgBuf , 1)  
         WRITE(msgBuf,'(A,A)')  
      &  'Re-compile with:  #define ALLOW_TIMEAVE',  
      &  '              or  -DALLOW_TIMEAVE'  
         CALL PRINT_ERROR( msgBuf , 1)  
         STOP 'ABNORMAL END: S/R INI_PARMS'  
       ENDIF  
 #endif  
   
650  C--   Grid parameters  C--   Grid parameters
651  C     In cartesian coords distances are in metres  C     In cartesian coords distances are in metres
652        rkFac = UNSET_RS        rkFac = UNSET_RS
# Line 702  C     X coordinate Line 695  C     X coordinate
695          IF (readBinaryPrec.EQ.precFloat32) THEN          IF (readBinaryPrec.EQ.precFloat32) THEN
696           OPEN(37,FILE=delXfile,STATUS='OLD',FORM='UNFORMATTED',           OPEN(37,FILE=delXfile,STATUS='OLD',FORM='UNFORMATTED',
697       &        ACCESS='DIRECT',RECL=WORDLENGTH*Nx)       &        ACCESS='DIRECT',RECL=WORDLENGTH*Nx)
698           READ(37,rec=1) delX           READ(37,rec=1) tmp4delX
699  #ifdef _BYTESWAPIO  #ifdef _BYTESWAPIO
700              call MDS_BYTESWAPR4( Nx, delX )              call MDS_BYTESWAPR4( Nx, tmp4delX )
701  #endif  #endif
702           CLOSE(37)           CLOSE(37)
703             DO i=1,Nx
704               delX(i) = tmp4delX(i)
705             ENDDO
706          ELSEIF (readBinaryPrec.EQ.precFloat64) THEN          ELSEIF (readBinaryPrec.EQ.precFloat64) THEN
707           OPEN(37,FILE=delXfile,STATUS='OLD',FORM='UNFORMATTED',           OPEN(37,FILE=delXfile,STATUS='OLD',FORM='UNFORMATTED',
708       &        ACCESS='DIRECT',RECL=WORDLENGTH*2*Nx)       &        ACCESS='DIRECT',RECL=WORDLENGTH*2*Nx)
709           READ(37,rec=1) delX           READ(37,rec=1) tmp8delX
710  #ifdef _BYTESWAPIO  #ifdef _BYTESWAPIO
711              call MDS_BYTESWAPR8( Nx, delX )              call MDS_BYTESWAPR8( Nx, tmp8delX )
712  #endif  #endif
713           CLOSE(37)           CLOSE(37)
714             DO i=1,Nx
715               delX(i) = tmp8delX(i)
716             ENDDO
717          ENDIF          ENDIF
718          _END_MASTER(myThid)          _END_MASTER(myThid)
719         ENDIF         ENDIF
# Line 736  C     Y coordinate Line 735  C     Y coordinate
735          IF (readBinaryPrec.EQ.precFloat32) THEN          IF (readBinaryPrec.EQ.precFloat32) THEN
736           OPEN(37,FILE=delYfile,STATUS='OLD',FORM='UNFORMATTED',           OPEN(37,FILE=delYfile,STATUS='OLD',FORM='UNFORMATTED',
737       &        ACCESS='DIRECT',RECL=WORDLENGTH*Ny)       &        ACCESS='DIRECT',RECL=WORDLENGTH*Ny)
738           READ(37,rec=1) delY           READ(37,rec=1) tmp4delY
739  #ifdef _BYTESWAPIO  #ifdef _BYTESWAPIO
740              call MDS_BYTESWAPR4( Ny, delY )              call MDS_BYTESWAPR4( Ny, tmp4delY )
741  #endif  #endif
742           CLOSE(37)           CLOSE(37)
743             DO j=1,Ny
744               delY(j) = tmp4delY(j)
745             ENDDO
746          ELSEIF (readBinaryPrec.EQ.precFloat64) THEN          ELSEIF (readBinaryPrec.EQ.precFloat64) THEN
747           OPEN(37,FILE=delYfile,STATUS='OLD',FORM='UNFORMATTED',           OPEN(37,FILE=delYfile,STATUS='OLD',FORM='UNFORMATTED',
748       &        ACCESS='DIRECT',RECL=WORDLENGTH*2*Ny)       &        ACCESS='DIRECT',RECL=WORDLENGTH*2*Ny)
749           READ(37,rec=1) delY           READ(37,rec=1) tmp8delY
750  #ifdef _BYTESWAPIO  #ifdef _BYTESWAPIO
751              call MDS_BYTESWAPR8( Ny, delY )              call MDS_BYTESWAPR8( Ny, tmp8delY )
752  #endif  #endif
753           CLOSE(37)           CLOSE(37)
754             DO j=1,Ny
755               delY(j) = tmp8delY(j)
756             ENDDO
757          ENDIF          ENDIF
758          _END_MASTER(myThid)          _END_MASTER(myThid)
759         ENDIF         ENDIF
# Line 857  C--   Input files Line 862  C--   Input files
862         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
863       &                    SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , 1)
864        ENDIF              ENDIF      
 C     o If pLoadFile is set, then we should make sure the corresponing  
 C       code is being compiled  
 #ifndef ATMOSPHERIC_LOADING  
       IF (pLoadFile.NE.' ') THEN  
         WRITE(msgBuf,'(A)')  
      &  'S/R INI_PARMS: pLoadFile is set but you have not'  
         CALL PRINT_ERROR( msgBuf , 1)  
         WRITE(msgBuf,'(A)')  
      &  'compiled the model with the pressure loading code.'  
         CALL PRINT_ERROR( msgBuf , 1)  
         WRITE(msgBuf,'(A,A)')  
      &  'Re-compile with:  #define ATMOSPHERIC_LOADING',  
      &  '              or  -DATMOSPHERIC_LOADING'  
         CALL PRINT_ERROR( msgBuf , 1)  
         STOP 'ABNORMAL END: S/R INI_PARMS'  
       ENDIF  
 #endif  
865    
 C  
866  C--   Set factors required for mixing pressure and meters as vertical coordinate.  C--   Set factors required for mixing pressure and meters as vertical coordinate.
867  C     rkFac is a "sign" parameter which is used where the orientation of the vertical  C     rkFac is a "sign" parameter which is used where the orientation of the vertical
868  C     coordinate (pressure or meters) relative to the vertical index (K) is important.  C     coordinate (pressure or meters) relative to the vertical index (K) is important.
# Line 889  C     being combined and a single frame Line 876  C     being combined and a single frame
876         horiVertRatio = 1.D0         horiVertRatio = 1.D0
877        ENDIF        ENDIF
878        IF ( pCoordInputData .AND. rkFac .EQ. UNSET_RS ) THEN        IF ( pCoordInputData .AND. rkFac .EQ. UNSET_RS ) THEN
879         rkFac = -1.D0  C- jmc: any time P-coordinate is used (ocean,atmos), it requires rkFac=1
880    c      rkFac = -1.D0
881         horiVertRatio = Gravity * rhoConst         horiVertRatio = Gravity * rhoConst
882        ENDIF        ENDIF
883        IF ( rCoordInputData .AND. rkFac .EQ. UNSET_RS ) THEN        IF ( rCoordInputData .AND. rkFac .EQ. UNSET_RS ) THEN

Legend:
Removed from v.1.88  
changed lines
  Added in v.1.89

  ViewVC Help
Powered by ViewVC 1.1.22