/[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.14 - (hide annotations) (download)
Thu Mar 25 15:35:53 2004 UTC (20 years, 2 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint54, checkpoint53, checkpoint53d_post, checkpoint54b_post, checkpoint52m_post, checkpoint54a_pre, checkpoint53c_post, checkpoint54a_post, checkpoint53a_post, checkpoint53g_post, checkpoint53f_post, checkpoint52n_post, checkpoint53b_pre, checkpoint53b_post, checkpoint53d_pre, checkpoint54c_post
Changes since 1.13: +8 -4 lines
Double check that CD scheme is not turned inconsistent with configuration.

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

  ViewVC Help
Powered by ViewVC 1.1.22