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/UKMO/dev_r5107_hadgem3_cplseq/NEMOGCM/NEMO/OPA_SRC – NEMO

source: branches/UKMO/dev_r5107_hadgem3_cplseq/NEMOGCM/NEMO/OPA_SRC/stpctl.F90 @ 5591

Last change on this file since 5591 was 5477, checked in by cguiavarch, 9 years ago

Clear svn keywords from UKMO/dev_r5107_hadgem3_cplseq

File size: 7.7 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
19   USE in_out_manager  ! I/O manager
20   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
21   USE lib_mpp         ! distributed memory computing
[367]22   USE dynspg_oce      ! pressure gradient schemes
[2528]23   USE c1d             ! 1D vertical configuration
[3]24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC stp_ctl           ! routine called by step.F90
29   !!----------------------------------------------------------------------
[2528]30   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[1489]31   !! $Id$
[2528]32   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[1489]33   !!----------------------------------------------------------------------
[3]34
35CONTAINS
36
37   SUBROUTINE stp_ctl( kt, kindic )
38      !!----------------------------------------------------------------------
39      !!                    ***  ROUTINE stp_ctl  ***
40      !!                     
41      !! ** Purpose :   Control the run
42      !!
43      !! ** Method  : - Save the time step in numstp
44      !!              - Print it each 50 time steps
45      !!              - Print solver statistics in numsol
46      !!              - Stop the run IF problem for the solver ( indec < 0 )
47      !!
[1489]48      !! ** Actions :   'time.step' file containing the last ocean time-step
49      !!               
[3]50      !!----------------------------------------------------------------------
51      INTEGER, INTENT( in ) ::   kt         ! ocean time-step index
52      INTEGER, INTENT( inout ) ::   kindic  ! indicator of solver convergence
[1489]53      !!
[3]54      INTEGER  ::   ji, jj, jk              ! dummy loop indices
55      INTEGER  ::   ii, ij, ik              ! temporary integers
[1489]56      REAL(wp) ::   zumax, zsmin, zssh2     ! temporary scalars
[3]57      INTEGER, DIMENSION(3) ::   ilocu      !
58      INTEGER, DIMENSION(2) ::   ilocs      !
59      !!----------------------------------------------------------------------
60
61      IF( kt == nit000 .AND. lwp ) THEN
62         WRITE(numout,*)
63         WRITE(numout,*) 'stp_ctl : time-stepping control'
[79]64         WRITE(numout,*) '~~~~~~~'
[3]65         ! open time.step file
[1581]66         CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
[3]67      ENDIF
68
[1489]69      IF(lwp) WRITE ( numstp, '(1x, i8)' )   kt      !* save the current time step in numstp
70      IF(lwp) REWIND( numstp )                       !  --------------------------
[3]71
[1489]72      !                                              !* Test maximum of velocity (zonal only)
73      !                                              !  ------------------------
74      !! zumax = MAXVAL( ABS( un(:,:,:) ) )                ! slower than the following loop on NEC SX5
[79]75      zumax = 0.e0
[3]76      DO jk = 1, jpk
77         DO jj = 1, jpj
78            DO ji = 1, jpi
79               zumax = MAX(zumax,ABS(un(ji,jj,jk)))
80          END DO
81        END DO
82      END DO       
[1489]83      IF( lk_mpp )   CALL mpp_max( zumax )                 ! max over the global domain
84      !
85      IF( MOD( kt, nwrite ) == 1 .AND. lwp )   WRITE(numout,*) ' ==>> time-step= ',kt,' abs(U) max: ', zumax
86      !
[1561]87      IF( zumax > 20.e0 ) THEN
[417]88         IF( lk_mpp ) THEN
89            CALL mpp_maxloc(ABS(un),umask,zumax,ii,ij,ik)
[181]90         ELSE
[417]91            ilocu = MAXLOC( ABS( un(:,:,:) ) )
92            ii = ilocu(1) + nimpp - 1
93            ij = ilocu(2) + njmpp - 1
94            ik = ilocu(3)
[15]95         ENDIF
[3]96         IF(lwp) THEN
97            WRITE(numout,cform_err)
98            WRITE(numout,*) ' stpctl: the zonal velocity is larger than 20 m/s'
99            WRITE(numout,*) ' ====== '
100            WRITE(numout,9400) kt, zumax, ii, ij, ik
101            WRITE(numout,*)
102            WRITE(numout,*) '          output of last fields in numwso'
103         ENDIF
[1561]104         kindic = -3
[3]105      ENDIF
[1442]1069400  FORMAT (' kt=',i6,' max abs(U): ',1pg11.4,', i j k: ',3i5)
[3]107
[1489]108      !                                              !* Test minimum of salinity
109      !                                              !  ------------------------
[3294]110      !! zsmin = MINVAL( tsn(:,:,1,jp_sal), mask = tmask(:,:,1) == 1.e0 )  slower than the following loop on NEC SX5
[79]111      zsmin = 100.e0
[3]112      DO jj = 2, jpjm1
113         DO ji = 1, jpi
[3294]114            IF( tmask(ji,jj,1) == 1) zsmin = MIN(zsmin,tsn(ji,jj,1,jp_sal))
[3]115         END DO
116      END DO
[1489]117      IF( lk_mpp )   CALL mpp_min( zsmin )                ! min over the global domain
118      !
119      IF( MOD( kt, nwrite ) == 1 .AND. lwp )   WRITE(numout,*) ' ==>> time-step= ',kt,' SSS min:', zsmin
120      !
[3]121      IF( zsmin < 0.) THEN
[181]122         IF (lk_mpp) THEN
[3294]123            CALL mpp_minloc ( tsn(:,:,1,jp_sal),tmask(:,:,1), zsmin, ii,ij )
[181]124         ELSE
[3294]125            ilocs = MINLOC( tsn(:,:,1,jp_sal), mask = tmask(:,:,1) == 1.e0 )
[181]126            ii = ilocs(1) + nimpp - 1
127            ij = ilocs(2) + njmpp - 1
[1489]128         ENDIF
129         !
[3]130         IF(lwp) THEN
131            WRITE(numout,cform_err)
132            WRITE(numout,*) 'stp_ctl : NEGATIVE sea surface salinity'
133            WRITE(numout,*) '======= '
134            WRITE(numout,9500) kt, zsmin, ii, ij
135            WRITE(numout,*)
136            WRITE(numout,*) '          output of last fields in numwso'
137         ENDIF
[1561]138         kindic = -3
[3]139      ENDIF
[1442]1409500  FORMAT (' kt=',i6,' min SSS: ',1pg11.4,', i j: ',2i5)
[3]141
[2528]142     
143      IF( lk_c1d )  RETURN          ! No log file in case of 1D vertical configuration
144
[1489]145      ! log file (solver or ssh statistics)
146      ! --------
[1528]147      IF( lk_dynspg_flt ) THEN      ! elliptic solver statistics (if required)
[1489]148         !
[1566]149         IF(lwp) WRITE(numsol,9200) kt, niter, res, SQRT(epsr)/eps       ! Solver
[1489]150         !
[1566]151         IF( kindic < 0 .AND. zsmin > 0.e0 .AND. zumax <= 20.e0 ) THEN   ! create a abort file if problem found
[1489]152            IF(lwp) THEN
153               WRITE(numout,*) ' stpctl: the elliptic solver DO not converge or explode'
154               WRITE(numout,*) ' ====== '
155               WRITE(numout,9200) kt, niter, res, sqrt(epsr)/eps
156               WRITE(numout,*)
157               WRITE(numout,*) ' stpctl: output of last fields'
158               WRITE(numout,*) ' ======  '
159            ENDIF
160         ENDIF
161         !
[1581]162      ELSE                                   !* ssh statistics (and others...)
163         IF( kt == nit000 .AND. lwp ) THEN   ! open ssh statistics file (put in solver.stat file)
164            CALL ctl_opn( numsol, 'solver.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
[1489]165         ENDIF
166         !
167         zssh2 = SUM( sshn(:,:) * sshn(:,:) * tmask_i(:,:) )
168         IF( lk_mpp )   CALL mpp_sum( zssh2 )      ! sum over the global domain
169         !
170         IF(lwp) WRITE(numsol,9300) kt, zssh2, zumax, zsmin      ! ssh statistics
171         !
172      ENDIF
173
[1588]1749200  FORMAT('it:', i8, ' iter:', i4, ' r: ',e16.10, ' b: ',e16.10 )
[1489]1759300  FORMAT(' it :', i8, ' ssh2: ', e16.10, ' Umax: ',e16.10,' Smin: ',e16.10)
176      !
[3]177   END SUBROUTINE stp_ctl
178
179   !!======================================================================
180END MODULE stpctl
Note: See TracBrowser for help on using the repository browser.