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

source: NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRD/trddyn.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: 10.4 KB
Line 
1MODULE trddyn
2   !!======================================================================
3   !!                       ***  MODULE  trddyn  ***
4   !! Ocean diagnostics:  ocean dynamic trends
5   !!=====================================================================
6   !! History :  3.5  !  2012-02  (G. Madec) creation from trdmod: split DYN and TRA trends
7   !!                                        and manage  3D trends output for U, V, and KE
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   trd_dyn       : manage the type of momentum trend diagnostics (3D I/O, domain averaged, KE)
12   !!   trd_dyn_iom   : output 3D momentum and/or tracer trends using IOM
13   !!   trd_dyn_init  : initialization step
14   !!----------------------------------------------------------------------
15   USE oce            ! ocean dynamics and tracers variables
16   USE dom_oce        ! ocean space and time domain variables
17   USE phycst         ! physical constants
18   USE sbc_oce        ! surface boundary condition: ocean
19   USE zdf_oce        ! ocean vertical physics: variables
20!!gm   USE zdfdrg         ! ocean vertical physics: bottom friction
21   USE trd_oce        ! trends: ocean variables
22   USE trdken         ! trends: Kinetic ENergy
23   USE trdglo         ! trends: global domain averaged
24   USE trdvor         ! trends: vertical averaged vorticity
25   USE trdmxl         ! trends: mixed layer averaged
26   !
27   USE in_out_manager ! I/O manager
28   USE lbclnk         ! lateral boundary condition
29   USE iom            ! I/O manager library
30   USE lib_mpp        ! MPP library
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC trd_dyn        ! called by all dynXXX modules
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 trd_dyn( putrd, pvtrd, ktrd, kt, Kmm )
48      !!---------------------------------------------------------------------
49      !!                  ***  ROUTINE trd_mod  ***
50      !!
51      !! ** Purpose :   Dispatch momentum trend computation, e.g. 3D output,
52      !!              integral constraints, barotropic vorticity, kinetic enrgy,
53      !!              and/or mixed layer budget.
54      !!----------------------------------------------------------------------
55      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   putrd, pvtrd   ! U and V trends
56      INTEGER                   , INTENT(in   ) ::   ktrd           ! trend index
57      INTEGER                   , INTENT(in   ) ::   kt             ! time step
58      INTEGER                   , INTENT(in   ) ::   Kmm            ! time level index
59      !!----------------------------------------------------------------------
60      !
61      putrd(:,:,:) = putrd(:,:,:) * umask(:,:,:)                       ! mask the trends
62      pvtrd(:,:,:) = pvtrd(:,:,:) * vmask(:,:,:)
63      !
64
65!!gm NB : here a lbc_lnk should probably be added
66
67      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
68      !   3D output of momentum and/or tracers trends using IOM interface
69      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
70      IF( ln_dyn_trd )   CALL trd_dyn_iom( putrd, pvtrd, ktrd, kt, Kmm )
71         
72      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
73      !  Integral Constraints Properties for momentum and/or tracers trends
74      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
75      IF( ln_glo_trd )   CALL trd_glo( putrd, pvtrd, ktrd, 'DYN', kt, Kmm )
76
77      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
78      !  Kinetic Energy trends
79      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
80      IF( ln_KE_trd  )   CALL trd_ken( putrd, pvtrd, ktrd, kt, Kmm )
81
82      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
83      !  Vorticity trends
84      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
85      IF( ln_vor_trd )   CALL trd_vor( putrd, pvtrd, ktrd, kt, Kmm )
86
87      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
88      !  Mixed layer trends for active tracers
89      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
90!!gm      IF( ln_dyn_mxl )   CALL trd_mxl_dyn   
91      !
92   END SUBROUTINE trd_dyn
93
94
95   SUBROUTINE trd_dyn_iom( putrd, pvtrd, ktrd, kt, Kmm )
96      !!---------------------------------------------------------------------
97      !!                  ***  ROUTINE trd_dyn_iom  ***
98      !!
99      !! ** Purpose :   output 3D trends using IOM
100      !!----------------------------------------------------------------------
101      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   putrd, pvtrd   ! U and V trends
102      INTEGER                   , INTENT(in   ) ::   ktrd           ! trend index
103      INTEGER                   , INTENT(in   ) ::   kt             ! time step
104      INTEGER                   , INTENT(in   ) ::   Kmm            ! time level index
105      !
106      INTEGER ::   ji, jj, jk   ! dummy loop indices
107      INTEGER ::   ikbu, ikbv   ! local integers
108      REAL(wp), ALLOCATABLE, DIMENSION(:,:)   ::   z2dx, z2dy   ! 2D workspace
109      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   z3dx, z3dy   ! 3D workspace
110      !!----------------------------------------------------------------------
111      !
112      SELECT CASE( ktrd )
113      CASE( jpdyn_hpg )   ;   CALL iom_put( "utrd_hpg", putrd )    ! hydrostatic pressure gradient
114                              CALL iom_put( "vtrd_hpg", pvtrd )
115      CASE( jpdyn_spg )   ;   CALL iom_put( "utrd_spg", putrd )    ! surface pressure gradient
116                              CALL iom_put( "vtrd_spg", pvtrd )
117      CASE( jpdyn_pvo )   ;   CALL iom_put( "utrd_pvo", putrd )    ! planetary vorticity
118                              CALL iom_put( "vtrd_pvo", pvtrd )
119      CASE( jpdyn_rvo )   ;   CALL iom_put( "utrd_rvo", putrd )    ! relative  vorticity     (or metric term)
120                              CALL iom_put( "vtrd_rvo", pvtrd )
121      CASE( jpdyn_keg )   ;   CALL iom_put( "utrd_keg", putrd )    ! Kinetic Energy gradient (or had)
122                              CALL iom_put( "vtrd_keg", pvtrd )
123                              ALLOCATE( z3dx(jpi,jpj,jpk) , z3dy(jpi,jpj,jpk) )
124                              z3dx(:,:,:) = 0._wp                  ! U.dxU & V.dyV (approximation)
125                              z3dy(:,:,:) = 0._wp
126                              DO_3D_00_00( 1, jpkm1 )
127                                 z3dx(ji,jj,jk) = uu(ji,jj,jk,Kmm) * ( uu(ji+1,jj,jk,Kmm) - uu(ji-1,jj,jk,Kmm) ) / ( 2._wp * e1u(ji,jj) )
128                                 z3dy(ji,jj,jk) = vv(ji,jj,jk,Kmm) * ( vv(ji,jj+1,jk,Kmm) - vv(ji,jj-1,jk,Kmm) ) / ( 2._wp * e2v(ji,jj) )
129                              END_3D
130                              CALL lbc_lnk_multi( 'trddyn', z3dx, 'U', -1., z3dy, 'V', -1. )
131                              CALL iom_put( "utrd_udx", z3dx  )
132                              CALL iom_put( "vtrd_vdy", z3dy  )
133                              DEALLOCATE( z3dx , z3dy )
134      CASE( jpdyn_zad )   ;   CALL iom_put( "utrd_zad", putrd )    ! vertical advection
135                              CALL iom_put( "vtrd_zad", pvtrd )
136      CASE( jpdyn_ldf )   ;   CALL iom_put( "utrd_ldf", putrd )    ! lateral  diffusion
137                              CALL iom_put( "vtrd_ldf", pvtrd )
138      CASE( jpdyn_zdf )   ;   CALL iom_put( "utrd_zdf", putrd )    ! vertical diffusion
139                              CALL iom_put( "vtrd_zdf", pvtrd )
140                              !
141                              !                                    ! wind stress trends
142                              ALLOCATE( z2dx(jpi,jpj) , z2dy(jpi,jpj) )
143                              z2dx(:,:) = ( utau_b(:,:) + utau(:,:) ) / ( e3u(:,:,1,Kmm) * rau0 )
144                              z2dy(:,:) = ( vtau_b(:,:) + vtau(:,:) ) / ( e3v(:,:,1,Kmm) * rau0 )
145                              CALL iom_put( "utrd_tau", z2dx )
146                              CALL iom_put( "vtrd_tau", z2dy )
147                              DEALLOCATE( z2dx , z2dy )
148!!gm  to be changed : computation should be done in dynzdf.F90
149!!gm                + missing the top friction
150!                              !                                    ! bottom stress tends (implicit case)
151!                              IF( ln_drgimp ) THEN
152!                                 ALLOCATE( z3dx(jpi,jpj,jpk) , z3dy(jpi,jpj,jpk) )
153!                             z3dx(:,:,:) = 0._wp   ;   z3dy(:,:,:) = 0._wp  ! after velocity known (now filed at this stage)
154!                            DO jk = 1, jpkm1
155!                                    DO jj = 2, jpjm1
156!                                       DO ji = 2, jpim1
157!                                      ikbu = mbku(ji,jj)          ! deepest ocean u- & v-levels
158!                                          ikbv = mbkv(ji,jj)
159!                                          z3dx(ji,jj,jk) = 0.5 * ( rCdU_bot(ji+1,jj) + rCdU_bot(ji,jj) ) &
160!                                               &         * uu(ji,jj,ikbu,Kmm) / e3u(ji,jj,ikbu,Kmm)
161!                                          z3dy(ji,jj,jk) = 0.5 * ( rCdU_bot(ji,jj+1) + rCdU_bot(ji,jj) ) &
162!                                               &         * vv(ji,jj,ikbv,Kmm) / e3v(ji,jj,ikbv,Kmm)
163!                                    END DO
164!                                 END DO
165!                              END DO
166!                              CALL lbc_lnk_multi( 'trddyn', z3dx, 'U', -1., z3dy, 'V', -1. )
167!                              CALL iom_put( "utrd_bfr", z3dx )
168!                              CALL iom_put( "vtrd_bfr", z3dy )
169!                                 DEALLOCATE( z3dx , z3dy )
170!                              ENDIF
171!!gm end
172      CASE( jpdyn_bfr )       ! called if ln_drgimp=F
173                              CALL iom_put( "utrd_bfr", putrd )    ! bottom friction (explicit case)
174                              CALL iom_put( "vtrd_bfr", pvtrd )
175      CASE( jpdyn_atf )   ;   CALL iom_put( "utrd_atf", putrd )        ! asselin filter trends
176                              CALL iom_put( "vtrd_atf", pvtrd )
177      END SELECT
178      !
179   END SUBROUTINE trd_dyn_iom
180
181   !!======================================================================
182END MODULE trddyn
Note: See TracBrowser for help on using the repository browser.