/[MITgcm]/MITgcm/model/src/config_check.F
ViewVC logotype

Annotation of /MITgcm/model/src/config_check.F

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


Revision 1.16 - (hide annotations) (download)
Thu Oct 14 13:44:54 2004 UTC (19 years, 7 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint55i_post, checkpoint55h_post
Changes since 1.15: +10 -1 lines
 o do package initialization earlier in the boot-up sequence
   - make MNC follow the package guidelines

1 edhill 1.16 C $Header: /u/gcmpack/MITgcm/model/src/config_check.F,v 1.15 2004/07/18 21:59:29 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4 edhill 1.10 #include "PACKAGES_CONFIG.h"
5 jmc 1.1 #include "CPP_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: CONFIG_CHECK
9     C !INTERFACE:
10     SUBROUTINE CONFIG_CHECK( myThid )
11     C !DESCRIPTION: \bv
12     C *=========================================================*
13     C | SUBROUTINE CONFIG_CHECK
14     C | o Check model parameter settings.
15     C *=========================================================*
16     C | This routine help to prevent the use of parameters
17     C | that are not compatible with the model configuration.
18     C *=========================================================*
19     C \ev
20    
21     C !USES:
22     IMPLICIT NONE
23     C === Global variables ===
24     #include "SIZE.h"
25     #include "EEPARAMS.h"
26     #include "PARAMS.h"
27     c #include "GRID.h"
28    
29     C !INPUT/OUTPUT PARAMETERS:
30     C === Routine arguments ===
31     C myThid - Number of this instances of CONFIG_CHECK
32     INTEGER myThid
33     CEndOfInterface
34    
35     C !LOCAL VARIABLES:
36     C == Local variables ==
37     C msgBuf :: Informational/error meesage buffer
38     CHARACTER*(MAX_LEN_MBUF) msgBuf
39     CEOP
40    
41     C- check that CPP option is "defined" when running-flag parameter is on:
42    
43 edhill 1.16 #ifndef ALLOW_MNC
44     IF (useMNC) THEN
45     WRITE(msgBuf,'(2A)') '**WARNNING** ',
46     & 'CONFIG_CHECK: useMNC is TRUE and #undef ALLOW_MNC'
47     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
48     & SQUEEZE_RIGHT , myThid)
49     ENDIF
50     #endif
51    
52 edhill 1.11 #ifndef ALLOW_CD_CODE
53 jmc 1.9 IF (useCDscheme) THEN
54 adcroft 1.14 WRITE(msgBuf,'(A)')
55     & 'CONFIG_CHECK: useCDscheme is TRUE and #undef ALLOW_CD_CODE'
56 jmc 1.9 CALL PRINT_ERROR( msgBuf , myThid)
57 adcroft 1.14 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
58     ENDIF
59     IF (tauCD.NE.0.) THEN
60 jmc 1.9 WRITE(msgBuf,'(A)')
61 adcroft 1.14 & 'CONFIG_CHECK: tauCD has been set but the cd_code package is',
62     & ' enabled'
63 jmc 1.9 CALL PRINT_ERROR( msgBuf , myThid)
64     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
65     ENDIF
66     #endif
67    
68 jmc 1.1 #ifndef ALLOW_NONHYDROSTATIC
69     IF (nonHydrostatic) THEN
70     WRITE(msgBuf,'(A)')
71     & 'CONFIG_CHECK: #undef ALLOW_NONHYDROSTATIC and'
72 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
73 jmc 1.1 WRITE(msgBuf,'(A)')
74     & 'CONFIG_CHECK: nonHydrostatic is TRUE'
75 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
76 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
77     ENDIF
78     #endif
79    
80 jmc 1.13 #ifndef INCLUDE_IMPLVERTADV_CODE
81     IF ( momImplVertAdv ) THEN
82     WRITE(msgBuf,'(A)')
83     & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
84     CALL PRINT_ERROR( msgBuf , myThid)
85     WRITE(msgBuf,'(A)')
86     & 'CONFIG_CHECK: but momImplVertAdv is TRUE'
87     CALL PRINT_ERROR( msgBuf , myThid)
88     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
89     ENDIF
90     IF ( tempImplVertAdv ) THEN
91     WRITE(msgBuf,'(A)')
92     & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
93     CALL PRINT_ERROR( msgBuf , myThid)
94     WRITE(msgBuf,'(A)')
95     & 'CONFIG_CHECK: but tempImplVertAdv is TRUE'
96     CALL PRINT_ERROR( msgBuf , myThid)
97     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
98     ENDIF
99     IF ( saltImplVertAdv ) THEN
100     WRITE(msgBuf,'(A)')
101     & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
102     CALL PRINT_ERROR( msgBuf , myThid)
103     WRITE(msgBuf,'(A)')
104     & 'CONFIG_CHECK: but saltImplVertAdv is TRUE'
105     CALL PRINT_ERROR( msgBuf , myThid)
106     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
107     ENDIF
108     #endif
109    
110 jmc 1.1 #ifndef EXACT_CONSERV
111     IF (exactConserv) THEN
112     WRITE(msgBuf,'(A)')
113     & 'CONFIG_CHECK: #undef EXACT_CONSERV and'
114 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
115 jmc 1.1 WRITE(msgBuf,'(A)')
116     & 'CONFIG_CHECK: exactConserv is TRUE'
117 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
118 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
119     ENDIF
120     #endif
121    
122     #ifndef NONLIN_FRSURF
123     IF (nonlinFreeSurf.NE.0) THEN
124     WRITE(msgBuf,'(A)')
125     & 'CONFIG_CHECK: #undef NONLIN_FRSURF and'
126 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
127 jmc 1.1 WRITE(msgBuf,'(A)')
128     & 'CONFIG_CHECK: nonlinFreeSurf is non-zero'
129 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
130 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
131     ENDIF
132     #endif
133    
134 jmc 1.9 #ifndef NONLIN_FRSURF
135     IF (select_rStar .NE. 0) THEN
136     WRITE(msgBuf,'(A)')
137     & 'CONFIG_CHECK: rStar is part of NonLin-FS '
138     CALL PRINT_ERROR( msgBuf, myThid)
139     WRITE(msgBuf,'(A)')
140     & 'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to use it'
141     CALL PRINT_ERROR( msgBuf, myThid)
142     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
143     ENDIF
144     #endif /* NONLIN_FRSURF */
145    
146 jmc 1.1 #ifdef USE_NATURAL_BCS
147     WRITE(msgBuf,'(A)')
148 jmc 1.3 & 'CONFIG_CHECK: USE_NATURAL_BCS option has been replaced'
149     CALL PRINT_ERROR( msgBuf , myThid)
150 jmc 1.1 WRITE(msgBuf,'(A)')
151 jmc 1.3 & 'CONFIG_CHECK: by useRealFreshWaterFlux=TRUE in data file'
152     CALL PRINT_ERROR( msgBuf , myThid)
153 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
154 jmc 1.3 #endif
155    
156 jmc 1.4 C o If pLoadFile is set, then we should make sure the corresponing
157     C code is being compiled
158     #ifndef ATMOSPHERIC_LOADING
159     IF (pLoadFile.NE.' ') THEN
160     WRITE(msgBuf,'(A)')
161     & 'CONFIG_CHECK: pLoadFile is set but you have not'
162     CALL PRINT_ERROR( msgBuf , myThid)
163     WRITE(msgBuf,'(A)')
164     & 'compiled the model with the pressure loading code.'
165     CALL PRINT_ERROR( msgBuf , myThid)
166 jmc 1.15 WRITE(msgBuf,'(A)')
167     & 'Re-compile with: #define ATMOSPHERIC_LOADING'
168     CALL PRINT_ERROR( msgBuf , myThid)
169     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
170     ENDIF
171     IF ( useRealFreshWaterFlux .AND. useThSIce ) THEN
172     WRITE(msgBuf,'(A)')
173     & 'CONFIG_CHECK: sIceLoad is computed but'
174     CALL PRINT_ERROR( msgBuf , myThid)
175     WRITE(msgBuf,'(A)')
176     & 'pressure loading code is not compiled.'
177     CALL PRINT_ERROR( msgBuf , myThid)
178     WRITE(msgBuf,'(A)')
179     & 'Re-compile with: #define ATMOSPHERIC_LOADING'
180 jmc 1.4 CALL PRINT_ERROR( msgBuf , myThid)
181     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
182     ENDIF
183     #endif
184    
185     C o If taveFreq is finite, then we must make sure the diagnostics
186     C code is being compiled
187     #ifndef ALLOW_TIMEAVE
188     IF (taveFreq.NE.0.) THEN
189     WRITE(msgBuf,'(A)')
190 jmc 1.15 & 'CONFIG_CHECK: taveFreq <> 0 but pkg/timeave is not compiled'
191 jmc 1.4 CALL PRINT_ERROR( msgBuf , 1)
192     WRITE(msgBuf,'(A)')
193 jmc 1.15 & 'Re-compile with pkg "timeave" in packages.conf'
194 jmc 1.4 CALL PRINT_ERROR( msgBuf , 1)
195     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
196     ENDIF
197     #endif
198    
199 jmc 1.3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
200    
201     C- check parameter consistency :
202 jmc 1.8
203     IF ( viscA4.NE.0. .AND. (Olx.LT.3 .OR. Oly.LT.3)) THEN
204     WRITE(msgBuf,'(A,A)')
205     & 'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',
206     & ' overlap (Olx,Oly) smaller than 3'
207     CALL PRINT_ERROR( msgBuf , myThid)
208     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
209     ENDIF
210 jmc 1.3
211     IF ( rigidLid .AND. implicitFreeSurface ) THEN
212     WRITE(msgBuf,'(A,A)')
213     & 'CONFIG_CHECK: Cannot select both implicitFreeSurface',
214     & ' and rigidLid.'
215     CALL PRINT_ERROR( msgBuf , myThid)
216     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
217     ENDIF
218    
219     IF (rigidLid .AND. exactConserv) THEN
220 jmc 1.1 WRITE(msgBuf,'(A)')
221 jmc 1.3 & 'CONFIG_CHECK: exactConserv not compatible with'
222     CALL PRINT_ERROR( msgBuf , myThid)
223 jmc 1.1 WRITE(msgBuf,'(A)')
224 jmc 1.3 & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
225     CALL PRINT_ERROR( msgBuf , myThid)
226 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
227     ENDIF
228    
229 jmc 1.3 IF (rigidLid .AND. useRealFreshWaterFlux) THEN
230 jmc 1.1 WRITE(msgBuf,'(A)')
231 jmc 1.3 & 'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'
232     CALL PRINT_ERROR( msgBuf , myThid)
233 jmc 1.1 WRITE(msgBuf,'(A)')
234     & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
235 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
236     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
237     ENDIF
238    
239     IF ( (implicSurfPress.NE.1. .OR. implicDiv2DFlow.NE.1.)
240     & .AND. nonHydrostatic ) THEN
241     WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: nonHydrostatic',
242     & ' NOT SAFE with non-fully implicit Barotropic solver'
243     CALL PRINT_ERROR( msgBuf , myThid)
244     WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: To by-pass this',
245     & 'STOP, comment this test and re-compile config_check'
246     CALL PRINT_ERROR( msgBuf , myThid)
247 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
248     ENDIF
249    
250     IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN
251     WRITE(msgBuf,'(A)')
252     & 'CONFIG_CHECK: nonlinFreeSurf cannot be used'
253 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
254 jmc 1.1 WRITE(msgBuf,'(A)')
255     & 'CONFIG_CHECK: without exactConserv'
256 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
257 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
258     ENDIF
259    
260 jmc 1.6 IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN
261     WRITE(msgBuf,'(A)')
262     & 'CONFIG_CHECK: r* Coordinate cannot be used'
263     CALL PRINT_ERROR( msgBuf , myThid)
264     WRITE(msgBuf,'(A)')
265     & 'CONFIG_CHECK: without exactConserv'
266     CALL PRINT_ERROR( msgBuf , myThid)
267     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
268     ENDIF
269    
270 jmc 1.7 C- note : not implemented in checkpoint48b but it's done now (since 01-28-03)
271     c IF (select_rStar.GT.0 .AND. useOBCS ) THEN
272     c WRITE(msgBuf,'(A)')
273     c & 'CONFIG_CHECK: r* Coordinate not yet implemented'
274     c CALL PRINT_ERROR( msgBuf , 1)
275     c WRITE(msgBuf,'(A)')
276     c & 'CONFIG_CHECK: in OBC package'
277     c CALL PRINT_ERROR( msgBuf , 1)
278     c STOP 'ABNORMAL END: S/R CONFIG_CHECK'
279     c ENDIF
280 jmc 1.1
281     IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN
282     WRITE(msgBuf,'(A)')
283     & 'CONFIG_CHECK: nonlinFreeSurf not yet implemented'
284 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
285 jmc 1.1 WRITE(msgBuf,'(A)')
286     & 'CONFIG_CHECK: in nonHydrostatic code'
287 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
288 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
289     ENDIF
290 jmc 1.3
291 jmc 1.4 IF (nonlinFreeSurf.NE.0.AND.deltaTfreesurf.NE.deltaTtracer) THEN
292 jmc 1.3 WRITE(msgBuf,'(A)')
293 jmc 1.4 & 'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'
294     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
295     & SQUEEZE_RIGHT , myThid)
296     WRITE(msgBuf,'(A)')
297     & 'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'
298     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
299     & SQUEEZE_RIGHT , myThid)
300 jmc 1.3 ENDIF
301    
302 jmc 1.15 IF ( useRealFreshWaterFlux .AND. exactConserv
303     & .AND. implicDiv2DFlow.EQ.0. _d 0
304     & .AND. startTime.NE.0. .AND. usePickupBeforeC54 ) THEN
305 jmc 1.3 WRITE(msgBuf,'(A)')
306     & 'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'
307     CALL PRINT_ERROR( msgBuf , myThid)
308     WRITE(msgBuf,'(A)')
309     & 'CONFIG_CHECK: restart not implemented in this config'
310     CALL PRINT_ERROR( msgBuf , myThid)
311     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
312     ENDIF
313    
314 jmc 1.15 IF ( useRealFreshWaterFlux .AND. .NOT.exactConserv
315     & .AND. implicDiv2DFlow.NE.1. ) THEN
316     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: **WARNNING** ',
317     & 'RealFreshWater & implicDiv2DFlow < 1'
318     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
319     & SQUEEZE_RIGHT , myThid)
320     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: works better',
321     & ' with exactConserv=.T. (+ #define EXACT_CONSERV)'
322     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
323     & SQUEEZE_RIGHT , myThid)
324     ENDIF
325    
326     #ifdef EXACT_CONSERV
327 jmc 1.4 IF (useRealFreshWaterFlux .AND. .NOT.exactConserv
328     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
329     WRITE(msgBuf,'(A)')
330     & 'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'
331     CALL PRINT_ERROR( msgBuf , myThid)
332     WRITE(msgBuf,'(A)')
333     & 'CONFIG_CHECK: requires exactConserv=T'
334     CALL PRINT_ERROR( msgBuf , myThid)
335     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
336     ENDIF
337     #else
338     IF (useRealFreshWaterFlux
339     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
340     WRITE(msgBuf,'(A)')
341     & 'CONFIG_CHECK: E-P effects on wVel are not included'
342     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
343     & SQUEEZE_RIGHT , myThid)
344     WRITE(msgBuf,'(A)')
345 jmc 1.15 & 'CONFIG_CHECK: ==> use #define EXACT_CONSERV to fix it'
346 jmc 1.5 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
347     & SQUEEZE_RIGHT , myThid)
348     ENDIF
349 jmc 1.15 #endif /* EXACT_CONSERV */
350 jmc 1.5
351 jmc 1.9 IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN
352     C- jmc: since useCDscheme is a new [04-13-03] flag (default=F),
353     C put this WARNING to stress that even if CD-scheme parameters
354     C (tauCD,rCD) are set, CD-scheme is not used without useCDscheme=T
355     C- and STOP if using mom_fluxform (following Chris advise).
356     C- jmc: but ultimately, this block can/will be removed.
357     IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN
358     WRITE(msgBuf,'(A)')
359     & 'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
360     CALL PRINT_ERROR( msgBuf , myThid)
361     WRITE(msgBuf,'(2A)')
362     & 'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
363     & ' in "data", namelist PARM01'
364     CALL PRINT_ERROR( msgBuf , myThid)
365     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
366     ENDIF
367     WRITE(msgBuf,'(2A)') '**WARNNING** ',
368     & 'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
369 jmc 1.5 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
370     & SQUEEZE_RIGHT , myThid)
371 jmc 1.9 WRITE(msgBuf,'(2A)')
372     & 'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
373     & ' in "data", namelist PARM01'
374 jmc 1.4 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
375     & SQUEEZE_RIGHT , myThid)
376 jmc 1.12 ENDIF
377    
378     IF ( useCDscheme .AND. useCubedSphereExchange ) THEN
379     WRITE(msgBuf,'(2A)')
380     & 'CONFIG_CHECK: CD-scheme not implemented on CubedSphere grid'
381     CALL PRINT_ERROR( msgBuf , myThid)
382     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
383     ENDIF
384    
385     IF ( useOldFreezing .AND. allowFreezing ) THEN
386     WRITE(msgBuf,'(2A)')
387     & 'CONFIG_CHECK: cannot set both: allowFreezing & useOldFreezing'
388     CALL PRINT_ERROR( msgBuf , myThid)
389     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
390 jmc 1.4 ENDIF
391 jmc 1.1
392     WRITE(msgBuf,'(A)') 'CONFIG_CHECK: OK'
393     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
394     & SQUEEZE_RIGHT,myThid)
395    
396     RETURN
397     END

  ViewVC Help
Powered by ViewVC 1.1.22