/[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.39 by baylor, Tue Jun 20 20:57:37 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 15  C     *================================= Line 16  C     *=================================
16  C     | This routine help to prevent the use of parameters  C     | This routine help to prevent the use of parameters
17  C     | that are not compatible with the model configuration.  C     | that are not compatible with the model configuration.
18  C     *=========================================================*  C     *=========================================================*
19  C     \ev                                                            C     \ev
20    
21  C     !USES:  C     !USES:
22        IMPLICIT NONE        IMPLICIT NONE
# 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)') '**WARNING** ',
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_MOM_VECINV
211          IF ( momStepping .AND. vectorInvariantMomentum ) THEN
212            WRITE(msgBuf,'(2A)')
213         &   'CONFIG_CHECK: cannot step forward Momentum',
214         &   ' without pkg/mom_vecinv'
215            CALL PRINT_ERROR( msgBuf , 1)
216            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
217         &   'Re-compile with pkg "mom_vecinv" in packages.conf'
218            CALL PRINT_ERROR( msgBuf , 1)
219            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
220          ENDIF
221    #endif
222    #ifndef ALLOW_MOM_FLUXFORM
223          IF ( momStepping .AND. .NOT.vectorInvariantMomentum ) THEN
224            WRITE(msgBuf,'(2A)')
225         &   'CONFIG_CHECK: cannot step forward Momentum',
226         &   ' without pkg/mom_fluxform'
227            CALL PRINT_ERROR( msgBuf , 1)
228            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
229         &   'Re-compile with pkg "mom_fluxform" in packages.conf'
230            CALL PRINT_ERROR( msgBuf , 1)
231            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
232          ENDIF
233    #endif
234    
235    #ifndef ALLOW_GENERIC_ADVDIFF
236          IF ( tempStepping .OR. saltStepping ) THEN
237            WRITE(msgBuf,'(2A)')
238         &  'CONFIG_CHECK: cannot step forward Temp or Salt',
239         &  ' without pkg/generic_advdiff'
240            CALL PRINT_ERROR( msgBuf , 1)
241            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
242         &  'Re-compile with pkg "generic_advdiff" in packages.conf'
243            CALL PRINT_ERROR( msgBuf , 1)
244            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
245          ENDIF
246    #endif
247    
248    C     o If taveFreq is finite, then we must make sure the diagnostics
249    C       code is being compiled
250    #ifndef ALLOW_TIMEAVE
251          IF (taveFreq.NE.0.) THEN
252            WRITE(msgBuf,'(A)')
253         &  'CONFIG_CHECK: taveFreq <> 0  but pkg/timeave is not compiled'
254          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
255          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
256       &   'CONFIG_CHECK: rigidLid are not compatible'       &  'Re-compile with pkg "timeave" in packages.conf'
257          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
258          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
259        ENDIF        ENDIF
260        IF (exactConserv) THEN  #endif
261          WRITE(msgBuf,'(A)')  
262       &   'CONFIG_CHECK: #define USE_NATURAL_BCS with'  #ifndef ALLOW_BALANCE_FLUXES
263          IF (balanceEmPmR .OR. balanceQnet) THEN
264            WRITE(msgBuf,'(A,A)')
265         &  'CONFIG_CHECK: balanceEmPmR/Qnet is set but balance code ',
266         &  'is not compiled.'
267          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
268          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
269       &   'CONFIG_CHECK: exactConserv not yet implemented'       &  'Re-compile with  ALLOW_BALANCE_FLUXES defined'
270          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
271          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
272        ENDIF        ENDIF
273  #endif  #endif
274    
275    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
276    
277    C-  check parameter consistency :
278    
279          IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
280         &     ( viscC4leithD.NE.0.  .OR. viscC4leith.NE.0.
281         &     .OR. viscC4smag.NE.0. .OR. viscA4Grid.NE.0.
282         &     .OR. viscA4D.NE.0.    .OR. viscA4Z.NE.0. ) ) THEN
283            WRITE(msgBuf,'(A,A)')
284         &  'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',
285         &  ' overlap (Olx,Oly) smaller than 3'
286            CALL PRINT_ERROR( msgBuf , myThid)
287            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
288          ENDIF
289          IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
290         &     ( viscC2leithD.NE.0. .OR. viscC4leithD.NE.0. )
291         &   ) THEN
292            WRITE(msgBuf,'(A,A)')
293         &  'CONFIG_CHECK: cannot use Leith Visc.(div.part) with',
294         &  ' overlap (Olx,Oly) smaller than 3'
295            CALL PRINT_ERROR( msgBuf , myThid)
296            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
297          ENDIF
298    
299          IF ( rigidLid .AND. implicitFreeSurface ) THEN
300            WRITE(msgBuf,'(A,A)')
301         &  'CONFIG_CHECK: Cannot select both implicitFreeSurface',
302         &  ' and rigidLid.'
303            CALL PRINT_ERROR( msgBuf , myThid)
304            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
305          ENDIF
306    
307        IF (rigidLid .AND. exactConserv) THEN        IF (rigidLid .AND. exactConserv) THEN
308          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
309       &   'CONFIG_CHECK: exactConserv not compatible with'       &   'CONFIG_CHECK: exactConserv not compatible with'
310          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
311          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
312       &   'CONFIG_CHECK: rigidLid (meaningless in that case)'       &   'CONFIG_CHECK: rigidLid (meaningless in that case)'
313          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
314            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
315          ENDIF
316    
317          IF (rigidLid .AND. useRealFreshWaterFlux) THEN
318            WRITE(msgBuf,'(A)')
319         &   'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'
320            CALL PRINT_ERROR( msgBuf , myThid)
321            WRITE(msgBuf,'(A)')
322         &   'CONFIG_CHECK: rigidLid (meaningless in that case)'
323            CALL PRINT_ERROR( msgBuf , myThid)
324            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
325          ENDIF
326    
327          IF ( (implicSurfPress.NE.1. .OR. implicDiv2DFlow.NE.1.)
328         &    .AND. nonHydrostatic ) THEN
329            WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: nonHydrostatic',
330         & ' NOT SAFE with non-fully implicit Barotropic solver'
331            CALL PRINT_ERROR( msgBuf , myThid)
332            WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: To by-pass this',
333         &    'STOP, comment this test and re-compile config_check'
334            CALL PRINT_ERROR( msgBuf , myThid)
335          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
336        ENDIF        ENDIF
337    
338        IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN        IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN
339          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
340       &   'CONFIG_CHECK: nonlinFreeSurf cannot be used'       &   'CONFIG_CHECK: nonlinFreeSurf cannot be used'
341          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
342          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
343       &   'CONFIG_CHECK: without exactConserv'       &   'CONFIG_CHECK: without exactConserv'
344          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
345          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
346        ENDIF        ENDIF
347    
348  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  
349          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
350       &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'       &   'CONFIG_CHECK: r* Coordinate cannot be used'
351          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
352          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
353       &   'CONFIG_CHECK: in OBC package'       &   'CONFIG_CHECK: without exactConserv'
354          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
355          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
356        ENDIF        ENDIF
357    
358        IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN  C- note : not implemented in checkpoint48b but it's done now (since 01-28-03)
359    c     IF (select_rStar.GT.0 .AND. useOBCS ) THEN
360    c       WRITE(msgBuf,'(A)')
361    c    &   'CONFIG_CHECK: r* Coordinate not yet implemented'
362    c       CALL PRINT_ERROR( msgBuf , 1)
363    c       WRITE(msgBuf,'(A)')
364    c    &   'CONFIG_CHECK: in OBC package'
365    c       CALL PRINT_ERROR( msgBuf , 1)
366    c       STOP 'ABNORMAL END: S/R CONFIG_CHECK'
367    c     ENDIF
368    
369    c     IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN
370          IF (nonlinFreeSurf.NE.0 .AND. use3Dsolver) THEN
371          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
372       &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'       &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'
373          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
374          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
375       &   'CONFIG_CHECK: in nonHydrostatic code'       &   'CONFIG_CHECK: in nonHydrostatic code'
376          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , myThid)
377            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
378          ENDIF
379    
380          IF ( nonlinFreeSurf.NE.0 .AND.
381         &     deltaTfreesurf.NE.dTtracerLev(1) ) THEN
382            WRITE(msgBuf,'(A)')
383         &   'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'
384            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
385         &                    SQUEEZE_RIGHT , myThid)
386            WRITE(msgBuf,'(A)')
387         &   'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'
388            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
389         &                    SQUEEZE_RIGHT , myThid)
390          ENDIF
391    
392          IF ( useRealFreshWaterFlux .AND. exactConserv
393         &     .AND. implicDiv2DFlow.EQ.0. _d 0
394         &     .AND. startTime.NE.baseTime .AND. usePickupBeforeC54 ) THEN
395            WRITE(msgBuf,'(A)')
396         &   'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'
397            CALL PRINT_ERROR( msgBuf , myThid)
398            WRITE(msgBuf,'(A)')
399         &   'CONFIG_CHECK: restart not implemented in this config'
400            CALL PRINT_ERROR( msgBuf , myThid)
401            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
402          ENDIF
403    
404          IF ( useRealFreshWaterFlux .AND. .NOT.exactConserv
405         &     .AND. implicDiv2DFlow.NE.1. ) THEN
406            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: **WARNNING** ',
407         &   'RealFreshWater & implicDiv2DFlow < 1'
408            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
409         &                    SQUEEZE_RIGHT , myThid)
410            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: works better',
411         &   ' with exactConserv=.T. (+ #define EXACT_CONSERV)'
412            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
413         &                    SQUEEZE_RIGHT , myThid)
414          ENDIF
415    
416    #ifdef EXACT_CONSERV
417          IF (useRealFreshWaterFlux .AND. .NOT.exactConserv
418         &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
419            WRITE(msgBuf,'(A)')
420         &   'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'
421            CALL PRINT_ERROR( msgBuf , myThid)
422            WRITE(msgBuf,'(A)')
423         &   'CONFIG_CHECK: requires exactConserv=T'
424            CALL PRINT_ERROR( msgBuf , myThid)
425            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
426          ENDIF
427    #else
428          IF (useRealFreshWaterFlux
429         &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
430            WRITE(msgBuf,'(A)')
431         &   'CONFIG_CHECK: E-P effects on wVel are not included'
432            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
433         &                    SQUEEZE_RIGHT , myThid)
434            WRITE(msgBuf,'(A)')
435         &   'CONFIG_CHECK: ==> use #define EXACT_CONSERV to fix it'
436            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
437         &                    SQUEEZE_RIGHT , myThid)
438          ENDIF
439    #endif /* EXACT_CONSERV */
440    
441          IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN
442    C- jmc: since useCDscheme is a new [04-13-03] flag (default=F),
443    C       put this WARNING to stress that even if CD-scheme parameters
444    C       (tauCD,rCD) are set, CD-scheme is not used without useCDscheme=T
445    C-    and STOP if using mom_fluxform (following Chris advise).
446    C- jmc: but ultimately, this block can/will be removed.
447           IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN
448            WRITE(msgBuf,'(A)')
449         &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
450            CALL PRINT_ERROR( msgBuf , myThid)
451            WRITE(msgBuf,'(2A)')
452         &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
453         &   ' in "data", namelist PARM01'
454            CALL PRINT_ERROR( msgBuf , myThid)
455            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
456           ENDIF
457            WRITE(msgBuf,'(2A)') '**WARNNING** ',
458         &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
459            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
460         &                    SQUEEZE_RIGHT , myThid)
461            WRITE(msgBuf,'(2A)')
462         &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
463         &   ' in "data", namelist PARM01'
464            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
465         &                    SQUEEZE_RIGHT , myThid)
466          ENDIF
467    
468          IF ( useCDscheme .AND. useCubedSphereExchange ) THEN
469            WRITE(msgBuf,'(2A)')
470         &   'CONFIG_CHECK: CD-scheme not implemented on CubedSphere grid'
471            CALL PRINT_ERROR( msgBuf , myThid)
472            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
473          ENDIF
474    
475          IF ( momForcingOutAB.NE.0 .AND. momForcingOutAB.NE.1 ) THEN
476            WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: momForcingOutAB=',
477         &                             momForcingOutAB, ' not allowed'
478            CALL PRINT_ERROR( msgBuf , myThid)
479            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: momForcingOutAB ',
480         &                       'should be =1 (Out of AB) or =0 (In AB)'
481            CALL PRINT_ERROR( msgBuf , myThid)
482            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
483          ENDIF
484          IF ( tracForcingOutAB.NE.0 .AND. tracForcingOutAB.NE.1 ) THEN
485            WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: tracForcingOutAB=',
486         &                             tracForcingOutAB, ' not allowed'
487            CALL PRINT_ERROR( msgBuf , myThid)
488            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: tracForcingOutAB ',
489         &                       'should be =1 (Out of AB) or =0 (In AB)'
490            CALL PRINT_ERROR( msgBuf , myThid)
491            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
492          ENDIF
493    
494          IF ( useMATRIX .AND. useGCHEM ) THEN
495            WRITE(msgBuf,'(2A)')
496         &   'CONFIG_CHECK: cannot set both: useMATRIX & useGCHEM'
497            CALL PRINT_ERROR( msgBuf , myThid)
498            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
499          ENDIF
500    
501          IF ( useMATRIX .AND. .NOT.usePTRACERS ) THEN
502            WRITE(msgBuf,'(2A)')
503         &       'CONFIG_CHECK: cannot set useMATRIX without ',
504         &       'setting usePTRACERS'
505            CALL PRINT_ERROR( msgBuf , myThid)
506          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
507        ENDIF        ENDIF
508    

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

  ViewVC Help
Powered by ViewVC 1.1.22