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.
ldfeiv.F90 in trunk/NEMO/OPA_SRC/LDF – NEMO

source: trunk/NEMO/OPA_SRC/LDF/ldfeiv.F90 @ 32

Last change on this file since 32 was 28, checked in by opalod, 20 years ago

CT : BUGFIX014 : Compilation problem is solved

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 14.4 KB
Line 
1MODULE ldfeiv
2   !!======================================================================
3   !!                     ***  MODULE  ldfeiv  ***
4   !! Ocean physics:  variable eddy induced velocity coefficients
5   !!======================================================================
6#if   defined key_traldf_eiv   &&   defined key_traldf_c2d
7   !!----------------------------------------------------------------------
8   !!   'key_traldf_eiv'      and                     eddy induced velocity
9   !!   'key_traldf_c2d'                    2D tracer lateral  mixing coef.
10   !!----------------------------------------------------------------------
11   !!   ldf_eiv      : compute the eddy induced velocity coefficients
12   !!                  Same results but not same routine if 'key_autotasking'
13   !!                  is defined or not
14   !!----------------------------------------------------------------------
15   !! * Modules used
16   USE oce             ! ocean dynamics and tracers
17   USE dom_oce         ! ocean space and time domain
18   USE ldftra_oce      ! ocean tracer   lateral physics
19   USE phycst          ! physical constants
20   USE ldfslp          ! iso-neutral slopes
21   USE flxrnf          !
22   USE in_out_manager  ! I/O manager
23   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
24
25   IMPLICIT NONE
26   PRIVATE
27   
28   !! * Routine accessibility
29   PUBLIC ldf_eiv               ! routine called by step.F90
30
31   !! * Substitutions
32#  include "domzgr_substitute.h90"
33#  include "vectopt_loop_substitute.h90"
34   !!----------------------------------------------------------------------
35
36CONTAINS
37
38#if defined key_autotasking
39   !!----------------------------------------------------------------------
40   !!   'key_autotasking' :                            autotasking (j-slab)
41   !!----------------------------------------------------------------------
42
43   SUBROUTINE ldf_eiv( kt )
44      !!----------------------------------------------------------------------
45      !!                  ***  ROUTINE ldf_eiv  ***
46      !!
47      !! ** Purpose :   Compute the eddy induced velocity coefficient from the
48      !!      growth rate of baroclinic instability.
49      !!
50      !! ** Method :
51      !!
52      !! ** Action :   uslp(),   : i- and j-slopes of neutral surfaces
53      !!               vslp()      at u- and v-points, resp.
54      !!               wslpi(),  : i- and j-slopes of neutral surfaces
55      !!               wslpj()     at w-points.
56      !!
57      !! History :
58      !!   8.1  !  99-03  (G. Madec, A. Jouzeau)  Original code
59      !!   8.5  !  02-06  (G. Madec)  Free form, F90
60      !!----------------------------------------------------------------------
61      !! * Arguments
62      INTEGER, INTENT( in ) ::   kt     ! ocean time-step inedx
63     
64      !! * Local declarations
65      INTEGER ::   ji, jj, jk           ! dummy loop indices
66      REAL(wp) ::   &
67         zfw, ze3w, zn2, zf20,       &  ! temporary scalars
68         zaht, zaht_min
69      REAL(wp), DIMENSION(jpi,jpj) ::   &
70         zn, zah, zhw, zross            ! workspace
71      !!----------------------------------------------------------------------
72
73      IF( kt == nit000 ) THEN
74         IF(lwp) WRITE(numout,*)
75         IF(lwp) WRITE(numout,*) 'ldf_eiv : eddy induced velocity coefficients'
76         IF(lwp) WRITE(numout,*) '~~~~~~~   key_autotasking'
77      ENDIF
78     
79      !                                                ! ===============
80      DO jj = 2, jpjm1                                 !  Vertical slab
81         !                                             ! ===============
82         
83         ! 0. Local initialization
84         ! -----------------------
85         zn   (:,jj) = 0.e0
86         zhw  (:,jj) = 5.e0
87         zah  (:,jj) = 0.e0
88         zross(:,jj) = 0.e0
89         
90         ! 1. Compute lateral diffusive coefficient
91         ! ----------------------------------------
92
93!CDIR NOVERRCHK
94         DO jk = 1, jpk
95!CDIR NOVERRCHK
96            DO ji = 2, jpim1
97               ! Take the max of N^2 and zero then take the vertical sum
98               ! of the square root of the resulting N^2 ( required to compute
99               ! internal Rossby radius Ro = .5 * sum_jpk(N) / f
100               zn2 = MAX( rn2(ji,jj,jk), 0.e0 )
101               ze3w = fse3w(ji,jj,jk) * tmask(ji,jj,jk)
102               zn(ji,jj) = zn(ji,jj) + SQRT( zn2 ) * fse3w(ji,jj,jk)
103               ! Compute elements required for the inverse time scale of baroclinic
104               ! eddies using the isopycnal slopes calculated in ldfslp.F :
105               ! T^-1 = sqrt(m_jpk(N^2*(r1^2+r2^2)*e3w))
106               zah(ji,jj) = zah(ji,jj) + zn2   &
107                              * ( wslpi(ji,jj,jk) * wslpi(ji,jj,jk)    &
108                                + wslpj(ji,jj,jk) * wslpj(ji,jj,jk) )   &
109                              * ze3w
110               zhw(ji,jj) = zhw(ji,jj) + ze3w
111            END DO
112         END DO 
113 
114!CDIR NOVERRCHK
115         DO ji = 2, jpim1
116            zfw = MAX( ABS( 2. * omega * SIN( rad * gphit(ji,jj) ) ) , 1.e-10 )
117            ! Rossby radius at w-point taken < 40km and  > 2km
118            zross(ji,jj) = MAX( MIN( .4 * zn(ji,jj) / zfw, 40.e3 ), 2.e3 )
119            ! Compute aeiw by multiplying Ro^2 and T^-1
120            aeiw(ji,jj) = zross(ji,jj) * zross(ji,jj) * SQRT( zah(ji,jj) / zhw(ji,jj) ) * tmask(ji,jj,1)
121            ! Take the minimum between aeiw and 1000m^2/s for depth levels
122            ! lower than 20 (21 in w- point)
123            IF( mbathy(ji,jj) <= 21. ) aeiw(ji,jj) = MIN( aeiw(ji,jj), 1000. )
124         END DO
125
126         ! Decrease the coefficient in the tropics (20N-20S)
127         zf20 = 2. * omega * sin( rad * 20. )
128         DO ji = 2, jpim1
129            aeiw(ji,jj) = MIN( 1., ABS( ff(ji,jj) / zf20 ) ) * aeiw(ji,jj)
130         END DO
131 
132         ! ORCA R05: Take the minimum between aeiw  and 1000m2/s
133         IF( cp_cfg == "orca" .AND. jp_cfg == 05 ) THEN   ! ORCA R05
134            DO ji = 2, jpim1
135               aeiw(ji,jj) = MIN( aeiw(ji,jj), 1000. )
136            END DO
137         ENDIF
138         !                                             ! ===============
139      END DO                                           !   End of slab
140      !                                                ! ===============
141
142      !,,,,,,,,,,,,,,,,,,,,,,,,,,,,,synchro,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,
143
144      ! lateral boundary condition on aeiw
145      CALL lbc_lnk( aeiw, 'W', 1. )
146
147      ! Average the diffusive coefficient at u- v- points
148      DO jj = 2, jpjm1
149         DO ji = fs_2, fs_jpim1   ! vector opt.
150            aeiu(ji,jj) = .5 * (aeiw(ji,jj) + aeiw(ji+1,jj  ))
151            aeiv(ji,jj) = .5 * (aeiw(ji,jj) + aeiw(ji  ,jj+1))
152         END DO
153      END DO 
154      !,,,,,,,,,,,,,,,,,,,,,,,,,,,,,synchro,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,
155
156      ! lateral boundary condition on aeiu, aeiv
157      CALL lbc_lnk( aeiu, 'U', 1. )
158      CALL lbc_lnk( aeiv, 'V', 1. )
159
160      ! ORCA R05: add a space variation on aht (=aeiv except at the equator and river mouth)
161      IF( cp_cfg == "orca" .AND. jp_cfg == 05 ) THEN
162         zf20     = 2. * omega * SIN( rad * 20. )
163         zaht_min = 100.                              ! minimum value for aht
164         DO jj = 1, jpj
165            DO ji = 1, jpi
166               zaht      = ( 1. -  MIN( 1., ABS( ff(ji,jj) / zf20 ) ) ) * ( aht0 - zaht_min )  &
167                  &      + aht0 * upsrnfh(ji,jj)                          ! enhanced near river mouths
168               ahtu(ji,jj) = MAX( zaht_min, aeiu(ji,jj) ) + zaht
169               ahtv(ji,jj) = MAX( zaht_min, aeiv(ji,jj) ) + zaht
170               ahtw(ji,jj) = MAX( zaht_min, aeiw(ji,jj) ) + zaht
171            END DO
172         END DO
173      ENDIF
174
175   END SUBROUTINE ldf_eiv
176
177#else
178   !!----------------------------------------------------------------------
179   !!   Default key                                             k-j-i loops
180   !!----------------------------------------------------------------------
181
182   SUBROUTINE ldf_eiv ( kt )
183      !!----------------------------------------------------------------------
184      !!                  ***  ROUTINE ldf_eiv  ***
185      !!
186      !! ** Purpose :   Compute the eddy induced velocity coefficient from the
187      !!      growth rate of baroclinic instability.
188      !!
189      !! ** Method :
190      !!
191      !! ** Action : - uslp(),  : i- and j-slopes of neutral surfaces
192      !!             - vslp()      at u- and v-points, resp.
193      !!             - wslpi(),  : i- and j-slopes of neutral surfaces
194      !!             - wslpj()     at w-points.
195      !!
196      !! History :
197      !!   8.1  !  99-03  (G. Madec, A. Jouzeau)  Original code
198      !!   8.5  !  02-06  (G. Madec)  Free form, F90
199      !!----------------------------------------------------------------------
200      !! * Arguments
201      INTEGER, INTENT( in ) ::   kt     ! ocean time-step inedx
202     
203      !! * Local declarations
204      INTEGER ::   ji, jj, jk           ! dummy loop indices
205      REAL(wp) ::   &
206         zfw, ze3w, zn2, zf20,       &  ! temporary scalars
207         zaht, zaht_min
208      REAL(wp), DIMENSION(jpi,jpj) ::   &
209         zn, zah, zhw, zross            ! workspace
210      !!----------------------------------------------------------------------
211     
212      IF( kt == nit000 ) THEN
213         IF(lwp) WRITE(numout,*)
214         IF(lwp) WRITE(numout,*) 'ldf_eiv : eddy induced velocity coefficients'
215         IF(lwp) WRITE(numout,*) '~~~~~~~'
216      ENDIF
217     
218      ! 0. Local initialization
219      ! -----------------------
220      zn   (:,:) = 0.e0
221      zhw  (:,:) = 5.e0
222      zah  (:,:) = 0.e0
223      zross(:,:) = 0.e0
224
225
226      ! 1. Compute lateral diffusive coefficient
227      ! ----------------------------------------
228
229      DO jk = 1, jpk
230#   if defined key_vectopt_loop  &&  ! defined key_autotasking
231!CDIR NOVERRCHK
232         DO ji = 1, jpij   ! vector opt.
233            ! Take the max of N^2 and zero then take the vertical sum
234            ! of the square root of the resulting N^2 ( required to compute
235            ! internal Rossby radius Ro = .5 * sum_jpk(N) / f
236            zn2 = MAX( rn2(ji,1,jk), 0.e0 )
237            zn(ji,1) = zn(ji,1) + SQRT( zn2 ) * fse3w(ji,1,jk)
238            ! Compute elements required for the inverse time scale of baroclinic
239            ! eddies using the isopycnal slopes calculated in ldfslp.F :
240            ! T^-1 = sqrt(m_jpk(N^2*(r1^2+r2^2)*e3w))
241            ze3w = fse3w(ji,1,jk) * tmask(ji,1,jk)
242               zah(ji,1) = zah(ji,1) + zn2   &
243                              * ( wslpi(ji,1,jk) * wslpi(ji,1,jk)    &
244                                + wslpj(ji,1,jk) * wslpj(ji,1,jk) )   &
245                              * ze3w
246            zhw(ji,1) = zhw(ji,1) + ze3w
247         END DO
248#   else
249         DO jj = 2, jpjm1
250!CDIR NOVERRCHK
251            DO ji = 2, jpim1
252               ! Take the max of N^2 and zero then take the vertical sum
253               ! of the square root of the resulting N^2 ( required to compute
254               ! internal Rossby radius Ro = .5 * sum_jpk(N) / f
255               zn2 = MAX( rn2(ji,jj,jk), 0.e0 )
256               zn(ji,jj) = zn(ji,jj) + SQRT( zn2 ) * fse3w(ji,jj,jk)
257               ! Compute elements required for the inverse time scale of baroclinic
258               ! eddies using the isopycnal slopes calculated in ldfslp.F :
259               ! T^-1 = sqrt(m_jpk(N^2*(r1^2+r2^2)*e3w))
260               ze3w = fse3w(ji,jj,jk) * tmask(ji,jj,jk)
261               zah(ji,jj) = zah(ji,jj) + zn2   &
262                              * ( wslpi(ji,jj,jk) * wslpi(ji,jj,jk)    &
263                                + wslpj(ji,jj,jk) * wslpj(ji,jj,jk) )  &
264                              * ze3w
265               zhw(ji,jj) = zhw(ji,jj) + ze3w
266            END DO
267         END DO 
268#   endif
269      END DO
270
271      DO jj = 2, jpjm1
272!CDIR NOVERRCHK
273         DO ji = fs_2, fs_jpim1   ! vector opt.
274            zfw = MAX( ABS( 2. * omega * SIN( rad * gphit(ji,jj) ) ) , 1.e-10 )
275            ! Rossby radius at w-point taken < 40km and  > 2km
276            zross(ji,jj) = MAX( MIN( .4 * zn(ji,jj) / zfw, 40.e3 ), 2.e3 )
277            ! Compute aeiw by multiplying Ro^2 and T^-1
278            aeiw(ji,jj) = zross(ji,jj) * zross(ji,jj) * SQRT( zah(ji,jj) / zhw(ji,jj) ) * tmask(ji,jj,1)
279            ! Take the minimum between aeiw and 1000m^2/s for depth levels
280            ! lower than 20 (21 in w- point)
281            IF( mbathy(ji,jj) <= 21. ) aeiw(ji,jj) = MIN( aeiw(ji,jj), 1000. )
282         END DO
283      END DO
284
285      ! Decrease the coefficient in the tropics (20N-20S)
286         zf20 = 2. * omega * sin( rad * 20. )
287      DO jj = 2, jpjm1
288         DO ji = fs_2, fs_jpim1   ! vector opt.
289            aeiw(ji,jj) = MIN( 1., ABS( ff(ji,jj) / zf20 ) ) * aeiw(ji,jj)
290         END DO
291      END DO
292
293      ! ORCA R05: Take the minimum between aeiw  and 1000m2/s
294      IF( cp_cfg == "orca" .AND. jp_cfg == 05 ) THEN
295         DO jj = 2, jpjm1
296            DO ji = fs_2, fs_jpim1   ! vector opt.
297               aeiw(ji,jj) = MIN( aeiw(ji,jj), aeiv0 )
298            END DO
299         END DO
300      ENDIF
301
302      ! lateral boundary condition on aeiw
303      CALL lbc_lnk( aeiw, 'W', 1. )
304
305      ! Average the diffusive coefficient at u- v- points
306      DO jj = 2, jpjm1
307         DO ji = fs_2, fs_jpim1   ! vector opt.
308            aeiu(ji,jj) = .5 * ( aeiw(ji,jj) + aeiw(ji+1,jj  ) )
309            aeiv(ji,jj) = .5 * ( aeiw(ji,jj) + aeiw(ji  ,jj+1) )
310         END DO
311      END DO 
312
313      ! lateral boundary condition on aeiu, aeiv
314      CALL lbc_lnk( aeiu, 'U', 1. )
315      CALL lbc_lnk( aeiv, 'V', 1. )
316
317      ! ORCA R05: add a space variation on aht (=aeiv except at the equator and river mouth)
318      IF( cp_cfg == "orca" .AND. jp_cfg == 05 ) THEN
319         zf20     = 2. * omega * SIN( rad * 20. )
320         zaht_min = 100.                              ! minimum value for aht
321         DO jj = 1, jpj
322            DO ji = 1, jpi
323               zaht      = ( 1. -  MIN( 1., ABS( ff(ji,jj) / zf20 ) ) ) * ( aht0 - zaht_min )  &
324                  &      + aht0 * upsrnfh(ji,jj)                          ! enhanced near river mouths
325               ahtu(ji,jj) = MAX( zaht_min, aeiu(ji,jj) ) + zaht
326               ahtv(ji,jj) = MAX( zaht_min, aeiv(ji,jj) ) + zaht
327               ahtw(ji,jj) = MAX( zaht_min, aeiw(ji,jj) ) + zaht
328            END DO
329         END DO
330      ENDIF
331
332   END SUBROUTINE ldf_eiv
333
334#endif
335
336#else
337   !!----------------------------------------------------------------------
338   !!   Default option                                         Dummy module
339   !!----------------------------------------------------------------------
340CONTAINS
341   SUBROUTINE ldf_eiv( kt )       ! Empty routine
342      WRITE(*,*) 'ldf_eiv: You should not have seen this print! error?', kt
343   END SUBROUTINE ldf_eiv
344#endif
345
346   !!======================================================================
347END MODULE ldfeiv
Note: See TracBrowser for help on using the repository browser.