New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 11143 for NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/OCE/stpctl.F90 – NEMO

Ignore:
Timestamp:
2019-06-19T18:15:12+02:00 (5 years ago)
Author:
agn
Message:

version w/o FK or local changes for NEMO repo

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/OCE/stpctl.F90

    r10570 r11143  
    6666      INTEGER, DIMENSION(3)  ::   iu, is1, is2        ! min/max loc indices 
    6767      REAL(wp)               ::   zzz                 ! local real  
    68       REAL(wp), DIMENSION(9) ::   zmax 
    69       LOGICAL                ::   ll_wrtstp, ll_colruns, ll_wrtruns 
     68      REAL(wp), DIMENSION(10) ::   zmax 
     69      LOGICAL                ::   ll_wrtstp, ll_colruns, ll_wrtruns, ll_isnan 
    7070      CHARACTER(len=20) :: clname 
    7171      !!---------------------------------------------------------------------- 
     
    109109      ENDIF 
    110110      ! 
     111      ll_isnan = ANY(ISNAN(tsn)) .OR. ANY(ISNAN(un)) 
     112      IF (ll_isnan) nstop = nstop + 1 
    111113      !                                   !==  test of extrema  ==! 
    112114      IF( ll_wd ) THEN 
     
    124126         zmax(8) = MAXVAL(  ABS( wi(:,:,:) ) , mask = wmask(:,:,:) == 1._wp ) ! implicit vertical vel. max 
    125127         zmax(9) = MAXVAL(   Cu_adv(:,:,:)   , mask = tmask(:,:,:) == 1._wp ) !       cell Courant no. max 
     128      ENDIF 
     129      IF (ll_isnan) THEN 
     130         zmax(10) = 1._wp                                           ! stop indicator 
     131      ELSE 
     132         zmax(10) = 0._wp 
    126133      ENDIF 
    127134      ! 
     
    147154      END IF 
    148155      !                                   !==  error handling  ==! 
    149       IF( ( ln_ctl .OR. lsomeoce ) .AND. (   &             ! have use mpp_max (because ln_ctl=.T.) or contains some ocean points 
     156      IF( ( (ln_ctl .OR. sn_cfctl%l_runstat) .OR. lsomeoce ) .AND. (   &             ! have use mpp_max (because ln_ctl=.T.) or contains some ocean points 
    150157         &  zmax(1) >   20._wp .OR.   &                    ! too large sea surface height ( > 20 m ) 
    151158         &  zmax(2) >   10._wp .OR.   &                    ! too large velocity ( > 10 m/s) 
     
    153160         &  zmax(4) >= 100._wp .OR.   &                    ! too large sea surface salinity ( > 100 ) 
    154161         &  zmax(4) <    0._wp .OR.   &                    ! too large sea surface salinity (keep this line for sea-ice) 
    155          &  ISNAN( zmax(1) + zmax(2) + zmax(3) ) ) ) THEN   ! NaN encounter in the tests 
    156          IF( lk_mpp .AND. ln_ctl ) THEN 
     162         &  zmax(10) >   0._wp  ) ) THEN   ! NaN encounter in the tests 
     163         ! &  ISNAN( zmax(1) + zmax(2) + zmax(3) ) ) ) THEN   ! NaN encounter in the tests 
     164         IF( lk_mpp .AND. (ln_ctl .OR. sn_cfctl%l_runstat)) THEN 
    157165            CALL mpp_maxloc( 'stpctl', ABS(sshn)        , ssmask(:,:)  , zzz, ih  ) 
    158166            CALL mpp_maxloc( 'stpctl', ABS(un)          , umask (:,:,:), zzz, iu  ) 
Note: See TracChangeset for help on using the changeset viewer.