/[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.9 - (hide annotations) (download)
Thu Apr 17 13:16:23 2003 UTC (21 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint50c_post, checkpoint50c_pre, checkpoint51, checkpoint50d_post, checkpoint51f_post, checkpoint51d_post, checkpoint51j_post, checkpoint51b_pre, checkpoint51h_pre, checkpoint50f_post, checkpoint50f_pre, branchpoint-genmake2, checkpoint51b_post, checkpoint51c_post, checkpoint50g_post, checkpoint50h_post, checkpoint50e_pre, checkpoint50i_post, checkpoint51i_pre, checkpoint50e_post, checkpoint50d_pre, checkpoint51e_post, checkpoint51f_pre, checkpoint51g_post, checkpoint50b_post, checkpoint51a_post
Branch point for: branch-genmake2
Changes since 1.8: +47 -7 lines
new flag "useCDscheme" (default=F);

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

  ViewVC Help
Powered by ViewVC 1.1.22