/[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.6 - (hide annotations) (download)
Tue Apr 19 14:36:08 2005 UTC (19 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, checkpoint57v_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint57i_post, checkpoint57y_post, checkpoint58n_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58j_post, checkpoint57r_post, checkpoint58, checkpoint57h_done, checkpoint58f_post, checkpoint57x_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58k_post, checkpoint58p_post, checkpoint57j_post, checkpoint58b_post, checkpoint57h_pre, checkpoint58m_post, checkpoint57l_post, checkpoint57h_post
Changes since 1.5: +36 -23 lines
fix I/O flags initialisation.

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

  ViewVC Help
Powered by ViewVC 1.1.22