/[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.14 by adcroft, Thu Mar 25 15:35:53 2004 UTC revision 1.45 by mlosch, Fri Feb 8 07:57:44 2008 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_CD_CODE  C     o If diffKrFile is set, then we should make sure the corresponing
44        IF (useCDscheme) THEN  C       code is being compiled
45    #if !(defined ALLOW_3D_DIFFKR || \
46          (defined (ALLOW_AUTODIFF_TAMC) && defined (ALLOW_DIFFKR_CONTROL)))
47          IF (diffKrFile.NE.' ') THEN
48          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
49       &   'CONFIG_CHECK: useCDscheme is TRUE and #undef ALLOW_CD_CODE'       &  'CONFIG_CHECK: diffKrFile is set but never used.'
50          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
         STOP 'ABNORMAL END: S/R CONFIG_CHECK'  
       ENDIF  
       IF (tauCD.NE.0.) THEN  
51          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
52       &   'CONFIG_CHECK: tauCD has been set but the cd_code package is',       &  'Re-compile with:  #define ALLOW_3D_DIFFKR'
      &   ' enabled'  
53          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
54          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
55        ENDIF        ENDIF
56  #endif  #endif
57    
58  #ifndef ALLOW_NONHYDROSTATIC  #ifndef ALLOW_NONHYDROSTATIC
59        IF (nonHydrostatic) THEN        IF (use3Dsolver) THEN
60          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
61       &   'CONFIG_CHECK: #undef ALLOW_NONHYDROSTATIC and'       &   'CONFIG_CHECK: #undef ALLOW_NONHYDROSTATIC and'
62          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
63          WRITE(msgBuf,'(A)')         IF ( implicitIntGravWave ) WRITE(msgBuf,'(A)')
64         &   'CONFIG_CHECK: implicitIntGravWave is TRUE'
65           IF ( nonHydrostatic ) WRITE(msgBuf,'(A)')
66       &   'CONFIG_CHECK: nonHydrostatic is TRUE'       &   'CONFIG_CHECK: nonHydrostatic is TRUE'
67          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
68          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
69        ENDIF        ENDIF
70  #endif  #endif
71    
72    #ifndef ALLOW_ADAMSBASHFORTH_3
73          IF ( alph_AB.NE.UNSET_RL .OR. beta_AB.NE.UNSET_RL ) THEN
74            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
75         &   '#undef ALLOW_ADAMSBASHFORTH_3 but alph_AB,beta_AB'
76            CALL PRINT_ERROR( msgBuf , myThid)
77            WRITE(msgBuf,'(A,1P2E20.7)')
78         &   'CONFIG_CHECK: are set to:',alph_AB,beta_AB
79            CALL PRINT_ERROR( msgBuf , myThid)
80            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
81          ENDIF
82    #endif
83    
84  #ifndef INCLUDE_IMPLVERTADV_CODE  #ifndef INCLUDE_IMPLVERTADV_CODE
85        IF ( momImplVertAdv ) THEN        IF ( momImplVertAdv ) THEN
86          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
87       &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'       &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
88          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
89          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 78  C-  check that CPP option is "defined" w Line 91  C-  check that CPP option is "defined" w
91          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
92          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
93        ENDIF        ENDIF
94        IF ( tempImplVertAdv ) THEN        IF ( tempImplVertAdv ) THEN
95          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
96       &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'       &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
97          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
98          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 87  C-  check that CPP option is "defined" w Line 100  C-  check that CPP option is "defined" w
100          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
101          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
102        ENDIF        ENDIF
103        IF ( saltImplVertAdv ) THEN        IF ( saltImplVertAdv ) THEN
104          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
105       &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'       &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
106          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
107          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 96  C-  check that CPP option is "defined" w Line 109  C-  check that CPP option is "defined" w
109          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
110          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
111        ENDIF        ENDIF
112          IF ( dTtracerLev(1).NE.dTtracerLev(Nr) .AND. implicitDiffusion
113         &     .AND. ( saltStepping .OR. tempStepping .OR. usePTRACERS )
114         &   ) THEN
115            WRITE(msgBuf,'(A)')
116         &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
117            CALL PRINT_ERROR( msgBuf , myThid)
118            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
119         &   'but implicitDiffusion=T with non-uniform dTtracerLev'
120            CALL PRINT_ERROR( msgBuf , myThid)
121            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
122          ENDIF
123  #endif  #endif
124    
125  #ifndef EXACT_CONSERV  #ifndef EXACT_CONSERV
126        IF (exactConserv) THEN        IF (exactConserv) THEN
127          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
128       &   'CONFIG_CHECK: #undef EXACT_CONSERV and'       &   'CONFIG_CHECK: #undef EXACT_CONSERV and'
129          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
130          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 111  C-  check that CPP option is "defined" w Line 135  C-  check that CPP option is "defined" w
135  #endif  #endif
136    
137  #ifndef NONLIN_FRSURF  #ifndef NONLIN_FRSURF
138        IF (nonlinFreeSurf.NE.0) THEN        IF (nonlinFreeSurf.NE.0) THEN
139          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
140       &   'CONFIG_CHECK: #undef NONLIN_FRSURF and'       &   'CONFIG_CHECK: #undef NONLIN_FRSURF and'
141          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
142          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 124  C-  check that CPP option is "defined" w Line 148  C-  check that CPP option is "defined" w
148    
149  #ifndef NONLIN_FRSURF  #ifndef NONLIN_FRSURF
150        IF (select_rStar .NE. 0) THEN        IF (select_rStar .NE. 0) THEN
151          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
152       &   'CONFIG_CHECK: rStar is part of NonLin-FS '       &   'CONFIG_CHECK: rStar is part of NonLin-FS '
153          CALL PRINT_ERROR( msgBuf, myThid)                                CALL PRINT_ERROR( msgBuf, myThid)
154          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
155       &   'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to use it'       &   'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to use it'
156          CALL PRINT_ERROR( msgBuf, myThid)                                CALL PRINT_ERROR( msgBuf, myThid)
157          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
158        ENDIF        ENDIF
159  #endif /* NONLIN_FRSURF */  #endif /* NONLIN_FRSURF */
160    
161  #ifdef USE_NATURAL_BCS  #ifdef USE_NATURAL_BCS
162          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
163       &   'CONFIG_CHECK: USE_NATURAL_BCS option has been replaced'       &   'CONFIG_CHECK: USE_NATURAL_BCS option has been replaced'
164          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
165          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 154  C       code is being compiled Line 178  C       code is being compiled
178          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
179       &  'compiled the model with the pressure loading code.'       &  'compiled the model with the pressure loading code.'
180          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
181          WRITE(msgBuf,'(A,A)')          WRITE(msgBuf,'(A)')
182       &  'Re-compile with:  #define ATMOSPHERIC_LOADING',       &  'Re-compile with:  #define ATMOSPHERIC_LOADING'
183       &  '              or  -DATMOSPHERIC_LOADING'          CALL PRINT_ERROR( msgBuf , myThid)
184            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
185          ENDIF
186          IF ( useRealFreshWaterFlux .AND. useThSIce ) THEN
187            WRITE(msgBuf,'(A)')
188         &  'CONFIG_CHECK: sIceLoad is computed but'
189            CALL PRINT_ERROR( msgBuf , myThid)
190            WRITE(msgBuf,'(A)')
191         &  'pressure loading code is not compiled.'
192            CALL PRINT_ERROR( msgBuf , myThid)
193            WRITE(msgBuf,'(A)')
194         &  'Re-compile with:  #define ATMOSPHERIC_LOADING'
195          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
196          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
197        ENDIF        ENDIF
198  #endif  #endif
199    
200  C     o If taveFreq is finite, then we must make sure the diagnostics  #ifndef ALLOW_BALANCE_FLUXES
201  C       code is being compiled        IF (balanceEmPmR .OR. balanceQnet) THEN
202  #ifndef ALLOW_TIMEAVE          WRITE(msgBuf,'(A,A)')
203        IF (taveFreq.NE.0.) THEN       &  'CONFIG_CHECK: balanceEmPmR/Qnet is set but balance code ',
204          WRITE(msgBuf,'(A)')       &  'is not compiled.'
      &  'CONFIG_CHECK: taveFreq <> 0  but you have'  
205          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
206          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
207       &  'not compiled the model with the diagnostics routines.'       &  'Re-compile with  ALLOW_BALANCE_FLUXES defined'
         CALL PRINT_ERROR( msgBuf , 1)  
         WRITE(msgBuf,'(A,A)')  
      &  'Re-compile with:  #define ALLOW_TIMEAVE',  
      &  '              or  -DALLOW_TIMEAVE'  
208          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf , 1)
209          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
210        ENDIF        ENDIF
# Line 184  C---+----1----+----2----+----3----+----4 Line 214  C---+----1----+----2----+----3----+----4
214    
215  C-  check parameter consistency :  C-  check parameter consistency :
216    
217        IF ( viscA4.NE.0. .AND. (Olx.LT.3 .OR. Oly.LT.3)) THEN        IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
218         &     ( viscC4leithD.NE.0.  .OR. viscC4leith.NE.0.
219         &     .OR. viscC4smag.NE.0. .OR. viscA4Grid.NE.0.
220         &     .OR. viscA4D.NE.0.    .OR. viscA4Z.NE.0. ) ) THEN
221          WRITE(msgBuf,'(A,A)')          WRITE(msgBuf,'(A,A)')
222       &  'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',       &  'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',
223       &  ' overlap (Olx,Oly) smaller than 3'       &  ' overlap (Olx,Oly) smaller than 3'
224          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
225          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
226        ENDIF                        ENDIF
227          IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
228         &     ( viscC2leithD.NE.0. .OR. viscC4leithD.NE.0. )
229         &   ) THEN
230            WRITE(msgBuf,'(A,A)')
231         &  'CONFIG_CHECK: cannot use Leith Visc.(div.part) with',
232         &  ' overlap (Olx,Oly) smaller than 3'
233            CALL PRINT_ERROR( msgBuf , myThid)
234            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
235          ENDIF
236    
237    C-    Deep-Atmosphere & Anelastic limitations:
238          IF ( deepAtmosphere .AND.
239         &     useRealFreshWaterFlux .AND. usingPCoords ) THEN
240            WRITE(msgBuf,'(A,A)')
241         &  'CONFIG_CHECK: Deep-Atmosphere not yet implemented with',
242         &  ' real-Fresh-Water option in P-coordinate'
243            CALL PRINT_ERROR( msgBuf , myThid)
244            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
245          ENDIF
246          IF ( select_rStar.NE.0 .AND.
247         &        ( deepAtmosphere .OR.
248         &          usingZCoords.AND.rhoRefFile .NE. ' ' ) ) THEN
249            WRITE(msgBuf,'(A,A)')
250         &  'CONFIG_CHECK: Deep-Atmosphere or Anelastic',
251         &  ' not yet implemented with rStar'
252            CALL PRINT_ERROR( msgBuf , myThid)
253            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
254          ENDIF
255          IF ( vectorInvariantMomentum .AND.
256         &        ( deepAtmosphere .OR.
257         &          usingZCoords.AND.rhoRefFile .NE. ' ' ) ) THEN
258            WRITE(msgBuf,'(A,A)')
259         &  'CONFIG_CHECK: Deep-Atmosphere or Anelastic',
260         &  ' not yet implemented in Vector-Invariant momentum code'
261            CALL PRINT_ERROR( msgBuf , myThid)
262            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
263          ENDIF
264    
265        IF ( rigidLid .AND. implicitFreeSurface ) THEN        IF ( rigidLid .AND. implicitFreeSurface ) THEN
266          WRITE(msgBuf,'(A,A)')          WRITE(msgBuf,'(A,A)')
# Line 198  C-  check parameter consistency : Line 268  C-  check parameter consistency :
268       &  ' and rigidLid.'       &  ' and rigidLid.'
269          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
270          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
271        ENDIF                        ENDIF
272    
273        IF (rigidLid .AND. exactConserv) THEN        IF (rigidLid .AND. exactConserv) THEN
274          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
275       &   'CONFIG_CHECK: exactConserv not compatible with'       &   'CONFIG_CHECK: exactConserv not compatible with'
276          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
277          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 210  C-  check parameter consistency : Line 280  C-  check parameter consistency :
280          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
281        ENDIF        ENDIF
282    
283          IF ( linFSConserveTr .AND. nonlinFreeSurf.NE.0 ) THEN
284            WRITE(msgBuf,'(A)')
285         &   'CONFIG_CHECK: Cannot select both a Nonlinear Free Surf.'
286            CALL PRINT_ERROR( msgBuf , myThid)
287            WRITE(msgBuf,'(A)')
288         &   'CONFIG_CHECK: and Tracer Correction of Lin. Free Surf.'
289            CALL PRINT_ERROR( msgBuf , myThid)
290            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
291          ENDIF
292    
293        IF (rigidLid .AND. useRealFreshWaterFlux) THEN        IF (rigidLid .AND. useRealFreshWaterFlux) THEN
294          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
295       &   'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'       &   'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'
296          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
297          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 232  C-  check parameter consistency : Line 312  C-  check parameter consistency :
312        ENDIF        ENDIF
313    
314        IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN        IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN
315          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
316       &   'CONFIG_CHECK: nonlinFreeSurf cannot be used'       &   'CONFIG_CHECK: nonlinFreeSurf cannot be used'
317          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
318          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 242  C-  check parameter consistency : Line 322  C-  check parameter consistency :
322        ENDIF        ENDIF
323    
324        IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN        IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN
325          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
326       &   'CONFIG_CHECK: r* Coordinate cannot be used'       &   'CONFIG_CHECK: r* Coordinate cannot be used'
327          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
328          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 253  C-  check parameter consistency : Line 333  C-  check parameter consistency :
333    
334  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)
335  c     IF (select_rStar.GT.0 .AND. useOBCS ) THEN  c     IF (select_rStar.GT.0 .AND. useOBCS ) THEN
336  c       WRITE(msgBuf,'(A)')  c       WRITE(msgBuf,'(A)')
337  c    &   'CONFIG_CHECK: r* Coordinate not yet implemented'  c    &   'CONFIG_CHECK: r* Coordinate not yet implemented'
338  c       CALL PRINT_ERROR( msgBuf , 1)  c       CALL PRINT_ERROR( msgBuf , 1)
339  c       WRITE(msgBuf,'(A)')  c       WRITE(msgBuf,'(A)')
# Line 262  c       CALL PRINT_ERROR( msgBuf , 1) Line 342  c       CALL PRINT_ERROR( msgBuf , 1)
342  c       STOP 'ABNORMAL END: S/R CONFIG_CHECK'  c       STOP 'ABNORMAL END: S/R CONFIG_CHECK'
343  c     ENDIF  c     ENDIF
344    
345        IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN  c     IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN
346          WRITE(msgBuf,'(A)')        IF (nonlinFreeSurf.NE.0 .AND. use3Dsolver) THEN
347            WRITE(msgBuf,'(A)')
348       &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'       &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'
349          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
350          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 272  c     ENDIF Line 353  c     ENDIF
353          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
354        ENDIF        ENDIF
355    
356        IF (nonlinFreeSurf.NE.0.AND.deltaTfreesurf.NE.deltaTtracer) THEN        IF ( nonlinFreeSurf.NE.0 .AND.
357          WRITE(msgBuf,'(A)')       &     deltaTfreesurf.NE.dTtracerLev(1) ) THEN
358            WRITE(msgBuf,'(A)')
359       &   'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'       &   'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'
360          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
361       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
362          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
363       &   'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'       &   'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'
364          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
365       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
366        ENDIF        ENDIF
367    
368        IF (useRealFreshWaterFlux .AND. exactConserv        IF ( useRealFreshWaterFlux .AND. exactConserv
369       &    .AND.startTime.NE.0. .AND. implicSurfPress.EQ.0. _d 0) THEN       &     .AND. implicDiv2DFlow.EQ.0. _d 0
370          WRITE(msgBuf,'(A)')       &     .AND. startTime.NE.baseTime .AND. usePickupBeforeC54 ) THEN
371            WRITE(msgBuf,'(A)')
372       &   'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'       &   'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'
373          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
374          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 294  c     ENDIF Line 377  c     ENDIF
377          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
378        ENDIF        ENDIF
379    
380  #ifdef NONLIN_FRSURF        IF ( useRealFreshWaterFlux .AND. .NOT.exactConserv
381         &     .AND. implicDiv2DFlow.NE.1. ) THEN
382            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: **WARNNING** ',
383         &   'RealFreshWater & implicDiv2DFlow < 1'
384            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
385         &                    SQUEEZE_RIGHT , myThid)
386            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: works better',
387         &   ' with exactConserv=.T. (+ #define EXACT_CONSERV)'
388            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
389         &                    SQUEEZE_RIGHT , myThid)
390          ENDIF
391    
392    #ifdef EXACT_CONSERV
393        IF (useRealFreshWaterFlux .AND. .NOT.exactConserv        IF (useRealFreshWaterFlux .AND. .NOT.exactConserv
394       &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN       &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
395          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
396       &   'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'       &   'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'
397          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
398          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 306  c     ENDIF Line 401  c     ENDIF
401          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
402        ENDIF        ENDIF
403  #else  #else
       IF (useRealFreshWaterFlux .AND. exactConserv  
      &            .AND. implicSurfPress.NE.1. _d 0 ) THEN  
         WRITE(msgBuf,'(A)')  
      &   'CONFIG_CHECK: Pb with restart in this config'  
         CALL PRINT_ERROR( msgBuf , myThid)  
         WRITE(msgBuf,'(A)')  
      &   'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to fix it'  
         CALL PRINT_ERROR( msgBuf , myThid)  
         STOP 'ABNORMAL END: S/R CONFIG_CHECK'  
       ENDIF  
   
404        IF (useRealFreshWaterFlux        IF (useRealFreshWaterFlux
405       &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN       &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
406          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
407       &   'CONFIG_CHECK: E-P effects on wVel are not included'       &   'CONFIG_CHECK: E-P effects on wVel are not included'
408          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
409       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
410          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
411       &   'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to fix it'       &   'CONFIG_CHECK: ==> use #define EXACT_CONSERV to fix it'
412          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
413       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
414        ENDIF        ENDIF
415  #endif /* NONLIN_FRSURF */  #endif /* EXACT_CONSERV */
416    
417        IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN        IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN
418  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),
419  C       put this WARNING to stress that even if CD-scheme parameters  C       put this WARNING to stress that even if CD-scheme parameters
420  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
421  C-    and STOP if using mom_fluxform (following Chris advise).  C-    and STOP if using mom_fluxform (following Chris advise).
422  C- jmc: but ultimately, this block can/will be removed.  C- jmc: but ultimately, this block can/will be removed.
423         IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN         IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN
424          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
425       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
426          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
427          WRITE(msgBuf,'(2A)')          WRITE(msgBuf,'(2A)')
428       &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',       &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
429       &   ' in "data", namelist PARM01'       &   ' in "data", namelist PARM01'
430          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
431          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
432         ENDIF         ENDIF
433          WRITE(msgBuf,'(2A)') '**WARNNING** ',          WRITE(msgBuf,'(2A)') '**WARNNING** ',
434       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
435          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
436       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
437          WRITE(msgBuf,'(2A)')          WRITE(msgBuf,'(2A)')
438       &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',       &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
439       &   ' in "data", namelist PARM01'       &   ' in "data", namelist PARM01'
440          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
441       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
442        ENDIF        ENDIF
443    
444        IF ( useCDscheme .AND. useCubedSphereExchange ) THEN        IF ( useCDscheme .AND. useCubedSphereExchange ) THEN
# Line 364  C- jmc: but ultimately, this block can/w Line 448  C- jmc: but ultimately, this block can/w
448          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
449        ENDIF        ENDIF
450    
451        IF ( useOldFreezing .AND. allowFreezing ) THEN        IF ( momForcingOutAB.NE.0 .AND. momForcingOutAB.NE.1 ) THEN
452            WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: momForcingOutAB=',
453         &                             momForcingOutAB, ' not allowed'
454            CALL PRINT_ERROR( msgBuf , myThid)
455            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: momForcingOutAB ',
456         &                       'should be =1 (Out of AB) or =0 (In AB)'
457            CALL PRINT_ERROR( msgBuf , myThid)
458            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
459          ENDIF
460          IF ( tracForcingOutAB.NE.0 .AND. tracForcingOutAB.NE.1 ) THEN
461            WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: tracForcingOutAB=',
462         &                             tracForcingOutAB, ' not allowed'
463            CALL PRINT_ERROR( msgBuf , myThid)
464            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: tracForcingOutAB ',
465         &                       'should be =1 (Out of AB) or =0 (In AB)'
466            CALL PRINT_ERROR( msgBuf , myThid)
467            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
468          ENDIF
469    
470          IF ( useMATRIX .AND. useGCHEM ) THEN
471            WRITE(msgBuf,'(2A)')
472         &   'CONFIG_CHECK: cannot set both: useMATRIX & useGCHEM'
473            CALL PRINT_ERROR( msgBuf , myThid)
474            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
475          ENDIF
476    
477          IF ( useMATRIX .AND. .NOT.usePTRACERS ) THEN
478            WRITE(msgBuf,'(2A)')
479         &       'CONFIG_CHECK: cannot set useMATRIX without ',
480         &       'setting usePTRACERS'
481            CALL PRINT_ERROR( msgBuf , myThid)
482            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
483          ENDIF
484    
485          IF ( rotateGrid ) THEN
486           IF ( .NOT. usingSphericalPolarGrid ) THEN
487            WRITE(msgBuf,'(2A)')
488         &       'CONFIG_CHECK: specifying Euler angles makes only ',
489         &       'sense with usingSphericalGrid=.TRUE.'
490            CALL PRINT_ERROR( msgBuf , myThid)
491            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
492           ENDIF
493           IF ( useFLT .OR. useZonal_Filt .OR. useECCO ) THEN
494            WRITE(msgBuf,'(2A)')
495         &       'CONFIG_CHECK: specifying Euler angles will probably ',
496         &       'not work with pkgs FLT, ZONAL_FLT, ECCO'
497            CALL PRINT_ERROR( msgBuf , myThid)
498            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
499           ENDIF
500           IF ( use3dCoriolis ) THEN
501            WRITE(msgBuf,'(3A)')
502         &       'CONFIG_CHECK: computation of angleCosC and angleSinC ',
503         &       'as required by use3dCoriolis ',
504         &       'not yet implemented with rotated grid. Sorry!'
505            CALL PRINT_ERROR( msgBuf , myThid)
506            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
507           ENDIF
508    #ifdef ALLOW_PROFILES
509          WRITE(msgBuf,'(2A)')          WRITE(msgBuf,'(2A)')
510       &   'CONFIG_CHECK: cannot set both: allowFreezing & useOldFreezing'       &       'CONFIG_CHECK: specifying Euler angles will probably ',
511         &       'not work with pkg profiles'
512          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
513          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
514    #endif /* ALLOW_PROFILES */
515        ENDIF        ENDIF
516    
517        WRITE(msgBuf,'(A)') 'CONFIG_CHECK: OK'        WRITE(msgBuf,'(A)') 'CONFIG_CHECK: OK'

Legend:
Removed from v.1.14  
changed lines
  Added in v.1.45

  ViewVC Help
Powered by ViewVC 1.1.22