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 NEMO/branches/UKMO/r8395_obs_oper_update/NEMOGCM/TOOLS/DOMAINcfg/src – NEMO

source: NEMO/branches/UKMO/r8395_obs_oper_update/NEMOGCM/TOOLS/DOMAINcfg/src/stpctl.f90 @ 11350

Last change on this file since 11350 was 11350, checked in by jcastill, 5 years ago

Clear svn keywords

File size: 6.8 KB
Line 
1MODULE stpctl
2   !!======================================================================
3   !!                       ***  MODULE  stpctl  ***
4   !! Ocean run control :  gross check of the ocean time stepping
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   !!----------------------------------------------------------------------
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 c1d             ! 1D vertical configuration
19   !
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
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC stp_ctl           ! routine called by step.F90
28   !!----------------------------------------------------------------------
29   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
30   !! $Id$
31   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33CONTAINS
34
35   SUBROUTINE stp_ctl( kt, kindic )
36      !!----------------------------------------------------------------------
37      !!                    ***  ROUTINE stp_ctl  ***
38      !!                     
39      !! ** Purpose :   Control the run
40      !!
41      !! ** Method  : - Save the time step in numstp
42      !!              - Print it each 50 time steps
43      !!              - Stop the run IF problem ( indic < 0 )
44      !!
45      !! ** Actions :   'time.step' file containing the last ocean time-step
46      !!               
47      !!----------------------------------------------------------------------
48      INTEGER, INTENT(in   ) ::   kt       ! ocean time-step index
49      INTEGER, INTENT(inout) ::   kindic   ! error indicator
50      !!
51      INTEGER  ::   ji, jj, jk             ! dummy loop indices
52      INTEGER  ::   ii, ij, ik             ! local integers
53      REAL(wp) ::   zumax, zsmin, zssh2    ! local scalars
54      INTEGER, DIMENSION(3) ::   ilocu     !
55      INTEGER, DIMENSION(2) ::   ilocs     !
56      !!----------------------------------------------------------------------
57      !
58      IF( kt == nit000 .AND. lwp ) THEN
59         WRITE(numout,*)
60         WRITE(numout,*) 'stp_ctl : time-stepping control'
61         WRITE(numout,*) '~~~~~~~'
62         ! open time.step file
63         CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
64      ENDIF
65      !
66      IF(lwp) WRITE ( numstp, '(1x, i8)' )   kt      !* save the current time step in numstp
67      IF(lwp) REWIND( numstp )                       !  --------------------------
68      !
69      !                                              !* Test maximum of velocity (zonal only)
70      !                                              !  ------------------------
71      !! zumax = MAXVAL( ABS( un(:,:,:) ) )                ! slower than the following loop on NEC SX5
72      zumax = 0.e0
73      DO jk = 1, jpk
74         DO jj = 1, jpj
75            DO ji = 1, jpi
76               zumax = MAX(zumax,ABS(un(ji,jj,jk)))
77          END DO
78        END DO
79      END DO       
80      IF( lk_mpp )   CALL mpp_max( zumax )                 ! max over the global domain
81      !
82      IF( MOD( kt, nwrite ) == 1 .AND. lwp )   WRITE(numout,*) ' ==>> time-step= ',kt,' abs(U) max: ', zumax
83      !
84      IF( zumax > 20.e0 ) THEN
85         IF( lk_mpp ) THEN
86            CALL mpp_maxloc(ABS(un),umask,zumax,ii,ij,ik)
87         ELSE
88            ilocu = MAXLOC( ABS( un(:,:,:) ) )
89            ii = ilocu(1) + nimpp - 1
90            ij = ilocu(2) + njmpp - 1
91            ik = ilocu(3)
92         ENDIF
93         IF(lwp) THEN
94            WRITE(numout,cform_err)
95            WRITE(numout,*) ' stpctl: the zonal velocity is larger than 20 m/s'
96            WRITE(numout,*) ' ====== '
97            WRITE(numout,9400) kt, zumax, ii, ij, ik
98            WRITE(numout,*)
99            WRITE(numout,*) '          output of last fields in numwso'
100         ENDIF
101         kindic = -3
102      ENDIF
1039400  FORMAT (' kt=',i6,' max abs(U): ',1pg11.4,', i j k: ',3i5)
104      !
105      !                                              !* Test minimum of salinity
106      !                                              !  ------------------------
107      !! zsmin = MINVAL( tsn(:,:,1,jp_sal), mask = tmask(:,:,1) == 1.e0 )  slower than the following loop on NEC SX5
108      zsmin = 100._wp
109      DO jj = 2, jpjm1
110         DO ji = 1, jpi
111            IF( tmask(ji,jj,1) == 1) zsmin = MIN(zsmin,tsn(ji,jj,1,jp_sal))
112         END DO
113      END DO
114      IF( lk_mpp )   CALL mpp_min( zsmin )                ! min over the global domain
115      !
116      IF( MOD( kt, nwrite ) == 1 .AND. lwp )   WRITE(numout,*) ' ==>> time-step= ',kt,' SSS min:', zsmin
117      !
118      IF( zsmin < 0.) THEN
119         IF (lk_mpp) THEN
120            CALL mpp_minloc ( tsn(:,:,1,jp_sal),tmask(:,:,1), zsmin, ii,ij )
121         ELSE
122            ilocs = MINLOC( tsn(:,:,1,jp_sal), mask = tmask(:,:,1) == 1.e0 )
123            ii = ilocs(1) + nimpp - 1
124            ij = ilocs(2) + njmpp - 1
125         ENDIF
126         !
127         IF(lwp) THEN
128            WRITE(numout,cform_err)
129            WRITE(numout,*) 'stp_ctl : NEGATIVE sea surface salinity'
130            WRITE(numout,*) '======= '
131            WRITE(numout,9500) kt, zsmin, ii, ij
132            WRITE(numout,*)
133            WRITE(numout,*) '          output of last fields in numwso'
134         ENDIF
135         kindic = -3
136      ENDIF
1379500  FORMAT (' kt=',i6,' min SSS: ',1pg11.4,', i j: ',2i5)
138      !
139      !
140      IF( lk_c1d )  RETURN          ! No log file in case of 1D vertical configuration
141
142      ! log file (ssh statistics)
143      ! --------                                   !* ssh statistics (and others...)
144      IF( kt == nit000 .AND. lwp ) THEN   ! open ssh statistics file (put in solver.stat file)
145         CALL ctl_opn( numsol, 'solver.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
146      ENDIF
147      !
148      zssh2 = SUM( sshn(:,:) * sshn(:,:) * tmask_i(:,:) )
149      IF( lk_mpp )   CALL mpp_sum( zssh2 )      ! sum over the global domain
150      !
151      IF(lwp) WRITE(numsol,9300) kt, zssh2, zumax, zsmin      ! ssh statistics
152      !
1539200  FORMAT('it:', i8, ' iter:', i4, ' r: ',e16.10, ' b: ',e16.10 )
1549300  FORMAT(' it :', i8, ' ssh2: ', e16.10, ' Umax: ',e16.10,' Smin: ',e16.10)
155      !
156   END SUBROUTINE stp_ctl
157
158   !!======================================================================
159END MODULE stpctl
Note: See TracBrowser for help on using the repository browser.