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

source: trunk/NEMO/TOP_SRC/TRP/trcldf_lap.F90 @ 197

Last change on this file since 197 was 186, checked in by opalod, 20 years ago

CL + CE : NEMO TRC_SRC start

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 6.6 KB
Line 
1MODULE trcldf_lap
2   !!==============================================================================
3   !!                       ***  MODULE  trcldf_lap  ***
4   !! Ocean passive tracers:  horizontal component of the lateral tracer mixing trend
5   !!==============================================================================
6#if defined key_passivetrc
7   !!----------------------------------------------------------------------
8   !!   trc_ldf_lap  : update the tracer trend with the horizontal diffusion
9   !!                 using a iso-level harmonic (laplacien) operator.
10   !!----------------------------------------------------------------------
11   !! * Modules used
12   USE oce_trc             ! ocean dynamics and active tracers
13   USE trc                 ! ocean space and time domain
14   USE lbclnk
15
16   IMPLICIT NONE
17   PRIVATE
18
19   !! * Routine accessibility
20   PUBLIC trc_ldf_lap  ! routine called by step.F90
21
22   !! * Substitutions
23#  include "passivetrc_substitute.h90"
24   !!----------------------------------------------------------------------
25   !!   OPA 9.0 , LODYC-IPSL (2003)
26   !!----------------------------------------------------------------------
27   
28CONTAINS
29
30   SUBROUTINE trc_ldf_lap( kt )
31      !!----------------------------------------------------------------------
32      !!                  ***  ROUTINE trc_ldf_lap  ***
33      !!                   
34      !! ** Purpose :   Compute the before horizontal tracer diffusive
35      !!      trend and add it to the general trend of tracer equation.
36      !!
37      !! ** Method  :   Second order diffusive operator evaluated using before
38      !!      fields (forward time scheme). The horizontal diffusive trends of
39      !!      the passive tracer is given by:
40      !!       * s-coordinate ('key_s_coord' defined), the vertical scale
41      !!      factors e3. are inside the derivatives:
42      !!          difft = 1/(e1t*e2t*e3t) {  di-1[ aht e2u*e3u/e1u di(trb) ]
43      !!                                   + dj-1[ aht e1v*e3v/e2v dj(trb) ] }
44      !!       * z-coordinate (default key), e3t=e3u=e3v, the trend becomes:
45      !!          difft = 1/(e1t*e2t) {  di-1[ aht e2u/e1u di(trb) ]
46      !!                               + dj-1[ aht e1v/e2v dj(trb) ] }
47      !!      Add this trend to the general tracer trend tra :
48      !!          tra = tra + difft
49      !!
50      !! ** Action  : - Update tra arrays with the before iso-level
51      !!                harmonic mixing trend.
52      !!              - Save the trends in trtrd ('key_trc_diatrd')
53      !!
54      !! History :
55      !!   1.0  !  87-06  (P. Andrich, D. L Hostis)  Original code
56      !!        !  91-11  (G. Madec)
57      !!        !  95-02  (M. Levy)    passive tracers
58      !!        !  95-11  (G. Madec)  suppress volumetric scale factors
59      !!        !  96-01  (G. Madec)  statement function for e3
60      !!   8.5  !  02-06  (G. Madec)  F90: Free form and module
61      !!   9.0  !  04-03  (C. Ethe)   passive tracer
62      !!----------------------------------------------------------------------
63      USE oce_trc          , ztu => ua,  &  ! use ua as workspace
64         &                   ztv => va      ! use va as workspace
65
66      !! * Arguments
67      INTEGER, INTENT( in ) ::   kt       ! ocean time-step index
68     
69      !! * Local save
70      REAL(wp), DIMENSION(jpi,jpj), SAVE ::   &
71         ze1ur, ze2vr, zbtr2              ! scale factor coefficients
72     
73      !! * Local declarations
74      INTEGER ::   ji, jj, jk,jn         ! dummy loop indices
75      REAL(wp) ::   &
76         zabe1, zabe2, zbtr              ! temporary scalars
77
78      REAL(wp) ::   &
79         ztrax, ztray 
80                       ! workspace
81      !!----------------------------------------------------------------------
82     
83      IF( kt == nittrc000 ) THEN
84         IF(lwp) WRITE(numout,*)
85         IF(lwp) WRITE(numout,*) 'trc_ldf_lap : iso-level laplacian diffusion'
86         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~ '
87         ze1ur(:,:) = e2u(:,:) / e1u(:,:)
88         ze2vr(:,:) = e1v(:,:) / e2v(:,:)
89         zbtr2(:,:) = 1. / ( e1t(:,:) * e2t(:,:) )
90      ENDIF
91 
92      DO jn = 1, jptra
93         
94         !                                                  ! =============
95         DO jk = 1, jpkm1                                   ! Vertical slab
96            !                                               ! =============
97            ! 1. First derivative (gradient)
98            ! -------------------
99            DO jj = 1, jpjm1
100               DO ji = 1, fs_jpim1   ! vector opt.
101#if defined key_s_coord
102                  zabe1 = fsahtru(ji,jj,jk) * umask(ji,jj,jk) * ze1ur(ji,jj) * fse3u(ji,jj,jk)
103                  zabe2 = fsahtrv(ji,jj,jk) * vmask(ji,jj,jk) * ze2vr(ji,jj) * fse3v(ji,jj,jk)
104#else
105                  zabe1 = fsahtru(ji,jj,jk) * umask(ji,jj,jk) * ze1ur(ji,jj)
106                  zabe2 = fsahtrv(ji,jj,jk) * vmask(ji,jj,jk) * ze2vr(ji,jj)
107#endif
108                  ztu(ji,jj,jk) = zabe1 * ( trb(ji+1,jj  ,jk,jn) - trb(ji,jj,jk,jn) )
109                  ztv(ji,jj,jk) = zabe2 * ( trb(ji  ,jj+1,jk,jn) - trb(ji,jj,jk,jn) )
110               END DO
111            END DO
112
113
114            ! 2. Second derivative (divergence)
115            ! --------------------
116            DO jj = 2, jpjm1
117               DO ji = fs_2, fs_jpim1   ! vector opt.
118#if defined key_s_coord
119                  zbtr = zbtr2(ji,jj) / fse3t(ji,jj,jk)
120#else
121                  zbtr = zbtr2(ji,jj)
122#endif
123                  ! horizontal diffusive trends
124                  ztrax = zbtr * ( ztu(ji,jj,jk) - ztu(ji-1,jj,jk) )
125                  ztray = zbtr * ( ztv(ji,jj,jk) - ztv(ji,jj-1,jk) )
126
127                  ! add it to the general tracer trends
128                  tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztrax + ztray
129
130#if defined key_trc_diatrd
131                  ! save the horizontal diffusive trends
132                  trtrd(ji,jj,jk,jn,4) = ztrax
133                  trtrd(ji,jj,jk,jn,5) = ztray
134#endif
135               END DO
136            END DO
137            !                                               ! =============
138         END DO                                             !  End of slab 
139         !                                                  ! =============
140
141      END DO
142
143   END SUBROUTINE trc_ldf_lap
144
145#else
146   !!----------------------------------------------------------------------
147   !!   Default option                                         Empty module
148   !!----------------------------------------------------------------------
149CONTAINS
150   SUBROUTINE trc_ldf_lap( kt ) 
151      INTEGER, INTENT(in) :: kt
152      WRITE(*,*) 'trc_ldf_lap: You should not have seen this print! error?', kt
153   END SUBROUTINE trc_ldf_lap
154#endif
155
156   !!==============================================================================
157END MODULE trcldf_lap
Note: See TracBrowser for help on using the repository browser.