/[MITgcm]/MITgcm/pkg/atm_compon_interf/cpl_readparms.F
ViewVC logotype

Diff of /MITgcm/pkg/atm_compon_interf/cpl_readparms.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.7 by jmc, Fri Dec 25 19:44:35 2009 UTC revision 1.9 by jmc, Tue Sep 24 23:13:54 2013 UTC
# Line 22  C     !USES: Line 22  C     !USES:
22        IMPLICIT NONE        IMPLICIT NONE
23    
24  C     == Global variables ===  C     == Global variables ===
   
25  #include "SIZE.h"  #include "SIZE.h"
   
26  #include "EEPARAMS.h"  #include "EEPARAMS.h"
27  #include "PARAMS.h"  #include "PARAMS.h"
28  #include "CPL_PARAMS.h"  #include "CPL_PARAMS.h"
# Line 47  C     msgBuf     :: Informational/error Line 45  C     msgBuf     :: Informational/error
45  C     iUnit      :: Work variable for IO unit number  C     iUnit      :: Work variable for IO unit number
46  C     k          :: loop counter  C     k          :: loop counter
47  C     iL         :: Work variable for length of file-name  C     iL         :: Work variable for length of file-name
48    C     cpl_earlyExpImpCall :: retired; always call coupler early in call sequence
49    
50        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
51        INTEGER iUnit        INTEGER iUnit
52  c     INTEGER k, iL  c     INTEGER k, iL
53        _RL  cpl_atmSendFrq        _RL  cpl_atmSendFrq
54          LOGICAL cpl_earlyExpImpCall
55    
56  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
57    
# Line 68  C     cpl_atmSendFrq :: Frequency^-1 for Line 69  C     cpl_atmSendFrq :: Frequency^-1 for
69       &    cpl_oldPickup,       &    cpl_oldPickup,
70       &    useImportMxlD, useImportSST, useImportSSS,       &    useImportMxlD, useImportSST, useImportSSS,
71       &    useImportVsq, useImportFlxCO2,       &    useImportVsq, useImportFlxCO2,
72       &    cpl_atmSendFrq       &    cpl_atmSendFrq,
73         &    maxNumberPrint
74    
75  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
76    
# Line 94  C-    Set default value: Line 96  C-    Set default value:
96          useImportFlxCO2 = .FALSE.          useImportFlxCO2 = .FALSE.
97        ENDIF        ENDIF
98        cpl_atmSendFrq= deltaTClock        cpl_atmSendFrq= deltaTClock
99          maxNumberPrint= 100
100          countPrtExp   = 0
101          countPrtImp   = 0
102    
103  C--   Read parameters from open data file:  C--   Read parameters from open data file:
104    
# Line 108  C--   Close the open data file Line 113  C--   Close the open data file
113        CLOSE(iUnit)        CLOSE(iUnit)
114    
115  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
116    C--   Check for retired parameters:
117          IF ( .NOT.cpl_earlyExpImpCall ) THEN
118            WRITE(msgBuf,'(2A)') 'CPL_READPARMS: ',
119         &   'Parameter "cpl_earlyExpImpCall" has been retired;'
120            CALL PRINT_ERROR( msgBuf, myThid )
121            WRITE(msgBuf,'(2A)') 'CPL_READPARMS: ',
122         &   '=> always call coupler early in sequence of calls'
123            CALL PRINT_ERROR( msgBuf, myThid )
124            STOP 'ABNORMAL END: S/R CPL_READPARMS'
125          ENDIF
126    
127  C--   Check parameters and model configuration  C--   Check parameters and model configuration
128        IF ( useImportFlxCO2 .AND. .NOT.atmCpl_exchange_DIC ) THEN        IF ( useImportFlxCO2 .AND. .NOT.atmCpl_exchange_DIC ) THEN
129          WRITE(msgBuf,'(2A)') 'CPL_READPARMS: useImportFlxCO2',          WRITE(msgBuf,'(2A)') 'CPL_READPARMS: useImportFlxCO2',
130       &    ' requires atmCpl_exchange_DIC TRUE'       &    ' requires atmCpl_exchange_DIC TRUE'
131          CALL PRINT_ERROR( msgBuf, myThid)          CALL PRINT_ERROR( msgBuf, myThid )
132          STOP 'ABNORMAL END: S/R CPL_READPARMS'          STOP 'ABNORMAL END: S/R CPL_READPARMS'
133        ENDIF        ENDIF
134    
# Line 134  C--   Print out parameter values : Line 150  C--   Print out parameter values :
150        CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)        CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
151    
152  C- namelist CPL_ATM_PARAM:  C- namelist CPL_ATM_PARAM:
        CALL WRITE_0D_L( cpl_earlyExpImpCall, INDEX_NONE,  
      &                 'cpl_earlyExpImpCall=',  
      &   ' /* call coupler early in the time-stepping */')  
153         CALL WRITE_0D_L( cpl_oldPickup , INDEX_NONE,         CALL WRITE_0D_L( cpl_oldPickup , INDEX_NONE,
154       &                 'cpl_oldPickup =',       &                 'cpl_oldPickup =',
155       &   ' /* restart from old pickup on/off flag */')       &   ' /* restart from old pickup on/off flag */')
# Line 159  C- namelist CPL_ATM_PARAM: Line 172  C- namelist CPL_ATM_PARAM:
172       &   ' /* Frequency^o-1 for sending data to Coupler (s) */')       &   ' /* Frequency^o-1 for sending data to Coupler (s) */')
173  C     cpl_atmSendFrq  :: Frequency^-1 for sending data to coupler (s)  C     cpl_atmSendFrq  :: Frequency^-1 for sending data to coupler (s)
174         CALL WRITE_0D_I( cplSendFrq_iter, INDEX_NONE,'cplSendFrq_iter =',         CALL WRITE_0D_I( cplSendFrq_iter, INDEX_NONE,'cplSendFrq_iter =',
175       &'   /* send data to coupler every "cplSendFrq" iter */')       &  ' /* send data to coupler every "cplSendFrq" iter */')
176           CALL WRITE_0D_I( maxNumberPrint, INDEX_NONE, 'maxNumberPrint =',
177         &  ' /* max number of printed Exp/Imp messages */')
178    
179  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
180    

Legend:
Removed from v.1.7  
changed lines
  Added in v.1.9

  ViewVC Help
Powered by ViewVC 1.1.22