/[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.3 by jmc, Mon Jul 26 20:08:34 2004 UTC revision 1.9 by jmc, Tue Sep 24 23:13:54 2013 UTC
# Line 17  C     *================================= Line 17  C     *=================================
17  C     |   this version is specific to 1 component (atmos)  C     |   this version is specific to 1 component (atmos)
18  C     *==========================================================*  C     *==========================================================*
19  C     \ev  C     \ev
20    
21  C     !USES:  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"
29    #include "ATMIDS.h"
30    
31  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
32  C     == Routine Arguments ==        C     == Routine Arguments ==
33  C     myThid -  Number of this instance  C     myThid     :: my Thread Id. number
34        INTEGER myThid        INTEGER myThid
35  CEOP  CEOP
36    
37  #ifdef COMPONENT_MODULE  #ifdef COMPONENT_MODULE
38    
39  C Functions  C     !FUNCTIONS:
40        INTEGER ILNBLNK  c     INTEGER ILNBLNK
41    
42  C     == Local Variables ==  C     !LOCAL VARIABLES:
43  C     msgBuf     :: Informational/error meesage buffer  C     == Local Variables ==
44    C     msgBuf     :: Informational/error message buffer
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, k, iL        INTEGER iUnit
52    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    
58  C--   Coupling parameters:  C--   Coupling parameters:
59  C     cpl_earlyExpImpCall :: call coupler early in the time stepping call sequence  C     cpl_earlyExpImpCall :: call coupler early in the time stepping call sequence
60  C     cpl_oldPickup  :: restart from an old pickup (= until checkpoint 52m_post)  C     cpl_oldPickup  :: restart from an old pickup (= until checkpoint 59h)
61  C     useImportMxlD  :: True => use Imported Mix.Layer Detph from coupler  C     useImportMxlD  :: True => use Imported Mix.Layer Detph from coupler
62  C     useImportSST   :: True => use the Imported SST from coupler  C     useImportSST   :: True => use the Imported SST from coupler
63  C     useImportSSS   :: True => use the Imported SSS from coupler  C     useImportSSS   :: True => use the Imported SSS from coupler
64  C     useImportVsq   :: True => use the Imported Surf. velocity^2  C     useImportVsq   :: True => use the Imported Surf. velocity^2
65  C     cpl_atmSendFrq :: Frequency^-1 for sending data to coupler (s)  C     useImportFlxCO2 :: True => use the Imported air-sea CO2 fluxes from coupler
66    C     cpl_atmSendFrq :: Frequency^-1 for sending data to coupler (s)
67        NAMELIST /CPL_ATM_PARAM/        NAMELIST /CPL_ATM_PARAM/
68       &    cpl_earlyExpImpCall,       &    cpl_earlyExpImpCall,
69       &    cpl_oldPickup,       &    cpl_oldPickup,
70       &    useImportMxlD, useImportSST, useImportSSS, useImportVsq,       &    useImportMxlD, useImportSST, useImportSSS,
71       &    cpl_atmSendFrq       &    useImportVsq, useImportFlxCO2,
72         &    cpl_atmSendFrq,
73         &    maxNumberPrint
74    
75  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
76    
 C-    Set default value:  
       cpl_earlyExpImpCall = .TRUE.  
       cpl_oldPickup = .FALSE.  
       useImportMxlD = .TRUE.  
       useImportSST  = .TRUE.  
       useImportSSS  = .TRUE.  
       useImportVsq  = .TRUE.  
       cpl_atmSendFrq= deltaTClock  
         
77        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
78          
79    C--   Open the data file
80        WRITE(msgBuf,'(A)') ' CPL_READPARMS: opening data.cpl'        WRITE(msgBuf,'(A)') ' CPL_READPARMS: opening data.cpl'
81        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
82    
83        CALL OPEN_COPY_DATA_FILE( 'data.cpl', 'CPL_READPARMS',        CALL OPEN_COPY_DATA_FILE( 'data.cpl', 'CPL_READPARMS',
84       O                          iUnit, myThid )       O                          iUnit, myThid )
85    
86    C-    Set default value:
87          cpl_earlyExpImpCall = .TRUE.
88          cpl_oldPickup = .FALSE.
89          useImportMxlD = .TRUE.
90          useImportSST  = .TRUE.
91          useImportSSS  = .TRUE.
92          useImportVsq  = .TRUE.
93          IF ( atmCpl_exchange_DIC ) THEN
94            useImportFlxCO2 = .TRUE.
95          ELSE
96            useImportFlxCO2 = .FALSE.
97          ENDIF
98          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    
105  C-    Parameters for coupling interface:  C-    Parameters for coupling interface:
106        READ(UNIT=iUnit,NML=CPL_ATM_PARAM)        READ(UNIT=iUnit,NML=CPL_ATM_PARAM)
107    
108        WRITE(msgBuf,'(A)')        WRITE(msgBuf,'(A)')
109       &   ' CPL_READPARMS: finished reading data.cpl'       &   ' CPL_READPARMS: finished reading data.cpl'
110        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
111    
112  C--   Close the open data file  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
129            WRITE(msgBuf,'(2A)') 'CPL_READPARMS: useImportFlxCO2',
130         &    ' requires atmCpl_exchange_DIC TRUE'
131            CALL PRINT_ERROR( msgBuf, myThid )
132            STOP 'ABNORMAL END: S/R CPL_READPARMS'
133          ENDIF
134    
135  C-    derive other parameters:  C-    derive other parameters:
136        cplSendFrq_iter = NINT( cpl_atmSendFrq / deltaTClock )        cplSendFrq_iter = NINT( cpl_atmSendFrq / deltaTClock )
# Line 117  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 */')
156         CALL WRITE_0D_L( useImportMxlD , INDEX_NONE,         CALL WRITE_0D_L( useImportMxlD , INDEX_NONE,
157       &                 'useImportMxlD =',       &                 'useImportMxlD =',
158       &   ' /* use Imported MxL. Depth from Coupler flag */')             &   ' /* use Imported MxL. Depth from Coupler flag */')
159         CALL WRITE_0D_L( useImportSST , INDEX_NONE,         CALL WRITE_0D_L( useImportSST , INDEX_NONE,
160       &                 'useImportSST =',       &                 'useImportSST =',
161       &   ' /* use Imported SST from Coupler on/off flag */')             &   ' /* use Imported SST from Coupler on/off flag */')
162         CALL WRITE_0D_L( useImportSSS , INDEX_NONE,         CALL WRITE_0D_L( useImportSSS , INDEX_NONE,
163       &                 'useImportSSS =',       &                 'useImportSSS =',
164       &   ' /* use Imported SSS from Coupler on/off flag */')             &   ' /* use Imported SSS from Coupler on/off flag */')
165         CALL WRITE_0D_L( useImportVsq , INDEX_NONE,         CALL WRITE_0D_L( useImportVsq , INDEX_NONE,
166       &                 'useImportVsq =',       &                 'useImportVsq =',
167       &   ' /* use Imported surf.Vel^2 from Coupler flag */')             &   ' /* use Imported surf.Vel^2 from Coupler flag */')
168         CALL WRITE_0D_R8( cpl_atmSendFrq, INDEX_NONE, 'cpl_atmSendFrq =',         CALL WRITE_0D_L( useImportFlxCO2 , INDEX_NONE,
169         &                 'useImportFlxCO2 =',
170         &   ' /* use Imported air-sea CO2 flux from Coupler flag */')
171           CALL WRITE_0D_RL( cpl_atmSendFrq, INDEX_NONE, 'cpl_atmSendFrq =',
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    
181        _END_MASTER(myThid)        _END_MASTER(myThid)
182    
183  C--   Everyone else must wait for the parameters to be loaded  C--   Everyone else must wait for the parameters to be loaded
184        _BARRIER        _BARRIER
185    

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

  ViewVC Help
Powered by ViewVC 1.1.22