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

Contents of /MITgcm/pkg/ocn_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 Jun 18 21:06:04 2007 UTC (16 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61l, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
Changes since 1.9: +5 -7 lines
always echo parameters to std-out

1 C $Header: /u/gcmpack/MITgcm/pkg/ocn_compon_interf/cpl_readparms.F,v 1.9 2007/05/10 21:15:52 jscott Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: CPL_READPARMS
9 C !INTERFACE:
10 SUBROUTINE CPL_READPARMS( myThid )
11
12 C !DESCRIPTION: \bv
13 C *==========================================================*
14 C | S/R CPL_READPARMS
15 C | o Read Coupling parameters that control import/export
16 C | from/to the coupler layer
17 C *==========================================================*
18 C | this version is specific to 1 component (ocean)
19 C *==========================================================*
20 C \ev
21
22 C !USES:
23 IMPLICIT NONE
24
25 C == Global variables ===
26
27 #include "SIZE.h"
28
29 #include "EEPARAMS.h"
30 #include "PARAMS.h"
31 #include "CPL_PARAMS.h"
32 #include "OCNIDS.h"
33 #ifdef ALLOW_MNC
34 #include "MNC_PARAMS.h"
35 #endif
36
37 C !INPUT/OUTPUT PARAMETERS:
38 C == Routine Arguments ==
39 C myThid - Number of this instance
40 INTEGER myThid
41 CEOP
42
43 #ifdef COMPONENT_MODULE
44
45 C Functions
46 INTEGER ILNBLNK
47
48 C == Local Variables ==
49 C msgBuf :: Informational/error meesage buffer
50 C iUnit :: Work variable for IO unit number
51 C k :: loop counter
52 C iL :: Work variable for length of file-name
53 CHARACTER*(MAX_LEN_MBUF) msgBuf
54 INTEGER iUnit, k, iL
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 useImportHFlx :: True => use the Imported HeatFlux from couler
61 C useImportFW :: True => use the Imported Fresh Water flux fr cpl
62 C useImportTau :: True => use the Imported Wind-Stress from couler
63 C useImportSLP :: True => use the Imported Sea-level Atmos. Pressure
64 C useImportSIce :: True => use the Imported Sea-Ice loading
65 C useImportFIce :: True => use the Imported Sea-Ice fraction (DIC-only)
66 C useImportCO2 :: True => use the Imported atmos. CO2 from coupler
67 C useImportWSpd :: True => use the Imported surface Wind speed fr cpl
68 C cpl_taveFreq :: Frequency^-1 for time-Aver. output (s)
69 NAMELIST /CPL_OCN_PARAM/
70 & cpl_earlyExpImpCall,
71 & useImportHFlx, useImportFW, useImportTau,
72 & useImportSLP, useImportSIce, useImportFIce,
73 & useImportCO2, useImportWSpd,
74 & cpl_taveFreq, cpl_snapshot_mnc, cpl_timeave_mnc
75
76 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
77
78 C- Set default value:
79 cpl_earlyExpImpCall = .TRUE.
80 useImportHFlx = .TRUE.
81 useImportFW = .TRUE.
82 useImportTau = .TRUE.
83 useImportSLP = .TRUE.
84 useImportSIce = .TRUE.
85 IF ( ocnCpl_exchange_DIC ) THEN
86 useImportFIce = .TRUE.
87 useImportCO2 = .TRUE.
88 useImportWSpd = .TRUE.
89 ELSE
90 useImportFIce = .FALSE.
91 useImportCO2 = .FALSE.
92 useImportWSpd = .FALSE.
93 ENDIF
94 cpl_taveFreq = taveFreq
95 #ifdef ALLOW_MNC
96 cpl_snapshot_mnc = snapshot_mnc
97 cpl_timeave_mnc = timeave_mnc
98 #else
99 cpl_snapshot_mnc = .FALSE.
100 cpl_timeave_mnc = .FALSE.
101 #endif
102
103 _BEGIN_MASTER(myThid)
104
105 WRITE(msgBuf,'(A)') ' CPL_READPARMS: opening data.cpl'
106 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
107
108 CALL OPEN_COPY_DATA_FILE( 'data.cpl', 'CPL_READPARMS',
109 O iUnit, myThid )
110
111 C-- Read parameters from open data file:
112
113 C- Parameters for coupling interface:
114 READ(UNIT=iUnit,NML=CPL_OCN_PARAM)
115
116 WRITE(msgBuf,'(A)')
117 & ' CPL_READPARMS: finished reading data.cpl'
118 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
119
120 C-- Close the open data file
121 CLOSE(iUnit)
122
123 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
124 C-- Check parameters and model configuration
125
126 C- If land_taveFreq is positive, then must compile the land-diagnostics code
127 #ifndef ALLOW_TIMEAVE
128 IF (cpl_taveFreq.GT.0.) THEN
129 WRITE(msgBuf,'(A)')
130 & 'CPL_READPARMS: cpl_taveFreq > 0 but not compiled pkg/timeave'
131 CALL PRINT_ERROR( msgBuf, myThid)
132 WRITE(msgBuf,'(A)')
133 & 'Re-compile with pkg "timeave" in packages.conf'
134 CALL PRINT_ERROR( msgBuf, myThid)
135 STOP 'ABNORMAL END: S/R CPL_READPARMS'
136 ENDIF
137 #endif /* ALLOW_TIMEAVE */
138
139 #ifndef ATMOSPHERIC_LOADING
140 iUnit = errorMessageUnit
141 IF ( useImportSLP ) THEN
142 WRITE(msgBuf,'(2A)') '** WARNING ** CPL_READPARMS:',
143 & ' useImportSLP is set but'
144 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
145 ELSEIF ( useImportSIce ) THEN
146 WRITE(msgBuf,'(2A)') '** WARNING ** CPL_READPARMS:',
147 & ' useImportSIce is set but'
148 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
149 ENDIF
150 IF ( useImportSLP .OR. useImportSIce ) THEN
151 WRITE(msgBuf,'(2A)') '** WARNING ** CPL_READPARMS:',
152 & ' pressure loading code is not active.'
153 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
154 C WRITE(msgBuf,'(2A)') '** WARNING **',
155 C & ' Re-compile with: #define ATMOSPHERIC_LOADING'
156 C CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
157 ENDIF
158 #endif /* ATMOSPHERIC_LOADING */
159
160 IF ( .NOT.cpl_earlyExpImpCall .AND. staggerTimeStep ) THEN
161 WRITE(msgBuf,'(A,L5,A,L5)')
162 & 'CPL_READPARMS: staggerTimeStep=',staggerTimeStep,
163 & ' ; cpl_earlyExpImpCall=', cpl_earlyExpImpCall
164 CALL PRINT_ERROR( msgBuf, myThid)
165 WRITE(msgBuf,'(A)')
166 & 'CPL_READPARMS: taggerTimeStep requires cpl_earlyExpImpCall'
167 CALL PRINT_ERROR( msgBuf, myThid)
168 STOP 'ABNORMAL END: S/R CPL_READPARMS'
169 ENDIF
170
171 IF ( ( useImportFice.OR.useImportCO2.OR.useImportWSpd ) .AND.
172 & (.NOT.ocnCpl_exchange_DIC) ) THEN
173 WRITE(msgBuf,'(2A)') 'CPL_READPARMS: useImport',
174 & ' with DIC variables requires ocnCpl_exchange_DIC TRUE'
175 CALL PRINT_ERROR( msgBuf, myThid)
176 STOP 'ABNORMAL END: S/R CPL_READPARMS'
177 ENDIF
178
179 C Set IO flags
180 cpl_snapshot_mdsio = .TRUE.
181 cpl_timeave_mdsio = .TRUE.
182 #ifdef ALLOW_MNC
183 IF (useMNC) THEN
184 IF ( .NOT.outputTypesInclusive
185 & .AND. cpl_snapshot_mnc ) cpl_snapshot_mdsio = .FALSE.
186 IF ( .NOT.outputTypesInclusive
187 & .AND. cpl_timeave_mnc ) cpl_timeave_mdsio = .FALSE.
188 ENDIF
189 #endif
190
191 C- derive other parameters:
192
193 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
194 C-- Print out parameter values :
195
196 iUnit = standardMessageUnit
197 WRITE(msgBuf,'(A)') ' '
198 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
199 WRITE(msgBuf,'(A)') '// ==================================='
200 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
201 WRITE(msgBuf,'(A)') '// Coupling package parameters :'
202 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
203 WRITE(msgBuf,'(A)') '// ==================================='
204 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
205
206 C- namelist CPL_OCN_PARAM:
207 CALL WRITE_0D_L( cpl_earlyExpImpCall, INDEX_NONE,
208 & 'cpl_earlyExpImpCall=',
209 & ' /* call coupler early in the time-stepping */')
210 CALL WRITE_0D_L( useImportHFlx, INDEX_NONE,
211 & 'useImportHFlx=',
212 & ' /* use Imported Heat-Flx fr Coupler on/off flag */')
213 CALL WRITE_0D_L( useImportFW , INDEX_NONE,
214 & 'useImportFW =',
215 & ' /* use Imported Fresh-Water fr Cpl. on/off flag */')
216 CALL WRITE_0D_L( useImportTau , INDEX_NONE,
217 & 'useImportTau =',
218 & ' /* use Imported Wind-Stress fr Cpl. on/off flag */')
219 CALL WRITE_0D_L( useImportSLP , INDEX_NONE,
220 & 'useImportSLP =',
221 & ' /* use Imported Sea-level Atm Press on/off flag */')
222 CALL WRITE_0D_L( useImportSIce , INDEX_NONE,
223 & 'useImportSIce=',
224 & ' /* use Imported Sea-Ice loading on/off flag */')
225 CALL WRITE_0D_L( useImportFIce , INDEX_NONE,
226 & 'useImportFIce=',
227 & ' /* use Imported Sea-Ice Fract fr Cpl. on/off flag */')
228 CALL WRITE_0D_L( useImportCO2 , INDEX_NONE,
229 & 'useImportCO2 =',
230 & ' /* use Imported Atmos. CO2 fr Cpl. on/off flag */')
231 CALL WRITE_0D_L( useImportWSpd , INDEX_NONE,
232 & 'useImportWSpd =',
233 & ' /* use Imported Windspeed fr Cpl. on/off flag */')
234 CALL WRITE_0D_R8( cpl_taveFreq, INDEX_NONE, 'cpl_taveFreq =',
235 & ' /* Frequency^-1 for time-Aver. output (s) */')
236 CALL WRITE_0D_L( cpl_timeave_mnc , INDEX_NONE,
237 & 'cpl_timeave_mnc =',
238 & ' /* write TimeAv to MNC file on/off flag */')
239 CALL WRITE_0D_L( cpl_timeave_mdsio , INDEX_NONE,
240 & 'cpl_timeave_mdsio =',
241 & ' /* write TimeAv to MDSIO file on/off flag */')
242
243 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
244
245 _END_MASTER(myThid)
246
247 C-- Everyone else must wait for the parameters to be loaded
248 _BARRIER
249
250 #endif /* COMPONENT_MODULE */
251
252 RETURN
253 END

  ViewVC Help
Powered by ViewVC 1.1.22