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

Annotation 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 - (hide 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 jmc 1.10 C $Header: /u/gcmpack/MITgcm/pkg/ocn_compon_interf/cpl_readparms.F,v 1.9 2007/05/10 21:15:52 jscott Exp $
2 jmc 1.1 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 jmc 1.6
22 jmc 1.1 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 jmc 1.5 #include "CPL_PARAMS.h"
32 jscott 1.9 #include "OCNIDS.h"
33 edhill 1.4 #ifdef ALLOW_MNC
34     #include "MNC_PARAMS.h"
35     #endif
36 jmc 1.1
37     C !INPUT/OUTPUT PARAMETERS:
38 jmc 1.8 C == Routine Arguments ==
39 jmc 1.1 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 jmc 1.8 C == Local Variables ==
49 jmc 1.1 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 jmc 1.8 C-- Coupling parameters:
59 jmc 1.2 C cpl_earlyExpImpCall :: call coupler early in the time stepping call sequence
60 jmc 1.1 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 jmc 1.2 C useImportSLP :: True => use the Imported Sea-level Atmos. Pressure
64 jmc 1.3 C useImportSIce :: True => use the Imported Sea-Ice loading
65 jscott 1.9 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 jmc 1.1 C cpl_taveFreq :: Frequency^-1 for time-Aver. output (s)
69     NAMELIST /CPL_OCN_PARAM/
70 jmc 1.2 & cpl_earlyExpImpCall,
71 jmc 1.3 & useImportHFlx, useImportFW, useImportTau,
72 jscott 1.9 & useImportSLP, useImportSIce, useImportFIce,
73     & useImportCO2, useImportWSpd,
74 edhill 1.4 & cpl_taveFreq, cpl_snapshot_mnc, cpl_timeave_mnc
75 jmc 1.1
76     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
77    
78     C- Set default value:
79 jmc 1.6 cpl_earlyExpImpCall = .TRUE.
80     useImportHFlx = .TRUE.
81 jmc 1.1 useImportFW = .TRUE.
82     useImportTau = .TRUE.
83 jmc 1.2 useImportSLP = .TRUE.
84 jmc 1.3 useImportSIce = .TRUE.
85 jscott 1.9 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 jmc 1.1 cpl_taveFreq = taveFreq
95 jmc 1.5 #ifdef ALLOW_MNC
96 edhill 1.4 cpl_snapshot_mnc = snapshot_mnc
97     cpl_timeave_mnc = timeave_mnc
98 jmc 1.6 #else
99     cpl_snapshot_mnc = .FALSE.
100     cpl_timeave_mnc = .FALSE.
101 jmc 1.5 #endif
102 jmc 1.6
103 jmc 1.1 _BEGIN_MASTER(myThid)
104 jmc 1.6
105 jmc 1.1 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 jmc 1.6 WRITE(msgBuf,'(A)')
117 jmc 1.1 & ' CPL_READPARMS: finished reading data.cpl'
118     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
119 jmc 1.6
120 jmc 1.1 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 jmc 1.3 & 'CPL_READPARMS: cpl_taveFreq > 0 but not compiled pkg/timeave'
131 jmc 1.1 CALL PRINT_ERROR( msgBuf, myThid)
132 jmc 1.3 WRITE(msgBuf,'(A)')
133     & 'Re-compile with pkg "timeave" in packages.conf'
134 jmc 1.1 CALL PRINT_ERROR( msgBuf, myThid)
135     STOP 'ABNORMAL END: S/R CPL_READPARMS'
136     ENDIF
137     #endif /* ALLOW_TIMEAVE */
138    
139 jmc 1.3 #ifndef ATMOSPHERIC_LOADING
140 jmc 1.8 iUnit = errorMessageUnit
141 jmc 1.3 IF ( useImportSLP ) THEN
142 jmc 1.8 WRITE(msgBuf,'(2A)') '** WARNING ** CPL_READPARMS:',
143     & ' useImportSLP is set but'
144     CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
145 jmc 1.3 ELSEIF ( useImportSIce ) THEN
146 jmc 1.8 WRITE(msgBuf,'(2A)') '** WARNING ** CPL_READPARMS:',
147     & ' useImportSIce is set but'
148     CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
149 jmc 1.3 ENDIF
150     IF ( useImportSLP .OR. useImportSIce ) THEN
151 jmc 1.8 WRITE(msgBuf,'(2A)') '** WARNING ** CPL_READPARMS:',
152     & ' pressure loading code is not active.'
153     CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
154 jscott 1.9 C WRITE(msgBuf,'(2A)') '** WARNING **',
155     C & ' Re-compile with: #define ATMOSPHERIC_LOADING'
156     C CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,myThid)
157 jmc 1.3 ENDIF
158 jmc 1.8 #endif /* ATMOSPHERIC_LOADING */
159 jmc 1.3
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 jscott 1.9 IF ( ( useImportFice.OR.useImportCO2.OR.useImportWSpd ) .AND.
172     & (.NOT.ocnCpl_exchange_DIC) ) THEN
173 jmc 1.10 WRITE(msgBuf,'(2A)') 'CPL_READPARMS: useImport',
174 jscott 1.9 & ' 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 edhill 1.4 C Set IO flags
180 jmc 1.6 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 jmc 1.1 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 jmc 1.2 C- namelist CPL_OCN_PARAM:
207     CALL WRITE_0D_L( cpl_earlyExpImpCall, INDEX_NONE,
208     & 'cpl_earlyExpImpCall=',
209 jmc 1.6 & ' /* call coupler early in the time-stepping */')
210 jmc 1.1 CALL WRITE_0D_L( useImportHFlx, INDEX_NONE,
211     & 'useImportHFlx=',
212 jmc 1.6 & ' /* use Imported Heat-Flx fr Coupler on/off flag */')
213 jmc 1.1 CALL WRITE_0D_L( useImportFW , INDEX_NONE,
214     & 'useImportFW =',
215 jmc 1.6 & ' /* use Imported Fresh-Water fr Cpl. on/off flag */')
216 jmc 1.1 CALL WRITE_0D_L( useImportTau , INDEX_NONE,
217     & 'useImportTau =',
218 jmc 1.6 & ' /* use Imported Wind-Stress fr Cpl. on/off flag */')
219 jmc 1.2 CALL WRITE_0D_L( useImportSLP , INDEX_NONE,
220     & 'useImportSLP =',
221 jmc 1.6 & ' /* use Imported Sea-level Atm Press on/off flag */')
222 jmc 1.3 CALL WRITE_0D_L( useImportSIce , INDEX_NONE,
223     & 'useImportSIce=',
224 jmc 1.6 & ' /* use Imported Sea-Ice loading on/off flag */')
225 jmc 1.10 CALL WRITE_0D_L( useImportFIce , INDEX_NONE,
226 jscott 1.9 & 'useImportFIce=',
227     & ' /* use Imported Sea-Ice Fract fr Cpl. on/off flag */')
228 jmc 1.10 CALL WRITE_0D_L( useImportCO2 , INDEX_NONE,
229 jscott 1.9 & 'useImportCO2 =',
230     & ' /* use Imported Atmos. CO2 fr Cpl. on/off flag */')
231 jmc 1.10 CALL WRITE_0D_L( useImportWSpd , INDEX_NONE,
232 jscott 1.9 & 'useImportWSpd =',
233     & ' /* use Imported Windspeed fr Cpl. on/off flag */')
234 jmc 1.1 CALL WRITE_0D_R8( cpl_taveFreq, INDEX_NONE, 'cpl_taveFreq =',
235     & ' /* Frequency^-1 for time-Aver. output (s) */')
236 jmc 1.6 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 jmc 1.1
243     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
244    
245     _END_MASTER(myThid)
246 jmc 1.6
247 jmc 1.1 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