MODULE stpctl !!====================================================================== !! *** MODULE stpctl *** !! Ocean run control : gross check of the ocean time stepping !!====================================================================== !! History : OPA ! 1991-03 (G. Madec) Original code !! 6.0 ! 1992-06 (M. Imbard) !! 8.0 ! 1997-06 (A.M. Treguier) !! NEMO 1.0 ! 2002-06 (G. Madec) F90: Free form and module !! 2.0 ! 2009-07 (G. Madec) Add statistic for time-spliting !! 3.7 ! 2016-09 (G. Madec) Remove solver !! 4.0 ! 2017-04 (G. Madec) regroup global communications !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! stp_ctl : Control the run !!---------------------------------------------------------------------- USE oce ! ocean dynamics and tracers variables USE dom_oce ! ocean space and time domain variables USE c1d ! 1D vertical configuration ! USE in_out_manager ! I/O manager USE lbclnk ! ocean lateral boundary conditions (or mpp link) USE lib_mpp ! distributed memory computing IMPLICIT NONE PRIVATE PUBLIC stp_ctl ! routine called by step.F90 !!---------------------------------------------------------------------- !! NEMO/OPA 4.0 , NEMO Consortium (2017) !! $Id$ !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE stp_ctl( kt, kindic ) !!---------------------------------------------------------------------- !! *** ROUTINE stp_ctl *** !! !! ** Purpose : Control the run !! !! ** Method : - Save the time step in numstp !! - Print it each 50 time steps !! - Stop the run IF problem encountered by setting indic=-3 !! Problems checked: |ssh| maximum larger than 10 m !! |U| maximum larger than 10 m/s !! negative sea surface salinity !! !! ** Actions : "time.step" file = last ocean time-step !! "run.stat" file = run statistics !!---------------------------------------------------------------------- INTEGER, INTENT(in ) :: kt ! ocean time-step index INTEGER, INTENT(inout) :: kindic ! error indicator !! INTEGER :: ji, jj, jk ! dummy loop indices INTEGER :: iih, ijh ! local integers INTEGER :: iiu, iju, iku ! - - INTEGER :: iis, ijs ! - - REAL(wp) :: zzz ! local real INTEGER , DIMENSION(3) :: ilocu INTEGER , DIMENSION(2) :: ilocs, iloch REAL(wp), DIMENSION(3) :: zmax !!---------------------------------------------------------------------- ! IF( kt == nit000 .AND. lwp ) THEN WRITE(numout,*) WRITE(numout,*) 'stp_ctl : time-stepping control' WRITE(numout,*) '~~~~~~~' ! ! open time.step file CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) ! ! open run.stat file CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) ENDIF ! IF(lwp) THEN !== current time step ==! ("time.step" file) WRITE ( numstp, '(1x, i8)' ) kt REWIND( numstp ) ENDIF ! ! !== test of extrema ==! zmax(1) = MAXVAL( ABS( sshn(:,:) ) ) ! ssh max zmax(2) = MAXVAL( ABS( un(:,:,:) ) ) ! velocity max (zonal only) zmax(3) = MAXVAL( -tsn(:,:,1,jp_sal) , mask = tmask(:,:,1) == 1._wp ) ! minus surface salinity max ! IF( lk_mpp ) CALL mpp_max_multiple( zmax(:), 3 ) ! max over the global domain ! IF( MOD( kt, nwrite ) == 1 .AND. lwp ) THEN WRITE(numout,*) ' ==>> time-step= ', kt, ' |ssh| max: ', zmax(1), ' |U| max: ', zmax(2), & & ' SSS min: ' , - zmax(3) ENDIF ! IF ( zmax(1) > 10._wp .OR. & ! too large sea surface height ( > 10 m) & zmax(2) > 10._wp .OR. & ! too large velocity ( > 10 m/s) & zmax(3) > 0._wp ) THEN ! negative sea surface salinity IF( lk_mpp ) THEN CALL mpp_maxloc( ABS(sshn) , tmask(:,:,1), zzz, iih, ijh ) CALL mpp_maxloc( ABS(un) , umask , zzz, iiu, iju, iku ) CALL mpp_minloc( tsn(:,:,1,jp_sal), tmask(:,:,1), zzz, iis, ijs ) ELSE iloch = MINLOC( ABS( sshn(:,:) ) ) ilocu = MAXLOC( ABS( un(:,:,:) ) ) ilocs = MINLOC( tsn(:,:,1,jp_sal), mask = tmask(:,:,1) == 1._wp ) iih = iloch(1) + nimpp - 1 ; ijh = iloch(2) + njmpp - 1 iiu = ilocu(1) + nimpp - 1 ; iju = ilocu(2) + njmpp - 1 ; iku = ilocu(3) iis = ilocs(1) + nimpp - 1 ; ijs = ilocs(2) + njmpp - 1 ENDIF IF(lwp) THEN WRITE(numout,cform_err) WRITE(numout,*) ' stpctl: |ssh| > 10 m or |U| > 10 m/s or SSS < 0' WRITE(numout,*) ' ====== ' WRITE(numout,9100) kt, zmax(1), iih, ijh WRITE(numout,9200) kt, zmax(2), iiu, iju, iku WRITE(numout,9300) kt, - zmax(3), iis, ijs WRITE(numout,*) WRITE(numout,*) ' output of last computed fields in output.abort.nc file' ENDIF kindic = -3 ENDIF 9100 FORMAT (' kt=',i8,' |ssh| max: ',1pg11.4,', at i j : ',2i5) 9200 FORMAT (' kt=',i8,' |U| max: ',1pg11.4,', at i j k: ',3i5) 9300 FORMAT (' kt=',i8,' SSS min: ',1pg11.4,', at i j : ',2i5) ! ! !== run statistics ==! ("run.stat" file) IF(lwp) WRITE(numrun,9400) kt, zmax(1), zmax(2), - zmax(3) ! 9400 FORMAT(' it :', i8, ' |ssh|_max: ', e16.10, ' |U|_max: ',e16.10,' SSS_min: ',e16.10) ! END SUBROUTINE stp_ctl !!====================================================================== END MODULE stpctl