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.
trcldf_bilap.F90 in trunk/NEMO/TOP_SRC/TRP – NEMO

source: trunk/NEMO/TOP_SRC/TRP/trcldf_bilap.F90 @ 724

Last change on this file since 724 was 724, checked in by cetlod, 17 years ago

Update modules for passive tracers transport trends computation, see ticket:13

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 10.1 KB
Line 
1MODULE trcldf_bilap
2   !!==============================================================================
3   !!                   ***  MODULE  trcldf_bilap  ***
4   !! Ocean passive tracers:  horizontal component of the lateral tracer mixing trend
5   !!==============================================================================
6#if defined key_passivetrc
7   !!----------------------------------------------------------------------
8   !!   trc_ldf_bilap : update the tracer trend with the horizontal diffusion
9   !!                   using a iso-level biharmonic operator
10   !!----------------------------------------------------------------------
11   !! * Modules used
12   USE oce_trc         ! ocean dynamics and active tracers variables
13   USE trc             ! ocean passive tracers variables
14   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
15   USE prtctl_trc      ! Print control for debbuging
16
17   IMPLICIT NONE
18   PRIVATE
19
20   !! * Routine accessibility
21   PUBLIC trc_ldf_bilap   ! routine called by step.F90
22
23   !! * Substitutions
24#  include "passivetrc_substitute.h90"
25   !!----------------------------------------------------------------------
26   !!   TOP 1.0 , LOCEAN-IPSL (2005)
27   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/TOP_SRC/TRP/trcldf_bilap.F90,v 1.12 2007/10/12 09:26:30 opalod Exp $
28   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
29   !!----------------------------------------------------------------------
30
31CONTAINS
32   
33   SUBROUTINE trc_ldf_bilap( kt )
34      !!----------------------------------------------------------------------
35      !!                  ***  ROUTINE trc_ldf_bilap  ***
36      !!
37      !! ** Purpose :   Compute the before horizontal tracer tra diffusive
38      !!      trend and add it to the general trend of tracer equation.
39      !!
40      !! ** Method  :   4th order diffusive operator along model level surfaces
41      !!      evaluated using before fields (forward time scheme). The hor.
42      !!      diffusive trends of passive tracer is given by:
43      !!       * s-coordinate, the vertical scale
44      !!      factors e3. are inside the derivatives:
45      !!      Laplacian of trb:
46      !!         zlt   = 1/(e1t*e2t*e3t) {  di-1[ e2u*e3u/e1u di(trb) ]
47      !!                                  + dj-1[ e1v*e3v/e2v dj(trb) ]  }
48      !!      Multiply by the eddy diffusivity coef. and insure lateral bc:
49      !!        zlt   = ahtt * zlt
50      !!        call to lbc_lnk
51      !!      Bilaplacian (laplacian of zlt):
52      !!         difft = 1/(e1t*e2t*e3t) {  di-1[ e2u*e3u/e1u di(zlt) ]
53      !!                                  + dj-1[ e1v*e3v/e2v dj(zlt) ]  }
54      !!       * z-coordinate (default key), e3t=e3u=e3v, the trend becomes:
55      !!      Laplacian of trb:
56      !!         zlt   = 1/(e1t*e2t) {  di-1[ e2u/e1u di(trb) ]
57      !!                              + dj-1[ e1v/e2v dj(trb) ] }
58      !!      Multiply by the eddy diffusivity coef. and insure lateral bc:
59      !!        zlt   = ahtt * zlt
60      !!        call to lbc_lnk
61      !!      Bilaplacian (laplacian of zlt):
62      !!         difft = 1/(e1t*e2t) {  di-1[ e2u/e1u di(zlt) ]
63      !!                              + dj-1[ e1v/e2v dj(zlt) ]  }
64      !!
65      !!      Add this trend to the general trend tra :
66      !!         tra = tra + difft
67      !!
68      !! ** Action : - Update tra arrays with the before iso-level
69      !!               biharmonic mixing trend.
70      !!             - Save the trends in trtrd ('key_trc_diatrd')
71      !!
72      !! History :
73      !!        !  91-11  (G. Madec)  Original code
74      !!        !  93-03  (M. Guyon)  symetrical conditions
75      !!        !  95-11  (G. Madec)  suppress volumetric scale factors
76      !!        !  96-01  (G. Madec)  statement function for e3
77      !!        !  96-01  (M. Imbard)  mpp exchange
78      !!        !  97-07  (G. Madec)  optimization, and ahtt
79      !!        !  00-05  (MA Foujols) add lbc for tracer trends
80      !!        !  00-10  (MA Foujols E. Kestenare) use passive tracer coefficient
81      !!   8.5  !  02-08  (G. Madec)  F90: Free form and module
82      !!   9.0  !  04-03  (C. Ethe )  F90: Free form and module
83      !!----------------------------------------------------------------------
84      !! * Arguments
85      INTEGER, INTENT( in ) ::   kt       ! ocean time-step index
86
87      !! * Local declarations
88      INTEGER ::   ji, jj, jk, jn             ! dummy loop indices
89      INTEGER ::   iku, ikv                   ! temporary integers
90
91      REAL(wp) ::   ztra     ! temporary scalars
92
93      REAL(wp), DIMENSION(jpi,jpj) ::   & 
94         zeeu, zeev, zbtr, zlt                 ! workspace
95      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   & 
96         ztu, ztv                              ! workspace
97      CHARACTER (len=22) :: charout
98      !!----------------------------------------------------------------------
99
100      IF( kt == nittrc000 ) THEN
101         IF(lwp) WRITE(numout,*)
102         IF(lwp) WRITE(numout,*) 'trc_ldf_bilap : iso-level biharmonic operator'
103         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~'
104      ENDIF
105      !
106
107      DO jn = 1, jptra
108                                                          ! ===============
109         DO jk = 1, jpkm1                                 ! Horizontal slab
110            !                                             ! ===============
111
112            ! 0. Initialization of metric arrays (for z- or s-coordinates)
113            ! ----------------------------------
114
115            DO jj = 1, jpjm1
116               DO ji = 1, fs_jpim1   ! vector opt.
117#if ! defined key_zco
118                  ! s-coordinates, vertical scale factor are used
119                  zbtr(ji,jj) = 1. / ( e1t(ji,jj)*e2t(ji,jj)*fse3t(ji,jj,jk) )
120                  zeeu(ji,jj) = e2u(ji,jj) * fse3u(ji,jj,jk) / e1u(ji,jj) * umask(ji,jj,jk)
121                  zeev(ji,jj) = e1v(ji,jj) * fse3v(ji,jj,jk) / e2v(ji,jj) * vmask(ji,jj,jk)
122#else
123                  ! z-coordinates, no vertical scale factors
124                  zbtr(ji,jj) = 1. / ( e1t(ji,jj)*e2t(ji,jj) )
125                  zeeu(ji,jj) = e2u(ji,jj) / e1u(ji,jj) * umask(ji,jj,jk)
126                  zeev(ji,jj) = e1v(ji,jj) / e2v(ji,jj) * vmask(ji,jj,jk)
127#endif
128               END DO
129            END DO
130
131
132            ! 1. Laplacian
133            ! ------------
134
135            ! First derivative (gradient)
136            DO jj = 1, jpjm1
137               DO ji = 1, fs_jpim1   ! vector opt.
138                  ztu(ji,jj,jk) = zeeu(ji,jj) * ( trb(ji+1,jj  ,jk,jn) - trb(ji,jj,jk,jn) )
139                  ztv(ji,jj,jk) = zeev(ji,jj) * ( trb(ji  ,jj+1,jk,jn) - trb(ji,jj,jk,jn) )
140               END DO
141            END DO
142
143            IF( ln_zps ) THEN
144               DO jj = 1, jpj-1
145                  DO ji = 1, jpi-1
146                     ! last level
147                     iku = MIN ( mbathy(ji,jj), mbathy(ji+1,jj  ) ) - 1
148                     ikv = MIN ( mbathy(ji,jj), mbathy(ji  ,jj+1) ) - 1
149                     IF( iku == jk ) THEN
150                        ztu(ji,jj,jk) = zeeu(ji,jj) * gtru(ji,jj,jn)
151                     ENDIF
152                     IF( ikv == jk ) THEN
153                        ztv(ji,jj,jk) = zeev(ji,jj) * gtrv(ji,jj,jn)
154                     ENDIF
155                  END DO
156               END DO
157            ENDIF
158
159            ! Second derivative (divergence)
160            DO jj = 2, jpjm1
161               DO ji = fs_2, fs_jpim1   ! vector opt.
162                  zlt(ji,jj) = zbtr(ji,jj) * (  ztu(ji,jj,jk) - ztu(ji-1,jj,jk) + ztv(ji,jj,jk) - ztv(ji,jj-1,jk)  )
163               END DO
164            END DO
165
166            ! Multiply by the eddy diffusivity coefficient
167            DO jj = 2, jpjm1
168               DO ji = fs_2, fs_jpim1   ! vector opt.
169                  zlt(ji,jj) = fsahtrt(ji,jj,jk) * zlt(ji,jj)
170               END DO
171            END DO
172
173            ! Lateral boundary conditions on the laplacian zlt   (unchanged sgn)
174            CALL lbc_lnk( zlt, 'T', 1. ) 
175
176            ! 2. Bilaplacian
177            ! --------------
178
179            ! third derivative (gradient)
180            DO jj = 1, jpjm1
181               DO ji = 1, fs_jpim1   ! vector opt.
182                  ztu(ji,jj,jk) = zeeu(ji,jj) * ( zlt(ji+1,jj  ) - zlt(ji,jj) )
183                  ztv(ji,jj,jk) = zeev(ji,jj) * ( zlt(ji  ,jj+1) - zlt(ji,jj) )
184               END DO
185            END DO
186
187            ! fourth derivative (divergence) and add to the general tracer trend
188            DO jj = 2, jpjm1
189               DO ji = fs_2, fs_jpim1   ! vector opt.
190                  ! horizontal diffusive trends
191                  ztra = zbtr(ji,jj) * (  ztu(ji,jj,jk) - ztu(ji-1,jj,jk) + ztv(ji,jj,jk) - ztv(ji,jj-1,jk)  )
192                  ! add it to the general tracer trends
193                  tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra
194#if defined key_trc_diatrd
195                  ! save the horizontal diffusive trends
196                  IF (luttrd(jn)) trtrd(ji,jj,jk,ikeep(jn),4) = (  ztu(ji,jj,jk) - ztu(ji-1,jj,jk) ) * zbtr(ji,jj)
197                  IF (luttrd(jn)) trtrd(ji,jj,jk,ikeep(jn),5) = (  ztv(ji,jj,jk) - ztv(ji-1,jj,jk) ) * zbtr(ji,jj)
198#endif
199               END DO
200            END DO
201            !                                             ! ===============
202         END DO                                           ! Horizontal slab
203         !                                                ! ===============
204#if defined key_trc_diatrd
205         ! Lateral boundary conditions on the laplacian zlt   (unchanged sgn)
206         IF (luttrd(jn)) CALL lbc_lnk( trtrd(:,:,:,ikeep(jn),5), 'T', 1. ) 
207#endif
208      END DO
209
210     IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
211         WRITE(charout, FMT="('ldf - bilap')")
212         CALL prt_ctl_trc_info(charout)
213         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd')
214      ENDIF
215
216   END SUBROUTINE trc_ldf_bilap
217
218#else
219   !!----------------------------------------------------------------------
220   !!   Default option                                         Empty module
221   !!----------------------------------------------------------------------
222CONTAINS
223   SUBROUTINE trc_ldf_bilap( kt ) 
224      INTEGER, INTENT(in) :: kt
225      WRITE(*,*) 'trc_ldf_bilap: You should not have seen this print! error?', kt
226   END SUBROUTINE trc_ldf_bilap
227#endif
228   !!==============================================================================
229END MODULE trcldf_bilap
Note: See TracBrowser for help on using the repository browser.