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.
traldf_blp.F90 in branches/UKMO/r5936_restart_datestamp/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/UKMO/r5936_restart_datestamp/NEMOGCM/NEMO/OPA_SRC/TRA/traldf_blp.F90 @ 7106

Last change on this file since 7106 was 7106, checked in by jcastill, 7 years ago

Remove svn keywords

File size: 8.3 KB
Line 
1MODULE traldf_blp
2   !!======================================================================
3   !!                   ***  MODULE  traldf_blp  ***
4   !! Ocean  tracers:  bilaplacian lateral mixing trend on tracers
5   !!======================================================================
6   !! History :  3.7  ! 2015-09  (G. Madec)  original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   traldf_blp    : update the tracer trend with the bilaplacian lateral mixing trend
11   !!----------------------------------------------------------------------
12   USE oce            ! ocean dynamics and active tracers
13   USE dom_oce        ! ocean space and time domain
14   USE phycst         ! physical constants
15   USE trc_oce        ! share passive tracers/Ocean variables
16   USE zdf_oce        ! ocean vertical physics
17   USE ldftra         ! lateral physics: eddy diffusivity
18   USE ldfslp         ! lateral physics: iso-neutral slopes
19   USE traldf_lap     ! lateral diffusion (Standard operator)         (tra_ldf_lap   routine)
20   USE traldf_iso     ! lateral diffusion (Standard operator)         (tra_ldf_iso   routine)
21   USE traldf_triad   ! lateral diffusion (Standard operator)         (tra_ldf_triad routine)
22   USE diaptr         ! poleward transport diagnostics
23   USE zpshde         ! partial step: hor. derivative     (zps_hde routine)
24   !
25   USE in_out_manager ! I/O manager
26   USE iom            ! I/O library
27   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
28   USE lib_mpp        ! MPP library
29   USE wrk_nemo       ! Memory Allocation
30   USE timing         ! Timing
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC   tra_ldf_blp   ! routine called by traldf.F90
36
37   !                      ! Flag to control the type of lateral diffusive operator
38   INTEGER, PARAMETER, PUBLIC ::   np_ERROR  =-10   ! error in specification of lateral diffusion
39   INTEGER, PARAMETER, PUBLIC ::   np_no_ldf = 00   ! without operator (i.e. no lateral diffusive trend)
40   !                          !!      laplacian     !    bilaplacian    !
41   INTEGER, PARAMETER, PUBLIC ::   np_lap    = 10   ,   np_blp    = 20  ! iso-level operator
42   INTEGER, PARAMETER, PUBLIC ::   np_lap_i  = 11   ,   np_blp_i  = 21  ! standard iso-neutral or geopotential operator
43   INTEGER, PARAMETER, PUBLIC ::   np_lap_it = 12   ,   np_blp_it = 22  ! triad    iso-neutral or geopotential operator
44
45   REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE ::   zdkt3d   !: vertical tracer gradient at 2 levels
46
47   !! * Substitutions
48#  include "domzgr_substitute.h90"
49#  include "vectopt_loop_substitute.h90"
50   !!----------------------------------------------------------------------
51   !! NEMO/OPA 3.7 , NEMO Consortium (2015)
52   !! $Id$
53   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
54   !!----------------------------------------------------------------------
55CONTAINS
56
57   SUBROUTINE tra_ldf_blp( kt, kit000, cdtype, pahu, pahv, pgu , pgv ,   &
58      &                                                    pgui, pgvi,   &
59      &                                                    ptb , pta , kjpt, kldf )
60      !!----------------------------------------------------------------------
61      !!                 ***  ROUTINE tra_ldf_blp  ***
62      !!                   
63      !! ** Purpose :   Compute the before lateral tracer diffusive
64      !!      trend and add it to the general trend of tracer equation.
65      !!
66      !! ** Method  :   The lateral diffusive trends is provided by a bilaplacian
67      !!      operator applied to before field (forward in time).
68      !!      It is computed by two successive calls to laplacian routine
69      !!
70      !! ** Action :   pta   updated with the before rotated bilaplacian diffusion
71      !!----------------------------------------------------------------------
72      INTEGER                              , INTENT(in   ) ::   kt         ! ocean time-step index
73      INTEGER                              , INTENT(in   ) ::   kit000     ! first time step index
74      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype     ! =TRA or TRC (tracer indicator)
75      INTEGER                              , INTENT(in   ) ::   kjpt       ! number of tracers
76      INTEGER                              , INTENT(in   ) ::   kldf       ! type of operator used
77      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   pahu, pahv ! eddy diffusivity at u- and v-points  [m2/s]
78      REAL(wp), DIMENSION(jpi,jpj    ,kjpt), INTENT(in   ) ::   pgu, pgv   ! tracer gradient at pstep levels
79      REAL(wp), DIMENSION(jpi,jpj,    kjpt), INTENT(in   ) ::   pgui, pgvi ! tracer gradient at top levels
80      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb        ! before and now tracer fields
81      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pta        ! tracer trend
82      !
83      INTEGER ::   ji, jj, jk, jn   ! dummy loop indices
84      REAL(wp), POINTER, DIMENSION(:,:,:,:) :: zlap         ! laplacian at t-point
85      REAL(wp), POINTER, DIMENSION(:,:,:)   :: zglu, zglv   ! bottom GRADh of the laplacian (u- and v-points)
86      REAL(wp), POINTER, DIMENSION(:,:,:)   :: zgui, zgvi   ! top    GRADh of the laplacian (u- and v-points)
87      !!---------------------------------------------------------------------
88      !
89      IF( nn_timing == 1 )  CALL timing_start('tra_ldf_blp')
90      !
91      CALL wrk_alloc( jpi,jpj,jpk,kjpt,   zlap ) 
92      CALL wrk_alloc( jpi,jpj,    kjpt,   zglu, zglv, zgui, zgvi ) 
93      !
94      IF( kt == kit000 .AND. lwp )  THEN
95         WRITE(numout,*)
96         SELECT CASE ( kldf )
97         CASE ( np_blp    )   ;   WRITE(numout,*) 'tra_ldf_blp : iso-level   bilaplacian operator on ', cdtype
98         CASE ( np_blp_i  )   ;   WRITE(numout,*) 'tra_ldf_blp : iso-neutral bilaplacian operator on ', cdtype, ' (Standard)'
99         CASE ( np_blp_it )   ;   WRITE(numout,*) 'tra_ldf_blp : iso-neutral bilaplacian operator on ', cdtype, ' (triad)'
100         END SELECT
101         WRITE(numout,*) '~~~~~~~~~~~'
102      ENDIF
103
104      zlap(:,:,:,:) = 0._wp
105      !
106      SELECT CASE ( kldf )       !==  1st laplacian applied to ptb (output in zlap)  ==!
107      !
108      CASE ( np_blp    )               ! iso-level bilaplacian
109         CALL tra_ldf_lap  ( kt, kit000, cdtype, pahu, pahv, pgu, pgv, pgui, pgvi, ptb,      zlap, kjpt, 1 )
110         !
111      CASE ( np_blp_i  )               ! rotated   bilaplacian : standard operator (Madec)
112         CALL tra_ldf_iso  ( kt, kit000, cdtype, pahu, pahv, pgu, pgv, pgui, pgvi, ptb, ptb, zlap, kjpt, 1 )
113         !
114      CASE ( np_blp_it )               ! rotated  bilaplacian : triad operator (griffies)
115         CALL tra_ldf_triad( kt, kit000, cdtype, pahu, pahv, pgu, pgv, pgui, pgvi, ptb, ptb, zlap, kjpt, 1 )
116         !
117      END SELECT
118      !
119      DO jn = 1, kjpt
120         CALL lbc_lnk( zlap(:,:,:,jn) , 'T', 1. )     ! Lateral boundary conditions (unchanged sign)
121      END DO
122      !                                               ! Partial top/bottom cell: GRADh( zlap ) 
123      IF( ln_isfcav .AND. ln_zps ) THEN   ;   CALL zps_hde_isf( kt, kjpt, zlap, zglu, zglv, zgui, zgvi )  ! both top & bottom
124      ELSEIF(             ln_zps ) THEN   ;   CALL zps_hde    ( kt, kjpt, zlap, zglu, zglv )              ! only bottom
125      ENDIF
126      !
127      SELECT CASE ( kldf )       !==  2nd laplacian applied to zlap (output in pta)  ==!
128      !
129      CASE ( np_blp    )               ! iso-level bilaplacian
130         CALL tra_ldf_lap  ( kt, kit000, cdtype, pahu, pahv, zglu, zglv, zgui, zgvi, zlap, pta,      kjpt, 2 )
131         !
132      CASE ( np_blp_i  )               ! rotated   bilaplacian : standard operator (Madec)
133         CALL tra_ldf_iso  ( kt, kit000, cdtype, pahu, pahv, zglu, zglv, zgui, zgvi, zlap, ptb, pta, kjpt, 2 )
134         !
135      CASE ( np_blp_it )               ! rotated  bilaplacian : triad operator (griffies)
136         CALL tra_ldf_triad( kt, kit000, cdtype, pahu, pahv, zglu, zglv, zgui, zgvi, zlap, ptb, pta, kjpt, 2 )
137         !
138      END SELECT
139      !
140      CALL wrk_dealloc( jpi,jpj,jpk,kjpt,   zlap ) 
141      CALL wrk_dealloc( jpi,jpj    ,kjpt,   zglu, zglv, zgui, zgvi ) 
142      !
143      IF( nn_timing == 1 )  CALL timing_stop('tra_ldf_blp')
144      !
145   END SUBROUTINE tra_ldf_blp
146
147   !!==============================================================================
148END MODULE traldf_blp
Note: See TracBrowser for help on using the repository browser.