/[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.18 by jmc, Sat Dec 4 00:12:14 2004 UTC revision 1.51 by heimbach, Sat Oct 10 22:36:14 2009 UTC
# Line 16  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 40  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  C     o If diffKrFile is set, then we should make sure the corresponing
44        IF (useMNC) THEN  C       code is being compiled
45          WRITE(msgBuf,'(2A)') '**WARNNING** ',  #ifndef ALLOW_3D_DIFFKR
46       &   'CONFIG_CHECK: useMNC is TRUE and #undef ALLOW_MNC'        IF (diffKrFile.NE.' ') THEN
         CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,  
      &       SQUEEZE_RIGHT , myThid)                        
       ENDIF  
 #endif  
   
 #ifndef ALLOW_CD_CODE  
       IF (useCDscheme) THEN  
47          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
48       &   'CONFIG_CHECK: useCDscheme is TRUE and #undef ALLOW_CD_CODE'       &  'CONFIG_CHECK: diffKrFile is set but never used.'
49          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
         STOP 'ABNORMAL END: S/R CONFIG_CHECK'  
       ENDIF  
       IF (tauCD.NE.0.) THEN  
50          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
51       &   'CONFIG_CHECK: tauCD has been set but the cd_code package is',       &  'Re-compile with:  #define ALLOW_3D_DIFFKR'
      &   ' enabled'  
52          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
53          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
54        ENDIF        ENDIF
55  #endif  #endif
56    
57  #ifndef ALLOW_NONHYDROSTATIC  #ifndef ALLOW_NONHYDROSTATIC
58        IF (nonHydrostatic) THEN        IF (use3Dsolver) THEN
59          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
60       &   'CONFIG_CHECK: #undef ALLOW_NONHYDROSTATIC and'       &   'CONFIG_CHECK: #undef ALLOW_NONHYDROSTATIC and'
61          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
62          WRITE(msgBuf,'(A)')         IF ( implicitIntGravWave ) WRITE(msgBuf,'(A)')
63         &   'CONFIG_CHECK: implicitIntGravWave is TRUE'
64           IF ( nonHydrostatic ) WRITE(msgBuf,'(A)')
65       &   'CONFIG_CHECK: nonHydrostatic is TRUE'       &   'CONFIG_CHECK: nonHydrostatic is TRUE'
66          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
67          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
68        ENDIF        ENDIF
69  #endif  #endif
70    
71    #ifndef ALLOW_ADAMSBASHFORTH_3
72          IF ( alph_AB.NE.UNSET_RL .OR. beta_AB.NE.UNSET_RL ) THEN
73            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
74         &   '#undef ALLOW_ADAMSBASHFORTH_3 but alph_AB,beta_AB'
75            CALL PRINT_ERROR( msgBuf , myThid)
76            WRITE(msgBuf,'(A,1P2E20.7)')
77         &   'CONFIG_CHECK: are set to:',alph_AB,beta_AB
78            CALL PRINT_ERROR( msgBuf , myThid)
79            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
80          ENDIF
81    #endif
82    
83  #ifndef INCLUDE_IMPLVERTADV_CODE  #ifndef INCLUDE_IMPLVERTADV_CODE
84        IF ( momImplVertAdv ) THEN        IF ( momImplVertAdv ) THEN
85          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
86       &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'       &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
87          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
88          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 87  C-  check that CPP option is "defined" w Line 90  C-  check that CPP option is "defined" w
90          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
91          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
92        ENDIF        ENDIF
93        IF ( tempImplVertAdv ) THEN        IF ( tempImplVertAdv ) THEN
94          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
95       &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'       &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
96          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
97          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 96  C-  check that CPP option is "defined" w Line 99  C-  check that CPP option is "defined" w
99          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
100          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
101        ENDIF        ENDIF
102        IF ( saltImplVertAdv ) THEN        IF ( saltImplVertAdv ) THEN
103          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
104       &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'       &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
105          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
106          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 105  C-  check that CPP option is "defined" w Line 108  C-  check that CPP option is "defined" w
108          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
109          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
110        ENDIF        ENDIF
111          IF ( dTtracerLev(1).NE.dTtracerLev(Nr) .AND. implicitDiffusion
112         &     .AND. ( saltStepping .OR. tempStepping .OR. usePTRACERS )
113         &   ) THEN
114            WRITE(msgBuf,'(A)')
115         &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
116            CALL PRINT_ERROR( msgBuf , myThid)
117            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
118         &   'but implicitDiffusion=T with non-uniform dTtracerLev'
119            CALL PRINT_ERROR( msgBuf , myThid)
120            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
121          ENDIF
122  #endif  #endif
123    
124  #ifndef EXACT_CONSERV  #ifndef EXACT_CONSERV
125        IF (exactConserv) THEN        IF (exactConserv) THEN
126          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
127       &   'CONFIG_CHECK: #undef EXACT_CONSERV and'       &   'CONFIG_CHECK: #undef EXACT_CONSERV and'
128          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
129          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 120  C-  check that CPP option is "defined" w Line 134  C-  check that CPP option is "defined" w
134  #endif  #endif
135    
136  #ifndef NONLIN_FRSURF  #ifndef NONLIN_FRSURF
137        IF (nonlinFreeSurf.NE.0) THEN        IF (nonlinFreeSurf.NE.0) THEN
138          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
139       &   'CONFIG_CHECK: #undef NONLIN_FRSURF and'       &   'CONFIG_CHECK: #undef NONLIN_FRSURF and'
140          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
141          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 133  C-  check that CPP option is "defined" w Line 147  C-  check that CPP option is "defined" w
147    
148  #ifndef NONLIN_FRSURF  #ifndef NONLIN_FRSURF
149        IF (select_rStar .NE. 0) THEN        IF (select_rStar .NE. 0) THEN
150          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
151       &   'CONFIG_CHECK: rStar is part of NonLin-FS '       &   'CONFIG_CHECK: rStar is part of NonLin-FS '
152          CALL PRINT_ERROR( msgBuf, myThid)                                CALL PRINT_ERROR( msgBuf, myThid)
153          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
154       &   'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to use it'       &   'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to use it'
155          CALL PRINT_ERROR( msgBuf, myThid)                                CALL PRINT_ERROR( msgBuf, myThid)
156          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
157        ENDIF        ENDIF
158  #endif /* NONLIN_FRSURF */  #endif /* NONLIN_FRSURF */
159    
160  #ifdef USE_NATURAL_BCS  #ifdef USE_NATURAL_BCS
161          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
162       &   'CONFIG_CHECK: USE_NATURAL_BCS option has been replaced'       &   'CONFIG_CHECK: USE_NATURAL_BCS option has been replaced'
163          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
164          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 153  C-  check that CPP option is "defined" w Line 167  C-  check that CPP option is "defined" w
167          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
168  #endif  #endif
169    
170    #ifndef ALLOW_ADDFLUID
171          IF ( selectAddFluid.NE.0 ) THEN
172            WRITE(msgBuf,'(A)')
173         &   'CONFIG_CHECK: #undef ALLOW_ADDFLUID and'
174            CALL PRINT_ERROR( msgBuf, myThid )
175            WRITE(msgBuf,'(A,I4,A)') 'CONFIG_CHECK: selectAddFluid=',
176         &                           selectAddFluid, ' is not zero'
177            CALL PRINT_ERROR( msgBuf, myThid )
178            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
179          ENDIF
180    #endif /* ALLOW_ADDFLUID */
181    
182  C     o If pLoadFile is set, then we should make sure the corresponing  C     o If pLoadFile is set, then we should make sure the corresponing
183  C       code is being compiled  C       code is being compiled
184  #ifndef ATMOSPHERIC_LOADING  #ifndef ATMOSPHERIC_LOADING
# Line 182  C       code is being compiled Line 208  C       code is being compiled
208        ENDIF        ENDIF
209  #endif  #endif
210    
211  #ifndef ALLOW_GENERIC_ADVDIFF  #ifndef ALLOW_BALANCE_FLUXES
212        IF ( tempStepping .OR. saltStepping .OR. usePTRACERS ) THEN        IF (balanceEmPmR .OR. balanceQnet) THEN
213          WRITE(msgBuf,'(2A)')          WRITE(msgBuf,'(A,A)')
214       &  'CONFIG_CHECK: cannot step forward Temp,Salt or pTracers',       &  'CONFIG_CHECK: balanceEmPmR/Qnet is set but balance code ',
215       &  ' without pkg/generic_advdiff'       &  'is not compiled.'
         CALL PRINT_ERROR( msgBuf , 1)  
         WRITE(msgBuf,'(A)')  
      &  'Re-compile with pkg "generic_advdiff" in packages.conf'  
         CALL PRINT_ERROR( msgBuf , 1)  
         STOP 'ABNORMAL END: S/R CONFIG_CHECK'  
       ENDIF  
 #endif  
   
 C     o If taveFreq is finite, then we must make sure the diagnostics  
 C       code is being compiled  
 #ifndef ALLOW_TIMEAVE  
       IF (taveFreq.NE.0.) THEN  
         WRITE(msgBuf,'(A)')  
      &  'CONFIG_CHECK: taveFreq <> 0  but pkg/timeave is not compiled'  
216          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
217          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
218       &  'Re-compile with pkg "timeave" in packages.conf'       &  'Re-compile with  ALLOW_BALANCE_FLUXES defined'
219          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
220          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
221        ENDIF        ENDIF
# Line 211  C       code is being compiled Line 223  C       code is being compiled
223    
224  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
225    
226  C-  check parameter consistency :  C--   Check parameter consistency :
227    
228        IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.        IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
229       &     ( viscC4leith.NE.0. .OR. viscA4Grid.NE.0.       &     ( viscC4leithD.NE.0.  .OR. viscC4leith.NE.0.
230       &      .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0. ) ) THEN       &     .OR. viscC4smag.NE.0. .OR. viscA4Grid.NE.0.
231         &     .OR. viscA4D.NE.0.    .OR. viscA4Z.NE.0. ) ) THEN
232          WRITE(msgBuf,'(A,A)')          WRITE(msgBuf,'(A,A)')
233       &  'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',       &  'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',
234       &  ' overlap (Olx,Oly) smaller than 3'       &  ' overlap (Olx,Oly) smaller than 3'
235          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
236          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
237        ENDIF                        ENDIF
238          IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
239         &     ( viscC2leithD.NE.0. .OR. viscC4leithD.NE.0. )
240         &   ) THEN
241            WRITE(msgBuf,'(A,A)')
242         &  'CONFIG_CHECK: cannot use Leith Visc.(div.part) with',
243         &  ' overlap (Olx,Oly) smaller than 3'
244            CALL PRINT_ERROR( msgBuf , myThid)
245            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
246          ENDIF
247    
248    C--   Deep-Atmosphere & Anelastic limitations:
249          IF ( deepAtmosphere .AND.
250         &     useRealFreshWaterFlux .AND. usingPCoords ) THEN
251            WRITE(msgBuf,'(A,A)')
252         &  'CONFIG_CHECK: Deep-Atmosphere not yet implemented with',
253         &  ' real-Fresh-Water option in P-coordinate'
254            CALL PRINT_ERROR( msgBuf , myThid)
255            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
256          ENDIF
257          IF ( select_rStar.NE.0 .AND.
258         &        ( deepAtmosphere .OR.
259         &          usingZCoords.AND.rhoRefFile .NE. ' ' ) ) THEN
260            WRITE(msgBuf,'(A,A)')
261         &  'CONFIG_CHECK: Deep-Atmosphere or Anelastic',
262         &  ' not yet implemented with rStar'
263            CALL PRINT_ERROR( msgBuf , myThid)
264            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
265          ENDIF
266          IF ( vectorInvariantMomentum .AND.
267         &        ( deepAtmosphere .OR.
268         &          usingZCoords.AND.rhoRefFile .NE. ' ' ) ) THEN
269            WRITE(msgBuf,'(A,A)')
270         &  'CONFIG_CHECK: Deep-Atmosphere or Anelastic',
271         &  ' not yet implemented in Vector-Invariant momentum code'
272            CALL PRINT_ERROR( msgBuf , myThid)
273            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
274          ENDIF
275    
276    C--   Free-surface related limitations:
277        IF ( rigidLid .AND. implicitFreeSurface ) THEN        IF ( rigidLid .AND. implicitFreeSurface ) THEN
278          WRITE(msgBuf,'(A,A)')          WRITE(msgBuf,'(A,A)')
279       &  'CONFIG_CHECK: Cannot select both implicitFreeSurface',       &  'CONFIG_CHECK: Cannot select both implicitFreeSurface',
280       &  ' and rigidLid.'       &  ' and rigidLid.'
281          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
282          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
283        ENDIF                        ENDIF
284    
285        IF (rigidLid .AND. exactConserv) THEN        IF (rigidLid .AND. exactConserv) THEN
286          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
287       &   'CONFIG_CHECK: exactConserv not compatible with'       &   'CONFIG_CHECK: exactConserv not compatible with'
288          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
289          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 241  C-  check parameter consistency : Line 292  C-  check parameter consistency :
292          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
293        ENDIF        ENDIF
294    
295          IF ( linFSConserveTr .AND. nonlinFreeSurf.NE.0 ) THEN
296            WRITE(msgBuf,'(A)')
297         &   'CONFIG_CHECK: Cannot select both a Nonlinear Free Surf.'
298            CALL PRINT_ERROR( msgBuf , myThid)
299            WRITE(msgBuf,'(A)')
300         &   'CONFIG_CHECK: and Tracer Correction of Lin. Free Surf.'
301            CALL PRINT_ERROR( msgBuf , myThid)
302            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
303          ENDIF
304    
305        IF (rigidLid .AND. useRealFreshWaterFlux) THEN        IF (rigidLid .AND. useRealFreshWaterFlux) THEN
306          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
307       &   'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'       &   'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'
308          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
309          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 251  C-  check parameter consistency : Line 312  C-  check parameter consistency :
312          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
313        ENDIF        ENDIF
314    
315        IF ( (implicSurfPress.NE.1. .OR. implicDiv2DFlow.NE.1.)        IF ( (implicSurfPress.NE.1. .OR. implicDiv2Dflow.NE.1.)
316       &    .AND. nonHydrostatic ) THEN       &    .AND. nonHydrostatic ) THEN
317          WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: nonHydrostatic',          WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: nonHydrostatic',
318       & ' NOT SAFE with non-fully implicit Barotropic solver'       & ' NOT SAFE with non-fully implicit Barotropic solver'
# Line 263  C-  check parameter consistency : Line 324  C-  check parameter consistency :
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 , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
330          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 273  C-  check parameter consistency : Line 334  C-  check parameter consistency :
334        ENDIF        ENDIF
335    
336        IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN        IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN
337          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
338       &   'CONFIG_CHECK: r* Coordinate cannot be used'       &   'CONFIG_CHECK: r* Coordinate cannot be used'
339          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
340          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 284  C-  check parameter consistency : Line 345  C-  check parameter consistency :
345    
346  C- note : not implemented in checkpoint48b but it's done now (since 01-28-03)  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  c     IF (select_rStar.GT.0 .AND. useOBCS ) THEN
 c       WRITE(msgBuf,'(A)')  
 c    &   'CONFIG_CHECK: r* Coordinate not yet implemented'  
 c       CALL PRINT_ERROR( msgBuf , 1)  
 c       WRITE(msgBuf,'(A)')  
 c    &   'CONFIG_CHECK: in OBC package'  
 c       CALL PRINT_ERROR( msgBuf , 1)  
348  c       STOP 'ABNORMAL END: S/R CONFIG_CHECK'  c       STOP 'ABNORMAL END: S/R CONFIG_CHECK'
349  c     ENDIF  c     ENDIF
350    
351        IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN  c     IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN
352          WRITE(msgBuf,'(A)')        IF (nonlinFreeSurf.NE.0 .AND. use3Dsolver) THEN
353            WRITE(msgBuf,'(A)')
354       &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'       &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'
355          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
356          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 303  c     ENDIF Line 359  c     ENDIF
359          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
360        ENDIF        ENDIF
361    
362        IF ( nonlinFreeSurf.NE.0 .AND.        IF ( nonlinFreeSurf.NE.0 .AND.
363       &     deltaTfreesurf.NE.dTtracerLev(1) ) THEN       &     deltaTfreesurf.NE.dTtracerLev(1) ) THEN
364          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
365       &   'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'       &   'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'
366          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
367       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
368          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
369       &   'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'       &   'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'
370          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
371       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
372        ENDIF        ENDIF
373    
374        IF ( useRealFreshWaterFlux .AND. exactConserv        IF ( useRealFreshWaterFlux .AND. exactConserv
375       &     .AND. implicDiv2DFlow.EQ.0. _d 0       &     .AND. implicDiv2Dflow.EQ.0. _d 0
376       &     .AND. startTime.NE.0. .AND. usePickupBeforeC54 ) THEN       &     .AND. startTime.NE.baseTime .AND. usePickupBeforeC54 ) THEN
377          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
378       &   'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'       &   'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'
379          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
380          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 327  c     ENDIF Line 383  c     ENDIF
383          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
384        ENDIF        ENDIF
385    
386        IF ( useRealFreshWaterFlux .AND. .NOT.exactConserv        IF ( useRealFreshWaterFlux .AND. .NOT.exactConserv
387       &     .AND. implicDiv2DFlow.NE.1. ) THEN       &     .AND. implicDiv2Dflow.NE.1. ) THEN
388          WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: **WARNNING** ',          WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: **WARNNING** ',
389       &   'RealFreshWater & implicDiv2DFlow < 1'       &   'RealFreshWater & implicDiv2Dflow < 1'
390          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
391       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
392          WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: works better',          WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: works better',
393       &   ' with exactConserv=.T. (+ #define EXACT_CONSERV)'       &   ' with exactConserv=.T. (+ #define EXACT_CONSERV)'
394          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
395       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
396        ENDIF        ENDIF
397    
398  #ifdef EXACT_CONSERV  #ifdef EXACT_CONSERV
399        IF (useRealFreshWaterFlux .AND. .NOT.exactConserv        IF (useRealFreshWaterFlux .AND. .NOT.exactConserv
400       &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN       &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
401          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
402       &   'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'       &   'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'
403          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
404          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 353  c     ENDIF Line 409  c     ENDIF
409  #else  #else
410        IF (useRealFreshWaterFlux        IF (useRealFreshWaterFlux
411       &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN       &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
412          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
413       &   'CONFIG_CHECK: E-P effects on wVel are not included'       &   'CONFIG_CHECK: E-P effects on wVel are not included'
414          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
415       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
416          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
417       &   'CONFIG_CHECK: ==> use #define EXACT_CONSERV to fix it'       &   'CONFIG_CHECK: ==> use #define EXACT_CONSERV to fix it'
418          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
419       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
420        ENDIF        ENDIF
421  #endif /* EXACT_CONSERV */  #endif /* EXACT_CONSERV */
422    
423          IF ( selectAddFluid.LT.-1 .OR. selectAddFluid.GT.2 ) THEN
424            WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: selectAddFluid=',
425         &                             selectAddFluid, ' not allowed'
426            CALL PRINT_ERROR( msgBuf , myThid)
427            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
428         &       'should be =0 (Off), 1,2 (Add Mass) or -1 (Virtual Flux)'
429            CALL PRINT_ERROR( msgBuf , myThid)
430            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
431          ENDIF
432          IF ( selectAddFluid.GE.1 .AND. rigidLid ) THEN
433            WRITE(msgBuf,'(A)')
434         &   'CONFIG_CHECK: selectAddFluid > 0 not compatible with'
435            CALL PRINT_ERROR( msgBuf , myThid)
436            WRITE(msgBuf,'(A)')
437         &   'CONFIG_CHECK: rigidLid (meaningless in that case)'
438            CALL PRINT_ERROR( msgBuf , myThid)
439            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
440          ENDIF
441          IF ( selectAddFluid.GE.1 .AND. .NOT.staggerTimeStep ) THEN
442            WRITE(msgBuf,'(2A)') '**WARNNING** ',
443         &   'CONFIG_CHECK: synchronous time-stepping =>'
444            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
445         &                      SQUEEZE_RIGHT , myThid)
446            WRITE(msgBuf,'(2A)') '**WARNNING** ',
447         &   '1 time-step mismatch in AddFluid effects on T & S'
448            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
449         &                      SQUEEZE_RIGHT , myThid)
450          ENDIF
451    
452    C--   Momentum related limitations:
453          IF ( vectorInvariantMomentum.AND.momStepping ) THEN
454           IF ( highOrderVorticity.AND.upwindVorticity ) THEN
455            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
456         &   '"highOrderVorticity" conflicts with "upwindVorticity"'
457            CALL PRINT_ERROR( msgBuf , myThid)
458            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
459           ENDIF
460          ENDIF
461    
462        IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN        IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN
463  C- jmc: since useCDscheme is a new [04-13-03] flag (default=F),  C- jmc: since useCDscheme is a new [04-13-03] flag (default=F),
464  C       put this WARNING to stress that even if CD-scheme parameters  C       put this WARNING to stress that even if CD-scheme parameters
465  C       (tauCD,rCD) are set, CD-scheme is not used without useCDscheme=T  C       (tauCD,rCD) are set, CD-scheme is not used without useCDscheme=T
466  C-    and STOP if using mom_fluxform (following Chris advise).  C-    and STOP if using mom_fluxform (following Chris advise).
467  C- jmc: but ultimately, this block can/will be removed.  C- jmc: but ultimately, this block can/will be removed.
468         IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN         IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN
469          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
470       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
471          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
472          WRITE(msgBuf,'(2A)')          WRITE(msgBuf,'(2A)')
473       &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',       &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
474       &   ' in "data", namelist PARM01'       &   ' in "data", namelist PARM01'
475          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
476          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
477         ENDIF         ENDIF
478          WRITE(msgBuf,'(2A)') '**WARNNING** ',          WRITE(msgBuf,'(2A)') '**WARNNING** ',
479       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
480          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
481       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
482          WRITE(msgBuf,'(2A)')          WRITE(msgBuf,'(2A)')
483       &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',       &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
484       &   ' in "data", namelist PARM01'       &   ' in "data", namelist PARM01'
485          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
486       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
487        ENDIF        ENDIF
488    
489        IF ( useCDscheme .AND. useCubedSphereExchange ) THEN        IF ( useCDscheme .AND. useCubedSphereExchange ) THEN
490          WRITE(msgBuf,'(2A)')          WRITE(msgBuf,'(2A)')
491       &   'CONFIG_CHECK: CD-scheme not implemented on CubedSphere grid'       &   'CONFIG_CHECK: CD-scheme not implemented on CubedSphere grid'
492          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
493    cph        STOP 'ABNORMAL END: S/R CONFIG_CHECK'
494          ENDIF
495    
496    C--   Time-stepping limitations
497          IF ( momForcingOutAB.NE.0 .AND. momForcingOutAB.NE.1 ) THEN
498            WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: momForcingOutAB=',
499         &                             momForcingOutAB, ' not allowed'
500            CALL PRINT_ERROR( msgBuf , myThid)
501            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: momForcingOutAB ',
502         &                       'should be =1 (Out of AB) or =0 (In AB)'
503            CALL PRINT_ERROR( msgBuf , myThid)
504            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
505          ENDIF
506          IF ( tracForcingOutAB.NE.0 .AND. tracForcingOutAB.NE.1 ) THEN
507            WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: tracForcingOutAB=',
508         &                             tracForcingOutAB, ' not allowed'
509            CALL PRINT_ERROR( msgBuf , myThid)
510            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: tracForcingOutAB ',
511         &                       'should be =1 (Out of AB) or =0 (In AB)'
512            CALL PRINT_ERROR( msgBuf , myThid)
513            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
514          ENDIF
515    
516    C--   Grid limitations:
517          IF ( rotateGrid ) THEN
518           IF ( .NOT. usingSphericalPolarGrid ) THEN
519            WRITE(msgBuf,'(2A)')
520         &       'CONFIG_CHECK: specifying Euler angles makes only ',
521         &       'sense with usingSphericalGrid=.TRUE.'
522            CALL PRINT_ERROR( msgBuf , myThid)
523            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
524           ENDIF
525           IF ( useFLT .OR. useZonal_Filt .OR. useECCO ) THEN
526            WRITE(msgBuf,'(2A)')
527         &       'CONFIG_CHECK: specifying Euler angles will probably ',
528         &       'not work with pkgs FLT, ZONAL_FLT, ECCO'
529            CALL PRINT_ERROR( msgBuf , myThid)
530            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
531           ENDIF
532    #ifdef ALLOW_PROFILES
533            WRITE(msgBuf,'(2A)')
534         &       'CONFIG_CHECK: specifying Euler angles will probably ',
535         &       'not work with pkg profiles'
536            CALL PRINT_ERROR( msgBuf , myThid)
537            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
538    #endif /* ALLOW_PROFILES */
539          ENDIF
540    
541    C--   Packages conflict
542          IF ( useMATRIX .AND. useGCHEM ) THEN
543            WRITE(msgBuf,'(2A)')
544         &   'CONFIG_CHECK: cannot set both: useMATRIX & useGCHEM'
545            CALL PRINT_ERROR( msgBuf , myThid)
546            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
547          ENDIF
548    
549          IF ( useMATRIX .AND. .NOT.usePTRACERS ) THEN
550            WRITE(msgBuf,'(2A)')
551         &       'CONFIG_CHECK: cannot set useMATRIX without ',
552         &       'setting usePTRACERS'
553            CALL PRINT_ERROR( msgBuf , myThid)
554          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
555        ENDIF        ENDIF
556    
557        IF ( useOldFreezing .AND. allowFreezing ) THEN        IF ( (useSEAICE .OR. useThSIce) .AND. allowFreezing ) THEN
558          WRITE(msgBuf,'(2A)')          WRITE(msgBuf,'(2A)')
559       &   'CONFIG_CHECK: cannot set both: allowFreezing & useOldFreezing'       &       'CONFIG_CHECK: cannot set allowFreezing',
560         &       ' with pkgs SEAICE or THSICE'
561          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
562          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
563        ENDIF        ENDIF
564    
565        WRITE(msgBuf,'(A)') 'CONFIG_CHECK: OK'        WRITE(msgBuf,'(A)')
566        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,       &'// ======================================================='
567       &                   SQUEEZE_RIGHT,myThid)        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
568         &                    SQUEEZE_RIGHT, myThid )
569          WRITE(msgBuf,'(A)') '// CONFIG_CHECK : Normal End'
570          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
571         &                    SQUEEZE_RIGHT, myThid )
572          WRITE(msgBuf,'(A)')
573         &'// ======================================================='
574          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
575         &                    SQUEEZE_RIGHT, myThid )
576          WRITE(msgBuf,'(A)') ' '
577          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
578         &                    SQUEEZE_RIGHT, myThid )
579    
580        RETURN        RETURN
581        END        END

Legend:
Removed from v.1.18  
changed lines
  Added in v.1.51

  ViewVC Help
Powered by ViewVC 1.1.22