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

source: trunk/NEMO/TOP_SRC/TRP/zpshde_trc.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: 8.8 KB
Line 
1MODULE zpshde_trc
2   !!==============================================================================
3   !!                       ***  MODULE zpshde_trc   ***
4   !! Ocean passive tracers:
5   !!==============================================================================
6#if defined key_passivetrc && ( defined key_partial_steps || defined key_esopa )
7   !!----------------------------------------------------------------------
8   !!   'key_partial_steps' :               z-coordinate with partial steps
9   !!----------------------------------------------------------------------
10   !!   zps_hde_trc  :  Horizontal DErivative of passive tracers at the last
11   !!                   ocean level (Z-coord. with Partial Steps)
12   !!----------------------------------------------------------------------
13   !! * Modules used
14   USE oce_trc         ! ocean dynamics and tracers variables
15   USE trc             ! ocean passive tracers variables
16   USE lbclnk          ! lateral boundary conditions (or mpp link)
17
18   IMPLICIT NONE
19   PRIVATE
20
21   !! * Routine accessibility
22   PUBLIC zps_hde_trc          ! routine called by step.F90
23
24   !! * module variables
25   INTEGER, DIMENSION(jpi,jpj) ::   &
26      mbatu, mbatv      ! bottom ocean level index at U- and V-points
27
28   !! * Substitutions
29#  include "passivetrc_substitute.h90"
30   !!----------------------------------------------------------------------
31
32CONTAINS
33
34   SUBROUTINE zps_hde_trc ( kt, ptra, pgtru, pgtrv )
35      !!----------------------------------------------------------------------
36      !!                     ***  ROUTINE zps_hde_trc  ***
37      !!                   
38      !! ** Purpose :   Compute the horizontal derivative of passive tracers
39      !!      TRA at u- and v-points with a linear interpolation for z-coordinate
40      !!      with partial steps.
41      !!
42      !! ** Method  :   In z-coord with partial steps, scale factors on last
43      !!      levels are different for each grid point, so that TRA points
44      !!      are not at the same depth as in z-coord. To have horizontal
45      !!      gradients again, we interpolate TRA at the good depth :
46      !!      Linear interpolation of TRA 
47      !!         Computation of di(trb) and dj(trb) by vertical interpolation:
48      !!          di(tra) = tra~ - tra(i,j,k) or tra(i+1,j,k) - tra~
49      !!          dj(tra) = tra~ - tra(i,j,k) or tra(i,j+1,k) - tra~
50      !!         This formulation computes the two cases:
51      !!                 CASE 1                   CASE 2 
52      !!         k-1  ___ ___________   k-1   ___ ___________
53      !!                  TRAi  TRA~             TRA~  TRAi+1
54      !!                  _____                        _____
55      !!         k        |   |TRAi+1   k         TRAi |   |
56      !!                  |   |____                ____|   |
57      !!              ___ |   |   |           ___  |   |   |
58      !!                 
59      !!      case 1->   e3w(i+1) >= e3w(i) ( and e3w(j+1) >= e3w(j) ) then
60      !!      tra~ = tra(i+1,j  ,k) + (e3w(i+1) - e3w(i)) * dk(TRAi+1)/e3w(i+1)
61      !!    ( tra~ = tra(i  ,j+1,k) + (e3w(j+1) - e3w(j)) * dk(TRAj+1)/e3w(j+1))
62      !!          or
63      !!      case 2->   e3w(i+1) <= e3w(i) ( and e3w(j+1) <= e3w(j) ) then
64      !!       tra~ = tra(i,j,k) + (e3w(i) - e3w(i+1)) * dk(TRAi)/e3w(i )
65      !!     ( tra~ = tra(i,j,k) + (e3w(j) - e3w(j+1)) * dk(TRAj)/e3w(j ) )
66      !!     
67      !!
68      !! ** Action  : - pgtru : horizontal gradient of TRA at U-points
69      !!              - pgtrv : horizontal gradient of TRA at V-points
70      !!
71      !! History :
72      !!   8.5  !  02-04  (A. Bozec)  Original code
73      !!   8.5  !  02-08  (G. Madec E. Durand)  Optimization and Free form
74      !!   9.0  !  04-03  (C. Ethe)  adapted for passive tracers
75      !!----------------------------------------------------------------------
76      !! * Arguments
77      INTEGER, INTENT( in ) ::   kt ! ocean time-step index
78      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra), INTENT( in ) ::   &
79         ptra                       ! 4D tracers fields
80      REAL(wp), DIMENSION(jpi,jpj,jptra), INTENT( out ) ::   &
81         pgtru,                 &  ! horizontal grad. of TRA u- and v-points
82         pgtrv                     ! of the partial step level
83
84      !! * Local declarations
85      INTEGER ::   ji, jj,jn,     &  ! Dummy loop indices
86                   iku,ikv          ! partial step level at u- and v-points
87      REAL(wp), DIMENSION(jpi,jpj) ::   &
88         zti, ztj                   ! tempory arrays
89
90      REAL(wp), DIMENSION(jpi,jpj,jptra) ::   &
91         ztrai, ztraj               ! interpolated value of TRA
92
93      REAL(wp) ::   &
94         ze3wu, ze3wv,           &  ! temporary scalars
95         zmaxu1, zmaxu2,         &  !    "         "
96         zmaxv1, zmaxv2             !    "         "
97      !!----------------------------------------------------------------------
98      !!  OPA 8.5, LODYC-IPSL (2002)
99      !!----------------------------------------------------------------------
100
101      ! Initialization (first time-step only): compute mbatu and mbatv
102      IF( kt == nittrc000 ) THEN
103         mbatu(:,:) = 0
104         mbatv(:,:) = 0
105         DO jj = 1, jpjm1
106            DO ji = 1, fs_jpim1   ! vector opt.
107               mbatu(ji,jj) = MAX( MIN( mbathy(ji,jj), mbathy(ji+1,jj  ) ) - 1, 2 )
108               mbatv(ji,jj) = MAX( MIN( mbathy(ji,jj), mbathy(ji  ,jj+1) ) - 1, 2 )
109            END DO
110         END DO
111         zti(:,:) = FLOAT( mbatu(:,:) )
112         ztj(:,:) = FLOAT( mbatv(:,:) )
113         ! lateral boundary conditions: T-point, sign unchanged
114         CALL lbc_lnk( zti , 'U', 1. )
115         CALL lbc_lnk( ztj , 'V', 1. )
116         mbatu(:,:) = MAX( INT( zti(:,:) ), 2 )
117         mbatv(:,:) = MAX( INT( ztj(:,:) ), 2 )
118      ENDIF
119     
120
121      DO jn = 1, jptra
122         ! Interpolation of passive tracers at the last ocean level
123# if defined key_vectopt_loop   &&   ! defined key_autotasking
124         jj = 1
125         DO ji = 1, jpij-jpi   ! vector opt. (forced unrolled)
126# else
127         DO jj = 1, jpjm1
128            DO ji = 1, jpim1
129# endif
130               ! last level
131               iku = mbatu(ji,jj)
132               ikv = mbatv(ji,jj)
133
134               ze3wu  = fse3w(ji+1,jj  ,iku) - fse3w(ji,jj,iku)
135               ze3wv  = fse3w(ji  ,jj+1,ikv) - fse3w(ji,jj,ikv)
136               zmaxu1 =  ze3wu / fse3w(ji+1,jj  ,iku)
137               zmaxu2 = -ze3wu / fse3w(ji  ,jj  ,iku)
138               zmaxv1 =  ze3wv / fse3w(ji  ,jj+1,ikv)
139               zmaxv2 = -ze3wv / fse3w(ji  ,jj  ,ikv)
140
141               ! i- direction
142
143               IF( ze3wu >= 0. ) THEN      ! case 1
144                  ! interpolated values of passive tracers
145                  ztrai(ji,jj,jn) = ptra(ji+1,jj,iku,jn) + zmaxu1 * ( ptra(ji+1,jj,iku-1,jn) - ptra(ji+1,jj,iku,jn) )
146                  ! gradient of passive tracers
147                  pgtru(ji,jj,jn) = umask(ji,jj,1) * ( ztrai(ji,jj,jn) - ptra(ji,jj,iku,jn) )
148               ELSE                        ! case 2
149                  ! interpolated values of passive tracers
150                  ztrai(ji,jj,jn) = ptra(ji,jj,iku,jn) + zmaxu2 * ( ptra(ji,jj,iku-1,jn) - ptra(ji,jj,iku,jn) )
151                  ! gradient of passive tracers
152                  pgtru(ji,jj,jn) = umask(ji,jj,1) * ( ptra(ji+1,jj,iku,jn) - ztrai (ji,jj,jn) )
153               ENDIF
154
155               ! j- direction
156
157               IF( ze3wv >= 0. ) THEN      ! case 1
158                  ! interpolated values of passive tracers
159                  ztraj(ji,jj,jn) = ptra(ji,jj+1,ikv,jn) + zmaxv1 * ( ptra(ji,jj+1,ikv-1,jn) - ptra(ji,jj+1,ikv,jn) )
160                  ! gradient of passive tracers
161                  pgtrv(ji,jj,jn) = vmask(ji,jj,1) * ( ztraj(ji,jj,jn) - ptra(ji,jj,ikv,jn) )
162               ELSE                        ! case 2
163                  ! interpolated values of passive tracers
164                  ztraj(ji,jj,jn) = ptra(ji,jj,ikv,jn) + zmaxv2 * ( ptra(ji,jj,ikv-1,jn) - ptra(ji,jj,ikv,jn) )
165                  ! gradient of passive tracers
166                  pgtrv(ji,jj,jn) = vmask(ji,jj,1) * ( ptra(ji,jj+1,ikv,jn) - ztraj(ji,jj,jn) )
167               ENDIF
168# if ! defined key_vectopt_loop   ||   defined key_autotasking
169            END DO
170# endif
171         END DO
172
173         ! Lateral boundary conditions on each gradient
174         CALL lbc_lnk( pgtru(:,:,jn) , 'U', -1. ) 
175         CALL lbc_lnk( pgtrv(:,:,jn) , 'V', -1. )
176
177      END DO
178
179   END SUBROUTINE zps_hde_trc
180
181#else
182   !!----------------------------------------------------------------------
183   !!   Default option                                         Empty module
184   !!----------------------------------------------------------------------
185   USE par_kind
186CONTAINS
187   SUBROUTINE zps_hde_trc ( kt, ptra, pgtru, pgtrv ) ! Empty routine
188      REAL(wp) :: kt,ptra,pgtru, pgtrv
189      WRITE(*,*) 'zps_hde_trc: You should not have seen this print! error?',   &
190         kt, ptra, pgtru, pgtrv
191   END SUBROUTINE zps_hde_trc
192#endif
193
194   !!======================================================================
195END MODULE zpshde_trc
Note: See TracBrowser for help on using the repository browser.