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

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

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

revision 1.1 by jmc, Thu Jan 31 14:52:28 2002 UTC revision 1.32 by jmc, Fri Feb 10 22:56:19 2006 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4    #include "PACKAGES_CONFIG.h"
5  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
6    
7  CBOP  CBOP
# Line 39  CEOP Line 40  CEOP
40    
41  C-  check that CPP option is "defined" when running-flag parameter is on:  C-  check that CPP option is "defined" when running-flag parameter is on:
42    
43    #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    #ifndef ALLOW_CD_CODE
53          IF (useCDscheme) THEN
54            WRITE(msgBuf,'(A)')
55         &   'CONFIG_CHECK: useCDscheme is TRUE and #undef ALLOW_CD_CODE'
56            CALL PRINT_ERROR( msgBuf , myThid)
57            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
58          ENDIF
59          IF (tauCD.NE.0.) THEN
60            WRITE(msgBuf,'(2A)')
61         &   'CONFIG_CHECK: tauCD has been set but the cd_code package is',
62         &   ' enabled'
63            CALL PRINT_ERROR( msgBuf , myThid)
64            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
65          ENDIF
66    #endif
67    
68  #ifndef ALLOW_NONHYDROSTATIC  #ifndef ALLOW_NONHYDROSTATIC
69        IF (nonHydrostatic) THEN        IF (use3Dsolver) THEN
70          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
71       &   'CONFIG_CHECK: #undef ALLOW_NONHYDROSTATIC and'       &   'CONFIG_CHECK: #undef ALLOW_NONHYDROSTATIC and'
72          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
73          WRITE(msgBuf,'(A)')         IF ( implicitIntGravWave ) WRITE(msgBuf,'(A)')
74         &   'CONFIG_CHECK: implicitIntGravWave is TRUE'
75           IF ( nonHydrostatic ) WRITE(msgBuf,'(A)')
76       &   'CONFIG_CHECK: nonHydrostatic is TRUE'       &   'CONFIG_CHECK: nonHydrostatic is TRUE'
77          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
78            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
79          ENDIF
80    #endif
81    
82    #ifndef ALLOW_ADAMSBASHFORTH_3
83          IF ( alph_AB.NE.UNSET_RL .OR. beta_AB.NE.UNSET_RL ) THEN
84            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
85         &   '#undef ALLOW_ADAMSBASHFORTH_3 but alph_AB,beta_AB'
86            CALL PRINT_ERROR( msgBuf , myThid)
87            WRITE(msgBuf,'(A,1P2E20.7)')
88         &   'CONFIG_CHECK: are set to:',alph_AB,beta_AB
89            CALL PRINT_ERROR( msgBuf , myThid)
90            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
91          ENDIF
92    #endif
93    
94    #ifndef INCLUDE_IMPLVERTADV_CODE
95          IF ( momImplVertAdv ) THEN
96            WRITE(msgBuf,'(A)')
97         &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
98            CALL PRINT_ERROR( msgBuf , myThid)
99            WRITE(msgBuf,'(A)')
100         &   'CONFIG_CHECK: but momImplVertAdv is TRUE'
101            CALL PRINT_ERROR( msgBuf , myThid)
102            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
103          ENDIF
104          IF ( tempImplVertAdv ) THEN
105            WRITE(msgBuf,'(A)')
106         &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
107            CALL PRINT_ERROR( msgBuf , myThid)
108            WRITE(msgBuf,'(A)')
109         &   'CONFIG_CHECK: but tempImplVertAdv is TRUE'
110            CALL PRINT_ERROR( msgBuf , myThid)
111            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
112          ENDIF
113          IF ( saltImplVertAdv ) THEN
114            WRITE(msgBuf,'(A)')
115         &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
116            CALL PRINT_ERROR( msgBuf , myThid)
117            WRITE(msgBuf,'(A)')
118         &   'CONFIG_CHECK: but saltImplVertAdv is TRUE'
119            CALL PRINT_ERROR( msgBuf , myThid)
120            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
121          ENDIF
122          IF ( dTtracerLev(1).NE.dTtracerLev(Nr) .AND. implicitDiffusion
123         &     .AND. ( saltStepping .OR. tempStepping .OR. usePTRACERS )
124         &   ) THEN
125            WRITE(msgBuf,'(A)')
126         &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
127            CALL PRINT_ERROR( msgBuf , myThid)
128            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
129         &   'but implicitDiffusion=T with non-uniform dTtracerLev'
130            CALL PRINT_ERROR( msgBuf , myThid)
131          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
132        ENDIF        ENDIF
133  #endif  #endif
# Line 55  C-  check that CPP option is "defined" w Line 136  C-  check that CPP option is "defined" w
136        IF (exactConserv) THEN        IF (exactConserv) THEN
137          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
138       &   'CONFIG_CHECK: #undef EXACT_CONSERV and'       &   'CONFIG_CHECK: #undef EXACT_CONSERV and'
139          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
140          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
141       &   'CONFIG_CHECK: exactConserv is TRUE'       &   'CONFIG_CHECK: exactConserv is TRUE'
142          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
143          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
144        ENDIF        ENDIF
145  #endif  #endif
# Line 67  C-  check that CPP option is "defined" w Line 148  C-  check that CPP option is "defined" w
148        IF (nonlinFreeSurf.NE.0) THEN        IF (nonlinFreeSurf.NE.0) THEN
149          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
150       &   'CONFIG_CHECK: #undef NONLIN_FRSURF and'       &   'CONFIG_CHECK: #undef NONLIN_FRSURF and'
151          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
152          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
153       &   'CONFIG_CHECK: nonlinFreeSurf is non-zero'       &   'CONFIG_CHECK: nonlinFreeSurf is non-zero'
154          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
155          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
156        ENDIF        ENDIF
157  #endif  #endif
158    
159  C-  check parameter consistency :  #ifndef NONLIN_FRSURF
160          IF (select_rStar .NE. 0) THEN
161            WRITE(msgBuf,'(A)')
162         &   'CONFIG_CHECK: rStar is part of NonLin-FS '
163            CALL PRINT_ERROR( msgBuf, myThid)                      
164            WRITE(msgBuf,'(A)')
165         &   'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to use it'
166            CALL PRINT_ERROR( msgBuf, myThid)                      
167            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
168          ENDIF
169    #endif /* NONLIN_FRSURF */
170    
171  #ifdef USE_NATURAL_BCS  #ifdef USE_NATURAL_BCS
       IF (rigidLid) THEN  
172          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
173       &   'CONFIG_CHECK: #define USE_NATURAL_BCS and'       &   'CONFIG_CHECK: USE_NATURAL_BCS option has been replaced'
174            CALL PRINT_ERROR( msgBuf , myThid)
175            WRITE(msgBuf,'(A)')
176         &   'CONFIG_CHECK: by useRealFreshWaterFlux=TRUE in data file'
177            CALL PRINT_ERROR( msgBuf , myThid)
178            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
179    #endif
180    
181    C     o If pLoadFile is set, then we should make sure the corresponing
182    C       code is being compiled
183    #ifndef ATMOSPHERIC_LOADING
184          IF (pLoadFile.NE.' ') THEN
185            WRITE(msgBuf,'(A)')
186         &  'CONFIG_CHECK: pLoadFile is set but you have not'
187            CALL PRINT_ERROR( msgBuf , myThid)
188            WRITE(msgBuf,'(A)')
189         &  'compiled the model with the pressure loading code.'
190            CALL PRINT_ERROR( msgBuf , myThid)
191            WRITE(msgBuf,'(A)')
192         &  'Re-compile with:  #define ATMOSPHERIC_LOADING'
193            CALL PRINT_ERROR( msgBuf , myThid)
194            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
195          ENDIF
196          IF ( useRealFreshWaterFlux .AND. useThSIce ) THEN
197            WRITE(msgBuf,'(A)')
198         &  'CONFIG_CHECK: sIceLoad is computed but'
199            CALL PRINT_ERROR( msgBuf , myThid)
200            WRITE(msgBuf,'(A)')
201         &  'pressure loading code is not compiled.'
202            CALL PRINT_ERROR( msgBuf , myThid)
203            WRITE(msgBuf,'(A)')
204         &  'Re-compile with:  #define ATMOSPHERIC_LOADING'
205            CALL PRINT_ERROR( msgBuf , myThid)
206            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
207          ENDIF
208    #endif
209    
210    #ifndef ALLOW_GENERIC_ADVDIFF
211          IF ( tempStepping .OR. saltStepping ) THEN
212            WRITE(msgBuf,'(2A)')
213         &  'CONFIG_CHECK: cannot step forward Temp or Salt',
214         &  ' without pkg/generic_advdiff'
215          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
216          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
217       &   'CONFIG_CHECK: rigidLid are not compatible'       &  'Re-compile with pkg "generic_advdiff" in packages.conf'
218          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
219          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
220        ENDIF        ENDIF
221        IF (exactConserv) THEN  #endif
222          WRITE(msgBuf,'(A)')  
223       &   'CONFIG_CHECK: #define USE_NATURAL_BCS with'  C     o If taveFreq is finite, then we must make sure the diagnostics
224    C       code is being compiled
225    #ifndef ALLOW_TIMEAVE
226          IF (taveFreq.NE.0.) THEN
227            WRITE(msgBuf,'(A)')
228         &  'CONFIG_CHECK: taveFreq <> 0  but pkg/timeave is not compiled'
229            CALL PRINT_ERROR( msgBuf , 1)
230            WRITE(msgBuf,'(A)')
231         &  'Re-compile with pkg "timeave" in packages.conf'
232          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
233            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
234          ENDIF
235    #endif
236    
237    C     o If calendarDumps is set, pkg/cal is required
238    #ifndef ALLOW_CAL
239          IF (calendarDumps) THEN
240          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
241       &   'CONFIG_CHECK: exactConserv not yet implemented'       &  'CONFIG_CHECK: calendarDumps is set but pkg/cal is not compiled'
242            CALL PRINT_ERROR( msgBuf , 1)
243            WRITE(msgBuf,'(A)')
244         &  'Re-compile with pkg "cal" in packages.conf'
245          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
246          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
247        ENDIF        ENDIF
248  #endif  #endif
249    
250    #ifndef ALLOW_BALANCE_FLUXES
251          IF (balanceEmPmR .OR. balanceQnet) THEN
252            WRITE(msgBuf,'(A,A)')
253         &  'CONFIG_CHECK: balanceEmPmR/Qnet is set but balance code ',
254         &  'is not compiled.'
255            CALL PRINT_ERROR( msgBuf , 1)
256            WRITE(msgBuf,'(A)')
257         &  'Re-compile with  ALLOW_BALANCE_FLUXES defined'
258            CALL PRINT_ERROR( msgBuf , 1)
259            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
260          ENDIF
261    #endif
262    
263    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
264    
265    C-  check parameter consistency :
266    
267          IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
268         &     ( viscC4leithD.NE.0.  .OR. viscC4leith.NE.0.
269         &     .OR. viscC4smag.NE.0. .OR. viscA4Grid.NE.0.
270         &     .OR. viscA4D.NE.0.    .OR. viscA4Z.NE.0. ) ) THEN
271            WRITE(msgBuf,'(A,A)')
272         &  'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',
273         &  ' overlap (Olx,Oly) smaller than 3'
274            CALL PRINT_ERROR( msgBuf , myThid)
275            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
276          ENDIF                
277          IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
278         &     ( viscC2leithD.NE.0. .OR. viscC4leithD.NE.0. )
279         &   ) THEN
280            WRITE(msgBuf,'(A,A)')
281         &  'CONFIG_CHECK: cannot use Leith Visc.(div.part) with',
282         &  ' overlap (Olx,Oly) smaller than 3'
283            CALL PRINT_ERROR( msgBuf , myThid)
284            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
285          ENDIF                
286    
287          IF ( rigidLid .AND. implicitFreeSurface ) THEN
288            WRITE(msgBuf,'(A,A)')
289         &  'CONFIG_CHECK: Cannot select both implicitFreeSurface',
290         &  ' and rigidLid.'
291            CALL PRINT_ERROR( msgBuf , myThid)
292            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
293          ENDIF                
294    
295        IF (rigidLid .AND. exactConserv) THEN        IF (rigidLid .AND. exactConserv) THEN
296          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
297       &   'CONFIG_CHECK: exactConserv not compatible with'       &   'CONFIG_CHECK: exactConserv not compatible with'
298          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
299          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
300       &   'CONFIG_CHECK: rigidLid (meaningless in that case)'       &   'CONFIG_CHECK: rigidLid (meaningless in that case)'
301          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
302            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
303          ENDIF
304    
305          IF (rigidLid .AND. useRealFreshWaterFlux) THEN
306            WRITE(msgBuf,'(A)')
307         &   'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'
308            CALL PRINT_ERROR( msgBuf , myThid)
309            WRITE(msgBuf,'(A)')
310         &   'CONFIG_CHECK: rigidLid (meaningless in that case)'
311            CALL PRINT_ERROR( msgBuf , myThid)
312            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
313          ENDIF
314    
315          IF ( (implicSurfPress.NE.1. .OR. implicDiv2DFlow.NE.1.)
316         &    .AND. nonHydrostatic ) THEN
317            WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: nonHydrostatic',
318         & ' NOT SAFE with non-fully implicit Barotropic solver'
319            CALL PRINT_ERROR( msgBuf , myThid)
320            WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: To by-pass this',
321         &    'STOP, comment this test and re-compile config_check'
322            CALL PRINT_ERROR( msgBuf , myThid)
323          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
324        ENDIF        ENDIF
325    
326        IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN        IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN
327          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
328       &   'CONFIG_CHECK: nonlinFreeSurf cannot be used'       &   'CONFIG_CHECK: nonlinFreeSurf cannot be used'
329          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
330          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
331       &   'CONFIG_CHECK: without exactConserv'       &   'CONFIG_CHECK: without exactConserv'
332          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
333          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
334        ENDIF        ENDIF
335    
336  C- note : not implemented in Release1_beta1 but it's done now (since 01-30-02)        IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN
       IF (nonlinFreeSurf.NE.0 .AND. useOBCS ) THEN  
337          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
338       &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'       &   'CONFIG_CHECK: r* Coordinate cannot be used'
339          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
340          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
341       &   'CONFIG_CHECK: in OBC package'       &   'CONFIG_CHECK: without exactConserv'
342          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
343          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
344        ENDIF        ENDIF
345    
346    C- note : not implemented in checkpoint48b but it's done now (since 01-28-03)
347    c     IF (select_rStar.GT.0 .AND. useOBCS ) THEN
348    c       WRITE(msgBuf,'(A)')
349    c    &   'CONFIG_CHECK: r* Coordinate not yet implemented'
350    c       CALL PRINT_ERROR( msgBuf , 1)
351    c       WRITE(msgBuf,'(A)')
352    c    &   'CONFIG_CHECK: in OBC package'
353    c       CALL PRINT_ERROR( msgBuf , 1)
354    c       STOP 'ABNORMAL END: S/R CONFIG_CHECK'
355    c     ENDIF
356    
357        IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN        IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN
358          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
359       &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'       &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'
360          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
361          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
362       &   'CONFIG_CHECK: in nonHydrostatic code'       &   'CONFIG_CHECK: in nonHydrostatic code'
363          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
364          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
365        ENDIF        ENDIF
366    
367          IF ( nonlinFreeSurf.NE.0 .AND.
368         &     deltaTfreesurf.NE.dTtracerLev(1) ) THEN
369            WRITE(msgBuf,'(A)')
370         &   'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'
371            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
372         &                    SQUEEZE_RIGHT , myThid)                      
373            WRITE(msgBuf,'(A)')
374         &   'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'
375            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
376         &                    SQUEEZE_RIGHT , myThid)                      
377          ENDIF
378    
379          IF ( useRealFreshWaterFlux .AND. exactConserv
380         &     .AND. implicDiv2DFlow.EQ.0. _d 0
381         &     .AND. startTime.NE.baseTime .AND. usePickupBeforeC54 ) THEN
382            WRITE(msgBuf,'(A)')
383         &   'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'
384            CALL PRINT_ERROR( msgBuf , myThid)
385            WRITE(msgBuf,'(A)')
386         &   'CONFIG_CHECK: restart not implemented in this config'
387            CALL PRINT_ERROR( msgBuf , myThid)
388            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
389          ENDIF
390    
391          IF ( useRealFreshWaterFlux .AND. .NOT.exactConserv
392         &     .AND. implicDiv2DFlow.NE.1. ) THEN
393            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: **WARNNING** ',
394         &   'RealFreshWater & implicDiv2DFlow < 1'
395            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
396         &                    SQUEEZE_RIGHT , myThid)                      
397            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: works better',
398         &   ' with exactConserv=.T. (+ #define EXACT_CONSERV)'
399            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
400         &                    SQUEEZE_RIGHT , myThid)                      
401          ENDIF
402    
403    #ifdef EXACT_CONSERV
404          IF (useRealFreshWaterFlux .AND. .NOT.exactConserv
405         &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
406            WRITE(msgBuf,'(A)')
407         &   'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'
408            CALL PRINT_ERROR( msgBuf , myThid)
409            WRITE(msgBuf,'(A)')
410         &   'CONFIG_CHECK: requires exactConserv=T'
411            CALL PRINT_ERROR( msgBuf , myThid)
412            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
413          ENDIF
414    #else
415          IF (useRealFreshWaterFlux
416         &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
417            WRITE(msgBuf,'(A)')
418         &   'CONFIG_CHECK: E-P effects on wVel are not included'
419            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
420         &                    SQUEEZE_RIGHT , myThid)                      
421            WRITE(msgBuf,'(A)')
422         &   'CONFIG_CHECK: ==> use #define EXACT_CONSERV to fix it'
423            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
424         &                    SQUEEZE_RIGHT , myThid)                      
425          ENDIF
426    #endif /* EXACT_CONSERV */
427    
428          IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN
429    C- jmc: since useCDscheme is a new [04-13-03] flag (default=F),
430    C       put this WARNING to stress that even if CD-scheme parameters
431    C       (tauCD,rCD) are set, CD-scheme is not used without useCDscheme=T
432    C-    and STOP if using mom_fluxform (following Chris advise).
433    C- jmc: but ultimately, this block can/will be removed.
434           IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN
435            WRITE(msgBuf,'(A)')
436         &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
437            CALL PRINT_ERROR( msgBuf , myThid)
438            WRITE(msgBuf,'(2A)')
439         &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
440         &   ' in "data", namelist PARM01'
441            CALL PRINT_ERROR( msgBuf , myThid)
442            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
443           ENDIF
444            WRITE(msgBuf,'(2A)') '**WARNNING** ',
445         &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
446            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
447         &                    SQUEEZE_RIGHT , myThid)                      
448            WRITE(msgBuf,'(2A)')
449         &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
450         &   ' in "data", namelist PARM01'
451            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
452         &                    SQUEEZE_RIGHT , myThid)                      
453          ENDIF
454    
455          IF ( useCDscheme .AND. useCubedSphereExchange ) THEN
456            WRITE(msgBuf,'(2A)')
457         &   'CONFIG_CHECK: CD-scheme not implemented on CubedSphere grid'
458            CALL PRINT_ERROR( msgBuf , myThid)
459            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
460          ENDIF
461    
462          IF ( highOrderVorticity .AND. useCubedSphereExchange ) THEN
463            WRITE(msgBuf,'(2A)')
464         &   'CONFIG_CHECK: highOrderVorticity Scheme does not work',
465         &   ' on CubedSphere grid'
466            CALL PRINT_ERROR( msgBuf , myThid)
467            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
468          ENDIF
469    
470          IF ( useOldFreezing .AND. allowFreezing ) THEN
471            WRITE(msgBuf,'(2A)')
472         &   'CONFIG_CHECK: cannot set both: allowFreezing & useOldFreezing'
473            CALL PRINT_ERROR( msgBuf , myThid)
474            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
475          ENDIF
476    
477          IF ( useMATRIX .AND. useGCHEM ) THEN
478            WRITE(msgBuf,'(2A)')
479         &   'CONFIG_CHECK: cannot set both: useMATRIX & useGCHEM'
480            CALL PRINT_ERROR( msgBuf , myThid)
481            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
482          ENDIF
483    
484          IF ( useMATRIX .AND. .NOT.usePTRACERS ) THEN
485            WRITE(msgBuf,'(2A)')
486         &       'CONFIG_CHECK: cannot set useMATRIX without ',
487         &       'setting usePTRACERS'
488            CALL PRINT_ERROR( msgBuf , myThid)
489            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
490          ENDIF      
491          
492          IF ( tauThetaClimRelax3Dim .NE. 0. .OR.
493         &     tauSaltClimRelax3Dim .NE. 0. ) THEN
494            WRITE(msgBuf,'(2A)')
495         &       'CONFIG_CHECK: 3-dim. relaxation code has moved to ',
496         &       'separate pkg/rbcs.'
497            CALL PRINT_ERROR( msgBuf , myThid)
498            WRITE(msgBuf,'(2A)')
499         &       'tauThetaClimRelax3Dim, tauSaltClimRelax3Dim no longer ',
500         &       'in use.'
501            CALL PRINT_ERROR( msgBuf , myThid)
502            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
503          ENDIF
504    
505    C------------------------------------------------------------------------------------------
506    
507        WRITE(msgBuf,'(A)') 'CONFIG_CHECK: OK'        WRITE(msgBuf,'(A)') 'CONFIG_CHECK: OK'
508        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
509       &                   SQUEEZE_RIGHT,myThid)       &                   SQUEEZE_RIGHT,myThid)

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.32

  ViewVC Help
Powered by ViewVC 1.1.22