/[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.32 by jmc, Fri Feb 10 22:56:19 2006 UTC revision 1.33 by jmc, Thu Feb 23 16:46:47 2006 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 45  C-  check that CPP option is "defined" w Line 45  C-  check that CPP option is "defined" w
45          WRITE(msgBuf,'(2A)') '**WARNNING** ',          WRITE(msgBuf,'(2A)') '**WARNNING** ',
46       &   'CONFIG_CHECK: useMNC is TRUE and #undef ALLOW_MNC'       &   'CONFIG_CHECK: useMNC is TRUE and #undef ALLOW_MNC'
47          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
48       &       SQUEEZE_RIGHT , myThid)                             &       SQUEEZE_RIGHT , myThid)
49        ENDIF        ENDIF
50  #endif  #endif
51    
# Line 160  C-  check that CPP option is "defined" w Line 160  C-  check that CPP option is "defined" w
160        IF (select_rStar .NE. 0) THEN        IF (select_rStar .NE. 0) THEN
161          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
162       &   'CONFIG_CHECK: rStar is part of NonLin-FS '       &   'CONFIG_CHECK: rStar is part of NonLin-FS '
163          CALL PRINT_ERROR( msgBuf, myThid)                                CALL PRINT_ERROR( msgBuf, myThid)
164          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
165       &   'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to use it'       &   'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to use it'
166          CALL PRINT_ERROR( msgBuf, myThid)                                CALL PRINT_ERROR( msgBuf, myThid)
167          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
168        ENDIF        ENDIF
169  #endif /* NONLIN_FRSURF */  #endif /* NONLIN_FRSURF */
# Line 273  C-  check parameter consistency : Line 273  C-  check parameter consistency :
273       &  ' overlap (Olx,Oly) smaller than 3'       &  ' overlap (Olx,Oly) smaller than 3'
274          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
275          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
276        ENDIF                        ENDIF
277        IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.        IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
278       &     ( viscC2leithD.NE.0. .OR. viscC4leithD.NE.0. )       &     ( viscC2leithD.NE.0. .OR. viscC4leithD.NE.0. )
279       &   ) THEN       &   ) THEN
# Line 282  C-  check parameter consistency : Line 282  C-  check parameter consistency :
282       &  ' overlap (Olx,Oly) smaller than 3'       &  ' overlap (Olx,Oly) smaller than 3'
283          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
284          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
285        ENDIF                        ENDIF
286    
287        IF ( rigidLid .AND. implicitFreeSurface ) THEN        IF ( rigidLid .AND. implicitFreeSurface ) THEN
288          WRITE(msgBuf,'(A,A)')          WRITE(msgBuf,'(A,A)')
# Line 290  C-  check parameter consistency : Line 290  C-  check parameter consistency :
290       &  ' and rigidLid.'       &  ' and rigidLid.'
291          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
292          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
293        ENDIF                        ENDIF
294    
295        IF (rigidLid .AND. exactConserv) THEN        IF (rigidLid .AND. exactConserv) THEN
296          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
# Line 354  c       CALL PRINT_ERROR( msgBuf , 1) Line 354  c       CALL PRINT_ERROR( msgBuf , 1)
354  c       STOP 'ABNORMAL END: S/R CONFIG_CHECK'  c       STOP 'ABNORMAL END: S/R CONFIG_CHECK'
355  c     ENDIF  c     ENDIF
356    
357        IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN  c     IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN
358          IF (nonlinFreeSurf.NE.0 .AND. use3Dsolver) THEN
359          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
360       &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'       &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'
361          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
# Line 369  c     ENDIF Line 370  c     ENDIF
370          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
371       &   'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'       &   'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'
372          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
373       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
374          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
375       &   'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'       &   'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'
376          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
377       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
378        ENDIF        ENDIF
379    
380        IF ( useRealFreshWaterFlux .AND. exactConserv        IF ( useRealFreshWaterFlux .AND. exactConserv
# Line 393  c     ENDIF Line 394  c     ENDIF
394          WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: **WARNNING** ',          WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: **WARNNING** ',
395       &   'RealFreshWater & implicDiv2DFlow < 1'       &   'RealFreshWater & implicDiv2DFlow < 1'
396          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
397       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
398          WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: works better',          WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: works better',
399       &   ' with exactConserv=.T. (+ #define EXACT_CONSERV)'       &   ' with exactConserv=.T. (+ #define EXACT_CONSERV)'
400          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
401       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
402        ENDIF        ENDIF
403    
404  #ifdef EXACT_CONSERV  #ifdef EXACT_CONSERV
# Line 417  c     ENDIF Line 418  c     ENDIF
418          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
419       &   'CONFIG_CHECK: E-P effects on wVel are not included'       &   'CONFIG_CHECK: E-P effects on wVel are not included'
420          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
421       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
422          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
423       &   'CONFIG_CHECK: ==> use #define EXACT_CONSERV to fix it'       &   'CONFIG_CHECK: ==> use #define EXACT_CONSERV to fix it'
424          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
425       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
426        ENDIF        ENDIF
427  #endif /* EXACT_CONSERV */  #endif /* EXACT_CONSERV */
428    
# Line 444  C- jmc: but ultimately, this block can/w Line 445  C- jmc: but ultimately, this block can/w
445          WRITE(msgBuf,'(2A)') '**WARNNING** ',          WRITE(msgBuf,'(2A)') '**WARNNING** ',
446       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
447          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
448       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
449          WRITE(msgBuf,'(2A)')          WRITE(msgBuf,'(2A)')
450       &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',       &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
451       &   ' in "data", namelist PARM01'       &   ' in "data", namelist PARM01'
452          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
453       &                    SQUEEZE_RIGHT , myThid)                             &                    SQUEEZE_RIGHT , myThid)
454        ENDIF        ENDIF
455    
456        IF ( useCDscheme .AND. useCubedSphereExchange ) THEN        IF ( useCDscheme .AND. useCubedSphereExchange ) THEN
# Line 487  C- jmc: but ultimately, this block can/w Line 488  C- jmc: but ultimately, this block can/w
488       &       'setting usePTRACERS'       &       'setting usePTRACERS'
489          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf , myThid)
490          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
       ENDIF        
         
       IF ( tauThetaClimRelax3Dim .NE. 0. .OR.  
      &     tauSaltClimRelax3Dim .NE. 0. ) THEN  
         WRITE(msgBuf,'(2A)')  
      &       'CONFIG_CHECK: 3-dim. relaxation code has moved to ',  
      &       'separate pkg/rbcs.'  
         CALL PRINT_ERROR( msgBuf , myThid)  
         WRITE(msgBuf,'(2A)')  
      &       'tauThetaClimRelax3Dim, tauSaltClimRelax3Dim no longer ',  
      &       'in use.'  
         CALL PRINT_ERROR( msgBuf , myThid)  
         STOP 'ABNORMAL END: S/R CONFIG_CHECK'  
491        ENDIF        ENDIF
492    
 C------------------------------------------------------------------------------------------  
   
493        WRITE(msgBuf,'(A)') 'CONFIG_CHECK: OK'        WRITE(msgBuf,'(A)') 'CONFIG_CHECK: OK'
494        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
495       &                   SQUEEZE_RIGHT,myThid)       &                   SQUEEZE_RIGHT,myThid)

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

  ViewVC Help
Powered by ViewVC 1.1.22