/[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.68 by jmc, Mon Jul 9 19:20:17 2012 UTC revision 1.83 by jmc, Mon Feb 15 17:59:40 2016 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "PACKAGES_CONFIG.h"  #include "PACKAGES_CONFIG.h"
5  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
6    #ifdef ALLOW_MOM_COMMON
7    # include "MOM_COMMON_OPTIONS.h"
8    #endif
9    
10  CBOP  CBOP
11  C     !ROUTINE: CONFIG_CHECK  C     !ROUTINE: CONFIG_CHECK
# Line 24  C     === Global variables === Line 27  C     === Global variables ===
27  #include "SIZE.h"  #include "SIZE.h"
28  #include "EEPARAMS.h"  #include "EEPARAMS.h"
29  #include "PARAMS.h"  #include "PARAMS.h"
 c #include "GRID.h"  
30    
31  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
32  C     === Routine arguments ===  C     === Routine arguments ===
# Line 39  C     msgBuf :: Informational/error mess Line 41  C     msgBuf :: Informational/error mess
41        INTEGER errCount        INTEGER errCount
42  CEOP  CEOP
43    
44          _BEGIN_MASTER(myThid)
45          WRITE(msgBuf,'(A)')
46         &'// ======================================================='
47          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
48         &                    SQUEEZE_RIGHT, myThid )
49          WRITE(msgBuf,'(A)') '// Check Model config. (CONFIG_CHECK):'
50          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
51         &                    SQUEEZE_RIGHT, myThid )
52          _END_MASTER(myThid)
53    
54  C--   MPI + multi-threads: seems to be OK to let master-thread check & stop  C--   MPI + multi-threads: seems to be OK to let master-thread check & stop
55  C      (as long as all procs finish cleanly by calling ALL_PROC_DIE)  C      (as long as all procs finish cleanly by calling ALL_PROC_DIE)
56        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
# Line 53  C       code is being compiled Line 65  C       code is being compiled
65          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
66       &  'CONFIG_CHECK: diffKrFile is set but never used.'       &  'CONFIG_CHECK: diffKrFile is set but never used.'
67          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
68          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
69       &  'Re-compile with:  #define ALLOW_3D_DIFFKR'       &  'Re-compile with: "#define ALLOW_3D_DIFFKR"'
70            CALL PRINT_ERROR( msgBuf, myThid )
71            errCount = errCount + 1
72          ENDIF
73    #endif
74    
75    #ifndef ALLOW_SMAG_3D
76          IF ( useSmag3D ) THEN
77            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
78         &  'Cannot set useSmag3D=TRUE when compiled with'
79            CALL PRINT_ERROR( msgBuf, myThid )
80            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
81         &  '"#undef ALLOW_SMAG_3D" in MOM_COMMON_OPTIONS.h'
82          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
83          errCount = errCount + 1          errCount = errCount + 1
84        ENDIF        ENDIF
# Line 127  C       code is being compiled Line 151  C       code is being compiled
151        ENDIF        ENDIF
152  #endif  #endif
153    
154  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF
155        IF ( momImplVertAdv ) THEN        IF ( momImplVertAdv ) THEN
156          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
157       &   'CONFIG_CHECK: momImplVertAdv is not yet'       &   'CONFIG_CHECK: momImplVertAdv is not yet'
# Line 221  C       code is being compiled Line 245  C       code is being compiled
245  #ifndef ALLOW_ADDFLUID  #ifndef ALLOW_ADDFLUID
246        IF ( selectAddFluid.NE.0 ) THEN        IF ( selectAddFluid.NE.0 ) THEN
247          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
248       &   'CONFIG_CHECK: #undef ALLOW_ADDFLUID and'       &   'CONFIG_CHECK: #undef ALLOW_ADDFLUID (CPP_OPTIONS.h) and'
249          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
250          WRITE(msgBuf,'(A,I4,A)') 'CONFIG_CHECK: selectAddFluid=',          WRITE(msgBuf,'(A,I4,A)') 'CONFIG_CHECK: selectAddFluid=',
251       &                           selectAddFluid, ' is not zero'       &                           selectAddFluid, ' is not zero'
# Line 238  C       code is being compiled Line 262  C       code is being compiled
262       &  'CONFIG_CHECK: pLoadFile is set but you have not'       &  'CONFIG_CHECK: pLoadFile is set but you have not'
263          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
264          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
265       &  'compiled the model with the pressure loading code.'       &  ' compiled the model with the pressure loading code.'
266          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
267          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
268       &  'Re-compile with:  #define ATMOSPHERIC_LOADING'       &  ' Re-compile with: "#define ATMOSPHERIC_LOADING"'
269          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
270          errCount = errCount + 1          errCount = errCount + 1
271        ENDIF        ENDIF
# Line 250  C       code is being compiled Line 274  C       code is being compiled
274       &  'CONFIG_CHECK: sIceLoad is computed but'       &  'CONFIG_CHECK: sIceLoad is computed but'
275          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
276          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
277       &  'pressure loading code is not compiled.'       &  ' pressure loading code is not compiled.'
278          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
279          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
280       &  'Re-compile with:  #define ATMOSPHERIC_LOADING'       &  ' Re-compile with: "#define ATMOSPHERIC_LOADING"'
281            CALL PRINT_ERROR( msgBuf, myThid )
282            errCount = errCount + 1
283          ENDIF
284    #endif
285    
286    C     o Need to define ALLOW_GEOTHERMAL_FLUX to use geothermalFile forcing
287    #ifndef ALLOW_GEOTHERMAL_FLUX
288          IF ( geothermalFile.NE.' ' ) THEN
289            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
290         &  'geothermalFile is set but Geothermal-Flux code'
291            CALL PRINT_ERROR( msgBuf, myThid )
292            WRITE(msgBuf,'(2A)')' is not compiled.',
293         &  ' Re-compile with "#define ALLOW_GEOTHERMAL_FLUX"'
294            CALL PRINT_ERROR( msgBuf, myThid )
295            errCount = errCount + 1
296          ENDIF
297    #endif /* ALLOW_GEOTHERMAL_FLUX */
298    
299    #ifndef ALLOW_FRICTION_HEATING
300          IF ( addFrictionHeating ) THEN
301            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: addFrictionHeating=T',
302         &  ' but FRICTIONAL_HEATING code is not compiled.'
303            CALL PRINT_ERROR( msgBuf, myThid )
304            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: Re-compile with:',
305         &   ' "#define ALLOW_FRICTION_HEATING" (CPP_OPTIONS.h)'
306          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
307          errCount = errCount + 1          errCount = errCount + 1
308        ENDIF        ENDIF
# Line 265  C       code is being compiled Line 314  C       code is being compiled
314       &  'CONFIG_CHECK: balanceEmPmR/Qnet is set but balance code ',       &  'CONFIG_CHECK: balanceEmPmR/Qnet is set but balance code ',
315       &  'is not compiled.'       &  'is not compiled.'
316          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
317          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
318       &  'Re-compile with  ALLOW_BALANCE_FLUXES defined'       &  'Re-compile with:  ALLOW_BALANCE_FLUXES defined'
319          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
320          errCount = errCount + 1          errCount = errCount + 1
321        ENDIF        ENDIF
# Line 278  C       code is being compiled Line 327  C       code is being compiled
327       &  'CONFIG_CHECK: balanceTheta/SaltClimRelax is set ',       &  'CONFIG_CHECK: balanceTheta/SaltClimRelax is set ',
328       &  'but balance code is not compiled.'       &  'but balance code is not compiled.'
329          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
330          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
331       &  'Re-compile with  ALLOW_BALANCE_RELAX defined'       &  'Re-compile with  ALLOW_BALANCE_RELAX defined'
332          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
333          errCount = errCount + 1          errCount = errCount + 1
# Line 321  C--   Check parameter consistency : Line 370  C--   Check parameter consistency :
370          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
371          errCount = errCount + 1          errCount = errCount + 1
372        ENDIF        ENDIF
373          IF ( ( OLx.LT.3 .OR. OLy.LT.3 ) .AND.
374         &     useSmag3D .AND. useCDscheme ) THEN
375            WRITE(msgBuf,'(A,A)')
376         &  'CONFIG_CHECK: cannot use Smag-3D + CD-scheme with',
377         &  ' overlap (OLx,OLy) smaller than 3'
378            CALL PRINT_ERROR( msgBuf, myThid )
379            errCount = errCount + 1
380          ENDIF
381    
382  #ifndef DISCONNECTED_TILES  #ifndef DISCONNECTED_TILES
383  C     Overlaps cannot be larger than interior tile except for special cases  C     Overlaps cannot be larger than interior tile except for special cases
# Line 354  C     Overlaps cannot be larger than int Line 411  C     Overlaps cannot be larger than int
411        ENDIF        ENDIF
412  #endif /* ndef DISCONNECTED_TILES */  #endif /* ndef DISCONNECTED_TILES */
413    
414    C--   Gravity vertical profile limitations:
415          IF ( usingPCoords .AND. gravityFile .NE. ' ' ) THEN
416            WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: Variable gravity',
417         &  ' not yet implemented for P-coordinate'
418            CALL PRINT_ERROR( msgBuf, myThid )
419            errCount = errCount + 1
420          ENDIF
421          IF ( select_rStar.NE.0 .AND. gravityFile .NE. ' ' ) THEN
422            WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: Variable gravity',
423         &  ' not yet implemented with rStar'
424            CALL PRINT_ERROR( msgBuf, myThid )
425            errCount = errCount + 1
426          ENDIF
427    
428  C--   Deep-Atmosphere & Anelastic limitations:  C--   Deep-Atmosphere & Anelastic limitations:
429        IF ( deepAtmosphere .AND.        IF ( deepAtmosphere .AND.
430       &     useRealFreshWaterFlux .AND. usingPCoords ) THEN       &     useRealFreshWaterFlux .AND. usingPCoords ) THEN
# Line 372  C--   Deep-Atmosphere & Anelastic limita Line 443  C--   Deep-Atmosphere & Anelastic limita
443          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
444          errCount = errCount + 1          errCount = errCount + 1
445        ENDIF        ENDIF
446        IF ( vectorInvariantMomentum .AND.  
447       &        ( deepAtmosphere .OR.  C--   Free-surface related limitations:
448       &          usingZCoords.AND.rhoRefFile .NE. ' ' ) ) THEN        IF ( cg2dUseMinResSol.LT.0 .OR. cg2dUseMinResSol.GT.1 ) THEN
449          WRITE(msgBuf,'(A,A)')          WRITE(msgBuf,'(A,I10,A)')
450       &  'CONFIG_CHECK: Deep-Atmosphere or Anelastic',       &   'CONFIG_CHECK: cg2dUseMinResSol set to unvalid value(=',
451       &  ' not yet implemented in Vector-Invariant momentum code'       &                  cg2dUseMinResSol, ')'
452          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
453          errCount = errCount + 1          errCount = errCount + 1
454        ENDIF        ENDIF
455    
 C--   Free-surface related limitations:  
456        IF ( rigidLid .AND. implicitFreeSurface ) THEN        IF ( rigidLid .AND. implicitFreeSurface ) THEN
457          WRITE(msgBuf,'(A,A)')          WRITE(msgBuf,'(A,A)')
458       &  'CONFIG_CHECK: Cannot select both implicitFreeSurface',       &  'CONFIG_CHECK: Cannot select both implicitFreeSurface',
# Line 450  C--   Free-surface related limitations: Line 520  C--   Free-surface related limitations:
520          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
521          errCount = errCount + 1          errCount = errCount + 1
522        ENDIF        ENDIF
523          IF ( select_rStar.EQ.2 .AND. nonlinFreeSurf.NE.4 ) THEN
524    C-    not consistent to account for the slope of the coordinate when
525    C     ignoring the variations of level-thickness in PhiHyd calculation;
526    C     for now, issue a warning (but might change the code later on):
527            WRITE(msgBuf,'(2A,I3)') '** WARNING ** CONFIG_CHECK: ',
528         &   'select_rStar=2 not right with nonlinFreeSurf=', nonlinFreeSurf
529            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
530         &                      SQUEEZE_RIGHT, myThid )
531          ENDIF
532    
533        IF ( selectSigmaCoord.NE.0 ) THEN        IF ( selectSigmaCoord.NE.0 ) THEN
534         IF ( fluidIsWater ) THEN         IF ( fluidIsWater ) THEN
# Line 482  c       STOP 'ABNORMAL END: S/R CONFIG_C Line 561  c       STOP 'ABNORMAL END: S/R CONFIG_C
561  c     ENDIF  c     ENDIF
562    
563        IF ( nonlinFreeSurf.NE.0 .AND.        IF ( nonlinFreeSurf.NE.0 .AND.
564       &     deltaTfreesurf.NE.dTtracerLev(1) ) THEN       &     deltaTFreeSurf.NE.dTtracerLev(1) ) THEN
565          WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',          WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
566       &                       'nonlinFreeSurf might cause problems'       &                       'nonlinFreeSurf might cause problems'
567          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
# Line 571  c     ENDIF Line 650  c     ENDIF
650       &                      SQUEEZE_RIGHT, myThid )       &                      SQUEEZE_RIGHT, myThid )
651        ENDIF        ENDIF
652    
653    C--   Pressure calculation and pressure gradient:
654    #ifndef INCLUDE_PHIHYD_CALCULATION_CODE
655          IF ( momPressureForcing .OR. storePhiHyd4Phys ) THEN
656            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
657         &   'missing code to calculate pressure (totPhiHyd)'
658            CALL PRINT_ERROR( msgBuf, myThid )
659            errCount = errCount + 1
660          ENDIF
661    #endif /* INCLUDE_PHIHYD_CALCULATION_CODE */
662          IF ( storePhiHyd4Phys .AND. .NOT.momStepping ) THEN
663            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
664         &   'storePhiHyd4Phys = TRUE but pressure is not computed'
665            CALL PRINT_ERROR( msgBuf, myThid )
666            errCount = errCount + 1
667          ENDIF
668    
669  C--   Non-hydrostatic and 3-D solver related limitations:  C--   Non-hydrostatic and 3-D solver related limitations:
670        IF (nonlinFreeSurf.NE.0 .AND. use3Dsolver) THEN        IF (nonlinFreeSurf.NE.0 .AND. use3Dsolver) THEN
671          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 617  C--   Non-hydrostatic and 3-D solver rel Line 712  C--   Non-hydrostatic and 3-D solver rel
712          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
713       &                      SQUEEZE_RIGHT, myThid )       &                      SQUEEZE_RIGHT, myThid )
714          WRITE(msgBuf,'(2A)') '** WARNING ** => not consistent with',          WRITE(msgBuf,'(2A)') '** WARNING ** => not consistent with',
715       &    'final vertical shear (after appling 3-D solver solution'       &    ' final vertical shear (after appling 3-D solver solution'
716          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
717       &                      SQUEEZE_RIGHT, myThid )       &                      SQUEEZE_RIGHT, myThid )
718        ENDIF        ENDIF
# Line 641  C--   Momentum related limitations: Line 736  C--   Momentum related limitations:
736          errCount = errCount + 1          errCount = errCount + 1
737         ENDIF         ENDIF
738        ENDIF        ENDIF
739          IF ( .NOT.vectorInvariantMomentum .AND. momAdvection ) THEN
740           IF ( usingCurvilinearGrid ) THEN
741            WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
742         &       'missing metric-terms for CurvilinearGrid'
743            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
744         &                      SQUEEZE_RIGHT, myThid )
745           ENDIF
746           IF ( hasWetCSCorners ) THEN
747            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: momAdvection ',
748         &   'in flux-form is wrong on CubedSphere grid (corners)'
749            CALL PRINT_ERROR( msgBuf, myThid )
750            errCount = errCount + 1
751           ENDIF
752          ENDIF
753        IF ( selectCoriMap.LT.0 .OR. selectCoriMap.GT.3 ) THEN        IF ( selectCoriMap.LT.0 .OR. selectCoriMap.GT.3 ) THEN
754          WRITE(msgBuf,'(2A,I4)') 'CONFIG_CHECK: ',          WRITE(msgBuf,'(2A,I4)') 'CONFIG_CHECK: ',
755       &       'Invalid option: selectCoriMap=', selectCoriMap       &       'Invalid option: selectCoriMap=', selectCoriMap
756          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
757          errCount = errCount + 1          errCount = errCount + 1
758        ENDIF        ENDIF
759          IF ( selectBotDragQuadr.LT.-1 .OR. selectBotDragQuadr.GT.2 ) THEN
760            WRITE(msgBuf,'(2A,I8,A)') 'CONFIG_CHECK: ',
761         &       'selectBotDragQuadr=', selectBotDragQuadr,
762         &       ' not valid (-1,0,1,2)'
763            CALL PRINT_ERROR( msgBuf, myThid )
764            errCount = errCount + 1
765          ENDIF
766          IF ( useSmag3D .AND.
767         &    ( usingPCoords .OR. deepAtmosphere .OR. selectSigmaCoord.NE.0
768         &                   .OR. rhoRefFile.NE.' ' .OR. hasWetCSCorners )
769         &   ) THEN
770            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
771         &       'Smag-3D not yet implemented for this set-up'
772            CALL PRINT_ERROR( msgBuf, myThid )
773            errCount = errCount + 1
774          ENDIF
775    
776        IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN        IF ( momStepping .AND. .NOT.useCDscheme
777         &                 .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN
778  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),
779  C       put this WARNING to stress that even if CD-scheme parameters  C       put this WARNING to stress that even if CD-scheme parameters
780  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
781  C-    and STOP if using mom_fluxform (following Chris advise).  C-    and STOP if using mom_fluxform (following Chris advise).
782  C- jmc: but ultimately, this block can/will be removed.  C- jmc: but ultimately, this block can/will be removed.
783         IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN         IF ( vectorInvariantMomentum ) THEN
784            WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
785         &   'CD-scheme is OFF but params(tauCD,rCD) are set'
786            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
787         &                      SQUEEZE_RIGHT, myThid )
788            WRITE(msgBuf,'(3A)') '** WARNING ** to turn ON CD-scheme:',
789         &   ' => "useCDscheme=.TRUE." in "data", namelist PARM01'
790            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
791         &                      SQUEEZE_RIGHT, myThid )
792           ELSE
793          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
794       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
795          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
# Line 664  C- jmc: but ultimately, this block can/w Line 799  C- jmc: but ultimately, this block can/w
799          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
800          errCount = errCount + 1          errCount = errCount + 1
801         ENDIF         ENDIF
         WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',  
      &   'CD-scheme is OFF but params(tauCD,rCD) are set'  
         CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,  
      &                      SQUEEZE_RIGHT, myThid )  
         WRITE(msgBuf,'(3A)') '** WARNING ** ',  
      &   'to turn ON CD-scheme: => "useCDscheme=.TRUE."',  
      &   ' in "data", namelist PARM01'  
         WRITE(msgBuf,'(3A)') '** WARNING ** to turn ON CD-scheme:',  
      &   ' => "useCDscheme=.TRUE." in "data", namelist PARM01'  
         CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,  
      &                      SQUEEZE_RIGHT, myThid )  
802        ENDIF        ENDIF
803    
804        IF ( useCDscheme .AND. useCubedSphereExchange ) THEN        IF ( useCDscheme .AND. hasWetCSCorners ) THEN
805          WRITE(msgBuf,'(2A)')          WRITE(msgBuf,'(2A)')
806       &   'CONFIG_CHECK: CD-scheme not implemented on CubedSphere grid'       &   'CONFIG_CHECK: CD-scheme not implemented on CubedSphere grid'
807          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
808  cph        errCount = errCount + 1          errCount = errCount + 1
809        ENDIF        ENDIF
810    
811  C--   Time-stepping limitations  C--   Time-stepping limitations
812          IF ( implicitIntGravWave .AND. staggerTimeStep ) THEN
813            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: staggerTimeStep',
814         &    ' incompatible with implicitIntGravWave'
815            CALL PRINT_ERROR( msgBuf, myThid )
816            errCount = errCount + 1
817          ENDIF
818        IF ( momForcingOutAB.NE.0 .AND. momForcingOutAB.NE.1 ) THEN        IF ( momForcingOutAB.NE.0 .AND. momForcingOutAB.NE.1 ) THEN
819          WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: momForcingOutAB=',          WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: momForcingOutAB=',
820       &                             momForcingOutAB, ' not allowed'       &                             momForcingOutAB, ' not allowed'
# Line 703  C--   Time-stepping limitations Line 833  C--   Time-stepping limitations
833          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
834          errCount = errCount + 1          errCount = errCount + 1
835        ENDIF        ENDIF
836          IF ( implBottomFriction ) THEN
837            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: implBottomFriction',
838         &  ' not yet coded.'
839            CALL PRINT_ERROR( msgBuf, myThid )
840            errCount = errCount + 1
841          ENDIF
842    
843  C--   Grid limitations:  C--   Grid limitations:
844        IF ( rotateGrid ) THEN        IF ( rotateGrid ) THEN
# Line 758  C--   Packages conflict Line 894  C--   Packages conflict
894  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
895    
896        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
       WRITE(msgBuf,'(A)')  
      &'// ======================================================='  
       CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,  
      &                    SQUEEZE_RIGHT, myThid )  
897        WRITE(msgBuf,'(A)') '// CONFIG_CHECK : Normal End'        WRITE(msgBuf,'(A)') '// CONFIG_CHECK : Normal End'
898        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
899       &                    SQUEEZE_RIGHT, myThid )       &                    SQUEEZE_RIGHT, myThid )

Legend:
Removed from v.1.68  
changed lines
  Added in v.1.83

  ViewVC Help
Powered by ViewVC 1.1.22