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.
trazdf.F90 in NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA – NEMO

source: NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA/trazdf.F90 @ 12340

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

Branch 2019/dev_r11943_MERGE_2019. This commit introduces basic do loop macro
substitution to the 2019 option 1, merge branch. These changes have been SETTE
tested. The only addition is the do_loop_substitute.h90 file in the OCE directory but
the macros defined therein are used throughout the code to replace identifiable, 2D-
and 3D- nested loop opening and closing statements with single-line alternatives. Code
indents are also adjusted accordingly.

The following explanation is taken from comments in the new header file:

This header file contains preprocessor definitions and macros used in the do-loop
substitutions introduced between version 4.0 and 4.2. The primary aim of these macros
is to assist in future applications of tiling to improve performance. This is expected
to be achieved by alternative versions of these macros in selected locations. The
initial introduction of these macros simply replaces all identifiable nested 2D- and
3D-loops with single line statements (and adjusts indenting accordingly). Do loops
are identifiable if they comform to either:

DO jk = ....

DO jj = .... DO jj = ...

DO ji = .... DO ji = ...
. OR .
. .

END DO END DO

END DO END DO

END DO

and white-space variants thereof.

Additionally, only loops with recognised jj and ji loops limits are treated; these are:
Lower limits of 1, 2 or fs_2
Upper limits of jpi, jpim1 or fs_jpim1 (for ji) or jpj, jpjm1 or fs_jpjm1 (for jj)

The macro naming convention takes the form: DO_2D_BT_LR where:

B is the Bottom offset from the PE's inner domain;
T is the Top offset from the PE's inner domain;
L is the Left offset from the PE's inner domain;
R is the Right offset from the PE's inner domain

So, given an inner domain of 2,jpim1 and 2,jpjm1, a typical example would replace:

DO jj = 2, jpj

DO ji = 1, jpim1
.
.

END DO

END DO

with:

DO_2D_01_10
.
.
END_2D

similar conventions apply to the 3D loops macros. jk loop limits are retained
through macro arguments and are not restricted. This includes the possibility of
strides for which an extra set of DO_3DS macros are defined.

In the example definition below the inner PE domain is defined by start indices of
(kIs, kJs) and end indices of (kIe, KJe)

#define DO_2D_00_00 DO jj = kJs, kJe ; DO ji = kIs, kIe
#define END_2D END DO ; END DO

TO DO:


Only conventional nested loops have been identified and replaced by this step. There are constructs such as:

DO jk = 2, jpkm1

z2d(:,:) = z2d(:,:) + e3w(:,:,jk,Kmm) * z3d(:,:,jk) * wmask(:,:,jk)

END DO

which may need to be considered.

  • Property svn:keywords set to Id
File size: 12.8 KB
Line 
1MODULE trazdf
2   !!==============================================================================
3   !!                 ***  MODULE  trazdf  ***
4   !! Ocean active tracers:  vertical component of the tracer mixing trend
5   !!==============================================================================
6   !! History :  1.0  !  2005-11  (G. Madec)  Original code
7   !!            3.0  !  2008-01  (C. Ethe, G. Madec)  merge TRC-TRA
8   !!            4.0  !  2017-06  (G. Madec)  remove explict time-stepping option
9   !!----------------------------------------------------------------------
10
11   !!----------------------------------------------------------------------
12   !!   tra_zdf       : Update the tracer trend with the vertical diffusion
13   !!----------------------------------------------------------------------
14   USE oce            ! ocean dynamics and tracers variables
15   USE dom_oce        ! ocean space and time domain variables
16   USE domvvl         ! variable volume
17   USE phycst         ! physical constant
18   USE zdf_oce        ! ocean vertical physics variables
19   USE sbc_oce        ! surface boundary condition: ocean
20   USE ldftra         ! lateral diffusion: eddy diffusivity
21   USE ldfslp         ! lateral diffusion: iso-neutral slope
22   USE trd_oce        ! trends: ocean variables
23   USE trdtra         ! trends: tracer trend manager
24   !
25   USE in_out_manager ! I/O manager
26   USE prtctl         ! Print control
27   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
28   USE lib_mpp        ! MPP library
29   USE timing         ! Timing
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   tra_zdf       ! called by step.F90
35   PUBLIC   tra_zdf_imp   ! called by trczdf.F90
36
37   !! * Substitutions
38#  include "vectopt_loop_substitute.h90"
39#  include "do_loop_substitute.h90"
40   !!----------------------------------------------------------------------
41   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
42   !! $Id$
43   !! Software governed by the CeCILL license (see ./LICENSE)
44   !!----------------------------------------------------------------------
45CONTAINS
46
47   SUBROUTINE tra_zdf( kt, Kbb, Kmm, Krhs, pts, Kaa )
48      !!----------------------------------------------------------------------
49      !!                  ***  ROUTINE tra_zdf  ***
50      !!
51      !! ** Purpose :   compute the vertical ocean tracer physics.
52      !!---------------------------------------------------------------------
53      INTEGER                                  , INTENT(in)    :: kt                  ! ocean time-step index
54      INTEGER                                  , INTENT(in)    :: Kbb, Kmm, Krhs, Kaa ! time level indices
55      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts                 ! active tracers and RHS of tracer equation
56      !
57      INTEGER  ::   jk   ! Dummy loop indices
58      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrdt, ztrds   ! 3D workspace
59      !!---------------------------------------------------------------------
60      !
61      IF( ln_timing )   CALL timing_start('tra_zdf')
62      !
63      IF( kt == nit000 )  THEN
64         IF(lwp)WRITE(numout,*)
65         IF(lwp)WRITE(numout,*) 'tra_zdf : implicit vertical mixing on T & S'
66         IF(lwp)WRITE(numout,*) '~~~~~~~ '
67      ENDIF
68      !
69      IF( neuler == 0 .AND. kt == nit000 ) THEN   ;   r2dt =      rdt   ! at nit000, =   rdt (restarting with Euler time stepping)
70      ELSEIF( kt <= nit000 + 1           ) THEN   ;   r2dt = 2. * rdt   ! otherwise, = 2 rdt (leapfrog)
71      ENDIF
72      !
73      IF( l_trdtra )   THEN                  !* Save ta and sa trends
74         ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) )
75         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Kaa)
76         ztrds(:,:,:) = pts(:,:,:,jp_sal,Kaa)
77      ENDIF
78      !
79      !                                      !* compute lateral mixing trend and add it to the general trend
80      CALL tra_zdf_imp( kt, nit000, 'TRA', r2dt, Kbb, Kmm, Krhs, pts, Kaa, jpts ) 
81
82!!gm WHY here !   and I don't like that !
83      ! DRAKKAR SSS control {
84      ! JMM avoid negative salinities near river outlet ! Ugly fix
85      ! JMM : restore negative salinities to small salinities:
86      WHERE( pts(:,:,:,jp_sal,Kaa) < 0._wp )   pts(:,:,:,jp_sal,Kaa) = 0.1_wp
87!!gm
88
89      IF( l_trdtra )   THEN                      ! save the vertical diffusive trends for further diagnostics
90         DO jk = 1, jpkm1
91            ztrdt(:,:,jk) = ( ( pts(:,:,jk,jp_tem,Kaa)*e3t(:,:,jk,Kaa) - pts(:,:,jk,jp_tem,Kbb)*e3t(:,:,jk,Kbb) ) &
92               &          / (e3t(:,:,jk,Kmm)*r2dt) ) - ztrdt(:,:,jk)
93            ztrds(:,:,jk) = ( ( pts(:,:,jk,jp_sal,Kaa)*e3t(:,:,jk,Kaa) - pts(:,:,jk,jp_sal,Kbb)*e3t(:,:,jk,Kbb) ) &
94              &           / (e3t(:,:,jk,Kmm)*r2dt) ) - ztrds(:,:,jk)
95         END DO
96!!gm this should be moved in trdtra.F90 and done on all trends
97         CALL lbc_lnk_multi( 'trazdf', ztrdt, 'T', 1. , ztrds, 'T', 1. )
98!!gm
99         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_zdf, ztrdt )
100         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_zdf, ztrds )
101         DEALLOCATE( ztrdt , ztrds )
102      ENDIF
103      !                                          ! print mean trends (used for debugging)
104      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Kaa), clinfo1=' zdf  - Ta: ', mask1=tmask,               &
105         &                                  tab3d_2=pts(:,:,:,jp_sal,Kaa), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
106      !
107      IF( ln_timing )   CALL timing_stop('tra_zdf')
108      !
109   END SUBROUTINE tra_zdf
110
111 
112   SUBROUTINE tra_zdf_imp( kt, kit000, cdtype, p2dt, Kbb, Kmm, Krhs, pt, Kaa, kjpt ) 
113      !!----------------------------------------------------------------------
114      !!                  ***  ROUTINE tra_zdf_imp  ***
115      !!
116      !! ** Purpose :   Compute the after tracer through a implicit computation
117      !!     of the vertical tracer diffusion (including the vertical component
118      !!     of lateral mixing (only for 2nd order operator, for fourth order
119      !!     it is already computed and add to the general trend in traldf)
120      !!
121      !! ** Method  :  The vertical diffusion of a tracer ,t , is given by:
122      !!          difft = dz( avt dz(t) ) = 1/e3t dk+1( avt/e3w dk(t) )
123      !!      It is computed using a backward time scheme (t=after field)
124      !!      which provide directly the after tracer field.
125      !!      If ln_zdfddm=T, use avs for salinity or for passive tracers
126      !!      Surface and bottom boundary conditions: no diffusive flux on
127      !!      both tracers (bottom, applied through the masked field avt).
128      !!      If iso-neutral mixing, add to avt the contribution due to lateral mixing.
129      !!
130      !! ** Action  : - pt(:,:,:,:,Kaa)  becomes the after tracer
131      !!---------------------------------------------------------------------
132      INTEGER                                  , INTENT(in   ) ::   kt       ! ocean time-step index
133      INTEGER                                  , INTENT(in   ) ::   Kbb, Kmm, Krhs, Kaa  ! ocean time level indices
134      INTEGER                                  , INTENT(in   ) ::   kit000   ! first time step index
135      CHARACTER(len=3)                         , INTENT(in   ) ::   cdtype   ! =TRA or TRC (tracer indicator)
136      INTEGER                                  , INTENT(in   ) ::   kjpt     ! number of tracers
137      REAL(wp)                                 , INTENT(in   ) ::   p2dt     ! tracer time-step
138      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt,jpt), INTENT(inout) ::   pt       ! tracers and RHS of tracer equation
139      !
140      INTEGER  ::  ji, jj, jk, jn   ! dummy loop indices
141      REAL(wp) ::  zrhs, zzwi, zzws ! local scalars
142      REAL(wp), DIMENSION(jpi,jpj,jpk) ::  zwi, zwt, zwd, zws
143      !!---------------------------------------------------------------------
144      !
145      !                                               ! ============= !
146      DO jn = 1, kjpt                                 !  tracer loop  !
147         !                                            ! ============= !
148         !  Matrix construction
149         ! --------------------
150         ! Build matrix if temperature or salinity (only in double diffusion case) or first passive tracer
151         !
152         IF(  ( cdtype == 'TRA' .AND. ( jn == jp_tem .OR. ( jn == jp_sal .AND. ln_zdfddm ) ) ) .OR.   &
153            & ( cdtype == 'TRC' .AND. jn == 1 )  )  THEN
154            !
155            ! vertical mixing coef.: avt for temperature, avs for salinity and passive tracers
156            IF( cdtype == 'TRA' .AND. jn == jp_tem ) THEN   ;   zwt(:,:,2:jpk) = avt(:,:,2:jpk)
157            ELSE                                            ;   zwt(:,:,2:jpk) = avs(:,:,2:jpk)
158            ENDIF
159            zwt(:,:,1) = 0._wp
160            !
161            IF( l_ldfslp ) THEN            ! isoneutral diffusion: add the contribution
162               IF( ln_traldf_msc  ) THEN     ! MSC iso-neutral operator
163                  DO_3D_00_00( 2, jpkm1 )
164                     zwt(ji,jj,jk) = zwt(ji,jj,jk) + akz(ji,jj,jk) 
165                  END_3D
166               ELSE                          ! standard or triad iso-neutral operator
167                  DO_3D_00_00( 2, jpkm1 )
168                     zwt(ji,jj,jk) = zwt(ji,jj,jk) + ah_wslp2(ji,jj,jk)
169                  END_3D
170               ENDIF
171            ENDIF
172            !
173            ! Diagonal, lower (i), upper (s)  (including the bottom boundary condition since avt is masked)
174            IF( ln_zad_Aimp ) THEN         ! Adaptive implicit vertical advection
175               DO_3D_00_00( 1, jpkm1 )
176                  zzwi = - p2dt * zwt(ji,jj,jk  ) / e3w(ji,jj,jk  ,Kmm)
177                  zzws = - p2dt * zwt(ji,jj,jk+1) / e3w(ji,jj,jk+1,Kmm)
178                  zwd(ji,jj,jk) = e3t(ji,jj,jk,Kaa) - zzwi - zzws   &
179                     &                 + p2dt * ( MAX( wi(ji,jj,jk  ) , 0._wp ) - MIN( wi(ji,jj,jk+1) , 0._wp ) )
180                  zwi(ji,jj,jk) = zzwi + p2dt *   MIN( wi(ji,jj,jk  ) , 0._wp )
181                  zws(ji,jj,jk) = zzws - p2dt *   MAX( wi(ji,jj,jk+1) , 0._wp )
182               END_3D
183            ELSE
184               DO_3D_00_00( 1, jpkm1 )
185                  zwi(ji,jj,jk) = - p2dt * zwt(ji,jj,jk  ) / e3w(ji,jj,jk,Kmm)
186                  zws(ji,jj,jk) = - p2dt * zwt(ji,jj,jk+1) / e3w(ji,jj,jk+1,Kmm)
187                  zwd(ji,jj,jk) = e3t(ji,jj,jk,Kaa) - zwi(ji,jj,jk) - zws(ji,jj,jk)
188               END_3D
189            ENDIF
190            !
191            !! Matrix inversion from the first level
192            !!----------------------------------------------------------------------
193            !   solve m.x = y  where m is a tri diagonal matrix ( jpk*jpk )
194            !
195            !        ( zwd1 zws1   0    0    0  )( zwx1 ) ( zwy1 )
196            !        ( zwi2 zwd2 zws2   0    0  )( zwx2 ) ( zwy2 )
197            !        (  0   zwi3 zwd3 zws3   0  )( zwx3 )=( zwy3 )
198            !        (        ...               )( ...  ) ( ...  )
199            !        (  0    0    0   zwik zwdk )( zwxk ) ( zwyk )
200            !
201            !   m is decomposed in the product of an upper and lower triangular matrix.
202            !   The 3 diagonal terms are in 3d arrays: zwd, zws, zwi.
203            !   Suffices i,s and d indicate "inferior" (below diagonal), diagonal
204            !   and "superior" (above diagonal) components of the tridiagonal system.
205            !   The solution will be in the 4d array pta.
206            !   The 3d array zwt is used as a work space array.
207            !   En route to the solution pt(:,:,:,:,Kaa) is used a to evaluate the rhs and then
208            !   used as a work space array: its value is modified.
209            !
210            DO_2D_00_00
211               zwt(ji,jj,1) = zwd(ji,jj,1)
212            END_2D
213            DO_3D_00_00( 2, jpkm1 )
214               zwt(ji,jj,jk) = zwd(ji,jj,jk) - zwi(ji,jj,jk) * zws(ji,jj,jk-1) / zwt(ji,jj,jk-1)
215            END_3D
216            !
217         ENDIF 
218         !         
219         DO_2D_00_00
220            pt(ji,jj,1,jn,Kaa) = e3t(ji,jj,1,Kbb) * pt(ji,jj,1,jn,Kbb) + p2dt * e3t(ji,jj,1,Kmm) * pt(ji,jj,1,jn,Krhs)
221         END_2D
222         DO_3D_00_00( 2, jpkm1 )
223            zrhs = e3t(ji,jj,jk,Kbb) * pt(ji,jj,jk,jn,Kbb) + p2dt * e3t(ji,jj,jk,Kmm) * pt(ji,jj,jk,jn,Krhs)   ! zrhs=right hand side
224            pt(ji,jj,jk,jn,Kaa) = zrhs - zwi(ji,jj,jk) / zwt(ji,jj,jk-1) * pt(ji,jj,jk-1,jn,Kaa)
225         END_3D
226         !
227         DO_2D_00_00
228            pt(ji,jj,jpkm1,jn,Kaa) = pt(ji,jj,jpkm1,jn,Kaa) / zwt(ji,jj,jpkm1) * tmask(ji,jj,jpkm1)
229         END_2D
230         DO_3DS_00_00( jpk-2, 1, -1 )
231            pt(ji,jj,jk,jn,Kaa) = ( pt(ji,jj,jk,jn,Kaa) - zws(ji,jj,jk) * pt(ji,jj,jk+1,jn,Kaa) )   &
232               &             / zwt(ji,jj,jk) * tmask(ji,jj,jk)
233         END_3D
234         !                                            ! ================= !
235      END DO                                          !  end tracer loop  !
236      !                                               ! ================= !
237   END SUBROUTINE tra_zdf_imp
238
239   !!==============================================================================
240END MODULE trazdf
Note: See TracBrowser for help on using the repository browser.