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_iso.F90 in branches/UKMO/dev_r5518_GO6_package_XIOS_read/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/UKMO/dev_r5518_GO6_package_XIOS_read/NEMOGCM/NEMO/OPA_SRC/TRA/traldf_iso.F90 @ 7923

Last change on this file since 7923 was 7923, checked in by andmirek, 7 years ago

merge changes up to 7573

File size: 19.1 KB
Line 
1MODULE traldf_iso
2   !!======================================================================
3   !!                   ***  MODULE  traldf_iso  ***
4   !! Ocean  tracers:  horizontal component of the lateral tracer mixing trend
5   !!======================================================================
6   !! History :  OPA  !  1994-08  (G. Madec, M. Imbard)
7   !!            8.0  !  1997-05  (G. Madec)  split into traldf and trazdf
8   !!            NEMO !  2002-08  (G. Madec)  Free form, F90
9   !!            1.0  !  2005-11  (G. Madec)  merge traldf and trazdf :-)
10   !!            3.3  !  2010-09  (C. Ethe, G. Madec) Merge TRA-TRC
11   !!----------------------------------------------------------------------
12#if   defined key_ldfslp   ||   defined key_esopa
13   !!----------------------------------------------------------------------
14   !!   'key_ldfslp'               slope of the lateral diffusive direction
15   !!----------------------------------------------------------------------
16   !!   tra_ldf_iso  : update the tracer trend with the horizontal
17   !!                  component of a iso-neutral laplacian operator
18   !!                  and with the vertical part of
19   !!                  the isopycnal or geopotential s-coord. operator
20   !!----------------------------------------------------------------------
21   USE oce             ! ocean dynamics and active tracers
22   USE dom_oce         ! ocean space and time domain
23   USE trc_oce         ! share passive tracers/Ocean variables
24   USE zdf_oce         ! ocean vertical physics
25   USE ldftra_oce      ! ocean active tracers: lateral physics
26   USE ldfslp          ! iso-neutral slopes
27   USE diaptr          ! poleward transport diagnostics
28   USE trd_oce         ! trends: ocean variables
29   USE trdtra          ! trends manager: tracers
30   USE in_out_manager  ! I/O manager
31   USE iom             ! I/O library
32   USE phycst          ! physical constants
33   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
34   USE wrk_nemo        ! Memory Allocation
35   USE timing          ! Timing
36
37   IMPLICIT NONE
38   PRIVATE
39
40   PUBLIC   tra_ldf_iso   ! routine called by step.F90
41
42   !! * Substitutions
43#  include "domzgr_substitute.h90"
44#  include "ldftra_substitute.h90"
45#  include "vectopt_loop_substitute.h90"
46   !!----------------------------------------------------------------------
47   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
48   !! $Id$
49   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
50   !!----------------------------------------------------------------------
51CONTAINS
52
53   SUBROUTINE tra_ldf_iso( kt, kit000, cdtype, pgu, pgv,              &
54      &                                pgui, pgvi,                    &
55      &                                ptb, pta, kjpt, pahtb0 )
56      !!----------------------------------------------------------------------
57      !!                  ***  ROUTINE tra_ldf_iso  ***
58      !!
59      !! ** Purpose :   Compute the before horizontal tracer (t & s) diffusive
60      !!      trend for a laplacian tensor (ezxcept the dz[ dz[.] ] term) and
61      !!      add it to the general trend of tracer equation.
62      !!
63      !! ** Method  :   The horizontal component of the lateral diffusive trends
64      !!      is provided by a 2nd order operator rotated along neural or geopo-
65      !!      tential surfaces to which an eddy induced advection can be added
66      !!      It is computed using before fields (forward in time) and isopyc-
67      !!      nal or geopotential slopes computed in routine ldfslp.
68      !!
69      !!      1st part :  masked horizontal derivative of T  ( di[ t ] )
70      !!      ========    with partial cell update if ln_zps=T.
71      !!
72      !!      2nd part :  horizontal fluxes of the lateral mixing operator
73      !!      ========   
74      !!         zftu = (aht+ahtb0) e2u*e3u/e1u di[ tb ]
75      !!               - aht       e2u*uslp    dk[ mi(mk(tb)) ]
76      !!         zftv = (aht+ahtb0) e1v*e3v/e2v dj[ tb ]
77      !!               - aht       e2u*vslp    dk[ mj(mk(tb)) ]
78      !!      take the horizontal divergence of the fluxes:
79      !!         difft = 1/(e1t*e2t*e3t) {  di-1[ zftu ] +  dj-1[ zftv ]  }
80      !!      Add this trend to the general trend (ta,sa):
81      !!         ta = ta + difft
82      !!
83      !!      3rd part: vertical trends of the lateral mixing operator
84      !!      ========  (excluding the vertical flux proportional to dk[t] )
85      !!      vertical fluxes associated with the rotated lateral mixing:
86      !!         zftw =-aht {  e2t*wslpi di[ mi(mk(tb)) ]
87      !!                     + e1t*wslpj dj[ mj(mk(tb)) ]  }
88      !!      take the horizontal divergence of the fluxes:
89      !!         difft = 1/(e1t*e2t*e3t) dk[ zftw ]
90      !!      Add this trend to the general trend (ta,sa):
91      !!         pta = pta + difft
92      !!
93      !! ** Action :   Update pta arrays with the before rotated diffusion
94      !!----------------------------------------------------------------------
95      USE oce     , ONLY:   zftu => ua       , zftv  => va         ! (ua,va) used as workspace
96      !
97      INTEGER                              , INTENT(in   ) ::   kt         ! ocean time-step index
98      INTEGER                              , INTENT(in   ) ::   kit000          ! first time step index
99      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype     ! =TRA or TRC (tracer indicator)
100      INTEGER                              , INTENT(in   ) ::   kjpt       ! number of tracers
101      REAL(wp), DIMENSION(jpi,jpj    ,kjpt), INTENT(in   ) ::   pgu , pgv    ! tracer gradient at pstep levels
102      REAL(wp), DIMENSION(jpi,jpj    ,kjpt), INTENT(in   ) ::   pgui, pgvi   ! tracer gradient at pstep levels
103      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb        ! before and now tracer fields
104      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pta        ! tracer trend
105      REAL(wp)                             , INTENT(in   ) ::   pahtb0     ! background diffusion coef
106      !
107      INTEGER  ::  ji, jj, jk, jn   ! dummy loop indices
108      INTEGER  ::  ikt
109      REAL(wp) ::  zmsku, zabe1, zcof1, zcoef3       ! local scalars
110      REAL(wp) ::  zmskv, zabe2, zcof2, zcoef4       !   -      -
111      REAL(wp) ::  zcoef0, zbtr                      !   -      -
112      REAL(wp), POINTER, DIMENSION(:,:  ) ::  z2d
113      REAL(wp), POINTER, DIMENSION(:,:,:) ::  zdkt, zdk1t, zdit, zdjt, ztfw 
114      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::  ztrax, ztray, ztraz 
115      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:), TARGET ::  ztrax_T, ztray_T, ztraz_T
116      !!----------------------------------------------------------------------
117      !
118      IF( nn_timing == 1 )  CALL timing_start('tra_ldf_iso')
119      !
120      CALL wrk_alloc( jpi, jpj,      z2d ) 
121      CALL wrk_alloc( jpi, jpj, jpk, zdit, zdjt, ztfw, zdkt, zdk1t) 
122      ALLOCATE( ztrax(jpi,jpj,jpk), ztray(jpi,jpj,jpk), ztraz(jpi,jpj,jpk) ) 
123      IF( l_trdtra .and. cdtype == 'TRA' ) ALLOCATE( ztrax_T(jpi,jpj,jpk), ztray_T(jpi,jpj,jpk), ztraz_T(jpi,jpj,jpk) ) 
124      !
125
126      IF( kt == kit000 )  THEN
127         IF(lwp) WRITE(numout,*)
128         IF(lwp) WRITE(numout,*) 'tra_ldf_iso : rotated laplacian diffusion operator on ', cdtype
129         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
130      ENDIF
131      !
132      !                                                          ! ===========
133      DO jn = 1, kjpt                                            ! tracer loop
134         !                                                       ! ===========
135         ztrax(:,:,:) = 0._wp ; ztray(:,:,:) = 0._wp ; ztraz(:,:,:) = 0._wp ; 
136         !                                               
137         !!----------------------------------------------------------------------
138         !!   I - masked horizontal derivative
139         !!----------------------------------------------------------------------
140         !!bug ajout.... why?   ( 1,jpj,:) and (jpi,1,:) should be sufficient....
141         zdit (1,:,:) = 0.e0     ;     zdit (jpi,:,:) = 0.e0
142         zdjt (1,:,:) = 0.e0     ;     zdjt (jpi,:,:) = 0.e0
143         !!end
144
145         ! Horizontal tracer gradient
146         DO jk = 1, jpkm1
147            DO jj = 1, jpjm1
148               DO ji = 1, fs_jpim1   ! vector opt.
149                  zdit(ji,jj,jk) = ( ptb(ji+1,jj  ,jk,jn) - ptb(ji,jj,jk,jn) ) * umask(ji,jj,jk)
150                  zdjt(ji,jj,jk) = ( ptb(ji  ,jj+1,jk,jn) - ptb(ji,jj,jk,jn) ) * vmask(ji,jj,jk)
151               END DO
152            END DO
153         END DO
154
155         ! partial cell correction
156         IF( ln_zps ) THEN      ! partial steps correction at the last ocean level
157            DO jj = 1, jpjm1
158               DO ji = 1, fs_jpim1   ! vector opt.
159! IF useless if zpshde defines pgu everywhere
160                  zdit(ji,jj,mbku(ji,jj)) = pgu(ji,jj,jn)         
161                  zdjt(ji,jj,mbkv(ji,jj)) = pgv(ji,jj,jn)
162               END DO
163            END DO
164         ENDIF
165         IF( ln_zps .AND. ln_isfcav ) THEN      ! partial steps correction at the first wet level beneath a cavity
166            DO jj = 1, jpjm1
167               DO ji = 1, fs_jpim1   ! vector opt.
168                  IF (miku(ji,jj) > 1) zdit(ji,jj,miku(ji,jj)) = pgui(ji,jj,jn)         
169                  IF (mikv(ji,jj) > 1) zdjt(ji,jj,mikv(ji,jj)) = pgvi(ji,jj,jn)     
170               END DO
171            END DO
172         END IF
173
174         !!----------------------------------------------------------------------
175         !!   II - horizontal trend  (full)
176         !!----------------------------------------------------------------------
177!!!!!!!!!!CDIR PARALLEL DO PRIVATE( zdk1t )
178            ! 1. Vertical tracer gradient at level jk and jk+1
179            ! ------------------------------------------------
180         !
181         ! interior value
182         DO jk = 2, jpkm1               
183            DO jj = 1, jpj
184               DO ji = 1, jpi   ! vector opt.
185                  zdk1t(ji,jj,jk) = ( ptb(ji,jj,jk,jn  ) - ptb(ji,jj,jk+1,jn) ) * wmask(ji,jj,jk+1)
186                  !
187                  zdkt(ji,jj,jk)  = ( ptb(ji,jj,jk-1,jn) - ptb(ji,jj,jk,jn  ) ) * wmask(ji,jj,jk)
188               END DO
189            END DO
190         END DO
191         ! surface boundary condition: zdkt(jk=1)=zdkt(jk=2)
192         zdk1t(:,:,1) = ( ptb(:,:,1,jn  ) - ptb(:,:,2,jn) ) * wmask(:,:,2)
193         zdkt (:,:,1) = zdk1t(:,:,1)
194         IF ( ln_isfcav ) THEN
195            DO jj = 1, jpj
196               DO ji = 1, jpi   ! vector opt.
197                  ikt = mikt(ji,jj) ! surface level
198                  zdk1t(ji,jj,ikt) = ( ptb(ji,jj,ikt,jn  ) - ptb(ji,jj,ikt+1,jn) ) * wmask(ji,jj,ikt+1)
199                  zdkt (ji,jj,ikt) = zdk1t(ji,jj,ikt)
200               END DO
201            END DO
202         END IF
203
204         ! 2. Horizontal fluxes
205         ! --------------------   
206         DO jk = 1, jpkm1
207            DO jj = 1 , jpjm1
208               DO ji = 1, fs_jpim1   ! vector opt.
209                  zabe1 = ( fsahtu(ji,jj,jk) + pahtb0 ) * re2u_e1u(ji,jj) * fse3u_n(ji,jj,jk)
210                  zabe2 = ( fsahtv(ji,jj,jk) + pahtb0 ) * re1v_e2v(ji,jj) * fse3v_n(ji,jj,jk)
211                  !
212                  zmsku = 1. / MAX(  tmask(ji+1,jj,jk  ) + tmask(ji,jj,jk+1)   &
213                     &             + tmask(ji+1,jj,jk+1) + tmask(ji,jj,jk  ), 1. )
214                  !
215                  zmskv = 1. / MAX(  tmask(ji,jj+1,jk  ) + tmask(ji,jj,jk+1)   &
216                     &             + tmask(ji,jj+1,jk+1) + tmask(ji,jj,jk  ), 1. )
217                  !
218                  zcof1 = - fsahtu(ji,jj,jk) * e2u(ji,jj) * uslp(ji,jj,jk) * zmsku
219                  zcof2 = - fsahtv(ji,jj,jk) * e1v(ji,jj) * vslp(ji,jj,jk) * zmskv
220                  !
221                  zftu(ji,jj,jk ) = (  zabe1 * zdit(ji,jj,jk)   &
222                     &              + zcof1 * (  zdkt (ji+1,jj,jk) + zdk1t(ji,jj,jk)      &
223                     &                         + zdk1t(ji+1,jj,jk) + zdkt (ji,jj,jk)  )  ) * umask(ji,jj,jk)
224                  zftv(ji,jj,jk) = (  zabe2 * zdjt(ji,jj,jk)   &
225                     &              + zcof2 * (  zdkt (ji,jj+1,jk) + zdk1t(ji,jj,jk)      &
226                     &                         + zdk1t(ji,jj+1,jk) + zdkt (ji,jj,jk)  )  ) * vmask(ji,jj,jk)                 
227               END DO
228            END DO
229
230            ! II.4 Second derivative (divergence) and add to the general trend
231            ! ----------------------------------------------------------------
232            DO jj = 2 , jpjm1
233               DO ji = fs_2, fs_jpim1   ! vector opt.
234                  zbtr = 1.0 / ( e12t(ji,jj) * fse3t_n(ji,jj,jk) )
235                  ztrax(ji,jj,jk) = zbtr * ( zftu(ji,jj,jk) - zftu(ji-1,jj,jk) )
236                  ztray(ji,jj,jk) = zbtr * ( zftv(ji,jj,jk) - zftv(ji,jj-1,jk) )
237               END DO
238            END DO
239            !                                          ! ===============
240         END DO                                        !   End of slab 
241         !                                             ! ===============
242         !
243         pta(:,:,:,jn) = pta(:,:,:,jn) + ztrax(:,:,:) + ztray(:,:,:)
244         !
245         ! "Poleward" diffusive heat or salt transports (T-S case only)
246            ! note sign is reversed to give down-gradient diffusive transports (#1043)
247         IF( cdtype == 'TRA' .AND. ln_diaptr ) CALL dia_ptr_ohst_components( jn, 'ldf', -zftv(:,:,:)  )
248 
249         IF( iom_use("udiff_heattr") .OR. iom_use("vdiff_heattr") ) THEN
250           !
251           IF( cdtype == 'TRA' .AND. jn == jp_tem  ) THEN
252               z2d(:,:) = 0._wp 
253               DO jk = 1, jpkm1
254                  DO jj = 2, jpjm1
255                     DO ji = fs_2, fs_jpim1   ! vector opt.
256                        z2d(ji,jj) = z2d(ji,jj) + zftu(ji,jj,jk) 
257                     END DO
258                  END DO
259               END DO
260               z2d(:,:) = - rau0_rcp * z2d(:,:)     ! note sign is reversed to give down-gradient diffusive transports (#1043)
261               CALL lbc_lnk( z2d, 'U', -1. )
262               CALL iom_put( "udiff_heattr", z2d )                  ! heat transport in i-direction
263               !
264               z2d(:,:) = 0._wp 
265               DO jk = 1, jpkm1
266                  DO jj = 2, jpjm1
267                     DO ji = fs_2, fs_jpim1   ! vector opt.
268                        z2d(ji,jj) = z2d(ji,jj) + zftv(ji,jj,jk) 
269                     END DO
270                  END DO
271               END DO
272               z2d(:,:) = - rau0_rcp * z2d(:,:)     ! note sign is reversed to give down-gradient diffusive transports (#1043)
273               CALL lbc_lnk( z2d, 'V', -1. )
274               CALL iom_put( "vdiff_heattr", z2d )                  !  heat transport in i-direction
275            END IF
276            !
277         ENDIF
278
279         !!----------------------------------------------------------------------
280         !!   III - vertical trend of T & S (extra diagonal terms only)
281         !!----------------------------------------------------------------------
282         
283         ! Local constant initialization
284         ! -----------------------------
285         ztfw(1,:,:) = 0.e0     ;     ztfw(jpi,:,:) = 0.e0
286         
287         ! Vertical fluxes
288         ! ---------------
289         
290         ! Surface and bottom vertical fluxes set to zero
291         ztfw(:,:, 1 ) = 0.e0      ;      ztfw(:,:,jpk) = 0.e0
292         
293         ! interior (2=<jk=<jpk-1)
294         DO jk = 2, jpkm1
295            DO jj = 2, jpjm1
296               DO ji = fs_2, fs_jpim1   ! vector opt.
297                  zcoef0 = - fsahtw(ji,jj,jk) * wmask(ji,jj,jk)
298                  !
299                  zmsku = 1./MAX(   umask(ji  ,jj,jk-1) + umask(ji-1,jj,jk)      &
300                     &            + umask(ji-1,jj,jk-1) + umask(ji  ,jj,jk), 1.  )
301                  zmskv = 1./MAX(   vmask(ji,jj  ,jk-1) + vmask(ji,jj-1,jk)      &
302                     &            + vmask(ji,jj-1,jk-1) + vmask(ji,jj  ,jk), 1.  )
303                  !
304                  zcoef3 = zcoef0 * e2t(ji,jj) * zmsku * wslpi (ji,jj,jk)
305                  zcoef4 = zcoef0 * e1t(ji,jj) * zmskv * wslpj (ji,jj,jk)
306                  !
307                  ztfw(ji,jj,jk) = zcoef3 * (   zdit(ji  ,jj  ,jk-1) + zdit(ji-1,jj  ,jk)      &
308                     &                        + zdit(ji-1,jj  ,jk-1) + zdit(ji  ,jj  ,jk)  )   &
309                     &           + zcoef4 * (   zdjt(ji  ,jj  ,jk-1) + zdjt(ji  ,jj-1,jk)      &
310                     &                        + zdjt(ji  ,jj-1,jk-1) + zdjt(ji  ,jj  ,jk)  )
311               END DO
312            END DO
313         END DO
314         
315         
316         ! I.5 Divergence of vertical fluxes added to the general tracer trend
317         ! -------------------------------------------------------------------
318         DO jk = 1, jpkm1
319            DO jj = 2, jpjm1
320               DO ji = fs_2, fs_jpim1   ! vector opt.
321                  zbtr = 1.0 / ( e12t(ji,jj) * fse3t_n(ji,jj,jk) )
322                  ztraz(ji,jj,jk) = (  ztfw(ji,jj,jk) - ztfw(ji,jj,jk+1)  ) * zbtr
323               END DO
324            END DO
325         END DO
326         pta(:,:,:,jn) = pta(:,:,:,jn) + ztraz(:,:,:)
327         !
328         IF( l_trdtra .AND. cdtype == "TRA" .AND. jn .eq. 1 )  THEN      ! save the temperature trends
329            ztrax_T(:,:,:) = ztrax(:,:,:)
330            ztray_T(:,:,:) = ztray(:,:,:)
331            ztraz_T(:,:,:) = ztraz(:,:,:)
332         ENDIF
333         IF( l_trdtrc .AND. cdtype == "TRC" )   THEN      ! save the horizontal component of diffusive trends for further diagnostics
334            CALL trd_tra( kt, cdtype, jn, jptra_iso_x, ztrax )
335            CALL trd_tra( kt, cdtype, jn, jptra_iso_y, ztray ) 
336            CALL trd_tra( kt, cdtype, jn, jptra_iso_z1, ztraz )  ! This is the first part of the vertical component.
337         ENDIF
338      END DO
339      !
340      IF( l_trdtra .AND. cdtype == "TRA" )   THEN      ! save the horizontal component of diffusive trends for further diagnostics
341         CALL trd_tra( kt, cdtype, jp_tem, jptra_iso_x, ztrax_T )
342         CALL trd_tra( kt, cdtype, jp_sal, jptra_iso_x, ztrax )
343         CALL trd_tra( kt, cdtype, jp_tem, jptra_iso_y, ztray_T )
344         CALL trd_tra( kt, cdtype, jp_sal, jptra_iso_y, ztray )
345         CALL trd_tra( kt, cdtype, jp_tem, jptra_iso_z1, ztraz_T )  ! This is the first part of the vertical component
346         CALL trd_tra( kt, cdtype, jp_sal, jptra_iso_z1, ztraz )    !
347      ENDIF
348      !
349      CALL wrk_dealloc( jpi, jpj, z2d ) 
350      CALL wrk_dealloc( jpi, jpj, jpk, zdit, zdjt, ztfw, zdkt, zdk1t ) 
351      DEALLOCATE( ztrax, ztray, ztraz ) 
352      IF( l_trdtra  .and. cdtype == 'TRA' ) DEALLOCATE( ztrax_T, ztray_T, ztraz_T ) 
353      !
354      IF( nn_timing == 1 )  CALL timing_stop('tra_ldf_iso')
355      !
356   END SUBROUTINE tra_ldf_iso
357
358#else
359   !!----------------------------------------------------------------------
360   !!   default option :   Dummy code   NO rotation of the diffusive tensor
361   !!----------------------------------------------------------------------
362CONTAINS
363   SUBROUTINE tra_ldf_iso( kt, kit000,cdtype, pgu, pgv, pgui, pgvi, ptb, pta, kjpt, pahtb0 )      ! Empty routine
364      INTEGER:: kt, kit000
365      CHARACTER(len=3) ::   cdtype
366      REAL, DIMENSION(:,:,:) ::   pgu, pgv, pgui, pgvi    ! tracer gradient at pstep levels
367      REAL, DIMENSION(:,:,:,:) ::   ptb, pta
368      WRITE(*,*) 'tra_ldf_iso: You should not have seen this print! error?', kt, kit000, cdtype,   &
369         &                       pgu(1,1,1), pgv(1,1,1), ptb(1,1,1,1), pta(1,1,1,1), kjpt, pahtb0
370   END SUBROUTINE tra_ldf_iso
371#endif
372
373   !!==============================================================================
374END MODULE traldf_iso
Note: See TracBrowser for help on using the repository browser.