/[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.4 by jmc, Mon Jun 18 21:28:53 2007 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    
# Line 28  C     == Global variables === Line 28  C     == Global variables ===
28  #include "EEPARAMS.h"  #include "EEPARAMS.h"
29  #include "PARAMS.h"  #include "PARAMS.h"
30  #include "CPL_PARAMS.h"  #include "CPL_PARAMS.h"
31    #include "ATMIDS.h"
32    
33  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
34  C     == Routine Arguments ==        C     == Routine Arguments ==
35  C     myThid -  Number of this instance  C     myThid -  Number of this instance
36        INTEGER myThid        INTEGER myThid
37  CEOP  CEOP
# Line 40  CEOP Line 41  CEOP
41  C Functions  C Functions
42        INTEGER ILNBLNK        INTEGER ILNBLNK
43    
44  C     == Local Variables ==  C     == Local Variables ==
45  C     msgBuf     :: Informational/error meesage buffer  C     msgBuf     :: Informational/error meesage buffer
46  C     iUnit      :: Work variable for IO unit number  C     iUnit      :: Work variable for IO unit number
47  C     k          :: loop counter  C     k          :: loop counter
# Line 51  C     iL         :: Work variable for le Line 52  C     iL         :: Work variable for le
52    
53  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
54    
55  C--   Coupling parameters:  C--   Coupling parameters:
56  C     cpl_earlyExpImpCall :: call coupler early in the time stepping call sequence  C     cpl_earlyExpImpCall :: call coupler early in the time stepping call sequence
57  C     cpl_oldPickup  :: restart from an old pickup (= until checkpoint 52m_post)  C     cpl_oldPickup  :: restart from an old pickup (= until checkpoint 52m_post)
58  C     useImportMxlD  :: True => use Imported Mix.Layer Detph from coupler  C     useImportMxlD  :: True => use Imported Mix.Layer Detph from coupler
59  C     useImportSST   :: True => use the Imported SST from coupler  C     useImportSST   :: True => use the Imported SST from coupler
60  C     useImportSSS   :: True => use the Imported SSS from coupler  C     useImportSSS   :: True => use the Imported SSS from coupler
61  C     useImportVsq   :: True => use the Imported Surf. velocity^2  C     useImportVsq   :: True => use the Imported Surf. velocity^2
62  C     cpl_atmSendFrq :: Frequency^-1 for sending data to coupler (s)  C     useImportFlxCO2 :: True => use the Imported air-sea CO2 fluxes from coupler
63    C     cpl_atmSendFrq :: Frequency^-1 for sending data to coupler (s)
64        NAMELIST /CPL_ATM_PARAM/        NAMELIST /CPL_ATM_PARAM/
65       &    cpl_earlyExpImpCall,       &    cpl_earlyExpImpCall,
66       &    cpl_oldPickup,       &    cpl_oldPickup,
67       &    useImportMxlD, useImportSST, useImportSSS, useImportVsq,       &    useImportMxlD, useImportSST, useImportSSS,
68         &    useImportVsq, useImportFlxCO2,
69       &    cpl_atmSendFrq       &    cpl_atmSendFrq
70    
71  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
72    
73  C-    Set default value:  C-    Set default value:
74        cpl_earlyExpImpCall = .TRUE.        cpl_earlyExpImpCall = .TRUE.
75        cpl_oldPickup = .FALSE.        cpl_oldPickup = .FALSE.
76        useImportMxlD = .TRUE.        useImportMxlD = .TRUE.
77        useImportSST  = .TRUE.        useImportSST  = .TRUE.
78        useImportSSS  = .TRUE.        useImportSSS  = .TRUE.
79        useImportVsq  = .TRUE.        useImportVsq  = .TRUE.
80          IF ( atmCpl_exchange_DIC ) THEN
81            useImportFlxCO2 = .TRUE.
82          ELSE
83            useImportFlxCO2 = .FALSE.
84          ENDIF
85        cpl_atmSendFrq= deltaTClock        cpl_atmSendFrq= deltaTClock
86          
87        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
88          
89        WRITE(msgBuf,'(A)') ' CPL_READPARMS: opening data.cpl'        WRITE(msgBuf,'(A)') ' CPL_READPARMS: opening data.cpl'
90        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
91    
# Line 89  C--   Read parameters from open data fil Line 97  C--   Read parameters from open data fil
97  C-    Parameters for coupling interface:  C-    Parameters for coupling interface:
98        READ(UNIT=iUnit,NML=CPL_ATM_PARAM)        READ(UNIT=iUnit,NML=CPL_ATM_PARAM)
99    
100        WRITE(msgBuf,'(A)')        WRITE(msgBuf,'(A)')
101       &   ' CPL_READPARMS: finished reading data.cpl'       &   ' CPL_READPARMS: finished reading data.cpl'
102        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
103    
104  C--   Close the open data file  C--   Close the open data file
105        CLOSE(iUnit)        CLOSE(iUnit)
106    
107  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
108  C--   Check parameters and model configuration  C--   Check parameters and model configuration
109          IF ( useImportFlxCO2 .AND. .NOT.atmCpl_exchange_DIC ) THEN
110            WRITE(msgBuf,'(2A)') 'CPL_READPARMS: useImportFlxCO2',
111         &    ' requires atmCpl_exchange_DIC TRUE'
112            CALL PRINT_ERROR( msgBuf, myThid)
113            STOP 'ABNORMAL END: S/R CPL_READPARMS'
114          ENDIF
115    
116  C-    derive other parameters:  C-    derive other parameters:
117        cplSendFrq_iter = NINT( cpl_atmSendFrq / deltaTClock )        cplSendFrq_iter = NINT( cpl_atmSendFrq / deltaTClock )
# Line 122  C- namelist CPL_ATM_PARAM: Line 136  C- namelist CPL_ATM_PARAM:
136       &   ' /* call coupler early in the time-stepping */')       &   ' /* call coupler early in the time-stepping */')
137         CALL WRITE_0D_L( cpl_oldPickup , INDEX_NONE,         CALL WRITE_0D_L( cpl_oldPickup , INDEX_NONE,
138       &                 'cpl_oldPickup =',       &                 'cpl_oldPickup =',
139       &   ' /* restart from old pickup on/off flag */')             &   ' /* restart from old pickup on/off flag */')
140         CALL WRITE_0D_L( useImportMxlD , INDEX_NONE,         CALL WRITE_0D_L( useImportMxlD , INDEX_NONE,
141       &                 'useImportMxlD =',       &                 'useImportMxlD =',
142       &   ' /* use Imported MxL. Depth from Coupler flag */')             &   ' /* use Imported MxL. Depth from Coupler flag */')
143         CALL WRITE_0D_L( useImportSST , INDEX_NONE,         CALL WRITE_0D_L( useImportSST , INDEX_NONE,
144       &                 'useImportSST =',       &                 'useImportSST =',
145       &   ' /* use Imported SST from Coupler on/off flag */')             &   ' /* use Imported SST from Coupler on/off flag */')
146         CALL WRITE_0D_L( useImportSSS , INDEX_NONE,         CALL WRITE_0D_L( useImportSSS , INDEX_NONE,
147       &                 'useImportSSS =',       &                 'useImportSSS =',
148       &   ' /* use Imported SSS from Coupler on/off flag */')             &   ' /* use Imported SSS from Coupler on/off flag */')
149         CALL WRITE_0D_L( useImportVsq , INDEX_NONE,         CALL WRITE_0D_L( useImportVsq , INDEX_NONE,
150       &                 'useImportVsq =',       &                 'useImportVsq =',
151       &   ' /* use Imported surf.Vel^2 from Coupler flag */')             &   ' /* use Imported surf.Vel^2 from Coupler flag */')
152           CALL WRITE_0D_L( useImportFlxCO2 , INDEX_NONE,
153         &                 'useImportFlxCO2 =',
154         &   ' /* use Imported air-sea CO2 flux from Coupler flag */')
155         CALL WRITE_0D_R8( cpl_atmSendFrq, INDEX_NONE, 'cpl_atmSendFrq =',         CALL WRITE_0D_R8( cpl_atmSendFrq, INDEX_NONE, 'cpl_atmSendFrq =',
156       &   ' /* Frequency^o-1 for sending data to Coupler (s) */')       &   ' /* Frequency^o-1 for sending data to Coupler (s) */')
157  C     cpl_atmSendFrq  :: Frequency^-1 for sending data to coupler (s)  C     cpl_atmSendFrq  :: Frequency^-1 for sending data to coupler (s)
158         CALL WRITE_0D_I( cplSendFrq_iter, INDEX_NONE,'cplSendFrq_iter =',         CALL WRITE_0D_I( cplSendFrq_iter, INDEX_NONE,'cplSendFrq_iter =',
159       &'   /* send data to coupler every "cplSendFrq" iter */')       &'   /* send data to coupler every "cplSendFrq" iter */')
160    
161  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
162    
163        _END_MASTER(myThid)        _END_MASTER(myThid)
164    
165  C--   Everyone else must wait for the parameters to be loaded  C--   Everyone else must wait for the parameters to be loaded
166        _BARRIER        _BARRIER
167    

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

  ViewVC Help
Powered by ViewVC 1.1.22