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/OFF_SRC/LDF – NEMO

source: trunk/NEMO/OFF_SRC/LDF/ldfeiv.F90 @ 1265

Last change on this file since 1265 was 1265, checked in by cetlod, 15 years ago

clean OFFLINE routines to avoid warning when compiling, see ticket:303

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 5.8 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 in_out_manager  ! I/O manager
21   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
22
23   IMPLICIT NONE
24   PRIVATE
25
26   !! * Routine accessibility
27   PUBLIC ldf_eiv               ! routine called by step.F90
28   !!----------------------------------------------------------------------
29   !!  OPA 9.0 , LOCEAN-IPSL (2005)
30   !! $Id$
31   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
32   !!----------------------------------------------------------------------
33   !! * Substitutions
34#  include "domzgr_substitute.h90"
35#  include "vectopt_loop_substitute.h90"
36   !!----------------------------------------------------------------------
37
38CONTAINS
39
40# if defined key_mpp_omp
41   !!----------------------------------------------------------------------
42   !!   'key_mpp_omp' :                  OpenMP /  NEC autotasking (j-slab)
43   !!----------------------------------------------------------------------
44
45   SUBROUTINE ldf_eiv( kt )
46      !!----------------------------------------------------------------------
47      !!                  ***  ROUTINE ldf_eiv  ***
48      !!
49      !! ** Purpose :   Compute the eddy induced velocity coefficient from the
50      !!      growth rate of baroclinic instability.
51      !!
52      !! ** Method : Specific to the offline model. Computes the horizontal
53      !!             values from the vertical value
54      !!
55      !! History :
56      !!   9.0  !  06-03  (O. Aumont)  Free form, F90
57      !!----------------------------------------------------------------------
58      !! * Arguments
59      INTEGER, INTENT( in ) ::   kt     ! ocean time-step inedx
60
61      !! * Local declarations
62      INTEGER ::   ji, jj, jk           ! dummy loop indices
63      !!----------------------------------------------------------------------
64
65      IF( kt == nit000 ) THEN
66         IF(lwp) WRITE(numout,*)
67         IF(lwp) WRITE(numout,*) 'ldf_eiv : eddy induced velocity coefficients'
68         IF(lwp) WRITE(numout,*) '~~~~~~~   NEC autotasking / OpenMP : j-slab'
69      ENDIF
70
71      ! Average the diffusive coefficient at u- v- points
72      DO jj = 2, jpjm1
73         DO ji = fs_2, fs_jpim1   ! vector opt.
74            aeiu(ji,jj) = .5 * (aeiw(ji,jj) + aeiw(ji+1,jj  ))
75            aeiv(ji,jj) = .5 * (aeiw(ji,jj) + aeiw(ji  ,jj+1))
76         END DO
77      END DO
78      !,,,,,,,,,,,,,,,,,,,,,,,,,,,,,synchro,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,
79
80      ! lateral boundary condition on aeiu, aeiv
81      CALL lbc_lnk( aeiu, 'U', 1. )
82      CALL lbc_lnk( aeiv, 'V', 1. )
83
84   END SUBROUTINE ldf_eiv
85
86# else
87   !!----------------------------------------------------------------------
88   !!   Default key                                             k-j-i loops
89   !!----------------------------------------------------------------------
90
91   SUBROUTINE ldf_eiv( kt )
92      !!----------------------------------------------------------------------
93      !!                  ***  ROUTINE ldf_eiv  ***
94      !!
95      !! ** Purpose :   Compute the eddy induced velocity coefficient from the
96      !!      growth rate of baroclinic instability.
97      !!
98      !! ** Method : Specific to the offline model. Computes the horizontal
99      !!             values from the vertical value
100      !!
101      !! History :
102      !!   9.0  !  06-03  (O. Aumont)  Free form, F90
103      !!----------------------------------------------------------------------
104      !! * Arguments
105      INTEGER, INTENT( in ) ::   kt     ! ocean time-step inedx
106
107      !! * Local declarations
108      INTEGER ::   ji, jj           ! dummy loop indices
109      !!----------------------------------------------------------------------
110
111      IF( kt == nit000 ) THEN
112         IF(lwp) WRITE(numout,*)
113         IF(lwp) WRITE(numout,*) 'ldf_eiv : eddy induced velocity coefficients'
114         IF(lwp) WRITE(numout,*) '~~~~~~~'
115      ENDIF
116
117      ! Average the diffusive coefficient at u- v- points
118      DO jj = 2, jpjm1
119         DO ji = fs_2, fs_jpim1   ! vector opt.
120            aeiu(ji,jj) = .5 * ( aeiw(ji,jj) + aeiw(ji+1,jj  ) )
121            aeiv(ji,jj) = .5 * ( aeiw(ji,jj) + aeiw(ji  ,jj+1) )
122         END DO
123      END DO
124
125      ! lateral boundary condition on aeiu, aeiv
126      CALL lbc_lnk( aeiu, 'U', 1. )
127      CALL lbc_lnk( aeiv, 'V', 1. )
128
129   END SUBROUTINE ldf_eiv
130
131# endif
132
133#else
134   !!----------------------------------------------------------------------
135   !!   Default option                                         Dummy module
136   !!----------------------------------------------------------------------
137CONTAINS
138   SUBROUTINE ldf_eiv( kt )       ! Empty routine
139      WRITE(*,*) 'ldf_eiv: You should not have seen this print! error?', kt
140   END SUBROUTINE ldf_eiv
141#endif
142
143   !!======================================================================
144END MODULE ldfeiv
Note: See TracBrowser for help on using the repository browser.