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: |U| and |ssh| maximum larger than 10 m/s !! sea surface salinity (SSS) minimum < 0 !! !! ** Actions : 'time.step' file containing the last ocean time-step !! !!---------------------------------------------------------------------- INTEGER, INTENT(in ) :: kt ! ocean time-step index INTEGER, INTENT(inout) :: kindic ! error indicator !! INTEGER :: ji, jj, jk ! dummy loop indices INTEGER :: ii, ij, ik ! local integers REAL(wp) :: zzt ! local real INTEGER , DIMENSION(3) :: ilocu ! INTEGER , DIMENSION(2) :: ilocs ! 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( un(:,:,:) ) ) ! velocity max (zonal only) zmax(2) = MAXVAL( -tsn(:,:,1,jp_sal) , mask = tmask(:,:,1) == 1._wp ) ! minus surface salinity max zmax(3) = MAXVAL( sshn(:,:)*sshn(:,:), mask = tmask(:,:,1) == 1._wp ) ! ssh^2 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,' |U| max: ', zmax(1), ' SSS min:', - zmax(2) ENDIF ! IF( zmax(1) > 10._wp ) THEN !* too large velocity ( > 10 m/s) IF( lk_mpp ) THEN CALL mpp_maxloc( ABS(un), umask, zmax(1), ii, ij, ik ) ELSE ilocu = MAXLOC( ABS( un(:,:,:) ) ) ii = ilocu(1) + nimpp - 1 ij = ilocu(2) + njmpp - 1 ik = ilocu(3) ENDIF IF(lwp) THEN WRITE(numout,cform_err) WRITE(numout,*) ' stpctl: the zonal velocity is larger than 20 m/s' WRITE(numout,*) ' ====== ' WRITE(numout,9400) kt, zmax(1), ii, ij, ik WRITE(numout,*) WRITE(numout,*) ' output of last computed fields in output.abort.nc file' ENDIF kindic = -3 ENDIF 9400 FORMAT (' kt=',i6,' max abs(U): ',1pg11.4,', i j k: ',3i5) ! IF( -zmax(2) < 0._wp ) THEN !* negative salinity IF( lk_mpp ) THEN CALL mpp_minloc( tsn(:,:,1,jp_sal),tmask(:,:,1), zzt, ii, ij ) ELSE ilocs = MINLOC( tsn(:,:,1,jp_sal), mask = tmask(:,:,1) == 1._wp ) ii = ilocs(1) + nimpp - 1 ij = ilocs(2) + njmpp - 1 ENDIF ! IF(lwp) THEN WRITE(numout,cform_err) WRITE(numout,*) 'stp_ctl : NEGATIVE sea surface salinity' WRITE(numout,*) '======= ' WRITE(numout,9500) kt, -zmax(2), ii, ij WRITE(numout,*) WRITE(numout,*) ' output of last fields in numwso' ENDIF kindic = -3 ENDIF 9500 FORMAT (' kt=',i6,' min SSS: ',1pg11.4,', i j: ',2i5) ! ! !== run statistics ==! ("run.stat" file) IF(lwp) WRITE(numrun,9200) kt, zmax(3), zmax(1), - zmax(2) ! formerly called "solver.stat" file ! 9200 FORMAT(' it :', i8, ' ssh2: ', e16.10, ' Umax: ',e16.10,' Smin: ',e16.10) ! END SUBROUTINE stp_ctl !!====================================================================== END MODULE stpctl