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.
stpctl.F90 in branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/OPA_SRC – NEMO

source: branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/OPA_SRC/stpctl.F90 @ 9294

Last change on this file since 9294 was 7847, checked in by cetlod, 7 years ago

Bugfix: clear stop with output.abort created after numerical explosion of ssh, see shaconemeo ticket #66

  • Property svn:keywords set to Id
File size: 9.2 KB
RevLine 
[3]1MODULE stpctl
[1489]2   !!======================================================================
[3]3   !!                       ***  MODULE  stpctl  ***
4   !! Ocean run control :  gross check of the ocean time stepping
[1489]5   !!======================================================================
6   !! History :  OPA  ! 1991-03  (G. Madec) Original code
7   !!            6.0  ! 1992-06  (M. Imbard)
8   !!            8.0  ! 1997-06  (A.M. Treguier)
9   !!   NEMO     1.0  ! 2002-06  (G. Madec)  F90: Free form and module
10   !!            2.0  ! 2009-07  (G. Madec)  Add statistic for time-spliting
11   !!----------------------------------------------------------------------
[3]12
13   !!----------------------------------------------------------------------
14   !!   stp_ctl      : Control the run
15   !!----------------------------------------------------------------------
16   USE oce             ! ocean dynamics and tracers variables
17   USE dom_oce         ! ocean space and time domain variables
18   USE sol_oce         ! ocean space and time domain variables
[6204]19   USE sbc_oce         ! surface boundary conditions variables
[3]20   USE in_out_manager  ! I/O manager
21   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
22   USE lib_mpp         ! distributed memory computing
[7847]23   USE lib_fortran     ! Fortran routines library
[367]24   USE dynspg_oce      ! pressure gradient schemes
[2528]25   USE c1d             ! 1D vertical configuration
[3]26
[6204]27
[3]28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC stp_ctl           ! routine called by step.F90
32   !!----------------------------------------------------------------------
[2528]33   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[1489]34   !! $Id$
[2528]35   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[1489]36   !!----------------------------------------------------------------------
[3]37
38CONTAINS
39
40   SUBROUTINE stp_ctl( kt, kindic )
41      !!----------------------------------------------------------------------
42      !!                    ***  ROUTINE stp_ctl  ***
43      !!                     
44      !! ** Purpose :   Control the run
45      !!
46      !! ** Method  : - Save the time step in numstp
47      !!              - Print it each 50 time steps
48      !!              - Print solver statistics in numsol
49      !!              - Stop the run IF problem for the solver ( indec < 0 )
50      !!
[1489]51      !! ** Actions :   'time.step' file containing the last ocean time-step
52      !!               
[3]53      !!----------------------------------------------------------------------
54      INTEGER, INTENT( in ) ::   kt         ! ocean time-step index
55      INTEGER, INTENT( inout ) ::   kindic  ! indicator of solver convergence
[1489]56      !!
[6204]57      CHARACTER(len = 32) ::        clfname ! time stepping output file name
[3]58      INTEGER  ::   ji, jj, jk              ! dummy loop indices
59      INTEGER  ::   ii, ij, ik              ! temporary integers
[7847]60      REAL(wp) ::   zumax, zsmin, zssh2, zsshmax     ! temporary scalars
[3]61      INTEGER, DIMENSION(3) ::   ilocu      !
62      INTEGER, DIMENSION(2) ::   ilocs      !
63      !!----------------------------------------------------------------------
64
65      IF( kt == nit000 .AND. lwp ) THEN
66         WRITE(numout,*)
67         WRITE(numout,*) 'stp_ctl : time-stepping control'
[79]68         WRITE(numout,*) '~~~~~~~'
[6204]69         ! open time.step file with special treatment for SAS
70         IF ( nn_components == jp_iam_sas ) THEN
71            clfname = 'time.step.sas'
72         ELSE
73            clfname = 'time.step'
74         ENDIF
75         CALL ctl_opn( numstp, TRIM(clfname), 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
[3]76      ENDIF
77
[1489]78      IF(lwp) WRITE ( numstp, '(1x, i8)' )   kt      !* save the current time step in numstp
79      IF(lwp) REWIND( numstp )                       !  --------------------------
[3]80
[1489]81      !                                              !* Test maximum of velocity (zonal only)
82      !                                              !  ------------------------
83      !! zumax = MAXVAL( ABS( un(:,:,:) ) )                ! slower than the following loop on NEC SX5
[79]84      zumax = 0.e0
[3]85      DO jk = 1, jpk
86         DO jj = 1, jpj
87            DO ji = 1, jpi
88               zumax = MAX(zumax,ABS(un(ji,jj,jk)))
89          END DO
90        END DO
91      END DO       
[1489]92      IF( lk_mpp )   CALL mpp_max( zumax )                 ! max over the global domain
93      !
94      IF( MOD( kt, nwrite ) == 1 .AND. lwp )   WRITE(numout,*) ' ==>> time-step= ',kt,' abs(U) max: ', zumax
95      !
[1561]96      IF( zumax > 20.e0 ) THEN
[417]97         IF( lk_mpp ) THEN
98            CALL mpp_maxloc(ABS(un),umask,zumax,ii,ij,ik)
[181]99         ELSE
[417]100            ilocu = MAXLOC( ABS( un(:,:,:) ) )
101            ii = ilocu(1) + nimpp - 1
102            ij = ilocu(2) + njmpp - 1
103            ik = ilocu(3)
[15]104         ENDIF
[3]105         IF(lwp) THEN
106            WRITE(numout,cform_err)
107            WRITE(numout,*) ' stpctl: the zonal velocity is larger than 20 m/s'
108            WRITE(numout,*) ' ====== '
109            WRITE(numout,9400) kt, zumax, ii, ij, ik
110            WRITE(numout,*)
111            WRITE(numout,*) '          output of last fields in numwso'
112         ENDIF
[1561]113         kindic = -3
[3]114      ENDIF
[1442]1159400  FORMAT (' kt=',i6,' max abs(U): ',1pg11.4,', i j k: ',3i5)
[3]116
[1489]117      !                                              !* Test minimum of salinity
118      !                                              !  ------------------------
[3294]119      !! zsmin = MINVAL( tsn(:,:,1,jp_sal), mask = tmask(:,:,1) == 1.e0 )  slower than the following loop on NEC SX5
[79]120      zsmin = 100.e0
[3]121      DO jj = 2, jpjm1
122         DO ji = 1, jpi
[3294]123            IF( tmask(ji,jj,1) == 1) zsmin = MIN(zsmin,tsn(ji,jj,1,jp_sal))
[3]124         END DO
125      END DO
[1489]126      IF( lk_mpp )   CALL mpp_min( zsmin )                ! min over the global domain
127      !
128      IF( MOD( kt, nwrite ) == 1 .AND. lwp )   WRITE(numout,*) ' ==>> time-step= ',kt,' SSS min:', zsmin
129      !
[3]130      IF( zsmin < 0.) THEN
[181]131         IF (lk_mpp) THEN
[3294]132            CALL mpp_minloc ( tsn(:,:,1,jp_sal),tmask(:,:,1), zsmin, ii,ij )
[181]133         ELSE
[3294]134            ilocs = MINLOC( tsn(:,:,1,jp_sal), mask = tmask(:,:,1) == 1.e0 )
[181]135            ii = ilocs(1) + nimpp - 1
136            ij = ilocs(2) + njmpp - 1
[1489]137         ENDIF
138         !
[3]139         IF(lwp) THEN
140            WRITE(numout,cform_err)
141            WRITE(numout,*) 'stp_ctl : NEGATIVE sea surface salinity'
142            WRITE(numout,*) '======= '
143            WRITE(numout,9500) kt, zsmin, ii, ij
144            WRITE(numout,*)
145            WRITE(numout,*) '          output of last fields in numwso'
146         ENDIF
[1561]147         kindic = -3
[3]148      ENDIF
[1442]1499500  FORMAT (' kt=',i6,' min SSS: ',1pg11.4,', i j: ',2i5)
[3]150
[2528]151     
152      IF( lk_c1d )  RETURN          ! No log file in case of 1D vertical configuration
153
[1489]154      ! log file (solver or ssh statistics)
155      ! --------
[1528]156      IF( lk_dynspg_flt ) THEN      ! elliptic solver statistics (if required)
[1489]157         !
[1566]158         IF(lwp) WRITE(numsol,9200) kt, niter, res, SQRT(epsr)/eps       ! Solver
[1489]159         !
[1566]160         IF( kindic < 0 .AND. zsmin > 0.e0 .AND. zumax <= 20.e0 ) THEN   ! create a abort file if problem found
[1489]161            IF(lwp) THEN
162               WRITE(numout,*) ' stpctl: the elliptic solver DO not converge or explode'
163               WRITE(numout,*) ' ====== '
164               WRITE(numout,9200) kt, niter, res, sqrt(epsr)/eps
165               WRITE(numout,*)
166               WRITE(numout,*) ' stpctl: output of last fields'
167               WRITE(numout,*) ' ======  '
168            ENDIF
169         ENDIF
170         !
[1581]171      ELSE                                   !* ssh statistics (and others...)
172         IF( kt == nit000 .AND. lwp ) THEN   ! open ssh statistics file (put in solver.stat file)
173            CALL ctl_opn( numsol, 'solver.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
[1489]174         ENDIF
175         !
[7847]176         zsshmax = 0.e0
177         DO jj = 1, jpj
178            DO ji = 1, jpi
179               IF( tmask(ji,jj,1) == 1) zsshmax = MAX( zsshmax, ABS(sshn(ji,jj)) )
180            END DO
181         END DO
182         IF( lk_mpp )   CALL mpp_max( zsshmax )                ! min over the global domain
[1489]183         !
[7847]184         IF( MOD( kt, nwrite ) == 1 .AND. lwp )   WRITE(numout,*) ' ==>> time-step= ',kt,' ssh max:', zsshmax
185           !
186           IF( zsshmax > 10.e0 ) THEN
187              IF (lk_mpp) THEN
188                CALL mpp_maxloc( ABS(sshn(:,:)),tmask(:,:,1),zsshmax,ii,ij)
189              ELSE
190                ilocs = MAXLOC( ABS(sshn(:,:)) )
191                ii = ilocs(1) + nimpp - 1
192                ij = ilocs(2) + njmpp - 1
193              ENDIF
194              !
195              IF(lwp) THEN
196                 WRITE(numout,cform_err)
197                 WRITE(numout,*) 'stp_ctl : the ssh is larger than 10m'
198                 WRITE(numout,*) '======= '
199                 WRITE(numout,9600) kt, zsshmax, ii, ij
200                 WRITE(numout,*)
201                 WRITE(numout,*) '          output of last fields in numwso'
202              ENDIF
203             kindic = -3
204         ENDIF
2059600     FORMAT (' kt=',i6,' max ssh: ',1pg11.4,', i j: ',2i5)
206
207         zssh2 = glob_sum( sshn(:,:) * sshn(:,:) )
208         !
[1489]209         IF(lwp) WRITE(numsol,9300) kt, zssh2, zumax, zsmin      ! ssh statistics
210         !
211      ENDIF
[7607]2129200  FORMAT('it:', i8, ' iter:', i4, ' r: ',d23.16, ' b: ',d23.16 )
2139300  FORMAT(' it :', i8, ' ssh2: ', d23.16, ' Umax: ',d23.16,' Smin: ',d23.16)
[1489]214      !
[3]215   END SUBROUTINE stp_ctl
216
217   !!======================================================================
218END MODULE stpctl
Note: See TracBrowser for help on using the repository browser.