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 trunk/NEMO/OPA_SRC – NEMO

source: trunk/NEMO/OPA_SRC/stpctl.F90 @ 1495

Last change on this file since 1495 was 1489, checked in by rblod, 15 years ago

Add control statistics in solver.stat for time splitting case, see ticket #471

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