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.
traldf_lap_blp.F90 in NEMO/trunk/src/OCE/TRA – NEMO

source: NEMO/trunk/src/OCE/TRA/traldf_lap_blp.F90 @ 14215

Last change on this file since 14215 was 14215, checked in by acc, 3 years ago

trunk changes to swap the order of arguments to the DO LOOP macros. These changes result in a more natural i-j-k ordering as explained in #2595. SETTE is passed before and after these changes and results are unchanged. This fixes #2595

  • Property svn:keywords set to Id
File size: 15.9 KB
Line 
1MODULE traldf_lap_blp
2   !!==============================================================================
3   !!                       ***  MODULE  traldf_lap_blp  ***
4   !! Ocean tracers:  lateral diffusivity trend  (laplacian and bilaplacian)
5   !!==============================================================================
6   !! History :  3.7  ! 2014-01  (G. Madec, S. Masson)  Original code, re-entrant laplacian
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   tra_ldf_lap   : tracer trend update with iso-level laplacian diffusive operator
11   !!   tra_ldf_blp   : tracer trend update with iso-level or iso-neutral bilaplacian operator
12   !!----------------------------------------------------------------------
13   USE oce            ! ocean dynamics and active tracers
14   USE dom_oce        ! ocean space and time domain
15   USE domutl, ONLY : is_tile
16   USE ldftra         ! lateral physics: eddy diffusivity
17   USE traldf_iso     ! iso-neutral lateral diffusion (standard operator)     (tra_ldf_iso   routine)
18   USE traldf_triad   ! iso-neutral lateral diffusion (triad    operator)     (tra_ldf_triad routine)
19   USE diaptr         ! poleward transport diagnostics
20   USE diaar5         ! AR5 diagnostics
21   USE trc_oce        ! share passive tracers/Ocean variables
22   USE zpshde         ! partial step: hor. derivative     (zps_hde routine)
23   !
24   USE in_out_manager ! I/O manager
25   USE iom            ! I/O library
26   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
27   USE lib_mpp        ! distribued memory computing library
28   USE timing         ! Timing
29
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC   tra_ldf_lap   ! called by traldf.F90
34   PUBLIC   tra_ldf_blp   ! called by traldf.F90
35
36   LOGICAL  ::   l_ptr   ! flag to compute poleward transport
37   LOGICAL  ::   l_hst   ! flag to compute heat transport
38
39   !! * Substitutions
40#  include "do_loop_substitute.h90"
41#  include "domzgr_substitute.h90"
42   !!----------------------------------------------------------------------
43   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
44   !! $Id$
45   !! Software governed by the CeCILL license (see ./LICENSE)
46   !!----------------------------------------------------------------------
47CONTAINS
48
49   SUBROUTINE tra_ldf_lap( kt, Kmm, kit000, cdtype, pahu, pahv,             &
50      &                                             pgu , pgv , pgui, pgvi, &
51      &                                             pt, pt_rhs, kjpt, kpass )
52      !!
53      INTEGER                     , INTENT(in   ) ::   kt         ! ocean time-step index
54      INTEGER                     , INTENT(in   ) ::   kit000     ! first time step index
55      CHARACTER(len=3)            , INTENT(in   ) ::   cdtype     ! =TRA or TRC (tracer indicator)
56      INTEGER                     , INTENT(in   ) ::   kjpt       ! number of tracers
57      INTEGER                     , INTENT(in   ) ::   kpass      ! =1/2 first or second passage
58      INTEGER                     , INTENT(in   ) ::   Kmm        ! ocean time level index
59      REAL(wp), DIMENSION(:,:,:)  , INTENT(in   ) ::   pahu, pahv ! eddy diffusivity at u- and v-points  [m2/s]
60      REAL(wp), DIMENSION(:,:,:)  , INTENT(in   ) ::   pgu, pgv   ! tracer gradient at pstep levels
61      REAL(wp), DIMENSION(:,:,:)  , INTENT(in   ) ::   pgui, pgvi ! tracer gradient at top   levels
62      REAL(wp), DIMENSION(:,:,:,:), INTENT(in   ) ::   pt         ! before tracer fields
63      REAL(wp), DIMENSION(:,:,:,:), INTENT(inout) ::   pt_rhs     ! tracer trend
64      !!
65      CALL tra_ldf_lap_t( kt, Kmm, kit000, cdtype, pahu, pahv, is_tile(pahu),                            &
66      &                                            pgu , pgv , is_tile(pgu) , pgui, pgvi, is_tile(pgui), &
67      &                                            pt, is_tile(pt), pt_rhs, is_tile(pt_rhs), kjpt, kpass )
68   END SUBROUTINE tra_ldf_lap
69
70
71   SUBROUTINE tra_ldf_lap_t( kt, Kmm, kit000, cdtype, pahu, pahv, ktah,                   &
72      &                                               pgu , pgv , ktg , pgui, pgvi, ktgi, &
73      &                                               pt, ktt, pt_rhs, ktt_rhs, kjpt, kpass )
74      !!----------------------------------------------------------------------
75      !!                  ***  ROUTINE tra_ldf_lap  ***
76      !!
77      !! ** Purpose :   Compute the before horizontal tracer (t & s) diffusive
78      !!      trend and add it to the general trend of tracer equation.
79      !!
80      !! ** Method  :   Second order diffusive operator evaluated using before
81      !!      fields (forward time scheme). The horizontal diffusive trends of
82      !!      the tracer is given by:
83      !!          difft = 1/(e1e2t*e3t) {  di-1[ pahu e2u*e3u/e1u di(tb) ]
84      !!                                 + dj-1[ pahv e1v*e3v/e2v dj(tb) ] }
85      !!      Add this trend to the general tracer trend pt_rhs :
86      !!          pt_rhs = pt_rhs + difft
87      !!
88      !! ** Action  : - Update pt_rhs arrays with the before iso-level
89      !!                harmonic mixing trend.
90      !!----------------------------------------------------------------------
91      INTEGER                              , INTENT(in   ) ::   kt         ! ocean time-step index
92      INTEGER                              , INTENT(in   ) ::   kit000     ! first time step index
93      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype     ! =TRA or TRC (tracer indicator)
94      INTEGER                              , INTENT(in   ) ::   kjpt       ! number of tracers
95      INTEGER                              , INTENT(in   ) ::   kpass      ! =1/2 first or second passage
96      INTEGER                              , INTENT(in   ) ::   Kmm        ! ocean time level index
97      INTEGER                              , INTENT(in   ) ::   ktah, ktg, ktgi, ktt, ktt_rhs
98      REAL(wp), DIMENSION(A2D_T(ktah),   JPK)     , INTENT(in   ) ::   pahu, pahv ! eddy diffusivity at u- and v-points  [m2/s]
99      REAL(wp), DIMENSION(A2D_T(ktg),        KJPT), INTENT(in   ) ::   pgu, pgv   ! tracer gradient at pstep levels
100      REAL(wp), DIMENSION(A2D_T(ktgi),       KJPT), INTENT(in   ) ::   pgui, pgvi ! tracer gradient at top   levels
101      REAL(wp), DIMENSION(A2D_T(ktt),    JPK,KJPT), INTENT(in   ) ::   pt         ! before tracer fields
102      REAL(wp), DIMENSION(A2D_T(ktt_rhs),JPK,KJPT), INTENT(inout) ::   pt_rhs     ! tracer trend
103      !
104      INTEGER  ::   ji, jj, jk, jn      ! dummy loop indices
105      INTEGER  ::   isi, iei, isj, iej  ! local integers
106      REAL(wp) ::   zsign               ! local scalars
107      REAL(wp), DIMENSION(A2D(nn_hls),jpk) ::   ztu, ztv, zaheeu, zaheev
108      !!----------------------------------------------------------------------
109      !
110      IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile
111         IF( kt == nit000 .AND. lwp )  THEN
112            WRITE(numout,*)
113            WRITE(numout,*) 'tra_ldf_lap : iso-level laplacian diffusion on ', cdtype, ', pass=', kpass
114            WRITE(numout,*) '~~~~~~~~~~~ '
115         ENDIF
116         !
117         l_hst = .FALSE.
118         l_ptr = .FALSE.
119         IF( cdtype == 'TRA' .AND. ( iom_use( 'sophtldf' ) .OR. iom_use( 'sopstldf' ) ) )     l_ptr = .TRUE.
120         IF( cdtype == 'TRA' .AND. ( iom_use("uadv_heattr") .OR. iom_use("vadv_heattr") .OR. &
121            &                        iom_use("uadv_salttr") .OR. iom_use("vadv_salttr")  ) )  l_hst = .TRUE.
122      ENDIF
123      !
124      !                                !==  Initialization of metric arrays used for all tracers  ==!
125      IF( kpass == 1 ) THEN   ;   zsign =  1._wp      ! bilaplacian operator require a minus sign (eddy diffusivity >0)
126      ELSE                    ;   zsign = -1._wp
127      ENDIF
128
129      IF( ntsi == Nis0 ) THEN ; isi = nn_hls - 1 ; ELSE ; isi = 0 ; ENDIF    ! Avoid double-counting when using tiling
130      IF( ntsj == Njs0 ) THEN ; isj = nn_hls - 1 ; ELSE ; isj = 0 ; ENDIF
131      IF( ntei == Nie0 ) THEN ; iei = nn_hls - 1 ; ELSE ; iei = 0 ; ENDIF
132      IF( ntej == Nje0 ) THEN ; iej = nn_hls - 1 ; ELSE ; iej = 0 ; ENDIF
133
134      DO_3D( nn_hls, nn_hls-1, nn_hls, nn_hls-1, 1, jpkm1 )            !== First derivative (gradient)  ==!
135         zaheeu(ji,jj,jk) = zsign * pahu(ji,jj,jk) * e2_e1u(ji,jj) * e3u(ji,jj,jk,Kmm)   !!gm   * umask(ji,jj,jk) pah masked!
136         zaheev(ji,jj,jk) = zsign * pahv(ji,jj,jk) * e1_e2v(ji,jj) * e3v(ji,jj,jk,Kmm)   !!gm   * vmask(ji,jj,jk)
137      END_3D
138      !
139      !                             ! =========== !
140      DO jn = 1, kjpt               ! tracer loop !
141         !                          ! =========== !
142         !
143         DO_3D( nn_hls, nn_hls-1, nn_hls, nn_hls-1, 1, jpkm1 )            !== First derivative (gradient)  ==!
144            ztu(ji,jj,jk) = zaheeu(ji,jj,jk) * ( pt(ji+1,jj  ,jk,jn) - pt(ji,jj,jk,jn) )
145            ztv(ji,jj,jk) = zaheev(ji,jj,jk) * ( pt(ji  ,jj+1,jk,jn) - pt(ji,jj,jk,jn) )
146         END_3D
147         IF( ln_zps ) THEN                             ! set gradient at bottom/top ocean level
148            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 )                              ! bottom
149               ztu(ji,jj,mbku(ji,jj)) = zaheeu(ji,jj,mbku(ji,jj)) * pgu(ji,jj,jn)
150               ztv(ji,jj,mbkv(ji,jj)) = zaheev(ji,jj,mbkv(ji,jj)) * pgv(ji,jj,jn)
151            END_2D
152            IF( ln_isfcav ) THEN                             ! top in ocean cavities only
153               DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 )
154                  IF( miku(ji,jj) > 1 )   ztu(ji,jj,miku(ji,jj)) = zaheeu(ji,jj,miku(ji,jj)) * pgui(ji,jj,jn)
155                  IF( mikv(ji,jj) > 1 )   ztv(ji,jj,mikv(ji,jj)) = zaheev(ji,jj,mikv(ji,jj)) * pgvi(ji,jj,jn)
156               END_2D
157            ENDIF
158         ENDIF
159         !
160         DO_3D( isi, iei, isj, iej, 1, jpkm1 )            !== Second derivative (divergence) added to the general tracer trends  ==!
161            pt_rhs(ji,jj,jk,jn) = pt_rhs(ji,jj,jk,jn) + (  ztu(ji,jj,jk) - ztu(ji-1,jj,jk)     &
162               &                                      +    ztv(ji,jj,jk) - ztv(ji,jj-1,jk) )   &
163               &                                      / ( e1e2t(ji,jj) * e3t(ji,jj,jk,Kmm) )
164         END_3D
165         !
166         !                             !== "Poleward" diffusive heat or salt transports  ==!
167         IF( ( kpass == 1 .AND. .NOT.ln_traldf_blp ) .OR.  &     !==  first pass only (  laplacian)  ==!
168             ( kpass == 2 .AND.      ln_traldf_blp ) ) THEN      !==  2nd   pass only (bilaplacian)  ==!
169
170            IF( l_ptr )  CALL dia_ptr_hst( jn, 'ldf', -ztv(:,:,:)  )
171            IF( l_hst )  CALL dia_ar5_hst( jn, 'ldf', -ztu(:,:,:), -ztv(:,:,:) )
172         ENDIF
173         !                          ! ==================
174      END DO                        ! end of tracer loop
175      !                             ! ==================
176      !
177   END SUBROUTINE tra_ldf_lap_t
178
179
180   SUBROUTINE tra_ldf_blp( kt, Kmm, kit000, cdtype, pahu, pahv  ,             &
181      &                                             pgu , pgv   , pgui, pgvi, &
182      &                                             pt  , pt_rhs, kjpt, kldf )
183      !!----------------------------------------------------------------------
184      !!                 ***  ROUTINE tra_ldf_blp  ***
185      !!
186      !! ** Purpose :   Compute the before lateral tracer diffusive
187      !!      trend and add it to the general trend of tracer equation.
188      !!
189      !! ** Method  :   The lateral diffusive trends is provided by a bilaplacian
190      !!      operator applied to before field (forward in time).
191      !!      It is computed by two successive calls to laplacian routine
192      !!
193      !! ** Action :   pta   updated with the before rotated bilaplacian diffusion
194      !!----------------------------------------------------------------------
195      INTEGER                              , INTENT(in   ) ::   kt         ! ocean time-step index
196      INTEGER                              , INTENT(in   ) ::   kit000     ! first time step index
197      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype     ! =TRA or TRC (tracer indicator)
198      INTEGER                              , INTENT(in   ) ::   kjpt       ! number of tracers
199      INTEGER                              , INTENT(in   ) ::   kldf       ! type of operator used
200      INTEGER                              , INTENT(in   ) ::   Kmm        ! ocean time level indices
201      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   pahu, pahv ! eddy diffusivity at u- and v-points  [m2/s]
202      REAL(wp), DIMENSION(jpi,jpj    ,kjpt), INTENT(in   ) ::   pgu, pgv   ! tracer gradient at pstep levels
203      REAL(wp), DIMENSION(jpi,jpj,    kjpt), INTENT(in   ) ::   pgui, pgvi ! tracer gradient at top levels
204      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   pt         ! before and now tracer fields
205      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pt_rhs     ! tracer trend
206      !
207      INTEGER ::   ji, jj, jk, jn   ! dummy loop indices
208      REAL(wp), DIMENSION(A2D(nn_hls),jpk,kjpt) :: zlap         ! laplacian at t-point
209      REAL(wp), DIMENSION(A2D(nn_hls),    kjpt) :: zglu, zglv   ! bottom GRADh of the laplacian (u- and v-points)
210      REAL(wp), DIMENSION(A2D(nn_hls),    kjpt) :: zgui, zgvi   ! top    GRADh of the laplacian (u- and v-points)
211      !!---------------------------------------------------------------------
212      !
213      IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile
214         IF( kt == kit000 .AND. lwp )  THEN
215            WRITE(numout,*)
216            SELECT CASE ( kldf )
217            CASE ( np_blp    )   ;   WRITE(numout,*) 'tra_ldf_blp : iso-level   bilaplacian operator on ', cdtype
218            CASE ( np_blp_i  )   ;   WRITE(numout,*) 'tra_ldf_blp : iso-neutral bilaplacian operator on ', cdtype, ' (Standard)'
219            CASE ( np_blp_it )   ;   WRITE(numout,*) 'tra_ldf_blp : iso-neutral bilaplacian operator on ', cdtype, ' (triad)'
220            END SELECT
221            WRITE(numout,*) '~~~~~~~~~~~'
222         ENDIF
223      ENDIF
224
225      zlap(:,:,:,:) = 0._wp
226      !
227      SELECT CASE ( kldf )       !==  1st laplacian applied to pt (output in zlap)  ==!
228      !
229      CASE ( np_blp    )               ! iso-level bilaplacian
230         CALL tra_ldf_lap  ( kt, Kmm, kit000, cdtype, pahu, pahv, pgu, pgv, pgui, pgvi, pt,     zlap, kjpt, 1 )
231      CASE ( np_blp_i  )               ! rotated   bilaplacian : standard operator (Madec)
232         CALL tra_ldf_iso  ( kt, Kmm, kit000, cdtype, pahu, pahv, pgu, pgv, pgui, pgvi, pt, pt, zlap, kjpt, 1 )
233      CASE ( np_blp_it )               ! rotated  bilaplacian : triad operator (griffies)
234         CALL tra_ldf_triad( kt, Kmm, kit000, cdtype, pahu, pahv, pgu, pgv, pgui, pgvi, pt, pt, zlap, kjpt, 1 )
235      END SELECT
236      !
237      CALL lbc_lnk( 'traldf_lap_blp', zlap(:,:,:,:) , 'T', 1.0_wp )     ! Lateral boundary conditions (unchanged sign)
238      !                                               ! Partial top/bottom cell: GRADh( zlap )
239      IF( ln_isfcav .AND. ln_zps ) THEN   ;   CALL zps_hde_isf( kt, Kmm, kjpt, zlap, zglu, zglv, zgui, zgvi )  ! both top & bottom
240      ELSEIF(             ln_zps ) THEN   ;   CALL zps_hde    ( kt, Kmm, kjpt, zlap, zglu, zglv )              ! only bottom
241      ENDIF
242      !
243      SELECT CASE ( kldf )       !==  2nd laplacian applied to zlap (output in pt_rhs)  ==!
244      !
245      CASE ( np_blp    )               ! iso-level bilaplacian
246         CALL tra_ldf_lap  ( kt, Kmm, kit000, cdtype, pahu, pahv, zglu, zglv, zgui, zgvi, zlap, pt_rhs,         kjpt, 2 )
247      CASE ( np_blp_i  )               ! rotated   bilaplacian : standard operator (Madec)
248         CALL tra_ldf_iso  ( kt, Kmm, kit000, cdtype, pahu, pahv, zglu, zglv, zgui, zgvi, zlap, pt    , pt_rhs, kjpt, 2 )
249      CASE ( np_blp_it )               ! rotated  bilaplacian : triad operator (griffies)
250         CALL tra_ldf_triad( kt, Kmm, kit000, cdtype, pahu, pahv, zglu, zglv, zgui, zgvi, zlap, pt    , pt_rhs, kjpt, 2 )
251      END SELECT
252      !
253   END SUBROUTINE tra_ldf_blp
254
255   !!==============================================================================
256END MODULE traldf_lap_blp
Note: See TracBrowser for help on using the repository browser.