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 @ 12377

Last change on this file since 12377 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 8.2 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)                         ::   z2dt, 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      !                       ! setup timestep multiplier to account for initial Eulerian timestep
62      IF( neuler == 0 .AND. kt == nit000 ) THEN   ;    z2dt = rdt
63      ELSE                                        ;    z2dt = rdt * 2._wp
64      ENDIF
65      !
66      !               
67      DO_3D_11_11( 1, jpk )
68         zCu_cfl(ji,jj,jk) = ABS( uu(ji,jj,jk,Kmm) ) * z2dt / e1u  (ji,jj)      ! for i-direction
69         zCv_cfl(ji,jj,jk) = ABS( vv(ji,jj,jk,Kmm) ) * z2dt / e2v  (ji,jj)      ! for j-direction
70         zCw_cfl(ji,jj,jk) = ABS( ww(ji,jj,jk) ) * z2dt / e3w(ji,jj,jk,Kmm)   ! for k-direction
71      END_3D
72      !
73      ! write outputs
74      IF( iom_use('cfl_cu') )   CALL iom_put( 'cfl_cu', MAXVAL( zCu_cfl, dim=3 ) )
75      IF( iom_use('cfl_cv') )   CALL iom_put( 'cfl_cv', MAXVAL( zCv_cfl, dim=3 ) )
76      IF( iom_use('cfl_cw') )   CALL iom_put( 'cfl_cw', MAXVAL( zCw_cfl, dim=3 ) )
77
78      !                    ! calculate maximum values and locations
79      IF( lk_mpp ) THEN
80         CALL mpp_maxloc( 'diacfl', zCu_cfl, umask, zCu_max, iloc_u )
81         CALL mpp_maxloc( 'diacfl', zCv_cfl, vmask, zCv_max, iloc_v )
82         CALL mpp_maxloc( 'diacfl', zCw_cfl, wmask, zCw_max, iloc_w )
83      ELSE
84         iloc = MAXLOC( ABS( zcu_cfl(:,:,:) ) )
85         iloc_u(1) = iloc(1) + nimpp - 1
86         iloc_u(2) = iloc(2) + njmpp - 1
87         iloc_u(3) = iloc(3)
88         zCu_max = zCu_cfl(iloc(1),iloc(2),iloc(3))
89         !
90         iloc = MAXLOC( ABS( zcv_cfl(:,:,:) ) )
91         iloc_v(1) = iloc(1) + nimpp - 1
92         iloc_v(2) = iloc(2) + njmpp - 1
93         iloc_v(3) = iloc(3)
94         zCv_max = zCv_cfl(iloc(1),iloc(2),iloc(3))
95         !
96         iloc = MAXLOC( ABS( zcw_cfl(:,:,:) ) )
97         iloc_w(1) = iloc(1) + nimpp - 1
98         iloc_w(2) = iloc(2) + njmpp - 1
99         iloc_w(3) = iloc(3)
100         zCw_max = zCw_cfl(iloc(1),iloc(2),iloc(3))
101      ENDIF
102      !
103      !                    ! write out to file
104      IF( lwp ) THEN
105         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)
106         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)
107         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)
108      ENDIF
109      !
110      !                    ! update maximum Courant numbers from whole run if applicable
111      IF( zCu_max > rCu_max ) THEN   ;   rCu_max = zCu_max   ;   nCu_loc(:) = iloc_u(:)   ;   ENDIF
112      IF( zCv_max > rCv_max ) THEN   ;   rCv_max = zCv_max   ;   nCv_loc(:) = iloc_v(:)   ;   ENDIF
113      IF( zCw_max > rCw_max ) THEN   ;   rCw_max = zCw_max   ;   nCw_loc(:) = iloc_w(:)   ;   ENDIF
114
115      !                    ! at end of run output max Cu and Cv and close ascii file
116      IF( kt == nitend .AND. lwp ) THEN
117         ! to ascii file
118         WRITE(numcfl,*) '******************************************'
119         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)
120         WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', z2dt/rCu_max
121         WRITE(numcfl,*) '******************************************'
122         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)
123         WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', z2dt/rCv_max
124         WRITE(numcfl,*) '******************************************'
125         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)
126         WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', z2dt/rCw_max
127         CLOSE( numcfl ) 
128         !
129         ! to ocean output
130         WRITE(numout,*)
131         WRITE(numout,*) 'dia_cfl : Maximum Courant number information for the run '
132         WRITE(numout,*) '~~~~~~~'
133         WRITE(numout,*) '   Max Cu = ', rCu_max, ' at (i,j,k) = (',nCu_loc(1),nCu_loc(2),nCu_loc(3),') => dt/C = ', z2dt/rCu_max
134         WRITE(numout,*) '   Max Cv = ', rCv_max, ' at (i,j,k) = (',nCv_loc(1),nCv_loc(2),nCv_loc(3),') => dt/C = ', z2dt/rCv_max
135         WRITE(numout,*) '   Max Cw = ', rCw_max, ' at (i,j,k) = (',nCw_loc(1),nCw_loc(2),nCw_loc(3),') => dt/C = ', z2dt/rCw_max
136      ENDIF
137      !
138      IF( ln_timing )   CALL timing_stop('dia_cfl')
139      !
140   END SUBROUTINE dia_cfl
141
142
143   SUBROUTINE dia_cfl_init
144      !!----------------------------------------------------------------------
145      !!                  ***  ROUTINE dia_cfl_init  ***
146      !!                   
147      !! ** Purpose :   create output file, initialise arrays
148      !!----------------------------------------------------------------------
149      !
150      IF(lwp) THEN
151         WRITE(numout,*)
152         WRITE(numout,*) 'dia_cfl : Outputting CFL diagnostics to ',TRIM(clname), ' file'
153         WRITE(numout,*) '~~~~~~~'
154         WRITE(numout,*)
155         !
156         ! create output ascii file
157         CALL ctl_opn( numcfl, clname, 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', 1, numout, lwp, 1 )
158         WRITE(numcfl,*) 'Timestep  Direction  Max C     i    j    k'
159         WRITE(numcfl,*) '******************************************'
160      ENDIF
161      !
162      rCu_max = 0._wp
163      rCv_max = 0._wp
164      rCw_max = 0._wp
165      !
166   END SUBROUTINE dia_cfl_init
167
168   !!======================================================================
169END MODULE diacfl
Note: See TracBrowser for help on using the repository browser.