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.
dynldf_lap.F90 in branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/DYN – NEMO

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/DYN/dynldf_lap.F90 @ 11738

Last change on this file since 11738 was 11738, checked in by marc, 5 years ago

The Dr Hook changes from my perl code.

File size: 5.3 KB
Line 
1MODULE dynldf_lap
2   !!======================================================================
3   !!                       ***  MODULE  dynldf_lap  ***
4   !! Ocean dynamics:  lateral viscosity trend
5   !!======================================================================
6   !! History :  OPA  ! 1990-09 (G. Madec) Original code
7   !!            4.0  ! 1991-11 (G. Madec)
8   !!            6.0  ! 1996-01 (G. Madec) statement function for e3 and ahm
9   !!   NEMO     1.0  ! 2002-06 (G. Madec)  F90: Free form and module
10   !!             -   ! 2004-08 (C. Talandier) New trends organization
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   dyn_ldf_lap  : update the momentum trend with the lateral diffusion
15   !!                  using an iso-level harmonic operator
16   !!----------------------------------------------------------------------
17   USE oce             ! ocean dynamics and tracers
18   USE dom_oce         ! ocean space and time domain
19   USE ldfdyn_oce      ! ocean dynamics: lateral physics
20   USE zdf_oce         ! ocean vertical physics
21   !
22   USE in_out_manager  ! I/O manager
23   USE timing          ! Timing
24
25   USE yomhook, ONLY: lhook, dr_hook
26   USE parkind1, ONLY: jprb, jpim
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC dyn_ldf_lap  ! called by step.F90
32
33   !! * Substitutions
34#  include "domzgr_substitute.h90"
35#  include "ldfdyn_substitute.h90"
36#  include "vectopt_loop_substitute.h90"
37   !!----------------------------------------------------------------------
38   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
39   !! $Id$
40   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
41   !!----------------------------------------------------------------------
42CONTAINS
43
44   SUBROUTINE dyn_ldf_lap( kt )
45      !!----------------------------------------------------------------------
46      !!                     ***  ROUTINE dyn_ldf_lap  ***
47      !!                       
48      !! ** Purpose :   Compute the before horizontal tracer (t & s) diffusive
49      !!      trend and add it to the general trend of tracer equation.
50      !!
51      !! ** Method  :   The before horizontal momentum diffusion trend is an
52      !!      harmonic operator (laplacian type) which separates the divergent
53      !!      and rotational parts of the flow.
54      !!      Its horizontal components are computed as follow:
55      !!         difu = 1/e1u di[ahmt hdivb] - 1/(e2u*e3u) dj-1[e3f ahmf rotb]
56      !!         difv = 1/e2v dj[ahmt hdivb] + 1/(e1v*e3v) di-1[e3f ahmf rotb]
57      !!      in the rotational part of the diffusion.
58      !!      Add this before trend to the general trend (ua,va):
59      !!            (ua,va) = (ua,va) + (diffu,diffv)
60      !!
61      !! ** Action : - Update (ua,va) with the iso-level harmonic mixing trend
62      !!----------------------------------------------------------------------
63      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
64      !
65      INTEGER  ::   ji, jj, jk             ! dummy loop indices
66      REAL(wp) ::   zua, zva, ze2u, ze1v   ! local scalars
67      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
68      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
69      REAL(KIND=jprb)               :: zhook_handle
70
71      CHARACTER(LEN=*), PARAMETER :: RoutineName='DYN_LDF_LAP'
72
73      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
74
75      !!----------------------------------------------------------------------
76      !
77      IF( nn_timing == 1 )  CALL timing_start('dyn_ldf_lap')
78      !
79      IF( kt == nit000 ) THEN
80         IF(lwp) WRITE(numout,*)
81         IF(lwp) WRITE(numout,*) 'dyn_ldf : iso-level harmonic (laplacian) operator'
82         IF(lwp) WRITE(numout,*) '~~~~~~~ '
83      ENDIF
84      !                                                ! ===============
85      DO jk = 1, jpkm1                                 ! Horizontal slab
86         !                                             ! ===============
87         DO jj = 2, jpjm1
88            DO ji = fs_2, fs_jpim1   ! vector opt.
89               ze2u = rotb (ji,jj,jk) * fsahmf(ji,jj,jk) * fse3f(ji,jj,jk)
90               ze1v = hdivb(ji,jj,jk) * fsahmt(ji,jj,jk)
91               ! horizontal diffusive trends
92               zua = - ( ze2u - rotb (ji,jj-1,jk)*fsahmf(ji,jj-1,jk)*fse3f(ji,jj-1,jk) ) / ( e2u(ji,jj) * fse3u(ji,jj,jk) )   &
93                     + ( hdivb(ji+1,jj,jk)*fsahmt(ji+1,jj,jk) - ze1v                   ) / e1u(ji,jj)
94
95               zva = + ( ze2u - rotb (ji-1,jj,jk)*fsahmf(ji-1,jj,jk)*fse3f(ji-1,jj,jk) ) / ( e1v(ji,jj) * fse3v(ji,jj,jk) )   &
96                     + ( hdivb(ji,jj+1,jk)*fsahmt(ji,jj+1,jk) - ze1v                   ) / e2v(ji,jj)
97
98               ! add it to the general momentum trends
99               ua(ji,jj,jk) = ua(ji,jj,jk) + zua
100               va(ji,jj,jk) = va(ji,jj,jk) + zva
101            END DO
102         END DO
103         !                                             ! ===============
104      END DO                                           !   End of slab
105      !                                                ! ===============
106      IF( nn_timing == 1 )  CALL timing_stop('dyn_ldf_lap')
107      !
108      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
109   END SUBROUTINE dyn_ldf_lap
110
111   !!======================================================================
112END MODULE dynldf_lap
Note: See TracBrowser for help on using the repository browser.