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

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

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


Revision 1.10 - (show annotations) (download)
Mon Dec 2 21:46:57 2013 UTC (10 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint65, checkpoint65p, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e
Changes since 1.9: +11 -3 lines
check that coupling exch frequency is a multiple of the time-step

1 C $Header: /u/gcmpack/MITgcm/pkg/atm_compon_interf/cpl_readparms.F,v 1.9 2013/09/24 23:13:54 jmc Exp $
2 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 #include "SIZE.h"
26 #include "EEPARAMS.h"
27 #include "PARAMS.h"
28 #include "CPL_PARAMS.h"
29 #include "ATMIDS.h"
30
31 C !INPUT/OUTPUT PARAMETERS:
32 C == Routine Arguments ==
33 C myThid :: my Thread Id. number
34 INTEGER myThid
35 CEOP
36
37 #ifdef COMPONENT_MODULE
38
39 C !FUNCTIONS:
40 c INTEGER ILNBLNK
41
42 C !LOCAL VARIABLES:
43 C == Local Variables ==
44 C msgBuf :: Informational/error message 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 C cpl_earlyExpImpCall :: retired; always call coupler early in call sequence
49
50 CHARACTER*(MAX_LEN_MBUF) msgBuf
51 INTEGER iUnit
52 c INTEGER k, iL
53 _RL cpl_atmSendFrq, tmpLoc
54 LOGICAL cpl_earlyExpImpCall
55
56 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
57
58 C-- Coupling parameters:
59 C cpl_earlyExpImpCall :: call coupler early in the time stepping call sequence
60 C cpl_oldPickup :: restart from an old pickup (= until checkpoint 59h)
61 C useImportMxlD :: True => use Imported Mix.Layer Detph from coupler
62 C useImportSST :: True => use the Imported SST from coupler
63 C useImportSSS :: True => use the Imported SSS from coupler
64 C useImportVsq :: True => use the Imported Surf. velocity^2
65 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/
68 & cpl_earlyExpImpCall,
69 & cpl_oldPickup,
70 & useImportMxlD, useImportSST, useImportSSS,
71 & useImportVsq, useImportFlxCO2,
72 & cpl_atmSendFrq,
73 & maxNumberPrint
74
75 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
76
77 _BEGIN_MASTER(myThid)
78
79 C-- Open the data file
80 WRITE(msgBuf,'(A)') ' CPL_READPARMS: opening data.cpl'
81 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
82
83 CALL OPEN_COPY_DATA_FILE( 'data.cpl', 'CPL_READPARMS',
84 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:
104
105 C- Parameters for coupling interface:
106 READ(UNIT=iUnit,NML=CPL_ATM_PARAM)
107
108 WRITE(msgBuf,'(A)')
109 & ' CPL_READPARMS: finished reading data.cpl'
110 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
111
112 C-- Close the open data file
113 CLOSE(iUnit)
114
115 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
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 tmpLoc = NINT( cpl_atmSendFrq / deltaTClock )
135 tmpLoc = ABS( tmpLoc - ( cpl_atmSendFrq / deltaTClock ) )
136 IF ( tmpLoc.GT.1. _d -12 .OR. cpl_atmSendFrq.EQ.zeroRL ) THEN
137 WRITE(msgBuf,'(2A)') 'CPL_READPARMS: cpl_atmSendFrq',
138 & ' is not a multiple of deltaT'
139 CALL PRINT_ERROR( msgBuf, myThid )
140 STOP 'ABNORMAL END: S/R CPL_READPARMS'
141 ENDIF
142
143 C- Derive other parameters:
144 cplSendFrq_iter = NINT( cpl_atmSendFrq / deltaTClock )
145 IF ( cplSendFrq_iter .LT. 1) cplSendFrq_iter = 1
146
147 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
148 C-- Print out parameter values :
149
150 iUnit = standardMessageUnit
151 WRITE(msgBuf,'(A)') ' '
152 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
153 WRITE(msgBuf,'(A)') '// ==================================='
154 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
155 WRITE(msgBuf,'(A)') '// Coupling package parameters :'
156 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
157 WRITE(msgBuf,'(A)') '// ==================================='
158 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
159
160 C- namelist CPL_ATM_PARAM:
161 CALL WRITE_0D_L( cpl_oldPickup , INDEX_NONE,
162 & 'cpl_oldPickup =',
163 & ' /* restart from old pickup on/off flag */')
164 CALL WRITE_0D_L( useImportMxlD , INDEX_NONE,
165 & 'useImportMxlD =',
166 & ' /* use Imported MxL. Depth from Coupler flag */')
167 CALL WRITE_0D_L( useImportSST , INDEX_NONE,
168 & 'useImportSST =',
169 & ' /* use Imported SST from Coupler on/off flag */')
170 CALL WRITE_0D_L( useImportSSS , INDEX_NONE,
171 & 'useImportSSS =',
172 & ' /* use Imported SSS from Coupler on/off flag */')
173 CALL WRITE_0D_L( useImportVsq , INDEX_NONE,
174 & 'useImportVsq =',
175 & ' /* use Imported surf.Vel^2 from Coupler flag */')
176 CALL WRITE_0D_L( useImportFlxCO2 , INDEX_NONE,
177 & 'useImportFlxCO2 =',
178 & ' /* use Imported air-sea CO2 flux from Coupler flag */')
179 CALL WRITE_0D_RL( cpl_atmSendFrq, INDEX_NONE, 'cpl_atmSendFrq =',
180 & ' /* Frequency^o-1 for sending data to Coupler (s) */')
181 C cpl_atmSendFrq :: Frequency^-1 for sending data to coupler (s)
182 CALL WRITE_0D_I( cplSendFrq_iter, INDEX_NONE,'cplSendFrq_iter =',
183 & ' /* send data to coupler every "cplSendFrq" iter */')
184 CALL WRITE_0D_I( maxNumberPrint, INDEX_NONE, 'maxNumberPrint =',
185 & ' /* max number of printed Exp/Imp messages */')
186
187 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
188
189 _END_MASTER(myThid)
190
191 C-- Everyone else must wait for the parameters to be loaded
192 _BARRIER
193
194 #endif /* COMPONENT_MODULE */
195
196 RETURN
197 END

  ViewVC Help
Powered by ViewVC 1.1.22