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/2019/dev_r11842_SI3-10_EAP/tests/CANAL/MY_SRC – NEMO

source: NEMO/branches/2019/dev_r11842_SI3-10_EAP/tests/CANAL/MY_SRC/stpctl.F90 @ 13662

Last change on this file since 13662 was 13662, checked in by clem, 3 years ago

update to almost r4.0.4

  • Property svn:keywords set to Id
File size: 16.9 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   !!            3.7  ! 2016-09  (G. Madec)  Remove solver
12   !!            4.0  ! 2017-04  (G. Madec)  regroup global communications
13   !!----------------------------------------------------------------------
14
15   !!----------------------------------------------------------------------
16   !!   stp_ctl      : Control the run
17   !!----------------------------------------------------------------------
18   USE oce             ! ocean dynamics and tracers variables
19   USE dom_oce         ! ocean space and time domain variables
20   USE c1d             ! 1D vertical configuration
21   USE diawri          ! Standard run outputs       (dia_wri_state routine)
22   !
23   USE in_out_manager  ! I/O manager
24   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
25   USE lib_mpp         ! distributed memory computing
26   USE zdf_oce ,  ONLY : ln_zad_Aimp       ! ocean vertical physics variables
27   USE wet_dry,   ONLY : ll_wd, ssh_ref    ! reference depth for negative bathy
28
29   USE netcdf          ! NetCDF library
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC stp_ctl           ! routine called by step.F90
34
35   INTEGER  ::   idrun, idtime, idssh, idu, ids1, ids2, idt1, idt2, idc1, idw1, istatus
36   !!----------------------------------------------------------------------
37   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
38   !! $Id$
39   !! Software governed by the CeCILL license (see ./LICENSE)
40   !!----------------------------------------------------------------------
41CONTAINS
42
43   SUBROUTINE stp_ctl( kt )
44      !!----------------------------------------------------------------------
45      !!                    ***  ROUTINE stp_ctl  ***
46      !!                     
47      !! ** Purpose :   Control the run
48      !!
49      !! ** Method  : - Save the time step in numstp
50      !!              - Print it each 50 time steps
51      !!              - Stop the run IF problem encountered by setting nstop > 0
52      !!                Problems checked: |ssh| maximum larger than 10 m
53      !!                                  |U|   maximum larger than 10 m/s
54      !!                                  negative sea surface salinity
55      !!
56      !! ** Actions :   "time.step" file = last ocean time-step
57      !!                "run.stat"  file = run statistics
58      !!                 nstop indicator sheared among all local domain
59      !!----------------------------------------------------------------------
60      INTEGER, INTENT(in   ) ::   kt       ! ocean time-step index
61      !!
62      INTEGER                ::   ji, jj, jk          ! dummy loop indices
63      INTEGER,  DIMENSION(3) ::   ih, iu, is1, is2    ! min/max loc indices
64      INTEGER,  DIMENSION(9) ::   iareasum, iareamin, iareamax
65      REAL(wp)               ::   zzz                 ! local real
66      REAL(wp), DIMENSION(9) ::   zmax, zmaxlocal
67      LOGICAL                ::   ll_wrtstp, ll_colruns, ll_wrtruns
68      LOGICAL, DIMENSION(jpi,jpj,jpk) ::   llmsk
69      CHARACTER(len=20) :: clname
70      !!----------------------------------------------------------------------
71      IF( nstop > 0 .AND. ngrdstop > -1 )   RETURN   !   stpctl was already called by a child grid
72      !
73      ll_wrtstp  = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend )
74      ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1 
75      ll_wrtruns = ( ll_colruns .OR. jpnij == 1 ) .AND. lwm
76      !
77      IF( kt == nit000 ) THEN
78         !
79         IF( lwp ) THEN
80            WRITE(numout,*)
81            WRITE(numout,*) 'stp_ctl : time-stepping control'
82            WRITE(numout,*) '~~~~~~~'
83         ENDIF
84         !                                ! open time.step file
85         IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
86         !                                ! open run.stat file(s) at start whatever
87         !                                ! the value of sn_cfctl%ptimincr
88         IF( ll_wrtruns ) THEN
89            CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
90            clname = 'run.stat.nc'
91            IF( .NOT. Agrif_Root() )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname)
92            istatus = NF90_CREATE( TRIM(clname), NF90_CLOBBER, idrun )
93            istatus = NF90_DEF_DIM( idrun, 'time', NF90_UNLIMITED, idtime )
94            istatus = NF90_DEF_VAR( idrun, 'abs_ssh_max', NF90_DOUBLE, (/ idtime /), idssh )
95            istatus = NF90_DEF_VAR( idrun,   'abs_u_max', NF90_DOUBLE, (/ idtime /), idu   )
96            istatus = NF90_DEF_VAR( idrun,       's_min', NF90_DOUBLE, (/ idtime /), ids1  )
97            istatus = NF90_DEF_VAR( idrun,       's_max', NF90_DOUBLE, (/ idtime /), ids2  )
98            istatus = NF90_DEF_VAR( idrun,       't_min', NF90_DOUBLE, (/ idtime /), idt1  )
99            istatus = NF90_DEF_VAR( idrun,       't_max', NF90_DOUBLE, (/ idtime /), idt2  )
100            IF( ln_zad_Aimp ) THEN
101               istatus = NF90_DEF_VAR( idrun,   'abs_wi_max', NF90_DOUBLE, (/ idtime /), idw1  )
102               istatus = NF90_DEF_VAR( idrun,       'Cf_max', NF90_DOUBLE, (/ idtime /), idc1  )
103            ENDIF
104            istatus = NF90_ENDDEF(idrun)
105         ENDIF
106      ENDIF
107      !
108      IF(lwm .AND. ll_wrtstp) THEN        !==  current time step  ==!   ("time.step" file)
109         WRITE ( numstp, '(1x, i8)' )   kt
110         REWIND( numstp )
111      ENDIF
112      !
113      !                                   !==  test of extrema  ==!
114      !
115      ! define zmax default value. needed for land processors
116      IF( ll_colruns ) THEN    ! default value: must not be kept when calling mpp_max -> must be as small as possible
117         zmax(:) = -HUGE(1._wp)
118      ELSE                     ! default value: must not give true for any of the tests bellow (-> avoid manipulating HUGE...)
119         zmax(:) =  0._wp
120         zmax(3) = -1._wp      ! avoid salinity minimum at 0.
121      ENDIF
122      !
123      IF( ll_wd ) THEN
124         zmax(1) = MAXVAL(  ABS( sshn(:,:) + ssh_ref*tmask(:,:,1) )  )        ! ssh max
125      ELSE
126         zmax(1) = MAXVAL(  ABS( sshn(:,:) )  )                               ! ssh max
127      ENDIF
128      zmax(2) = MAXVAL(  ABS( un(:,:,:) )  )                                  ! velocity max (zonal only)
129      llmsk(:,:,:) = tmask(:,:,:) == 1._wp
130      IF( COUNT( llmsk(:,:,:) ) > 0 ) THEN   ! avoid huge values sent back for land processors...     
131         zmax(3) = MAXVAL( -tsn(:,:,:,jp_sal) , mask = llmsk )   ! minus salinity max
132         zmax(4) = MAXVAL(  tsn(:,:,:,jp_sal) , mask = llmsk )   !       salinity max
133         IF( ll_colruns .OR. jpnij == 1 ) THEN     ! following variables are used only in the netcdf file
134            zmax(5) = MAXVAL( -tsn(:,:,:,jp_tem) , mask = llmsk )   ! minus temperature max
135            zmax(6) = MAXVAL(  tsn(:,:,:,jp_tem) , mask = llmsk )   !       temperature max
136            IF( ln_zad_Aimp ) THEN
137               zmax(9) = MAXVAL(   Cu_adv(:,:,:)   , mask = llmsk ) ! partitioning coeff. max
138               llmsk(:,:,:) = wmask(:,:,:) == 1._wp
139               IF( COUNT( llmsk(:,:,:) ) > 0 ) THEN   ! avoid huge values sent back for land processors...
140                  zmax(8) = MAXVAL(  ABS( wi(:,:,:) ) , mask = wmask(:,:,:) == 1._wp ) ! implicit vertical vel. max
141               ENDIF
142            ENDIF
143         ENDIF
144      ENDIF
145      zmax(7) = REAL( nstop , wp )                                            ! stop indicator
146      !
147      IF( ll_colruns ) THEN
148         zmaxlocal(:) = zmax(:)
149         CALL mpp_max( "stpctl", zmax )          ! max over the global domain
150         nstop = NINT( zmax(7) )                 ! nstop indicator sheared among all local domains
151      ENDIF
152      !                                   !==  run statistics  ==!   ("run.stat" files)
153      IF( ll_wrtruns ) THEN
154         WRITE(numrun,9500) kt, zmax(1), zmax(2), -zmax(3), zmax(4)
155         istatus = NF90_PUT_VAR( idrun, idssh, (/ zmax(1)/), (/kt/), (/1/) )
156         istatus = NF90_PUT_VAR( idrun,   idu, (/ zmax(2)/), (/kt/), (/1/) )
157         istatus = NF90_PUT_VAR( idrun,  ids1, (/-zmax(3)/), (/kt/), (/1/) )
158         istatus = NF90_PUT_VAR( idrun,  ids2, (/ zmax(4)/), (/kt/), (/1/) )
159         istatus = NF90_PUT_VAR( idrun,  idt1, (/-zmax(5)/), (/kt/), (/1/) )
160         istatus = NF90_PUT_VAR( idrun,  idt2, (/ zmax(6)/), (/kt/), (/1/) )
161         IF( ln_zad_Aimp ) THEN
162            istatus = NF90_PUT_VAR( idrun,  idw1, (/ zmax(8)/), (/kt/), (/1/) )
163            istatus = NF90_PUT_VAR( idrun,  idc1, (/ zmax(9)/), (/kt/), (/1/) )
164         ENDIF
165         IF( kt == nitend ) istatus = NF90_CLOSE(idrun)
166      END IF
167      !                                   !==  error handling  ==!
168      IF(   zmax(1) >   20._wp .OR.   &                    ! too large sea surface height ( > 20 m )
169         &  zmax(2) >   10._wp .OR.   &                    ! too large velocity ( > 10 m/s)
170!!$         &  zmax(3) >=   0._wp .OR.   &                    ! negative or zero sea surface salinity
171!!$         &  zmax(4) >= 100._wp .OR.   &                    ! too large sea surface salinity ( > 100 )
172!!$         &  zmax(4) <    0._wp .OR.   &                    ! too large sea surface salinity (keep this line for sea-ice)
173         &  ISNAN( zmax(1) + zmax(2) + zmax(3) ) .OR.  &   ! NaN encounter in the tests
174         &  ABS(   zmax(1) + zmax(2) + zmax(3) ) > HUGE(1._wp) ) THEN    ! Infinity encounter in the tests
175         IF( ll_colruns ) THEN
176            ! first: close the netcdf file, so we can read it
177            IF( lwm .AND. kt /= nitend )   istatus = NF90_CLOSE(idrun)
178            CALL mpp_maxloc( 'stpctl', ABS(sshn)        , ssmask(:,:)  , zzz, ih(1:2)  )   ;   ih(3) = 0
179            CALL mpp_maxloc( 'stpctl', ABS(un)          , umask (:,:,:), zzz, iu  )
180            CALL mpp_minloc( 'stpctl', tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, is1 )
181            CALL mpp_maxloc( 'stpctl', tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, is2 )
182            ! find which subdomain has the max.
183            iareamin(:) = jpnij+1   ;   iareamax(:) = 0   ;   iareasum(:) = 0
184            DO ji = 1, 9
185               IF( zmaxlocal(ji) == zmax(ji) ) THEN
186                  iareamin(ji) = narea   ;   iareamax(ji) = narea   ;   iareasum(ji) = 1
187               ENDIF
188            END DO
189            CALL mpp_min( "stpctl", iareamin )         ! min over the global domain
190            CALL mpp_max( "stpctl", iareamax )         ! max over the global domain
191            CALL mpp_sum( "stpctl", iareasum )         ! sum over the global domain
192         ELSE
193            ih(1:2)= MAXLOC( ABS( sshn(:,:)   )                              ) + (/ nimpp - 1, njmpp - 1    /)   ;   ih(3) = 0
194            iu(:)  = MAXLOC( ABS( un  (:,:,:) )                              ) + (/ nimpp - 1, njmpp - 1, 0 /)
195            is1(:) = MINLOC( tsn(:,:,:,jp_sal), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /)
196            is2(:) = MAXLOC( tsn(:,:,:,jp_sal), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /)
197            iareamin(:) = narea   ;   iareamax(:) = narea   ;   iareasum(:) = 1         ! this is local information
198         ENDIF
199         !
200         WRITE(ctmp1,*) ' stp_ctl: |ssh| > 20 m  or  |U| > 10 m/s  or  S <= 0  or  S >= 100  or  NaN encounter in the tests'
201         CALL wrt_line(ctmp2, kt, ' |ssh| max ',   zmax(1), ih , iareasum(1), iareamin(1), iareamax(1) ) 
202         CALL wrt_line(ctmp3, kt, ' |U|   max ',   zmax(2), iu , iareasum(2), iareamin(2), iareamax(2) ) 
203         CALL wrt_line(ctmp4, kt, ' Sal   min ', - zmax(3), is1, iareasum(3), iareamin(3), iareamax(3) ) 
204         CALL wrt_line(ctmp5, kt, ' Sal   max ',   zmax(4), is2, iareasum(4), iareamin(4), iareamax(4) ) 
205         IF( Agrif_Root() ) THEN
206            WRITE(ctmp6,*) '      ===> output of last computed fields in output.abort* files'
207         ELSE
208            WRITE(ctmp6,*) '      ===> output of last computed fields in '//TRIM(Agrif_CFixed())//'_output.abort* files'
209         ENDIF
210         !
211         CALL dia_wri_state( 'output.abort' )    ! create an output.abort file
212         !
213         IF( ll_colruns .or. jpnij == 1 ) THEN   ! all processes synchronized -> use lwp to print in opened ocean.output files
214            IF(lwp) THEN   ;   CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 )
215            ELSE           ;   nstop = MAX(1, nstop)   ! make sure nstop > 0 (automatically done when calling ctl_stop)
216            ENDIF
217         ELSE                                    ! only mpi subdomains with errors are here -> STOP now
218            CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 )
219         ENDIF
220         !
221      ENDIF
222      !
223      IF( nstop > 0 ) THEN                                                  ! an error was detected and we did not abort yet...
224         ngrdstop = Agrif_Fixed()                                           ! store which grid got this error
225         IF( .NOT. ll_colruns .AND. jpnij > 1 )   CALL ctl_stop( 'STOP' )   ! we must abort here to avoid MPI deadlock
226      ENDIF
227      !
2289500  FORMAT(' it :', i8, '    |ssh|_max: ', D23.16, ' |U|_max: ', D23.16,' S_min: ', D23.16,' S_max: ', D23.16)
229      !
230   END SUBROUTINE stp_ctl
231
232
233   SUBROUTINE wrt_line( cdline, kt, cdprefix, pval, kloc, ksum, kmin, kmax )
234      !!----------------------------------------------------------------------
235      !!                     ***  ROUTINE wrt_line  ***
236      !!
237      !! ** Purpose :   write information line
238      !!
239      !!----------------------------------------------------------------------
240      CHARACTER(len=*),      INTENT(  out) ::   cdline
241      CHARACTER(len=*),      INTENT(in   ) ::   cdprefix
242      REAL(wp),              INTENT(in   ) ::   pval
243      INTEGER, DIMENSION(3), INTENT(in   ) ::   kloc
244      INTEGER,               INTENT(in   ) ::   kt, ksum, kmin, kmax
245      !
246      CHARACTER(len=80) ::   clsuff
247      CHARACTER(len=9 ) ::   clkt, clsum, clmin, clmax
248      CHARACTER(len=9 ) ::   cli, clj, clk
249      CHARACTER(len=1 ) ::   clfmt
250      CHARACTER(len=4 ) ::   cl4   ! needed to be able to compile with Agrif, I don't know why
251      INTEGER           ::   ifmtk
252      !!----------------------------------------------------------------------
253      WRITE(clkt , '(i9)') kt
254     
255      WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpnij  ,wp))) + 1     ! how many digits to we need to write ? (we decide max = 9)
256      !!! WRITE(clsum, '(i'//clfmt//')') ksum                   ! this is creating a compilation error with AGRIF
257      cl4 = '(i'//clfmt//')'   ;   WRITE(clsum, cl4) ksum
258      WRITE(clfmt, '(i1)') INT(LOG10(REAL(MAX(1,jpnij-1),wp))) + 1    ! how many digits to we need to write ? (we decide max = 9)
259      cl4 = '(i'//clfmt//')'   ;   WRITE(clmin, cl4) kmin-1
260                                   WRITE(clmax, cl4) kmax-1
261      !
262      WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpiglo,wp))) + 1      ! how many digits to we need to write jpiglo? (we decide max = 9)
263      cl4 = '(i'//clfmt//')'   ;   WRITE(cli, cl4) kloc(1)      ! this is ok with AGRIF
264      WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpjglo,wp))) + 1      ! how many digits to we need to write jpjglo? (we decide max = 9)
265      cl4 = '(i'//clfmt//')'   ;   WRITE(clj, cl4) kloc(2)      ! this is ok with AGRIF
266      !
267      IF( ksum == 1 ) THEN   ;   WRITE(clsuff,9100) TRIM(clmin)
268      ELSE                   ;   WRITE(clsuff,9200) TRIM(clsum), TRIM(clmin), TRIM(clmax)
269      ENDIF
270      IF(kloc(3) == 0) THEN
271         ifmtk = INT(LOG10(REAL(jpk,wp))) + 1                   ! how many digits to we need to write jpk? (we decide max = 9)
272         clk = REPEAT(' ', ifmtk)                               ! create the equivalent in blank string
273         WRITE(cdline,9300) TRIM(ADJUSTL(clkt)), TRIM(ADJUSTL(cdprefix)), pval, TRIM(cli), TRIM(clj), clk(1:ifmtk), TRIM(clsuff)
274      ELSE
275         WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpk,wp))) + 1      ! how many digits to we need to write jpk? (we decide max = 9)
276         !!! WRITE(clk, '(i'//clfmt//')') kloc(3)               ! this is creating a compilation error with AGRIF
277         cl4 = '(i'//clfmt//')'   ;   WRITE(clk, cl4) kloc(3)   ! this is ok with AGRIF
278         WRITE(cdline,9400) TRIM(ADJUSTL(clkt)), TRIM(ADJUSTL(cdprefix)), pval, TRIM(cli), TRIM(clj),    TRIM(clk), TRIM(clsuff)
279      ENDIF
280      !
2819100  FORMAT('MPI rank ', a)
2829200  FORMAT('found in ', a, ' MPI tasks, spread out among ranks ', a, ' to ', a)
2839300  FORMAT('kt ', a, ' ', a, ' ', 1pg11.4, ' at i j   ', a, ' ', a, ' ', a, ' ', a)
2849400  FORMAT('kt ', a, ' ', a, ' ', 1pg11.4, ' at i j k ', a, ' ', a, ' ', a, ' ', a)
285      !
286   END SUBROUTINE wrt_line
287
288
289   !!======================================================================
290END MODULE stpctl
Note: See TracBrowser for help on using the repository browser.