MODULE stpctl !!====================================================================== !! *** MODULE stpctl *** !! Ocean run control : gross check of the ocean time stepping !! version for standalone surface scheme !!====================================================================== !! 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.5 ! 2012-03 (S. Alderson) !! 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 ice , ONLY : vt_i, u_ice, tm_i ! 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 !! !! ** 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 ! indicator of solver convergence !! 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( vt_i (:,:) ) ! max ice thickness zmax(2) = MAXVAL( ABS( u_ice(:,:) ) ) ! max ice velocity (zonal only) zmax(3) = MAXVAL( -tm_i (:,:)+273.15_wp , mask = ssmask(:,:) == 1._wp ) ! min ice temperature ! IF( lk_mpp ) THEN CALL mpp_max_multiple( zmax(:), 3 ) ! max over the global domain ENDIF ! IF( MOD( kt, nwrite ) == 1 .AND. lwp ) THEN WRITE(numout,*) ' ==>> time-step= ', kt, ' vt_i max: ', zmax(1), ' |u_ice| max: ', zmax(2), ' tm_i min: ', -zmax(3) ENDIF ! !== run statistics ==! ("run.stat" file) IF(lwp) WRITE(numrun,9400) kt, zmax(1), zmax(2), -zmax(3) ! 9400 FORMAT(' it :', i8, ' vt_i_max: ', e16.10, ' |u_ice|_max: ',e16.10,' tm_i_min: ',e16.10) ! END SUBROUTINE stp_ctl !!====================================================================== END MODULE stpctl