Back to home page

MITgcm

 
 

    


File indexing completed on 2018-03-02 18:37:36 UTC

view on githubraw file Latest commit add29e06 on 2018-01-31 20:35:05 UTC
1be817fa63 Jean*0001 #include "ATM_CPL_OPTIONS.h"
a9cdd26a43 Jean*0002 
                0003 CBOP
                0004 C     !ROUTINE: CPL_READPARMS
                0005 C     !INTERFACE:
                0006       SUBROUTINE CPL_READPARMS( myThid )
                0007 
                0008 C     !DESCRIPTION: \bv
                0009 C     *==========================================================*
                0010 C     | S/R CPL_READPARMS
                0011 C     | o Read Coupling parameters that control import/export
                0012 C     |   from/to the coupler layer
                0013 C     *==========================================================*
                0014 C     |   this version is specific to 1 component (atmos)
                0015 C     *==========================================================*
                0016 C     \ev
4ff1cd5702 Jean*0017 
a9cdd26a43 Jean*0018 C     !USES:
                0019       IMPLICIT NONE
                0020 
                0021 C     == Global variables ===
                0022 #include "SIZE.h"
                0023 #include "EEPARAMS.h"
                0024 #include "PARAMS.h"
                0025 #include "CPL_PARAMS.h"
                0026 
                0027 C     !INPUT/OUTPUT PARAMETERS:
4ff1cd5702 Jean*0028 C     == Routine Arguments ==
49715ba709 Jean*0029 C     myThid     :: my Thread Id. number
a9cdd26a43 Jean*0030       INTEGER myThid
                0031 CEOP
                0032 
                0033 #ifdef COMPONENT_MODULE
                0034 
49715ba709 Jean*0035 C     !FUNCTIONS:
                0036 c     INTEGER ILNBLNK
a9cdd26a43 Jean*0037 
49715ba709 Jean*0038 C     !LOCAL VARIABLES:
4ff1cd5702 Jean*0039 C     == Local Variables ==
49715ba709 Jean*0040 C     msgBuf     :: Informational/error message buffer
a9cdd26a43 Jean*0041 C     iUnit      :: Work variable for IO unit number
                0042 C     k          :: loop counter
                0043 C     iL         :: Work variable for length of file-name
44ff40f0ae Jean*0044 C     cpl_earlyExpImpCall :: retired; always call coupler early in call sequence
                0045 
a9cdd26a43 Jean*0046       CHARACTER*(MAX_LEN_MBUF) msgBuf
49715ba709 Jean*0047       INTEGER iUnit
                0048 c     INTEGER k, iL
7ed44c3f84 Jean*0049       _RL  cpl_atmSendFrq, tmpLoc
44ff40f0ae Jean*0050       LOGICAL cpl_earlyExpImpCall
a9cdd26a43 Jean*0051 
                0052 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0053 
4ff1cd5702 Jean*0054 C--   Coupling parameters:
bbdc4c9ae5 Jean*0055 C     cpl_oldPickup  :: restart from an old pickup (= until checkpoint 59h)
5a2fc21c93 Jean*0056 C     useImportMxlD  :: True => use Imported Mix.Layer Detph from coupler
                0057 C     useImportSST   :: True => use the Imported SST from coupler
                0058 C     useImportSSS   :: True => use the Imported SSS from coupler
                0059 C     useImportVsq   :: True => use the Imported Surf. velocity^2
fa4a0a5486 Jean*0060 C     useImportThSIce :: True => use the Imported thSIce state vars from coupler
                0061 C     useImportFlxCO2 :: True => use the Imported air-sea CO2 flux from coupler
4ff1cd5702 Jean*0062 C     cpl_atmSendFrq :: Frequency^-1 for sending data to coupler (s)
a9cdd26a43 Jean*0063       NAMELIST /CPL_ATM_PARAM/
5a2fc21c93 Jean*0064      &    cpl_earlyExpImpCall,
                0065      &    cpl_oldPickup,
4ff1cd5702 Jean*0066      &    useImportMxlD, useImportSST, useImportSSS,
fa4a0a5486 Jean*0067      &    useImportVsq, useImportThSIce, useImportFlxCO2,
0b50a127d4 Jean*0068      &    cpl_atmSendFrq,
                0069      &    maxNumberPrint
a9cdd26a43 Jean*0070 
                0071 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0072 
49715ba709 Jean*0073       _BEGIN_MASTER(myThid)
                0074 
                0075 C--   Open the data file
                0076       WRITE(msgBuf,'(A)') ' CPL_READPARMS: opening data.cpl'
1be817fa63 Jean*0077       CALL PRINT_MESSAGE( msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1 )
49715ba709 Jean*0078 
                0079       CALL OPEN_COPY_DATA_FILE( 'data.cpl', 'CPL_READPARMS',
                0080      O                          iUnit, myThid )
                0081 
a9cdd26a43 Jean*0082 C-    Set default value:
4ff1cd5702 Jean*0083       cpl_earlyExpImpCall = .TRUE.
                0084       cpl_oldPickup = .FALSE.
                0085       useImportMxlD = .TRUE.
                0086       useImportSST  = .TRUE.
                0087       useImportSSS  = .TRUE.
                0088       useImportVsq  = .TRUE.
fa4a0a5486 Jean*0089       useImportThSIce = cpl_exchange2W_sIce.EQ.3
                0090       useImportFlxCO2 =  cpl_exchange_DIC .EQ. 3
5a2fc21c93 Jean*0091       cpl_atmSendFrq= deltaTClock
0b50a127d4 Jean*0092       maxNumberPrint= 100
                0093       countPrtExp   = 0
                0094       countPrtImp   = 0
4ff1cd5702 Jean*0095 
a9cdd26a43 Jean*0096 C--   Read parameters from open data file:
                0097 
                0098 C-    Parameters for coupling interface:
                0099       READ(UNIT=iUnit,NML=CPL_ATM_PARAM)
                0100 
4ff1cd5702 Jean*0101       WRITE(msgBuf,'(A)')
a9cdd26a43 Jean*0102      &   ' CPL_READPARMS: finished reading data.cpl'
1be817fa63 Jean*0103       CALL PRINT_MESSAGE( msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1 )
4ff1cd5702 Jean*0104 
a9cdd26a43 Jean*0105 C--   Close the open data file
7a77863887 Mart*0106 #ifdef SINGLE_DISK_IO
a9cdd26a43 Jean*0107       CLOSE(iUnit)
7a77863887 Mart*0108 #else
                0109       CLOSE(iUnit,STATUS='DELETE')
                0110 #endif /* SINGLE_DISK_IO */
a9cdd26a43 Jean*0111 
                0112 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
44ff40f0ae Jean*0113 C--   Check for retired parameters:
                0114       IF ( .NOT.cpl_earlyExpImpCall ) THEN
                0115         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: ',
                0116      &   'Parameter "cpl_earlyExpImpCall" has been retired;'
                0117         CALL PRINT_ERROR( msgBuf, myThid )
                0118         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: ',
                0119      &   '=> always call coupler early in sequence of calls'
                0120         CALL PRINT_ERROR( msgBuf, myThid )
1be817fa63 Jean*0121         cplErrorCount = cplErrorCount + 1
44ff40f0ae Jean*0122       ENDIF
                0123 
a9cdd26a43 Jean*0124 C--   Check parameters and model configuration
fa4a0a5486 Jean*0125 
                0126 #ifndef ALLOW_LAND
                0127       IF ( atm_cplExch_RunOff ) THEN
                0128         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: needs',
                0129      &    ' to compile pkg/land to use: atm_cplExch_RunOff=T'
                0130         CALL PRINT_ERROR( msgBuf, myThid )
                0131         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: ',
                0132      &    ' (set from Coupler "data.cpl": cpl_exchange_RunOff > 1)'
                0133         CALL PRINT_ERROR( msgBuf, myThid )
                0134         cplErrorCount = cplErrorCount + 1
                0135       ENDIF
                0136 #endif /* ndef ALLOW_LAND */
                0137 #ifndef ALLOW_THSICE
                0138       IF ( atm_cplExch1W_sIce ) THEN
                0139         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: needs',
                0140      &    ' to compile pkg/thsice to use: atm_cplExch1W_sIce=T'
                0141         CALL PRINT_ERROR( msgBuf, myThid )
                0142         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: ',
                0143      &    ' (set from Coupler "data.cpl": cpl_exchange1W_sIce > 1)'
                0144         CALL PRINT_ERROR( msgBuf, myThid )
                0145         cplErrorCount = cplErrorCount + 1
                0146       ENDIF
                0147       IF ( atm_cplExch2W_sIce ) THEN
                0148         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: needs',
                0149      &    ' to compile pkg/thsice to use: atm_cplExch2W_sIce=T'
                0150         CALL PRINT_ERROR( msgBuf, myThid )
                0151         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: ',
                0152      &    ' (set from Coupler "data.cpl": cpl_exchange2W_sIce > 1)'
                0153         CALL PRINT_ERROR( msgBuf, myThid )
                0154         cplErrorCount = cplErrorCount + 1
                0155       ENDIF
                0156       IF ( atm_cplExch_SaltPl ) THEN
                0157         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: needs',
                0158      &    ' to compile pkg/thsice to use: atm_cplExch_SaltPl=T'
                0159         CALL PRINT_ERROR( msgBuf, myThid )
                0160         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: ',
                0161      &    ' (set from Coupler "data.cpl": cpl_exchange_SaltPl > 1)'
                0162         CALL PRINT_ERROR( msgBuf, myThid )
                0163         cplErrorCount = cplErrorCount + 1
                0164       ENDIF
                0165 #endif /* ndef ALLOW_THSICE */
                0166 #ifndef ALLOW_AIM
                0167       IF ( atm_cplExch_DIC ) THEN
                0168         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: needs',
                0169      &    ' to compile pkg/aim_v23 to use: atm_cplExch_DIC = T'
                0170         CALL PRINT_ERROR( msgBuf, myThid )
                0171         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: ',
                0172      &    ' (set from Coupler "data.cpl": cpl_exchange_DIC > 1)'
                0173         CALL PRINT_ERROR( msgBuf, myThid )
                0174         cplErrorCount = cplErrorCount + 1
                0175       ENDIF
                0176 #endif /* ndef ALLOW_AIM */
                0177 
                0178       IF ( useImportThSIce .AND. .NOT.atm_cplExch2W_sIce ) THEN
                0179         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: useImportThSIce',
                0180      &    ' requires setting'
                0181         CALL PRINT_ERROR( msgBuf, myThid )
                0182         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: ',
                0183      &    ' cpl_exchange2W_sIce > 1 (in Coupler "data.cpl")'
                0184         CALL PRINT_ERROR( msgBuf, myThid )
                0185         cplErrorCount = cplErrorCount + 1
                0186       ELSEIF ( useImportThSIce .AND. cpl_exchange2W_sIce.NE.3 ) THEN
                0187         WRITE(msgBuf,'(2A)') '** WARNING ** CPL_READPARMS: ',
                0188      &    'useImportThSIce useless without'
                0189         CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
                0190      &                      SQUEEZE_RIGHT, myThid )
                0191         WRITE(msgBuf,'(2A)') '** WARNING ** CPL_READPARMS: ',
                0192      &    ' cpl_exchange2W_sIce = 3 (in Coupler "data.cpl")'
                0193         CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
                0194      &                      SQUEEZE_RIGHT, myThid )
                0195       ENDIF
                0196       IF ( useImportFlxCO2 .AND. cpl_exchange_DIC.NE.3  ) THEN
4ff1cd5702 Jean*0197         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: useImportFlxCO2',
fa4a0a5486 Jean*0198      &    ' requires setting'
                0199         CALL PRINT_ERROR( msgBuf, myThid )
                0200         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: ',
                0201      &    ' cpl_exchange_DIC = 3 (in Coupler "data.cpl")'
44ff40f0ae Jean*0202         CALL PRINT_ERROR( msgBuf, myThid )
1be817fa63 Jean*0203         cplErrorCount = cplErrorCount + 1
4ff1cd5702 Jean*0204       ENDIF
7ed44c3f84 Jean*0205       tmpLoc = NINT( cpl_atmSendFrq / deltaTClock )
                0206       tmpLoc = ABS( tmpLoc - ( cpl_atmSendFrq / deltaTClock ) )
                0207       IF ( tmpLoc.GT.1. _d -12 .OR. cpl_atmSendFrq.EQ.zeroRL ) THEN
                0208         WRITE(msgBuf,'(2A)') 'CPL_READPARMS: cpl_atmSendFrq',
                0209      &    ' is not a multiple of deltaT'
                0210         CALL PRINT_ERROR( msgBuf, myThid )
1be817fa63 Jean*0211         cplErrorCount = cplErrorCount + 1
7ed44c3f84 Jean*0212       ENDIF
a9cdd26a43 Jean*0213 
7ed44c3f84 Jean*0214 C-    Derive other parameters:
a9cdd26a43 Jean*0215       cplSendFrq_iter = NINT( cpl_atmSendFrq / deltaTClock )
1be817fa63 Jean*0216       IF ( cplSendFrq_iter.LT.1 ) cplSendFrq_iter = 1
a9cdd26a43 Jean*0217 
                0218 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
1be817fa63 Jean*0219 C--   Print out set-up summary
a9cdd26a43 Jean*0220 
                0221       iUnit = standardMessageUnit
                0222       WRITE(msgBuf,'(A)') ' '
1be817fa63 Jean*0223       CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
a9cdd26a43 Jean*0224       WRITE(msgBuf,'(A)') '// ==================================='
1be817fa63 Jean*0225       CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
                0226       WRITE(msgBuf,'(A)') '// Coupling set-up summary :'
                0227       CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
a9cdd26a43 Jean*0228       WRITE(msgBuf,'(A)') '// ==================================='
1be817fa63 Jean*0229       CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
                0230 
                0231 C-    o Print Coupler-Exchange config (set from params in coupler 'data.cpl')
                0232        WRITE(msgBuf,'(A)') '// -------'
                0233        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
                0234        WRITE(msgBuf,'(A)')
                0235      &        '// Coupler-exchange switch (received from coupler):'
                0236        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
                0237 
                0238        CALL WRITE_0D_L( atm_cplSequential, INDEX_NONE,
                0239      &                 'atm_cplSequential =',
                0240      &   ' /* use Sequential Coupling Exchange on/off flag */')
                0241        CALL WRITE_0D_L( atm_cplExch_RunOff, INDEX_NONE,
                0242      &                 'atm_cplExch_RunOff =',
                0243      &     ' /* exchange RunOff fields with coupler on/off */')
                0244        CALL WRITE_0D_L( atm_cplExch1W_sIce, INDEX_NONE,
                0245      &                 'atm_cplExch1W_sIce =',
                0246      &     ' /* 1-way exchange of seaice vars with coupler */')
                0247        CALL WRITE_0D_L( atm_cplExch2W_sIce, INDEX_NONE,
                0248      &                 'atm_cplExch2W_sIce =',
                0249      &     ' /* 2-way exchange of ThSIce vars with coupler */')
                0250        CALL WRITE_0D_L( atm_cplExch_SaltPl, INDEX_NONE,
                0251      &                 'atm_cplExch_SaltPl =',
                0252      &     ' /* exchange Salt-Plume fields with coupler */')
                0253        CALL WRITE_0D_L( atm_cplExch_DIC, INDEX_NONE,
                0254      &                 'atm_cplExch_DIC    =',
                0255      &     ' /* exchange DIC    fields with coupler on/off */')
                0256 
                0257 C-    print namelist parameter value:
                0258        WRITE(msgBuf,'(A)') '// -------'
                0259        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
                0260        WRITE(msgBuf,'(A)')
                0261      &        '// Coupler parameters (from local param file):'
                0262        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
a9cdd26a43 Jean*0263 
5a2fc21c93 Jean*0264        CALL WRITE_0D_L( cpl_oldPickup , INDEX_NONE,
                0265      &                 'cpl_oldPickup =',
4ff1cd5702 Jean*0266      &   ' /* restart from old pickup on/off flag */')
5a2fc21c93 Jean*0267        CALL WRITE_0D_L( useImportMxlD , INDEX_NONE,
                0268      &                 'useImportMxlD =',
4ff1cd5702 Jean*0269      &   ' /* use Imported MxL. Depth from Coupler flag */')
fa4a0a5486 Jean*0270        CALL WRITE_0D_L( useImportSST  , INDEX_NONE,
                0271      &                 'useImportSST  =',
4ff1cd5702 Jean*0272      &   ' /* use Imported SST from Coupler on/off flag */')
fa4a0a5486 Jean*0273        CALL WRITE_0D_L( useImportSSS  , INDEX_NONE,
                0274      &                 'useImportSSS  =',
4ff1cd5702 Jean*0275      &   ' /* use Imported SSS from Coupler on/off flag */')
fa4a0a5486 Jean*0276        CALL WRITE_0D_L( useImportVsq  , INDEX_NONE,
                0277      &                 'useImportVsq  =',
4ff1cd5702 Jean*0278      &   ' /* use Imported surf.Vel^2 from Coupler flag */')
fa4a0a5486 Jean*0279        CALL WRITE_0D_L( useImportThSIce, INDEX_NONE,
                0280      &                 'useImportThSIce=',
                0281      &   ' /* use Imported thSIce state-var fr Cpl. flag */')
                0282        CALL WRITE_0D_L( useImportFlxCO2, INDEX_NONE,
                0283      &                 'useImportFlxCO2=',
                0284      &   ' /* use Imported air-sea CO2 flux fr Cpl.  flag */')
4da4b49499 Jean*0285        CALL WRITE_0D_RL( cpl_atmSendFrq, INDEX_NONE, 'cpl_atmSendFrq =',
a9cdd26a43 Jean*0286      &   ' /* Frequency^o-1 for sending data to Coupler (s) */')
4ff1cd5702 Jean*0287 C     cpl_atmSendFrq  :: Frequency^-1 for sending data to coupler (s)
a9cdd26a43 Jean*0288        CALL WRITE_0D_I( cplSendFrq_iter, INDEX_NONE,'cplSendFrq_iter =',
0b50a127d4 Jean*0289      &  ' /* send data to coupler every "cplSendFrq" iter */')
                0290        CALL WRITE_0D_I( maxNumberPrint, INDEX_NONE, 'maxNumberPrint =',
                0291      &  ' /* max number of printed Exp/Imp messages */')
a9cdd26a43 Jean*0292 
1be817fa63 Jean*0293       WRITE(msgBuf,'(A)') '// ==================================='
                0294       CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
                0295       WRITE(msgBuf,'(A)') '// End of Coupling set-up summary'
                0296       CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
                0297       WRITE(msgBuf,'(A)') '// ==================================='
                0298       CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
                0299 
a9cdd26a43 Jean*0300 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0301 
                0302       _END_MASTER(myThid)
4ff1cd5702 Jean*0303 
a9cdd26a43 Jean*0304 C--   Everyone else must wait for the parameters to be loaded
                0305       _BARRIER
                0306 
                0307 #endif /* COMPONENT_MODULE */
                0308 
                0309       RETURN
                0310       END