/[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.13 - (hide annotations) (download)
Sat Jan 3 00:34:00 2004 UTC (20 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, hrcube5, checkpoint52j_pre, checkpoint52l_post, checkpoint52k_post, checkpoint52f_post, checkpoint52i_pre, hrcube_1, hrcube_2, hrcube_3, checkpoint52e_post, checkpoint52f_pre, checkpoint52i_post, checkpoint52h_pre, checkpoint52j_post
Changes since 1.12: +31 -2 lines
add run-time parameters for implicit vertical advection.

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

  ViewVC Help
Powered by ViewVC 1.1.22