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

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

CL : Add CVS Header and CeCILL licence information

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 7.0 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   !!   TOP 1.0 , LOCEAN-IPSL (2005)
25   !! $Header$
26   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
27   !!----------------------------------------------------------------------
28   
29CONTAINS
30
31   SUBROUTINE trc_ldf_lap( kt )
32      !!----------------------------------------------------------------------
33      !!                  ***  ROUTINE trc_ldf_lap  ***
34      !!                   
35      !! ** Purpose :   Compute the before horizontal tracer diffusive
36      !!      trend and add it to the general trend of tracer equation.
37      !!
38      !! ** Method  :   Second order diffusive operator evaluated using before
39      !!      fields (forward time scheme). The horizontal diffusive trends of
40      !!      the passive tracer is given by:
41      !!       * s-coordinate ('key_s_coord' defined), the vertical scale
42      !!      factors e3. are inside the derivatives:
43      !!          difft = 1/(e1t*e2t*e3t) {  di-1[ aht e2u*e3u/e1u di(trb) ]
44      !!                                   + dj-1[ aht e1v*e3v/e2v dj(trb) ] }
45      !!       * z-coordinate (default key), e3t=e3u=e3v, the trend becomes:
46      !!          difft = 1/(e1t*e2t) {  di-1[ aht e2u/e1u di(trb) ]
47      !!                               + dj-1[ aht e1v/e2v dj(trb) ] }
48      !!      Add this trend to the general tracer trend tra :
49      !!          tra = tra + difft
50      !!
51      !! ** Action  : - Update tra arrays with the before iso-level
52      !!                harmonic mixing trend.
53      !!              - Save the trends in trtrd ('key_trc_diatrd')
54      !!
55      !! History :
56      !!   1.0  !  87-06  (P. Andrich, D. L Hostis)  Original code
57      !!        !  91-11  (G. Madec)
58      !!        !  95-02  (M. Levy)    passive tracers
59      !!        !  95-11  (G. Madec)  suppress volumetric scale factors
60      !!        !  96-01  (G. Madec)  statement function for e3
61      !!   8.5  !  02-06  (G. Madec)  F90: Free form and module
62      !!   9.0  !  04-03  (C. Ethe)   passive tracer
63      !!----------------------------------------------------------------------
64      USE oce_trc          , ztu => ua,  &  ! use ua as workspace
65         &                   ztv => va      ! use va as workspace
66
67      !! * Arguments
68      INTEGER, INTENT( in ) ::   kt       ! ocean time-step index
69     
70      !! * Local save
71      REAL(wp), DIMENSION(jpi,jpj), SAVE ::   &
72         ze1ur, ze2vr, zbtr2              ! scale factor coefficients
73     
74      !! * Local declarations
75      INTEGER ::   ji, jj, jk,jn         ! dummy loop indices
76      REAL(wp) ::   &
77         zabe1, zabe2, zbtr              ! temporary scalars
78
79      REAL(wp) ::   &
80         ztra, ztrax, ztray              ! 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         IF(l_ctl) THEN         ! print mean trends (used for debugging)
142            ztra = SUM( tra(2:nictl,2:njctl,1:jpkm1,jn) * tmask(2:nictl,2:njctl,1:jpkm1) )
143            WRITE(numout,*) ' trc/ldf  - ',ctrcnm(jn),' : ', ztra-tra_ctl(jn)
144            tra_ctl(jn) = ztra 
145         ENDIF
146
147      END DO
148
149   END SUBROUTINE trc_ldf_lap
150
151#else
152   !!----------------------------------------------------------------------
153   !!   Default option                                         Empty module
154   !!----------------------------------------------------------------------
155CONTAINS
156   SUBROUTINE trc_ldf_lap( kt ) 
157      INTEGER, INTENT(in) :: kt
158      WRITE(*,*) 'trc_ldf_lap: You should not have seen this print! error?', kt
159   END SUBROUTINE trc_ldf_lap
160#endif
161
162   !!==============================================================================
163END MODULE trcldf_lap
Note: See TracBrowser for help on using the repository browser.