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 trunk/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/TRA/traldf_iso.F90 @ 2528

Last change on this file since 2528 was 2528, checked in by rblod, 13 years ago

Update NEMOGCM from branch nemo_v3_3_beta

  • Property svn:keywords set to Id
File size: 15.5 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 in_out_manager  ! I/O manager
29   USE iom             ! I/O library
30#if defined key_diaar5
31   USE phycst          ! physical constants
32   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
33#endif
34
35   IMPLICIT NONE
36   PRIVATE
37
38   PUBLIC   tra_ldf_iso   ! routine called by step.F90
39
40   !! * Substitutions
41#  include "domzgr_substitute.h90"
42#  include "ldftra_substitute.h90"
43#  include "vectopt_loop_substitute.h90"
44   !!----------------------------------------------------------------------
45   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
46   !! $Id$
47   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
48   !!----------------------------------------------------------------------
49CONTAINS
50
51   SUBROUTINE tra_ldf_iso( kt, cdtype, pgu, pgv,              &
52      &                                ptb, pta, kjpt, pahtb0 )
53      !!----------------------------------------------------------------------
54      !!                  ***  ROUTINE tra_ldf_iso  ***
55      !!
56      !! ** Purpose :   Compute the before horizontal tracer (t & s) diffusive
57      !!      trend for a laplacian tensor (ezxcept the dz[ dz[.] ] term) and
58      !!      add it to the general trend of tracer equation.
59      !!
60      !! ** Method  :   The horizontal component of the lateral diffusive trends
61      !!      is provided by a 2nd order operator rotated along neural or geopo-
62      !!      tential surfaces to which an eddy induced advection can be added
63      !!      It is computed using before fields (forward in time) and isopyc-
64      !!      nal or geopotential slopes computed in routine ldfslp.
65      !!
66      !!      1st part :  masked horizontal derivative of T  ( di[ t ] )
67      !!      ========    with partial cell update if ln_zps=T.
68      !!
69      !!      2nd part :  horizontal fluxes of the lateral mixing operator
70      !!      ========   
71      !!         zftu = (aht+ahtb0) e2u*e3u/e1u di[ tb ]
72      !!               - aht       e2u*uslp    dk[ mi(mk(tb)) ]
73      !!         zftv = (aht+ahtb0) e1v*e3v/e2v dj[ tb ]
74      !!               - aht       e2u*vslp    dk[ mj(mk(tb)) ]
75      !!      take the horizontal divergence of the fluxes:
76      !!         difft = 1/(e1t*e2t*e3t) {  di-1[ zftu ] +  dj-1[ zftv ]  }
77      !!      Add this trend to the general trend (ta,sa):
78      !!         ta = ta + difft
79      !!
80      !!      3rd part: vertical trends of the lateral mixing operator
81      !!      ========  (excluding the vertical flux proportional to dk[t] )
82      !!      vertical fluxes associated with the rotated lateral mixing:
83      !!         zftw =-aht {  e2t*wslpi di[ mi(mk(tb)) ]
84      !!                     + e1t*wslpj dj[ mj(mk(tb)) ]  }
85      !!      take the horizontal divergence of the fluxes:
86      !!         difft = 1/(e1t*e2t*e3t) dk[ zftw ]
87      !!      Add this trend to the general trend (ta,sa):
88      !!         pta = pta + difft
89      !!
90      !! ** Action :   Update pta arrays with the before rotated diffusion
91      !!----------------------------------------------------------------------
92      USE oce         , zftu => ua   ! use ua as workspace
93      USE oce         , zftv => va   ! use va as workspace
94      !!
95      INTEGER                              , INTENT(in   ) ::   kt         ! ocean time-step index
96      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype     ! =TRA or TRC (tracer indicator)
97      INTEGER                              , INTENT(in   ) ::   kjpt       ! number of tracers
98      REAL(wp), DIMENSION(jpi,jpj    ,kjpt), INTENT(in   ) ::   pgu, pgv   ! tracer gradient at pstep levels
99      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb        ! before and now tracer fields
100      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pta        ! tracer trend
101      REAL(wp)                             , INTENT(in   ) ::   pahtb0     ! background diffusion coef
102      !!
103      INTEGER  ::  ji, jj, jk, jn   ! dummy loop indices
104      REAL(wp) ::  zmsku, zabe1, zcof1, zcoef3   ! local scalars
105      REAL(wp) ::  zmskv, zabe2, zcof2, zcoef4   !   -      -
106      REAL(wp) ::  zcoef0, zbtr, ztra            !   -      -
107      REAL(wp), DIMENSION(jpi,jpj)     ::   zdkt, zdk1t         ! 2D workspace
108      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zdit, zdjt, ztfw    ! 3D workspace
109#if defined key_diaar5
110      REAL(wp), DIMENSION(jpi,jpj)     ::   z2d                 ! 2D workspace
111      REAL(wp)                         ::   zztmp               ! local scalar
112#endif
113      !!----------------------------------------------------------------------
114
115      IF( kt == nit000 )  THEN
116         IF(lwp) WRITE(numout,*)
117         IF(lwp) WRITE(numout,*) 'tra_ldf_iso : rotated laplacian diffusion operator on ', cdtype
118         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
119      ENDIF
120      !
121      !                                                          ! ===========
122      DO jn = 1, kjpt                                            ! tracer loop
123         !                                                       ! ===========
124         !                                               
125         !!----------------------------------------------------------------------
126         !!   I - masked horizontal derivative
127         !!----------------------------------------------------------------------
128         !!bug ajout.... why?   ( 1,jpj,:) and (jpi,1,:) should be sufficient....
129         zdit (1,:,:) = 0.e0     ;     zdit (jpi,:,:) = 0.e0
130         zdjt (1,:,:) = 0.e0     ;     zdjt (jpi,:,:) = 0.e0
131         !!end
132
133         ! Horizontal tracer gradient
134         DO jk = 1, jpkm1
135            DO jj = 1, jpjm1
136               DO ji = 1, fs_jpim1   ! vector opt.
137                  zdit(ji,jj,jk) = ( ptb(ji+1,jj  ,jk,jn) - ptb(ji,jj,jk,jn) ) * umask(ji,jj,jk)
138                  zdjt(ji,jj,jk) = ( ptb(ji  ,jj+1,jk,jn) - ptb(ji,jj,jk,jn) ) * vmask(ji,jj,jk)
139               END DO
140            END DO
141         END DO
142         IF( ln_zps ) THEN      ! partial steps correction at the last ocean level
143            DO jj = 1, jpjm1
144               DO ji = 1, fs_jpim1   ! vector opt.
145                  zdit(ji,jj,mbku(ji,jj)) = pgu(ji,jj,jn)         
146                  zdjt(ji,jj,mbkv(ji,jj)) = pgv(ji,jj,jn)     
147               END DO
148            END DO
149         ENDIF
150
151         !!----------------------------------------------------------------------
152         !!   II - horizontal trend  (full)
153         !!----------------------------------------------------------------------
154!CDIR PARALLEL DO PRIVATE( zdk1t )
155         !                                                ! ===============
156         DO jk = 1, jpkm1                                 ! Horizontal slab
157            !                                             ! ===============
158            ! 1. Vertical tracer gradient at level jk and jk+1
159            ! ------------------------------------------------
160            ! surface boundary condition: zdkt(jk=1)=zdkt(jk=2)
161            zdk1t(:,:) = ( ptb(:,:,jk,jn) - ptb(:,:,jk+1,jn) ) * tmask(:,:,jk+1)
162            !
163            IF( jk == 1 ) THEN   ;   zdkt(:,:) = zdk1t(:,:)
164            ELSE                 ;   zdkt(:,:) = ( ptb(:,:,jk-1,jn) - ptb(:,:,jk,jn) ) * tmask(:,:,jk)
165            ENDIF
166
167            ! 2. Horizontal fluxes
168            ! --------------------   
169            DO jj = 1 , jpjm1
170               DO ji = 1, fs_jpim1   ! vector opt.
171                  zabe1 = ( fsahtu(ji,jj,jk) + pahtb0 ) * e2u(ji,jj) * fse3u(ji,jj,jk) / e1u(ji,jj)
172                  zabe2 = ( fsahtv(ji,jj,jk) + pahtb0 ) * e1v(ji,jj) * fse3v(ji,jj,jk) / e2v(ji,jj)
173                  !
174                  zmsku = 1. / MAX(  tmask(ji+1,jj,jk  ) + tmask(ji,jj,jk+1)   &
175                     &             + tmask(ji+1,jj,jk+1) + tmask(ji,jj,jk  ), 1. )
176                  !
177                  zmskv = 1. / MAX(  tmask(ji,jj+1,jk  ) + tmask(ji,jj,jk+1)   &
178                     &             + tmask(ji,jj+1,jk+1) + tmask(ji,jj,jk  ), 1. )
179                  !
180                  zcof1 = - fsahtu(ji,jj,jk) * e2u(ji,jj) * uslp(ji,jj,jk) * zmsku
181                  zcof2 = - fsahtv(ji,jj,jk) * e1v(ji,jj) * vslp(ji,jj,jk) * zmskv
182                  !
183                  zftu(ji,jj,jk ) = (  zabe1 * zdit(ji,jj,jk)   &
184                     &              + zcof1 * (  zdkt (ji+1,jj) + zdk1t(ji,jj)      &
185                     &                         + zdk1t(ji+1,jj) + zdkt (ji,jj)  )  ) * umask(ji,jj,jk)
186                  zftv(ji,jj,jk) = (  zabe2 * zdjt(ji,jj,jk)   &
187                     &              + zcof2 * (  zdkt (ji,jj+1) + zdk1t(ji,jj)      &
188                     &                         + zdk1t(ji,jj+1) + zdkt (ji,jj)  )  ) * vmask(ji,jj,jk)                 
189               END DO
190            END DO
191
192            ! II.4 Second derivative (divergence) and add to the general trend
193            ! ----------------------------------------------------------------
194            DO jj = 2 , jpjm1
195               DO ji = fs_2, fs_jpim1   ! vector opt.
196                  zbtr = 1.0 / ( e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) )
197                  ztra = zbtr * ( zftu(ji,jj,jk) - zftu(ji-1,jj,jk) + zftv(ji,jj,jk) - zftv(ji,jj-1,jk)  )
198                  pta(ji,jj,jk,jn) = pta(ji,jj,jk,jn) + ztra
199               END DO
200            END DO
201            !                                          ! ===============
202         END DO                                        !   End of slab 
203         !                                             ! ===============
204         !
205         ! "Poleward" diffusive heat or salt transports (T-S case only)
206         IF( cdtype == 'TRA' .AND. ln_diaptr .AND. ( MOD( kt, nn_fptr ) == 0 ) ) THEN
207            IF( jn == jp_tem)   htr_ldf(:) = ptr_vj( zftv(:,:,:) )
208            IF( jn == jp_sal)   str_ldf(:) = ptr_vj( zftv(:,:,:) )
209         ENDIF
210 
211#if defined key_diaar5
212         IF( cdtype == 'TRA' .AND. jn == jp_tem  ) THEN
213            z2d(:,:) = 0._wp 
214            zztmp = rau0 * rcp 
215            DO jk = 1, jpkm1
216               DO jj = 2, jpjm1
217                  DO ji = fs_2, fs_jpim1   ! vector opt.
218                     z2d(ji,jj) = z2d(ji,jj) + zftu(ji,jj,jk) 
219                  END DO
220               END DO
221            END DO
222            z2d(:,:) = zztmp * z2d(:,:)
223            CALL lbc_lnk( z2d, 'U', -1. )
224            CALL iom_put( "udiff_heattr", z2d )                  ! heat transport in i-direction
225            z2d(:,:) = 0._wp 
226            DO jk = 1, jpkm1
227               DO jj = 2, jpjm1
228                  DO ji = fs_2, fs_jpim1   ! vector opt.
229                     z2d(ji,jj) = z2d(ji,jj) + zftv(ji,jj,jk) 
230                  END DO
231               END DO
232            END DO
233            z2d(:,:) = zztmp * z2d(:,:)
234            CALL lbc_lnk( z2d, 'V', -1. )
235            CALL iom_put( "vdiff_heattr", z2d )                  !  heat transport in i-direction
236         END IF
237#endif
238
239         !!----------------------------------------------------------------------
240         !!   III - vertical trend of T & S (extra diagonal terms only)
241         !!----------------------------------------------------------------------
242         
243         ! Local constant initialization
244         ! -----------------------------
245         ztfw(1,:,:) = 0.e0     ;     ztfw(jpi,:,:) = 0.e0
246         
247         ! Vertical fluxes
248         ! ---------------
249         
250         ! Surface and bottom vertical fluxes set to zero
251         ztfw(:,:, 1 ) = 0.e0      ;      ztfw(:,:,jpk) = 0.e0
252         
253         ! interior (2=<jk=<jpk-1)
254         DO jk = 2, jpkm1
255            DO jj = 2, jpjm1
256               DO ji = fs_2, fs_jpim1   ! vector opt.
257                  zcoef0 = - fsahtw(ji,jj,jk) * tmask(ji,jj,jk)
258                  !
259                  zmsku = 1./MAX(   umask(ji  ,jj,jk-1) + umask(ji-1,jj,jk)      &
260                     &            + umask(ji-1,jj,jk-1) + umask(ji  ,jj,jk), 1.  )
261                  zmskv = 1./MAX(   vmask(ji,jj  ,jk-1) + vmask(ji,jj-1,jk)      &
262                     &            + vmask(ji,jj-1,jk-1) + vmask(ji,jj  ,jk), 1.  )
263                  !
264                  zcoef3 = zcoef0 * e2t(ji,jj) * zmsku * wslpi (ji,jj,jk)
265                  zcoef4 = zcoef0 * e1t(ji,jj) * zmskv * wslpj (ji,jj,jk)
266                  !
267                  ztfw(ji,jj,jk) = zcoef3 * (   zdit(ji  ,jj  ,jk-1) + zdit(ji-1,jj  ,jk)      &
268                     &                        + zdit(ji-1,jj  ,jk-1) + zdit(ji  ,jj  ,jk)  )   &
269                     &           + zcoef4 * (   zdjt(ji  ,jj  ,jk-1) + zdjt(ji  ,jj-1,jk)      &
270                     &                        + zdjt(ji  ,jj-1,jk-1) + zdjt(ji  ,jj  ,jk)  )
271               END DO
272            END DO
273         END DO
274         
275         
276         ! I.5 Divergence of vertical fluxes added to the general tracer trend
277         ! -------------------------------------------------------------------
278         DO jk = 1, jpkm1
279            DO jj = 2, jpjm1
280               DO ji = fs_2, fs_jpim1   ! vector opt.
281                  zbtr = 1.0 / ( e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) )
282                  ztra = (  ztfw(ji,jj,jk) - ztfw(ji,jj,jk+1)  ) * zbtr
283                  pta(ji,jj,jk,jn) = pta(ji,jj,jk,jn) + ztra
284               END DO
285            END DO
286         END DO
287         !
288      END DO
289      !
290   END SUBROUTINE tra_ldf_iso
291
292#else
293   !!----------------------------------------------------------------------
294   !!   default option :   Dummy code   NO rotation of the diffusive tensor
295   !!----------------------------------------------------------------------
296CONTAINS
297   SUBROUTINE tra_ldf_iso( kt, cdtype, pgu, pgv, ptb, pta, kjpt, pahtb0 )      ! Empty routine
298      CHARACTER(len=3) ::   cdtype
299      REAL, DIMENSION(:,:,:) ::   pgu, pgv   ! tracer gradient at pstep levels
300      REAL, DIMENSION(:,:,:,:) ::   ptb, pta
301      WRITE(*,*) 'tra_ldf_iso: You should not have seen this print! error?', kt, cdtype, pgu(1,1,1), pgv(1,1,1),   &
302         &                                                             ptb(1,1,1,1), pta(1,1,1,1), kjpt, pahtb0
303   END SUBROUTINE tra_ldf_iso
304#endif
305
306   !!==============================================================================
307END MODULE traldf_iso
Note: See TracBrowser for help on using the repository browser.