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

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

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


Revision 1.2 - (hide annotations) (download)
Fri May 21 20:00:48 2004 UTC (20 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint53d_post, checkpoint54a_pre, checkpoint54a_post, checkpoint53c_post, checkpoint54b_post, checkpoint54, checkpoint53g_post, checkpoint53f_post, checkpoint53d_pre, checkpoint54c_post
Changes since 1.1: +32 -6 lines
new version of atmosphere-coupler interface for AIM+thSIce and ocean models

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/aim_compon_interf/cpl_readparms.F,v 1.1 2003/12/15 02:44:48 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "CPP_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: CPL_READPARMS
8     C !INTERFACE:
9     SUBROUTINE CPL_READPARMS( myThid )
10    
11     C !DESCRIPTION: \bv
12     C *==========================================================*
13     C | S/R CPL_READPARMS
14     C | o Read Coupling parameters that control import/export
15     C | from/to the coupler layer
16     C *==========================================================*
17     C | this version is specific to 1 component (atmos)
18     C *==========================================================*
19     C \ev
20    
21     C !USES:
22     IMPLICIT NONE
23    
24     C == Global variables ===
25    
26     #include "SIZE.h"
27    
28     #include "EEPARAMS.h"
29     #include "PARAMS.h"
30     #include "CPL_PARAMS.h"
31    
32     C !INPUT/OUTPUT PARAMETERS:
33     C == Routine Arguments ==
34     C myThid - Number of this instance
35     INTEGER myThid
36     CEOP
37    
38     #ifdef COMPONENT_MODULE
39    
40     C Functions
41     INTEGER ILNBLNK
42    
43     C == Local Variables ==
44     C msgBuf :: Informational/error meesage buffer
45     C iUnit :: Work variable for IO unit number
46     C k :: loop counter
47     C iL :: Work variable for length of file-name
48     CHARACTER*(MAX_LEN_MBUF) msgBuf
49     INTEGER iUnit, k, iL
50     _RL cpl_atmSendFrq
51    
52     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
53    
54     C-- Coupling parameters:
55 jmc 1.2 C cpl_earlyExpImpCall :: call coupler early in the time stepping call sequence
56     C cpl_oldPickup :: restart from an old pickup (= until checkpoint 52m_post)
57     C useImportMxlD :: True => use Imported Mix.Layer Detph from coupler
58     C useImportSST :: True => use the Imported SST from coupler
59     C useImportSSS :: True => use the Imported SSS from coupler
60     C useImportVsq :: True => use the Imported Surf. velocity^2
61 jmc 1.1 C cpl_atmSendFrq :: Frequency^-1 for sending data to coupler (s)
62     NAMELIST /CPL_ATM_PARAM/
63 jmc 1.2 & cpl_earlyExpImpCall,
64     & cpl_oldPickup,
65     & useImportMxlD, useImportSST, useImportSSS, useImportVsq,
66 jmc 1.1 & cpl_atmSendFrq
67    
68     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
69    
70     C- Set default value:
71 jmc 1.2 cpl_earlyExpImpCall = .FALSE.
72     cpl_oldPickup = .FALSE.
73     useImportMxlD = .TRUE.
74     useImportSST = .TRUE.
75     useImportSSS = .TRUE.
76     useImportVsq = .TRUE.
77     cpl_atmSendFrq= deltaTClock
78 jmc 1.1
79     _BEGIN_MASTER(myThid)
80    
81     WRITE(msgBuf,'(A)') ' CPL_READPARMS: opening data.cpl'
82     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
83    
84     CALL OPEN_COPY_DATA_FILE( 'data.cpl', 'CPL_READPARMS',
85     O iUnit, myThid )
86    
87     C-- Read parameters from open data file:
88    
89     C- Parameters for coupling interface:
90     READ(UNIT=iUnit,NML=CPL_ATM_PARAM)
91    
92     WRITE(msgBuf,'(A)')
93     & ' CPL_READPARMS: finished reading data.cpl'
94     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
95    
96     C-- Close the open data file
97     CLOSE(iUnit)
98    
99     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
100     C-- Check parameters and model configuration
101    
102     C- derive other parameters:
103     cplSendFrq_iter = NINT( cpl_atmSendFrq / deltaTClock )
104     IF ( cplSendFrq_iter .LT. 1) cplSendFrq_iter = 1
105    
106     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
107     C-- Print out parameter values :
108    
109     iUnit = standardMessageUnit
110     WRITE(msgBuf,'(A)') ' '
111     CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
112     WRITE(msgBuf,'(A)') '// ==================================='
113     CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
114     WRITE(msgBuf,'(A)') '// Coupling package parameters :'
115     CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
116     WRITE(msgBuf,'(A)') '// ==================================='
117     CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
118    
119     C- namelist CPL_ATM_PARAM:
120 jmc 1.2 CALL WRITE_0D_L( cpl_earlyExpImpCall, INDEX_NONE,
121     & 'cpl_earlyExpImpCall=',
122     & ' /* call coupler early in the time-stepping */')
123     CALL WRITE_0D_L( cpl_oldPickup , INDEX_NONE,
124     & 'cpl_oldPickup =',
125     & ' /* restart from old pickup on/off flag */')
126     CALL WRITE_0D_L( useImportMxlD , INDEX_NONE,
127     & 'useImportMxlD =',
128     & ' /* use Imported MxL. Depth from Coupler flag */')
129 jmc 1.1 CALL WRITE_0D_L( useImportSST , INDEX_NONE,
130     & 'useImportSST =',
131     & ' /* use Imported SST from Coupler on/off flag */')
132 jmc 1.2 CALL WRITE_0D_L( useImportSSS , INDEX_NONE,
133     & 'useImportSSS =',
134     & ' /* use Imported SSS from Coupler on/off flag */')
135     CALL WRITE_0D_L( useImportVsq , INDEX_NONE,
136     & 'useImportVsq =',
137     & ' /* use Imported surf.Vel^2 from Coupler flag */')
138 jmc 1.1 CALL WRITE_0D_R8( cpl_atmSendFrq, INDEX_NONE, 'cpl_atmSendFrq =',
139     & ' /* Frequency^o-1 for sending data to Coupler (s) */')
140     C cpl_atmSendFrq :: Frequency^-1 for sending data to coupler (s)
141     CALL WRITE_0D_I( cplSendFrq_iter, INDEX_NONE,'cplSendFrq_iter =',
142     &' /* send data to coupler every "cplSendFrq" iter */')
143    
144     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
145    
146     _END_MASTER(myThid)
147    
148     C-- Everyone else must wait for the parameters to be loaded
149     _BARRIER
150    
151     #endif /* COMPONENT_MODULE */
152    
153     RETURN
154     END

  ViewVC Help
Powered by ViewVC 1.1.22