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/branches/2020/KERNEL-03_Storkey_Coward_RK3_stage2/src/OCE/DIA – NEMO

source: NEMO/branches/2020/KERNEL-03_Storkey_Coward_RK3_stage2/src/OCE/DIA/diacfl.F90 @ 12424

Last change on this file since 12424 was 12424, checked in by davestorkey, 4 years ago
  1. Rename r2dt -> rDt
  2. Rename r1_2dt -> r1_Dt
  3. Reorganise management of initial Euler timestep for leapfrogging.

This version passes all SETTE tests and bit-compares with the trunk @ 12377

  • Property svn:keywords set to Id
File size: 7.9 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   !!----------------------------------------------------------------------
37   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
38   !! $Id$
39   !! Software governed by the CeCILL license (see ./LICENSE)
40   !!----------------------------------------------------------------------
41CONTAINS
42
43   SUBROUTINE dia_cfl ( kt, Kmm )
44      !!----------------------------------------------------------------------
45      !!                  ***  ROUTINE dia_cfl  ***
46      !!
47      !! ** Purpose :  Compute the Courant numbers Cu=u*dt/dx and Cv=v*dt/dy
48      !!               and output to ascii file 'cfl_diagnostics.ascii'
49      !!----------------------------------------------------------------------
50      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
51      INTEGER, INTENT(in) ::   Kmm  ! ocean time level index
52      !
53      INTEGER                          ::   ji, jj, jk                       ! dummy loop indices
54      REAL(wp)                         ::   zCu_max, zCv_max, zCw_max        ! local scalars
55      INTEGER , DIMENSION(3)           ::   iloc_u , iloc_v , iloc_w , iloc  ! workspace
56      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zCu_cfl, zCv_cfl, zCw_cfl        ! workspace
57      !!----------------------------------------------------------------------
58      !
59      IF( ln_timing )   CALL timing_start('dia_cfl')
60      !
61      DO_3D_11_11( 1, jpk )
62         zCu_cfl(ji,jj,jk) = ABS( uu(ji,jj,jk,Kmm) ) * rDt / e1u  (ji,jj)      ! for i-direction
63         zCv_cfl(ji,jj,jk) = ABS( vv(ji,jj,jk,Kmm) ) * rDt / e2v  (ji,jj)      ! for j-direction
64         zCw_cfl(ji,jj,jk) = ABS( ww(ji,jj,jk) ) * rDt / e3w(ji,jj,jk,Kmm)   ! for k-direction
65      END_3D
66      !
67      ! write outputs
68      IF( iom_use('cfl_cu') )   CALL iom_put( 'cfl_cu', MAXVAL( zCu_cfl, dim=3 ) )
69      IF( iom_use('cfl_cv') )   CALL iom_put( 'cfl_cv', MAXVAL( zCv_cfl, dim=3 ) )
70      IF( iom_use('cfl_cw') )   CALL iom_put( 'cfl_cw', MAXVAL( zCw_cfl, dim=3 ) )
71
72      !                    ! calculate maximum values and locations
73      IF( lk_mpp ) THEN
74         CALL mpp_maxloc( 'diacfl', zCu_cfl, umask, zCu_max, iloc_u )
75         CALL mpp_maxloc( 'diacfl', zCv_cfl, vmask, zCv_max, iloc_v )
76         CALL mpp_maxloc( 'diacfl', zCw_cfl, wmask, zCw_max, iloc_w )
77      ELSE
78         iloc = MAXLOC( ABS( zcu_cfl(:,:,:) ) )
79         iloc_u(1) = iloc(1) + nimpp - 1
80         iloc_u(2) = iloc(2) + njmpp - 1
81         iloc_u(3) = iloc(3)
82         zCu_max = zCu_cfl(iloc(1),iloc(2),iloc(3))
83         !
84         iloc = MAXLOC( ABS( zcv_cfl(:,:,:) ) )
85         iloc_v(1) = iloc(1) + nimpp - 1
86         iloc_v(2) = iloc(2) + njmpp - 1
87         iloc_v(3) = iloc(3)
88         zCv_max = zCv_cfl(iloc(1),iloc(2),iloc(3))
89         !
90         iloc = MAXLOC( ABS( zcw_cfl(:,:,:) ) )
91         iloc_w(1) = iloc(1) + nimpp - 1
92         iloc_w(2) = iloc(2) + njmpp - 1
93         iloc_w(3) = iloc(3)
94         zCw_max = zCw_cfl(iloc(1),iloc(2),iloc(3))
95      ENDIF
96      !
97      !                    ! write out to file
98      IF( lwp ) THEN
99         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)
100         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)
101         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)
102      ENDIF
103      !
104      !                    ! update maximum Courant numbers from whole run if applicable
105      IF( zCu_max > rCu_max ) THEN   ;   rCu_max = zCu_max   ;   nCu_loc(:) = iloc_u(:)   ;   ENDIF
106      IF( zCv_max > rCv_max ) THEN   ;   rCv_max = zCv_max   ;   nCv_loc(:) = iloc_v(:)   ;   ENDIF
107      IF( zCw_max > rCw_max ) THEN   ;   rCw_max = zCw_max   ;   nCw_loc(:) = iloc_w(:)   ;   ENDIF
108
109      !                    ! at end of run output max Cu and Cv and close ascii file
110      IF( kt == nitend .AND. lwp ) THEN
111         ! to ascii file
112         WRITE(numcfl,*) '******************************************'
113         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)
114         WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', rDt/rCu_max
115         WRITE(numcfl,*) '******************************************'
116         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)
117         WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', rDt/rCv_max
118         WRITE(numcfl,*) '******************************************'
119         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)
120         WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', rDt/rCw_max
121         CLOSE( numcfl ) 
122         !
123         ! to ocean output
124         WRITE(numout,*)
125         WRITE(numout,*) 'dia_cfl : Maximum Courant number information for the run '
126         WRITE(numout,*) '~~~~~~~'
127         WRITE(numout,*) '   Max Cu = ', rCu_max, ' at (i,j,k) = (',nCu_loc(1),nCu_loc(2),nCu_loc(3),') => dt/C = ', rDt/rCu_max
128         WRITE(numout,*) '   Max Cv = ', rCv_max, ' at (i,j,k) = (',nCv_loc(1),nCv_loc(2),nCv_loc(3),') => dt/C = ', rDt/rCv_max
129         WRITE(numout,*) '   Max Cw = ', rCw_max, ' at (i,j,k) = (',nCw_loc(1),nCw_loc(2),nCw_loc(3),') => dt/C = ', rDt/rCw_max
130      ENDIF
131      !
132      IF( ln_timing )   CALL timing_stop('dia_cfl')
133      !
134   END SUBROUTINE dia_cfl
135
136
137   SUBROUTINE dia_cfl_init
138      !!----------------------------------------------------------------------
139      !!                  ***  ROUTINE dia_cfl_init  ***
140      !!                   
141      !! ** Purpose :   create output file, initialise arrays
142      !!----------------------------------------------------------------------
143      !
144      IF(lwp) THEN
145         WRITE(numout,*)
146         WRITE(numout,*) 'dia_cfl : Outputting CFL diagnostics to ',TRIM(clname), ' file'
147         WRITE(numout,*) '~~~~~~~'
148         WRITE(numout,*)
149         !
150         ! create output ascii file
151         CALL ctl_opn( numcfl, clname, 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', 1, numout, lwp, 1 )
152         WRITE(numcfl,*) 'Timestep  Direction  Max C     i    j    k'
153         WRITE(numcfl,*) '******************************************'
154      ENDIF
155      !
156      rCu_max = 0._wp
157      rCv_max = 0._wp
158      rCw_max = 0._wp
159      !
160   END SUBROUTINE dia_cfl_init
161
162   !!======================================================================
163END MODULE diacfl
Note: See TracBrowser for help on using the repository browser.