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 10425 for NEMO/trunk/src/OCE/stpctl.F90 – NEMO

Ignore:
Timestamp:
2018-12-19T22:54:16+01:00 (5 years ago)
Author:
smasson
Message:

trunk: merge back dev_r10164_HPC09_ESIWACE_PREP_MERGE@10424 into the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/stpctl.F90

    r10415 r10425  
    3434 
    3535   INTEGER  ::   idrun, idtime, idssh, idu, ids1, ids2, idt1, idt2, idc1, idw1, istatus 
     36   LOGICAL  ::   lsomeoce 
    3637   !!---------------------------------------------------------------------- 
    3738   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    5051      !!              - Print it each 50 time steps 
    5152      !!              - Stop the run IF problem encountered by setting indic=-3 
    52       !!                Problems checked: |ssh| maximum larger than 20 m 
     53      !!                Problems checked: |ssh| maximum larger than 10 m 
    5354      !!                                  |U|   maximum larger than 10 m/s  
    5455      !!                                  negative sea surface salinity 
     
    6162      INTEGER, INTENT(inout) ::   kindic   ! error indicator 
    6263      !! 
    63       INTEGER  ::   ji, jj, jk             ! dummy loop indices 
    64       INTEGER  ::   iih, ijh               ! local integers 
    65       INTEGER  ::   iiu, iju, iku          !   -       - 
    66       INTEGER  ::   iis1, ijs1, iks1       !   -       - 
    67       INTEGER  ::   iis2, ijs2, iks2       !   -       - 
    68       REAL(wp) ::   zzz                    ! local real  
    69       INTEGER , DIMENSION(3) ::   ilocu, ilocs1, ilocs2 
    70       INTEGER , DIMENSION(2) ::   iloch 
     64      INTEGER                ::   ji, jj, jk          ! dummy loop indices 
     65      INTEGER, DIMENSION(2)  ::   ih                  ! min/max loc indices 
     66      INTEGER, DIMENSION(3)  ::   iu, is1, is2        ! min/max loc indices 
     67      REAL(wp)               ::   zzz                 ! local real  
    7168      REAL(wp), DIMENSION(9) ::   zmax 
    7269      CHARACTER(len=20) :: clname 
     
    7875         WRITE(numout,*) '~~~~~~~' 
    7976         !                                ! open time.step file 
    80          CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
     77         IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    8178         !                                ! open run.stat file 
    82          CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    83  
    84          IF( lwm ) THEN 
     79         IF( ln_ctl .AND. lwm ) THEN 
     80            CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    8581            clname = 'run.stat.nc' 
    8682            IF( .NOT. Agrif_Root() )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname) 
     
    9894            ENDIF 
    9995            istatus = NF90_ENDDEF(idrun) 
     96            zmax(8:9) = 0._wp    ! initialise to zero in case ln_zad_Aimp option is not in use 
    10097         ENDIF 
    101          zmax(8:9) = 0._wp    ! initialise to zero in case ln_zad_Aimp option is not in use 
    102           
    10398      ENDIF 
     99      IF( kt == nit000 )   lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 0 
    104100      ! 
    105       IF(lwp) THEN                        !==  current time step  ==!   ("time.step" file) 
     101      IF(lwm) THEN                        !==  current time step  ==!   ("time.step" file) 
    106102         WRITE ( numstp, '(1x, i8)' )   kt 
    107103         REWIND( numstp ) 
     
    125121      ENDIF 
    126122      ! 
    127       IF( lk_mpp ) THEN 
    128          CALL mpp_max_multiple( zmax(:), 9 )    ! max over the global domain 
    129          ! 
     123      IF( ln_ctl ) THEN 
     124         CALL mpp_max( "stpctl", zmax )          ! max over the global domain 
    130125         nstop = NINT( zmax(7) )                 ! nstop indicator sheared among all local domains 
    131126      ENDIF 
    132       ! 
    133       IF( MOD( kt, nwrite ) == 1 .AND. lwp ) THEN 
    134          WRITE(numout,*) ' ==>> time-step= ', kt, ' |ssh| max: ',   zmax(1), ' |U| max: ', zmax(2),   & 
    135             &                                     ' S min: '    , - zmax(3), ' S max: ', zmax(4) 
    136       ENDIF 
    137       ! 
    138       IF (  zmax(1) >   20._wp .OR.   &                    ! too large sea surface height ( > 20 m ) 
    139          &  zmax(2) >   10._wp .OR.   &                    ! too large velocity ( > 10 m/s) 
    140          &  zmax(3) >=   0._wp .OR.   &                    ! negative or zero sea surface salinity 
    141          &  zmax(4) >= 100._wp .OR.   &                    ! too large sea surface salinity ( > 100 ) 
    142          &  zmax(4) <    0._wp .OR.   &                    ! too large sea surface salinity (keep this line for sea-ice) 
    143          &  ISNAN( zmax(1) + zmax(2) + zmax(3) )  ) THEN   ! NaN encounter in the tests 
    144          IF( lk_mpp ) THEN 
    145             CALL mpp_maxloc( ABS(sshn)        , ssmask(:,:)  , zzz, iih , ijh        ) 
    146             CALL mpp_maxloc( ABS(un)          , umask (:,:,:), zzz, iiu , iju , iku  ) 
    147             CALL mpp_minloc( tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, iis1, ijs1, iks1 ) 
    148             CALL mpp_maxloc( tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, iis2, ijs2, iks2 ) 
    149          ELSE 
    150             iloch  = MINLOC( ABS( sshn(:,:)   )                               ) 
    151             ilocu  = MAXLOC( ABS( un  (:,:,:) )                               ) 
    152             ilocs1 = MINLOC( tsn(:,:,:,jp_sal) , mask = tmask(:,:,:) == 1._wp ) 
    153             ilocs2 = MAXLOC( tsn(:,:,:,jp_sal) , mask = tmask(:,:,:) == 1._wp ) 
    154             iih  = iloch (1) + nimpp - 1   ;   ijh  = iloch (2) + njmpp - 1 
    155             iiu  = ilocu (1) + nimpp - 1   ;   iju  = ilocu (2) + njmpp - 1   ;   iku  = ilocu (3) 
    156             iis1 = ilocs1(1) + nimpp - 1   ;   ijs1 = ilocs1(2) + njmpp - 1   ;   iks1 = ilocs1(3) 
    157             iis2 = ilocs2(1) + nimpp - 1   ;   ijs2 = ilocs2(2) + njmpp - 1   ;   iks2 = ilocs2(3) 
    158          ENDIF 
    159          IF(lwp) THEN 
    160             WRITE(numout,cform_err) 
    161             WRITE(numout,*) ' stp_ctl: |ssh| > 20 m  or  |U| > 10 m/s  or  S <= 0  or  S >= 100  or  NaN encounter in the tests' 
    162             WRITE(numout,*) ' ======= ' 
    163             WRITE(numout,9100) kt,   zmax(1), iih , ijh 
    164             WRITE(numout,9200) kt,   zmax(2), iiu , iju , iku 
    165             WRITE(numout,9300) kt, - zmax(3), iis1, ijs1, iks1 
    166             WRITE(numout,9400) kt,   zmax(4), iis2, ijs2, iks2 
    167             WRITE(numout,*) 
    168             WRITE(numout,*) '          output of last computed fields in output.abort.nc file' 
    169          ENDIF 
    170          kindic = -3 
    171          ! 
    172          nstop = nstop + 1                            ! increase nstop by 1 (on all local domains) 
    173          CALL dia_wri_state( 'output.abort', kt )     ! create an output.abort file 
    174          ! 
    175       ENDIF 
    176 9100  FORMAT (' kt=',i8,'   |ssh| max: ',1pg11.4,', at  i j  : ',2i5) 
    177 9200  FORMAT (' kt=',i8,'   |U|   max: ',1pg11.4,', at  i j k: ',3i5) 
    178 9300  FORMAT (' kt=',i8,'   S     min: ',1pg11.4,', at  i j k: ',3i5) 
    179 9400  FORMAT (' kt=',i8,'   S     max: ',1pg11.4,', at  i j k: ',3i5) 
    180       ! 
    181       !                                            !==  run statistics  ==!   ("run.stat" file) 
    182       IF(lwp) WRITE(numrun,9500) kt, zmax(1), zmax(2), -zmax(3), zmax(4) 
    183       IF( lwm ) THEN 
     127      !                                   !==  run statistics  ==!   ("run.stat" files) 
     128      IF( ln_ctl .AND. lwm ) THEN 
     129         WRITE(numrun,9500) kt, zmax(1), zmax(2), -zmax(3), zmax(4) 
    184130         istatus = NF90_PUT_VAR( idrun, idssh, (/ zmax(1)/), (/kt/), (/1/) ) 
    185131         istatus = NF90_PUT_VAR( idrun,   idu, (/ zmax(2)/), (/kt/), (/1/) ) 
     
    195141         IF( kt == nitend         ) istatus = NF90_CLOSE(idrun) 
    196142      END IF 
     143      !                                   !==  error handling  ==! 
     144      IF( ( ln_ctl .OR. lsomeoce ) .AND. (   &             ! have use mpp_max (because ln_ctl=.T.) or contains some ocean points 
     145         &  zmax(1) >   20._wp .OR.   &                    ! too large sea surface height ( > 20 m ) 
     146         &  zmax(2) >   10._wp .OR.   &                    ! too large velocity ( > 10 m/s) 
     147         &  zmax(3) >=   0._wp .OR.   &                    ! negative or zero sea surface salinity 
     148         &  zmax(4) >= 100._wp .OR.   &                    ! too large sea surface salinity ( > 100 ) 
     149         &  zmax(4) <    0._wp .OR.   &                    ! too large sea surface salinity (keep this line for sea-ice) 
     150         &  ISNAN( zmax(1) + zmax(2) + zmax(3) ) ) ) THEN   ! NaN encounter in the tests 
     151         IF( lk_mpp .AND. ln_ctl ) THEN 
     152            CALL mpp_maxloc( 'stpctl', ABS(sshn)        , ssmask(:,:)  , zzz, ih  ) 
     153            CALL mpp_maxloc( 'stpctl', ABS(un)          , umask (:,:,:), zzz, iu  ) 
     154            CALL mpp_minloc( 'stpctl', tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, is1 ) 
     155            CALL mpp_maxloc( 'stpctl', tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, is2 ) 
     156         ELSE 
     157            ih(:)  = MAXLOC( ABS( sshn(:,:)   )                              ) + (/ nimpp - 1, njmpp - 1    /) 
     158            iu(:)  = MAXLOC( ABS( un  (:,:,:) )                              ) + (/ nimpp - 1, njmpp - 1, 0 /) 
     159            is1(:) = MINLOC( tsn(:,:,:,jp_sal), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 
     160            is2(:) = MAXLOC( tsn(:,:,:,jp_sal), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 
     161         ENDIF 
     162          
     163         WRITE(ctmp1,*) ' stp_ctl: |ssh| > 20 m  or  |U| > 10 m/s  or  S <= 0  or  S >= 100  or  NaN encounter in the tests' 
     164         WRITE(ctmp2,9100) kt,   zmax(1), ih(1) , ih(2) 
     165         WRITE(ctmp3,9200) kt,   zmax(2), iu(1) , iu(2) , iu(3) 
     166         WRITE(ctmp4,9300) kt, - zmax(3), is1(1), is1(2), is1(3) 
     167         WRITE(ctmp5,9400) kt,   zmax(4), is2(1), is2(2), is2(3) 
     168         WRITE(ctmp6,*) '      ===> output of last computed fields in output.abort.nc file' 
     169          
     170         CALL dia_wri_state( 'output.abort' )     ! create an output.abort file 
     171          
     172         IF( .NOT. ln_ctl ) THEN 
     173            WRITE(ctmp8,*) 'E R R O R message from sub-domain: ', narea 
     174            CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp8, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ctmp6 ) 
     175         ELSE 
     176            CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6, ' ' ) 
     177         ENDIF 
     178 
     179         kindic = -3 
     180         ! 
     181      ENDIF 
    197182      ! 
     1839100  FORMAT (' kt=',i8,'   |ssh| max: ',1pg11.4,', at  i j  : ',2i5) 
     1849200  FORMAT (' kt=',i8,'   |U|   max: ',1pg11.4,', at  i j k: ',3i5) 
     1859300  FORMAT (' kt=',i8,'   S     min: ',1pg11.4,', at  i j k: ',3i5) 
     1869400  FORMAT (' kt=',i8,'   S     max: ',1pg11.4,', at  i j k: ',3i5) 
    1981879500  FORMAT(' it :', i8, '    |ssh|_max: ', D23.16, ' |U|_max: ', D23.16,' S_min: ', D23.16,' S_max: ', D23.16) 
    199188      ! 
Note: See TracChangeset for help on using the changeset viewer.