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

source: NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA/trasbc.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.9 KB
Line 
1MODULE trasbc
2   !!==============================================================================
3   !!                       ***  MODULE  trasbc  ***
4   !! Ocean active tracers:  surface boundary condition
5   !!==============================================================================
6   !! History :  OPA  !  1998-10  (G. Madec, G. Roullet, M. Imbard)  Original code
7   !!            8.2  !  2001-02  (D. Ludicone)  sea ice and free surface
8   !!  NEMO      1.0  !  2002-06  (G. Madec)  F90: Free form and module
9   !!            3.3  !  2010-04  (M. Leclair, G. Madec)  Forcing averaged over 2 time steps
10   !!             -   !  2010-09  (C. Ethe, G. Madec) Merge TRA-TRC
11   !!            3.6  !  2014-11  (P. Mathiot) isf melting forcing
12   !!            4.1  !  2019-09  (P. Mathiot) isf moved in traisf
13   !!----------------------------------------------------------------------
14
15   !!----------------------------------------------------------------------
16   !!   tra_sbc       : update the tracer trend at ocean surface
17   !!----------------------------------------------------------------------
18   USE oce            ! ocean dynamics and active tracers
19   USE sbc_oce        ! surface boundary condition: ocean
20   USE dom_oce        ! ocean space domain variables
21   USE phycst         ! physical constant
22   USE eosbn2         ! Equation Of State
23   USE sbcmod         ! ln_rnf 
24   USE sbcrnf         ! River runoff 
25   USE traqsr         ! solar radiation penetration
26   USE trd_oce        ! trends: ocean variables
27   USE trdtra         ! trends manager: tracers
28#if defined key_asminc   
29   USE asminc         ! Assimilation increment
30#endif
31   !
32   USE in_out_manager ! I/O manager
33   USE prtctl         ! Print control
34   USE iom            ! xIOS server
35   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
36   USE timing         ! Timing
37
38   IMPLICIT NONE
39   PRIVATE
40
41   PUBLIC   tra_sbc   ! routine called by step.F90
42
43   !! * Substitutions
44#  include "vectopt_loop_substitute.h90"
45#  include "do_loop_substitute.h90"
46   !!----------------------------------------------------------------------
47   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
48   !! $Id$
49   !! Software governed by the CeCILL license (see ./LICENSE)
50   !!----------------------------------------------------------------------
51CONTAINS
52
53   SUBROUTINE tra_sbc ( kt, Kmm, pts, Krhs )
54      !!----------------------------------------------------------------------
55      !!                  ***  ROUTINE tra_sbc  ***
56      !!                   
57      !! ** Purpose :   Compute the tracer surface boundary condition trend of
58      !!      (flux through the interface, concentration/dilution effect)
59      !!      and add it to the general trend of tracer equations.
60      !!
61      !! ** Method :   The (air+ice)-sea flux has two components:
62      !!      (1) Fext, external forcing (i.e. flux through the (air+ice)-sea interface);
63      !!      (2) Fwe , tracer carried with the water that is exchanged with air+ice.
64      !!               The input forcing fields (emp, rnf, sfx) contain Fext+Fwe,
65      !!             they are simply added to the tracer trend (ts(Krhs)).
66      !!               In linear free surface case (ln_linssh=T), the volume of the
67      !!             ocean does not change with the water exchanges at the (air+ice)-sea
68      !!             interface. Therefore another term has to be added, to mimic the
69      !!             concentration/dilution effect associated with water exchanges.
70      !!
71      !! ** Action  : - Update ts(Krhs) with the surface boundary condition trend
72      !!              - send trends to trdtra module for further diagnostics(l_trdtra=T)
73      !!----------------------------------------------------------------------
74      INTEGER,                                   INTENT(in   ) :: kt         ! ocean time-step index
75      INTEGER,                                   INTENT(in   ) :: Kmm, Krhs  ! time level indices
76      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts        ! active tracers and RHS of tracer equation
77      !
78      INTEGER  ::   ji, jj, jk, jn              ! dummy loop indices 
79      INTEGER  ::   ikt, ikb                    ! local integers
80      REAL(wp) ::   zfact, z1_e3t, zdep, ztim   ! local scalar
81      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::  ztrdt, ztrds
82      !!----------------------------------------------------------------------
83      !
84      IF( ln_timing )   CALL timing_start('tra_sbc')
85      !
86      IF( kt == nit000 ) THEN
87         IF(lwp) WRITE(numout,*)
88         IF(lwp) WRITE(numout,*) 'tra_sbc : TRAcer Surface Boundary Condition'
89         IF(lwp) WRITE(numout,*) '~~~~~~~ '
90      ENDIF
91      !
92      IF( l_trdtra ) THEN                    !* Save ta and sa trends
93         ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) ) 
94         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs)
95         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs)
96      ENDIF
97      !
98!!gm  This should be moved into sbcmod.F90 module ? (especially now that ln_traqsr is read in namsbc namelist)
99      IF( .NOT.ln_traqsr ) THEN     ! no solar radiation penetration
100         qns(:,:) = qns(:,:) + qsr(:,:)      ! total heat flux in qns
101         qsr(:,:) = 0._wp                     ! qsr set to zero
102      ENDIF
103
104      !----------------------------------------
105      !        EMP, SFX and QNS effects
106      !----------------------------------------
107      !                             !==  Set before sbc tracer content fields  ==!
108      IF( kt == nit000 ) THEN             !* 1st time-step
109         IF( ln_rstart .AND.    &               ! Restart: read in restart file
110              & iom_varid( numror, 'sbc_hc_b', ldstop = .FALSE. ) > 0 ) THEN
111            IF(lwp) WRITE(numout,*) '          nit000-1 sbc tracer content field read in the restart file'
112            zfact = 0.5_wp
113            sbc_tsc(:,:,:) = 0._wp
114            CALL iom_get( numror, jpdom_autoglo, 'sbc_hc_b', sbc_tsc_b(:,:,jp_tem), ldxios = lrxios )   ! before heat content sbc trend
115            CALL iom_get( numror, jpdom_autoglo, 'sbc_sc_b', sbc_tsc_b(:,:,jp_sal), ldxios = lrxios )   ! before salt content sbc trend
116         ELSE                                   ! No restart or restart not found: Euler forward time stepping
117            zfact = 1._wp
118            sbc_tsc(:,:,:) = 0._wp
119            sbc_tsc_b(:,:,:) = 0._wp
120         ENDIF
121      ELSE                                !* other time-steps: swap of forcing fields
122         zfact = 0.5_wp
123         sbc_tsc_b(:,:,:) = sbc_tsc(:,:,:)
124      ENDIF
125      !                             !==  Now sbc tracer content fields  ==!
126      DO_2D_01_00
127         sbc_tsc(ji,jj,jp_tem) = r1_rau0_rcp * qns(ji,jj)   ! non solar heat flux
128         sbc_tsc(ji,jj,jp_sal) = r1_rau0     * sfx(ji,jj)   ! salt flux due to freezing/melting
129      END_2D
130      IF( ln_linssh ) THEN                !* linear free surface 
131         DO_2D_01_00
132            sbc_tsc(ji,jj,jp_tem) = sbc_tsc(ji,jj,jp_tem) + r1_rau0 * emp(ji,jj) * pts(ji,jj,1,jp_tem,Kmm)
133            sbc_tsc(ji,jj,jp_sal) = sbc_tsc(ji,jj,jp_sal) + r1_rau0 * emp(ji,jj) * pts(ji,jj,1,jp_sal,Kmm)
134         END_2D
135         IF( iom_use('emp_x_sst') )   CALL iom_put( "emp_x_sst", emp (:,:) * pts(:,:,1,jp_tem,Kmm) )
136         IF( iom_use('emp_x_sss') )   CALL iom_put( "emp_x_sss", emp (:,:) * pts(:,:,1,jp_sal,Kmm) )
137      ENDIF
138      !
139      DO jn = 1, jpts               !==  update tracer trend  ==!
140         DO_2D_01_00
141            pts(ji,jj,1,jn,Krhs) = pts(ji,jj,1,jn,Krhs) + zfact * ( sbc_tsc_b(ji,jj,jn) + sbc_tsc(ji,jj,jn) ) / e3t(ji,jj,1,Kmm)
142         END_2D
143      END DO
144      !                 
145      IF( lrst_oce ) THEN           !==  write sbc_tsc in the ocean restart file  ==!
146         IF( lwxios ) CALL iom_swap(      cwxios_context          )
147         CALL iom_rstput( kt, nitrst, numrow, 'sbc_hc_b', sbc_tsc(:,:,jp_tem), ldxios = lwxios )
148         CALL iom_rstput( kt, nitrst, numrow, 'sbc_sc_b', sbc_tsc(:,:,jp_sal), ldxios = lwxios )
149         IF( lwxios ) CALL iom_swap(      cxios_context          )
150      ENDIF
151      !
152      !----------------------------------------
153      !        River Runoff effects
154      !----------------------------------------
155      !
156      IF( ln_rnf ) THEN         ! input of heat and salt due to river runoff
157         zfact = 0.5_wp
158         DO_2D_01_00
159            IF( rnf(ji,jj) /= 0._wp ) THEN
160               zdep = zfact / h_rnf(ji,jj)
161               DO jk = 1, nk_rnf(ji,jj)
162                                     pts(ji,jj,jk,jp_tem,Krhs) = pts(ji,jj,jk,jp_tem,Krhs)                                  &
163                                        &                      +  ( rnf_tsc_b(ji,jj,jp_tem) + rnf_tsc(ji,jj,jp_tem) ) * zdep
164                  IF( ln_rnf_sal )   pts(ji,jj,jk,jp_sal,Krhs) = pts(ji,jj,jk,jp_sal,Krhs)                                  &
165                                        &                      +  ( rnf_tsc_b(ji,jj,jp_sal) + rnf_tsc(ji,jj,jp_sal) ) * zdep 
166               END DO
167            ENDIF
168         END_2D
169      ENDIF
170
171      IF( iom_use('rnf_x_sst') )   CALL iom_put( "rnf_x_sst", rnf*pts(:,:,1,jp_tem,Kmm) )   ! runoff term on sst
172      IF( iom_use('rnf_x_sss') )   CALL iom_put( "rnf_x_sss", rnf*pts(:,:,1,jp_sal,Kmm) )   ! runoff term on sss
173
174#if defined key_asminc
175      !
176      !----------------------------------------
177      !        Assmilation effects
178      !----------------------------------------
179      !
180      IF( ln_sshinc ) THEN         ! input of heat and salt due to assimilation
181          !
182         IF( ln_linssh ) THEN
183            DO_2D_01_00
184               ztim = ssh_iau(ji,jj) / e3t(ji,jj,1,Kmm)
185               pts(ji,jj,1,jp_tem,Krhs) = pts(ji,jj,1,jp_tem,Krhs) + pts(ji,jj,1,jp_tem,Kmm) * ztim
186               pts(ji,jj,1,jp_sal,Krhs) = pts(ji,jj,1,jp_sal,Krhs) + pts(ji,jj,1,jp_sal,Kmm) * ztim
187            END_2D
188         ELSE
189            DO_2D_01_00
190               ztim = ssh_iau(ji,jj) / ( ht(ji,jj) + 1. - ssmask(ji, jj) )
191               pts(ji,jj,:,jp_tem,Krhs) = pts(ji,jj,:,jp_tem,Krhs) + pts(ji,jj,:,jp_tem,Kmm) * ztim
192               pts(ji,jj,:,jp_sal,Krhs) = pts(ji,jj,:,jp_sal,Krhs) + pts(ji,jj,:,jp_sal,Kmm) * ztim
193            END_2D
194         ENDIF
195         !
196      ENDIF
197      !
198#endif
199      !
200      IF( l_trdtra )   THEN                      ! save the horizontal diffusive trends for further diagnostics
201         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:)
202         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:)
203         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_nsr, ztrdt )
204         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_nsr, ztrds )
205         DEALLOCATE( ztrdt , ztrds ) 
206      ENDIF
207      !
208      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' sbc  - Ta: ', mask1=tmask,   &
209         &                                  tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
210      !
211      IF( ln_timing )   CALL timing_stop('tra_sbc')
212      !
213   END SUBROUTINE tra_sbc
214
215   !!======================================================================
216END MODULE trasbc
Note: See TracBrowser for help on using the repository browser.