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.
ldfc1d.F90 in branches/2014/dev_CNRS0_NOC1_LDF/NEMOGCM/NEMO/OPA_SRC/LDF – NEMO

source: branches/2014/dev_CNRS0_NOC1_LDF/NEMOGCM/NEMO/OPA_SRC/LDF/ldfc1d.F90 @ 4596

Last change on this file since 4596 was 4596, checked in by gm, 10 years ago

#1260: LDF simplification + bilap iso-neutral for TRA and GYRE

File size: 5.2 KB
Line 
1MODULE ldfc1d
2   !!======================================================================
3   !!                    ***  MODULE  ldfc1d  ***
4   !! Ocean physics:  profile of lateral eddy coefficients
5   !!=====================================================================
6   !! History :  3.7  ! 2013-12  (G. Madec)  restructuration/simplification of aht/aeiv specification,
7   !!                 !                      add velocity dependent coefficient and optional read in file
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   ldf_c1d       : ah reduced by 1/4 on the vertical (tanh profile, inflection at 300m)
12   !!----------------------------------------------------------------------
13   USE oce            ! ocean dynamics and tracers
14   USE dom_oce        ! ocean space and time domain
15   USE phycst         ! physical constants
16   !
17   USE in_out_manager ! I/O manager
18   USE lib_mpp        ! distribued memory computing library
19   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
20
21   IMPLICIT NONE
22   PRIVATE
23
24   PUBLIC   ldf_c1d   ! called by ldftra and ldfdyn modules
25
26   !! * Substitutions
27#  include "domzgr_substitute.h90"
28#  include "vectopt_loop_substitute.h90"
29   !!----------------------------------------------------------------------
30   !! NEMO/OPA 3.7 , NEMO Consortium (2014)
31   !! $Id: $
32   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
33   !!----------------------------------------------------------------------
34CONTAINS
35
36   SUBROUTINE ldf_c1d( cd_type, prat, pahs1, pahs2, pah1, pah2 )
37      !!----------------------------------------------------------------------
38      !!                  ***  ROUTINE ldftra_c1d  ***
39      !!             
40      !! ** Purpose :   1D eddy diffusivity/viscosity coefficients
41      !!
42      !! ** Method  :   1D eddy diffusivity coefficients F( depth )
43      !!                Reduction by prat from surface to bottom
44      !!                hyperbolic tangent profile with inflection point
45      !!                at zh=500m and a width of zw=200m
46      !!
47      !!   cd_type = TRA      pah1, pah2 defined at U- and V-points
48      !!             DYN      pah1, pah2 defined at T- and F-points
49      !!----------------------------------------------------------------------
50      CHARACTER(len=2)                , INTENT(in   ) ::   cd_type        ! DYNamique or TRAcers
51      REAL(wp)                        , INTENT(in   ) ::   prat           ! ratio surface/deep values           [-]
52      REAL(wp), DIMENSION(jpi,jpj)    , INTENT(in   ) ::   pahs1, pahs2   ! surface value of eddy coefficient   [m2/s]
53      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pah1 , pah2    ! eddy coefficient                    [m2/s]
54      !
55      INTEGER  ::   ji, jj, jk      ! dummy loop indices
56      REAL(wp) ::   zh, zc, zdep1   ! local scalars
57      REAL(wp) ::   zw    , zdep2   !   -      -
58      !!----------------------------------------------------------------------
59
60      ! initialization of the profile
61      zh =  500._wp              ! depth    of the inflection point [m]
62      zw =  1._wp / 200._wp      ! width^-1     -        -      -   [1/m]
63      !                          ! associated coefficient           [-]
64      zc = ( 1._wp - prat ) / ( 1._wp + TANH( zh * zw) )
65      !
66      !
67      SELECT CASE( cd_type )        ! point of calculation
68      !
69      CASE( 'DYN' )                     ! T- and F-points
70         DO jk = 1, jpk                      ! pah1 at T-point
71            pah1(:,:,jk) = pahs1(:,:) * (  prat + zc * ( 1._wp + TANH( - ( fsdept(:,:,jk) - zh ) * zw) )  ) * tmask(:,:,jk)
72         END DO
73         DO jk = 1, jpk                      ! pah2 at F-point (zdep2 is an approximation in zps-coord.)
74            DO jj = 1, jpjm1
75               DO ji = 1, fs_jpim1
76                  zdep2 = (  fsdept(ji,jj+1,jk) + fsdept(ji+1,jj+1,jk)   &
77                     &     + fsdept(ji,jj  ,jk) + fsdept(ji+1,jj  ,jk)  ) * 0.25_wp
78                  pah2(ji,jj,jk) = pahs2(ji,jj) * (  prat + zc * ( 1._wp + TANH( - ( zdep2 - zh ) * zw) )  ) * fmask(ji,jj,jk)
79               END DO
80            END DO
81         END DO
82         CALL lbc_lnk( pah2, 'F', 1. )   ! Lateral boundary conditions
83         !
84      CASE( 'TRA' )                     ! U- and V-points (zdep1 & 2 are an approximation in zps-coord.)
85         DO jk = 1, jpk
86            DO jj = 1, jpjm1
87               DO ji = 1, fs_jpim1
88                  zdep1 = (  fsdept(ji,jj,jk) + fsdept(ji+1,jj,jk)  ) * 0.5_wp
89                  zdep2 = (  fsdept(ji,jj,jk) + fsdept(ji,jj+1,jk)  ) * 0.5_wp
90                  pah1(ji,jj,jk) = pahs1(ji,jj) * (  prat + zc * ( 1._wp + TANH( - ( zdep1 - zh ) * zw) )  ) * umask(ji,jj,jk)
91                  pah2(ji,jj,jk) = pahs2(ji,jj) * (  prat + zc * ( 1._wp + TANH( - ( zdep2 - zh ) * zw) )  ) * vmask(ji,jj,jk)
92               END DO
93            END DO
94         END DO
95         CALL lbc_lnk( pah1, 'U', 1. )   ! Lateral boundary conditions
96         CALL lbc_lnk( pah2, 'V', 1. )   
97         !
98      END SELECT
99      !
100   END SUBROUTINE ldf_c1d
101
102   !!======================================================================
103END MODULE ldfc1d
Note: See TracBrowser for help on using the repository browser.