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 @ 202

Last change on this file since 202 was 202, checked in by opalod, 19 years ago

CT : UPDATE142 : Check the consistency between passive tracers transport modules (in TRP directory) and those used for the active tracers

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