/[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.12 - (show annotations) (download)
Fri Dec 25 19:45:13 2009 UTC (14 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64i, checkpoint64h, checkpoint64j, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.11: +17 -14 lines
fix for multi-threaded

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

  ViewVC Help
Powered by ViewVC 1.1.22