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.
diacfl.F90 in NEMO/trunk/src/OCE/DIA – NEMO

source: NEMO/trunk/src/OCE/DIA/diacfl.F90 @ 13458

Last change on this file since 13458 was 13458, checked in by smasson, 4 years ago

trunk: mpp_min(max)loc testing only inner domain, see #2521

  • Property svn:keywords set to Id
File size: 8.3 KB
Line 
1MODULE diacfl
2   !!======================================================================
3   !!                       ***  MODULE  diacfl  ***
4   !! Output CFL diagnostics to ascii file
5   !!======================================================================
6   !! History :  3.4  !  2010-03  (E. Blockley)  Original code
7   !!            3.6  !  2014-06  (T. Graham)  Removed CPP key & Updated to vn3.6
8   !!            4.0  !  2017-09  (G. Madec)  style + comments
9   !!----------------------------------------------------------------------
10   !!   dia_cfl        : Compute and output Courant numbers at each timestep
11   !!----------------------------------------------------------------------
12   USE oce             ! ocean dynamics and active tracers
13   USE dom_oce         ! ocean space and time domain
14   USE domvvl          !
15   !
16   USE lib_mpp         ! distribued memory computing
17   USE lbclnk          ! ocean lateral boundary condition (or mpp link)
18   USE in_out_manager  ! I/O manager
19   USE iom             !
20   USE timing          ! Performance output
21
22   IMPLICIT NONE
23   PRIVATE
24
25   CHARACTER(LEN=50) :: clname="cfl_diagnostics.ascii"    ! ascii filename
26   INTEGER           :: numcfl                            ! outfile unit
27   !
28   INTEGER, DIMENSION(3) ::   nCu_loc, nCv_loc, nCw_loc   ! U, V, and W run max locations in the global domain
29   REAL(wp)              ::   rCu_max, rCv_max, rCw_max   ! associated run max Courant number
30
31   PUBLIC   dia_cfl       ! routine called by step.F90
32   PUBLIC   dia_cfl_init  ! routine called by nemogcm
33
34   !! * Substitutions
35#  include "do_loop_substitute.h90"
36#  include "domzgr_substitute.h90"
37   !!----------------------------------------------------------------------
38   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
39   !! $Id$
40   !! Software governed by the CeCILL license (see ./LICENSE)
41   !!----------------------------------------------------------------------
42CONTAINS
43
44   SUBROUTINE dia_cfl ( kt, Kmm )
45      !!----------------------------------------------------------------------
46      !!                  ***  ROUTINE dia_cfl  ***
47      !!
48      !! ** Purpose :  Compute the Courant numbers Cu=u*dt/dx and Cv=v*dt/dy
49      !!               and output to ascii file 'cfl_diagnostics.ascii'
50      !!----------------------------------------------------------------------
51      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
52      INTEGER, INTENT(in) ::   Kmm  ! ocean time level index
53      !
54      INTEGER                          ::   ji, jj, jk                       ! dummy loop indices
55      REAL(wp)                         ::   zCu_max, zCv_max, zCw_max        ! local scalars
56      INTEGER , DIMENSION(3)           ::   iloc_u , iloc_v , iloc_w , iloc  ! workspace
57      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zCu_cfl, zCv_cfl, zCw_cfl        ! workspace
58      LOGICAL , DIMENSION(jpi,jpj,jpk) ::   llmsk
59      !!----------------------------------------------------------------------
60      !
61      IF( ln_timing )   CALL timing_start('dia_cfl')
62      !
63      llmsk(   1:Nis1,:,:) = .FALSE.                                              ! exclude halos from the checked region
64      llmsk(Nie1: jpi,:,:) = .FALSE.
65      llmsk(:,   1:Njs1,:) = .FALSE.
66      llmsk(:,Nje1: jpj,:) = .FALSE.
67      !
68      DO_3D( 0, 0, 0, 0, 1, jpk )
69         zCu_cfl(ji,jj,jk) = ABS( uu(ji,jj,jk,Kmm) ) * rDt / e1u  (ji,jj)      ! for i-direction
70         zCv_cfl(ji,jj,jk) = ABS( vv(ji,jj,jk,Kmm) ) * rDt / e2v  (ji,jj)      ! for j-direction
71         zCw_cfl(ji,jj,jk) = ABS( ww(ji,jj,jk) ) * rDt / e3w(ji,jj,jk,Kmm)     ! for k-direction
72      END_3D
73      !
74      ! write outputs
75      IF( iom_use('cfl_cu') ) THEN
76         llmsk(Nis0:Nie0,Njs0:Nje0,:) = umask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp        ! define only the inner domain
77         CALL iom_put( 'cfl_cu', MAXVAL( zCu_cfl, mask = llmsk, dim=3 ) )
78      ENDIF
79      IF( iom_use('cfl_cv') ) THEN
80         llmsk(Nis0:Nie0,Njs0:Nje0,:) = vmask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp        ! define only the inner domain
81         CALL iom_put( 'cfl_cv', MAXVAL( zCv_cfl, mask = llmsk, dim=3 ) )
82      ENDIF
83      IF( iom_use('cfl_cw') ) THEN
84         llmsk(Nis0:Nie0,Njs0:Nje0,:) = wmask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp        ! define only the inner domain
85         CALL iom_put( 'cfl_cw', MAXVAL( zCw_cfl, mask = llmsk, dim=3 ) )
86      ENDIF
87
88      !                    ! calculate maximum values and locations
89      llmsk(Nis0:Nie0,Njs0:Nje0,:) = umask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp        ! define only the inner domain
90      CALL mpp_maxloc( 'diacfl', zCu_cfl, llmsk, zCu_max, iloc_u )
91      llmsk(Nis0:Nie0,Njs0:Nje0,:) = vmask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp        ! define only the inner domain
92      CALL mpp_maxloc( 'diacfl', zCv_cfl, llmsk, zCv_max, iloc_v )
93      llmsk(Nis0:Nie0,Njs0:Nje0,:) = wmask(Nis0:Nie0,Njs0:Nje0,:) == 1._wp        ! define only the inner domain
94      CALL mpp_maxloc( 'diacfl', zCw_cfl, llmsk, zCw_max, iloc_w )
95      !
96      IF( lwp ) THEN       ! write out to file
97         WRITE(numcfl,FMT='(2x,i6,3x,a6,4x,f7.4,1x,i4,1x,i4,1x,i4)') kt, 'Max Cu', zCu_max, iloc_u(1), iloc_u(2), iloc_u(3)
98         WRITE(numcfl,FMT='(11x,     a6,4x,f7.4,1x,i4,1x,i4,1x,i4)')     'Max Cv', zCv_max, iloc_v(1), iloc_v(2), iloc_v(3)
99         WRITE(numcfl,FMT='(11x,     a6,4x,f7.4,1x,i4,1x,i4,1x,i4)')     'Max Cw', zCw_max, iloc_w(1), iloc_w(2), iloc_w(3)
100      ENDIF
101      !
102      !                    ! update maximum Courant numbers from whole run if applicable
103      IF( zCu_max > rCu_max ) THEN   ;   rCu_max = zCu_max   ;   nCu_loc(:) = iloc_u(:)   ;   ENDIF
104      IF( zCv_max > rCv_max ) THEN   ;   rCv_max = zCv_max   ;   nCv_loc(:) = iloc_v(:)   ;   ENDIF
105      IF( zCw_max > rCw_max ) THEN   ;   rCw_max = zCw_max   ;   nCw_loc(:) = iloc_w(:)   ;   ENDIF
106
107      !                    ! at end of run output max Cu and Cv and close ascii file
108      IF( kt == nitend .AND. lwp ) THEN
109         ! to ascii file
110         WRITE(numcfl,*) '******************************************'
111         WRITE(numcfl,FMT='(3x,a12,6x,f7.4,1x,i4,1x,i4,1x,i4)') 'Run Max Cu', rCu_max, nCu_loc(1), nCu_loc(2), nCu_loc(3)
112         WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', rDt/rCu_max
113         WRITE(numcfl,*) '******************************************'
114         WRITE(numcfl,FMT='(3x,a12,6x,f7.4,1x,i4,1x,i4,1x,i4)') 'Run Max Cv', rCv_max, nCv_loc(1), nCv_loc(2), nCv_loc(3)
115         WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', rDt/rCv_max
116         WRITE(numcfl,*) '******************************************'
117         WRITE(numcfl,FMT='(3x,a12,6x,f7.4,1x,i4,1x,i4,1x,i4)') 'Run Max Cw', rCw_max, nCw_loc(1), nCw_loc(2), nCw_loc(3)
118         WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', rDt/rCw_max
119         CLOSE( numcfl ) 
120         !
121         ! to ocean output
122         WRITE(numout,*)
123         WRITE(numout,*) 'dia_cfl : Maximum Courant number information for the run '
124         WRITE(numout,*) '~~~~~~~'
125         WRITE(numout,*) '   Max Cu = ', rCu_max, ' at (i,j,k) = (',nCu_loc(1),nCu_loc(2),nCu_loc(3),') => dt/C = ', rDt/rCu_max
126         WRITE(numout,*) '   Max Cv = ', rCv_max, ' at (i,j,k) = (',nCv_loc(1),nCv_loc(2),nCv_loc(3),') => dt/C = ', rDt/rCv_max
127         WRITE(numout,*) '   Max Cw = ', rCw_max, ' at (i,j,k) = (',nCw_loc(1),nCw_loc(2),nCw_loc(3),') => dt/C = ', rDt/rCw_max
128      ENDIF
129      !
130      IF( ln_timing )   CALL timing_stop('dia_cfl')
131      !
132   END SUBROUTINE dia_cfl
133
134
135   SUBROUTINE dia_cfl_init
136      !!----------------------------------------------------------------------
137      !!                  ***  ROUTINE dia_cfl_init  ***
138      !!                   
139      !! ** Purpose :   create output file, initialise arrays
140      !!----------------------------------------------------------------------
141      !
142      IF(lwp) THEN
143         WRITE(numout,*)
144         WRITE(numout,*) 'dia_cfl : Outputting CFL diagnostics to ',TRIM(clname), ' file'
145         WRITE(numout,*) '~~~~~~~'
146         WRITE(numout,*)
147         !
148         ! create output ascii file
149         CALL ctl_opn( numcfl, clname, 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', 1, numout, lwp, 1 )
150         WRITE(numcfl,*) 'Timestep  Direction  Max C     i    j    k'
151         WRITE(numcfl,*) '******************************************'
152      ENDIF
153      !
154      rCu_max = 0._wp
155      rCv_max = 0._wp
156      rCw_max = 0._wp
157      !
158   END SUBROUTINE dia_cfl_init
159
160   !!======================================================================
161END MODULE diacfl
Note: See TracBrowser for help on using the repository browser.