/[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.21 - (hide annotations) (download)
Wed Apr 6 18:29:52 2005 UTC (19 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57g_pre, checkpoint57f_post
Changes since 1.20: +2 -2 lines
use baseTime as time origin ; DIFF_BASE_MULTIPLE replaces DIFFERENT_MULTIPLE

1 jmc 1.21 C $Header: /u/gcmpack/MITgcm/model/src/config_check.F,v 1.20 2005/02/20 11:46:24 dimitri 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 jmc 1.19 IF ( dTtracerLev(1).NE.dTtracerLev(Nr) .AND. implicitDiffusion
109     & .AND. ( saltStepping .OR. tempStepping .OR. usePTRACERS )
110     & ) THEN
111     WRITE(msgBuf,'(A)')
112     & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
113     CALL PRINT_ERROR( msgBuf , myThid)
114     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
115     & 'but implicitDiffusion=T with non-uniform dTtracerLev'
116     CALL PRINT_ERROR( msgBuf , myThid)
117     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
118     ENDIF
119 jmc 1.13 #endif
120    
121 jmc 1.1 #ifndef EXACT_CONSERV
122     IF (exactConserv) THEN
123     WRITE(msgBuf,'(A)')
124     & 'CONFIG_CHECK: #undef EXACT_CONSERV and'
125 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
126 jmc 1.1 WRITE(msgBuf,'(A)')
127     & 'CONFIG_CHECK: exactConserv is TRUE'
128 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
129 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
130     ENDIF
131     #endif
132    
133     #ifndef NONLIN_FRSURF
134     IF (nonlinFreeSurf.NE.0) THEN
135     WRITE(msgBuf,'(A)')
136     & 'CONFIG_CHECK: #undef NONLIN_FRSURF and'
137 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
138 jmc 1.1 WRITE(msgBuf,'(A)')
139     & 'CONFIG_CHECK: nonlinFreeSurf is non-zero'
140 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
141 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
142     ENDIF
143     #endif
144    
145 jmc 1.9 #ifndef NONLIN_FRSURF
146     IF (select_rStar .NE. 0) THEN
147     WRITE(msgBuf,'(A)')
148     & 'CONFIG_CHECK: rStar is part of NonLin-FS '
149     CALL PRINT_ERROR( msgBuf, myThid)
150     WRITE(msgBuf,'(A)')
151     & 'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to use it'
152     CALL PRINT_ERROR( msgBuf, myThid)
153     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
154     ENDIF
155     #endif /* NONLIN_FRSURF */
156    
157 jmc 1.1 #ifdef USE_NATURAL_BCS
158     WRITE(msgBuf,'(A)')
159 jmc 1.3 & 'CONFIG_CHECK: USE_NATURAL_BCS option has been replaced'
160     CALL PRINT_ERROR( msgBuf , myThid)
161 jmc 1.1 WRITE(msgBuf,'(A)')
162 jmc 1.3 & 'CONFIG_CHECK: by useRealFreshWaterFlux=TRUE in data file'
163     CALL PRINT_ERROR( msgBuf , myThid)
164 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
165 jmc 1.3 #endif
166    
167 jmc 1.4 C o If pLoadFile is set, then we should make sure the corresponing
168     C code is being compiled
169     #ifndef ATMOSPHERIC_LOADING
170     IF (pLoadFile.NE.' ') THEN
171     WRITE(msgBuf,'(A)')
172     & 'CONFIG_CHECK: pLoadFile is set but you have not'
173     CALL PRINT_ERROR( msgBuf , myThid)
174     WRITE(msgBuf,'(A)')
175     & 'compiled the model with the pressure loading code.'
176     CALL PRINT_ERROR( msgBuf , myThid)
177 jmc 1.15 WRITE(msgBuf,'(A)')
178     & 'Re-compile with: #define ATMOSPHERIC_LOADING'
179     CALL PRINT_ERROR( msgBuf , myThid)
180     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
181     ENDIF
182     IF ( useRealFreshWaterFlux .AND. useThSIce ) THEN
183     WRITE(msgBuf,'(A)')
184     & 'CONFIG_CHECK: sIceLoad is computed but'
185     CALL PRINT_ERROR( msgBuf , myThid)
186     WRITE(msgBuf,'(A)')
187     & 'pressure loading code is not compiled.'
188     CALL PRINT_ERROR( msgBuf , myThid)
189     WRITE(msgBuf,'(A)')
190     & 'Re-compile with: #define ATMOSPHERIC_LOADING'
191 jmc 1.4 CALL PRINT_ERROR( msgBuf , myThid)
192     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
193     ENDIF
194     #endif
195    
196 jmc 1.18 #ifndef ALLOW_GENERIC_ADVDIFF
197 jmc 1.19 IF ( tempStepping .OR. saltStepping ) THEN
198 jmc 1.18 WRITE(msgBuf,'(2A)')
199 jmc 1.19 & 'CONFIG_CHECK: cannot step forward Temp or Salt',
200 jmc 1.18 & ' without pkg/generic_advdiff'
201     CALL PRINT_ERROR( msgBuf , 1)
202     WRITE(msgBuf,'(A)')
203     & 'Re-compile with pkg "generic_advdiff" in packages.conf'
204     CALL PRINT_ERROR( msgBuf , 1)
205     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
206     ENDIF
207     #endif
208    
209 jmc 1.4 C o If taveFreq is finite, then we must make sure the diagnostics
210     C code is being compiled
211     #ifndef ALLOW_TIMEAVE
212     IF (taveFreq.NE.0.) THEN
213     WRITE(msgBuf,'(A)')
214 jmc 1.15 & 'CONFIG_CHECK: taveFreq <> 0 but pkg/timeave is not compiled'
215 jmc 1.4 CALL PRINT_ERROR( msgBuf , 1)
216     WRITE(msgBuf,'(A)')
217 jmc 1.15 & 'Re-compile with pkg "timeave" in packages.conf'
218 jmc 1.4 CALL PRINT_ERROR( msgBuf , 1)
219     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
220     ENDIF
221     #endif
222    
223 dimitri 1.20 C o If calendarDumps is set, pkg/cal is required
224     #ifndef ALLOW_CAL
225     IF (calendarDumps) THEN
226     WRITE(msgBuf,'(A)')
227     & 'CONFIG_CHECK: calendarDumps is set but pkg/cal is not compiled'
228     CALL PRINT_ERROR( msgBuf , 1)
229     WRITE(msgBuf,'(A)')
230     & 'Re-compile with pkg "cal" in packages.conf'
231     CALL PRINT_ERROR( msgBuf , 1)
232     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
233     ENDIF
234     #endif
235    
236 jmc 1.3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
237    
238     C- check parameter consistency :
239 jmc 1.8
240 jmc 1.17 IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
241     & ( viscC4leith.NE.0. .OR. viscA4Grid.NE.0.
242     & .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0. ) ) THEN
243 jmc 1.8 WRITE(msgBuf,'(A,A)')
244     & 'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',
245     & ' overlap (Olx,Oly) smaller than 3'
246     CALL PRINT_ERROR( msgBuf , myThid)
247     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
248     ENDIF
249 jmc 1.3
250     IF ( rigidLid .AND. implicitFreeSurface ) THEN
251     WRITE(msgBuf,'(A,A)')
252     & 'CONFIG_CHECK: Cannot select both implicitFreeSurface',
253     & ' and rigidLid.'
254     CALL PRINT_ERROR( msgBuf , myThid)
255     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
256     ENDIF
257    
258     IF (rigidLid .AND. exactConserv) THEN
259 jmc 1.1 WRITE(msgBuf,'(A)')
260 jmc 1.3 & 'CONFIG_CHECK: exactConserv not compatible with'
261     CALL PRINT_ERROR( msgBuf , myThid)
262 jmc 1.1 WRITE(msgBuf,'(A)')
263 jmc 1.3 & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
264     CALL PRINT_ERROR( msgBuf , myThid)
265 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
266     ENDIF
267    
268 jmc 1.3 IF (rigidLid .AND. useRealFreshWaterFlux) THEN
269 jmc 1.1 WRITE(msgBuf,'(A)')
270 jmc 1.3 & 'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'
271     CALL PRINT_ERROR( msgBuf , myThid)
272 jmc 1.1 WRITE(msgBuf,'(A)')
273     & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
274 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
275     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
276     ENDIF
277    
278     IF ( (implicSurfPress.NE.1. .OR. implicDiv2DFlow.NE.1.)
279     & .AND. nonHydrostatic ) THEN
280     WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: nonHydrostatic',
281     & ' NOT SAFE with non-fully implicit Barotropic solver'
282     CALL PRINT_ERROR( msgBuf , myThid)
283     WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: To by-pass this',
284     & 'STOP, comment this test and re-compile config_check'
285     CALL PRINT_ERROR( msgBuf , myThid)
286 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
287     ENDIF
288    
289     IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN
290     WRITE(msgBuf,'(A)')
291     & 'CONFIG_CHECK: nonlinFreeSurf cannot be used'
292 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
293 jmc 1.1 WRITE(msgBuf,'(A)')
294     & 'CONFIG_CHECK: without exactConserv'
295 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
296 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
297     ENDIF
298    
299 jmc 1.6 IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN
300     WRITE(msgBuf,'(A)')
301     & 'CONFIG_CHECK: r* Coordinate cannot be used'
302     CALL PRINT_ERROR( msgBuf , myThid)
303     WRITE(msgBuf,'(A)')
304     & 'CONFIG_CHECK: without exactConserv'
305     CALL PRINT_ERROR( msgBuf , myThid)
306     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
307     ENDIF
308    
309 jmc 1.7 C- note : not implemented in checkpoint48b but it's done now (since 01-28-03)
310     c IF (select_rStar.GT.0 .AND. useOBCS ) THEN
311     c WRITE(msgBuf,'(A)')
312     c & 'CONFIG_CHECK: r* Coordinate not yet implemented'
313     c CALL PRINT_ERROR( msgBuf , 1)
314     c WRITE(msgBuf,'(A)')
315     c & 'CONFIG_CHECK: in OBC package'
316     c CALL PRINT_ERROR( msgBuf , 1)
317     c STOP 'ABNORMAL END: S/R CONFIG_CHECK'
318     c ENDIF
319 jmc 1.1
320     IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN
321     WRITE(msgBuf,'(A)')
322     & 'CONFIG_CHECK: nonlinFreeSurf not yet implemented'
323 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
324 jmc 1.1 WRITE(msgBuf,'(A)')
325     & 'CONFIG_CHECK: in nonHydrostatic code'
326 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
327 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
328     ENDIF
329 jmc 1.3
330 jmc 1.18 IF ( nonlinFreeSurf.NE.0 .AND.
331     & deltaTfreesurf.NE.dTtracerLev(1) ) THEN
332 jmc 1.3 WRITE(msgBuf,'(A)')
333 jmc 1.4 & 'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'
334     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
335     & SQUEEZE_RIGHT , myThid)
336     WRITE(msgBuf,'(A)')
337     & 'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'
338     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
339     & SQUEEZE_RIGHT , myThid)
340 jmc 1.3 ENDIF
341    
342 jmc 1.15 IF ( useRealFreshWaterFlux .AND. exactConserv
343     & .AND. implicDiv2DFlow.EQ.0. _d 0
344 jmc 1.21 & .AND. startTime.NE.baseTime .AND. usePickupBeforeC54 ) THEN
345 jmc 1.3 WRITE(msgBuf,'(A)')
346     & 'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'
347     CALL PRINT_ERROR( msgBuf , myThid)
348     WRITE(msgBuf,'(A)')
349     & 'CONFIG_CHECK: restart not implemented in this config'
350     CALL PRINT_ERROR( msgBuf , myThid)
351     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
352     ENDIF
353    
354 jmc 1.15 IF ( useRealFreshWaterFlux .AND. .NOT.exactConserv
355     & .AND. implicDiv2DFlow.NE.1. ) THEN
356     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: **WARNNING** ',
357     & 'RealFreshWater & implicDiv2DFlow < 1'
358     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
359     & SQUEEZE_RIGHT , myThid)
360     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: works better',
361     & ' with exactConserv=.T. (+ #define EXACT_CONSERV)'
362     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
363     & SQUEEZE_RIGHT , myThid)
364     ENDIF
365    
366     #ifdef EXACT_CONSERV
367 jmc 1.4 IF (useRealFreshWaterFlux .AND. .NOT.exactConserv
368     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
369     WRITE(msgBuf,'(A)')
370     & 'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'
371     CALL PRINT_ERROR( msgBuf , myThid)
372     WRITE(msgBuf,'(A)')
373     & 'CONFIG_CHECK: requires exactConserv=T'
374     CALL PRINT_ERROR( msgBuf , myThid)
375     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
376     ENDIF
377     #else
378     IF (useRealFreshWaterFlux
379     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
380     WRITE(msgBuf,'(A)')
381     & 'CONFIG_CHECK: E-P effects on wVel are not included'
382     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
383     & SQUEEZE_RIGHT , myThid)
384     WRITE(msgBuf,'(A)')
385 jmc 1.15 & 'CONFIG_CHECK: ==> use #define EXACT_CONSERV to fix it'
386 jmc 1.5 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
387     & SQUEEZE_RIGHT , myThid)
388     ENDIF
389 jmc 1.15 #endif /* EXACT_CONSERV */
390 jmc 1.5
391 jmc 1.9 IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN
392     C- jmc: since useCDscheme is a new [04-13-03] flag (default=F),
393     C put this WARNING to stress that even if CD-scheme parameters
394     C (tauCD,rCD) are set, CD-scheme is not used without useCDscheme=T
395     C- and STOP if using mom_fluxform (following Chris advise).
396     C- jmc: but ultimately, this block can/will be removed.
397     IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN
398     WRITE(msgBuf,'(A)')
399     & 'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
400     CALL PRINT_ERROR( msgBuf , myThid)
401     WRITE(msgBuf,'(2A)')
402     & 'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
403     & ' in "data", namelist PARM01'
404     CALL PRINT_ERROR( msgBuf , myThid)
405     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
406     ENDIF
407     WRITE(msgBuf,'(2A)') '**WARNNING** ',
408     & 'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
409 jmc 1.5 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
410     & SQUEEZE_RIGHT , myThid)
411 jmc 1.9 WRITE(msgBuf,'(2A)')
412     & 'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
413     & ' in "data", namelist PARM01'
414 jmc 1.4 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
415     & SQUEEZE_RIGHT , myThid)
416 jmc 1.12 ENDIF
417    
418     IF ( useCDscheme .AND. useCubedSphereExchange ) THEN
419     WRITE(msgBuf,'(2A)')
420     & 'CONFIG_CHECK: CD-scheme not implemented on CubedSphere grid'
421     CALL PRINT_ERROR( msgBuf , myThid)
422     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
423     ENDIF
424    
425     IF ( useOldFreezing .AND. allowFreezing ) THEN
426     WRITE(msgBuf,'(2A)')
427     & 'CONFIG_CHECK: cannot set both: allowFreezing & useOldFreezing'
428     CALL PRINT_ERROR( msgBuf , myThid)
429     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
430 jmc 1.4 ENDIF
431 jmc 1.1
432     WRITE(msgBuf,'(A)') 'CONFIG_CHECK: OK'
433     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
434     & SQUEEZE_RIGHT,myThid)
435    
436     RETURN
437     END

  ViewVC Help
Powered by ViewVC 1.1.22