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.
trabbl.F90 in tags/nemo_v3_2/nemo_v3_2/NEMO/OFF_SRC/TRA – NEMO

source: tags/nemo_v3_2/nemo_v3_2/NEMO/OFF_SRC/TRA/trabbl.F90 @ 1878

Last change on this file since 1878 was 1878, checked in by flavoni, 14 years ago

initial test for nemogcm

File size: 6.1 KB
Line 
1MODULE trabbl
2   !!==============================================================================
3   !!                       ***  MODULE  trabbl  ***
4   !! Ocean physics :  advective and/or diffusive bottom boundary layer scheme
5   !!==============================================================================
6#if   defined key_trabbl_dif   ||   defined key_trabbl_adv   || defined key_esopa
7   !!----------------------------------------------------------------------
8   !!   'key_trabbl_dif'   or            diffusive bottom boundary layer
9   !!----------------------------------------------------------------------
10   !!   tra_bbl_dif  : update the active tracer trends due to the bottom
11   !!                  boundary layer (diffusive only)
12   !!   tra_bbl_init : initialization, namlist read, parameters control
13   !!----------------------------------------------------------------------
14   !!   OPA 9.0 , LOCEAN-IPSL  (2005)
15   !!   $Id: trabbl.F90 1152 2008-06-26 14:11:13Z rblod $
16   !!   This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
17   !!----------------------------------------------------------------------
18   !! * Modules used
19   USE in_out_manager  ! I/O manager
20
21   IMPLICIT NONE
22   PRIVATE
23
24   !! * Routine accessibility
25   PUBLIC tra_bbl_dif    ! routine called by step.F90
26
27   !! * Shared module variables
28   REAL(wp), PUBLIC ::            &  !!: * bbl namelist *
29      atrbbl = 1.e+3                  !: lateral coeff. for bottom boundary
30      !                               !  layer scheme (m2/s)
31   REAL(wp) , PUBLIC , DIMENSION(jpi,jpj) :: &
32      bblx, bbly    ! Bottom boundary layer coefficients
33
34   !! * Substitutions
35#  include "domzgr_substitute.h90"
36#  include "vectopt_loop_substitute.h90"
37
38CONTAINS
39
40   SUBROUTINE tra_bbl_dif( kt )
41      !!----------------------------------------------------------------------
42      !!                   ***  ROUTINE tra_bbl_dif  ***
43      !!
44      !! ** Purpose :   Compute the before tracer (t & s) trend associated
45      !!      with the bottom boundary layer and add it to the general trend
46      !!      of tracer equations. The bottom boundary layer is supposed to be
47      !!      a purely diffusive bottom boundary layer.
48      !!
49      !! ** Method  :   When the product grad( rho) * grad(h) < 0 (where grad
50      !!      is an along bottom slope gradient) an additional lateral diffu-
51      !!      sive trend along the bottom slope is added to the general tracer
52      !!      trend, otherwise nothing is done.
53      !!      Second order operator (laplacian type) with variable coefficient
54      !!      computed as follow for temperature (idem on s):
55      !!         difft = 1/(e1t*e2t*e3t) { di-1[ ahbt e2u*e3u/e1u di[ztb] ]
56      !!                                 + dj-1[ ahbt e1v*e3v/e2v dj[ztb] ] }
57      !!      where ztb is a 2D array: the bottom ocean temperature and ahtb
58      !!      is a time and space varying diffusive coefficient defined by:
59      !!         ahbt = zahbp    if grad(rho).grad(h) < 0
60      !!              = 0.       otherwise.
61      !!      Note that grad(.) is the along bottom slope gradient. grad(rho)
62      !!      is evaluated using the local density (i.e. referenced at the
63      !!      local depth). Typical value of ahbt is 2000 m2/s (equivalent to
64      !!      a downslope velocity of 20 cm/s if the condition for slope
65      !!      convection is satified)
66      !!      Add this before trend to the general trend (ta,sa) of the
67      !!      botton ocean tracer point:
68      !!         ta = ta + difft
69      !!
70      !! ** Action  : - update (ta,sa) at the bottom level with the bottom
71      !!                boundary layer trend
72      !!              - save the trends in bbltrd ('key_diatrends')
73      !!
74      !! References :
75      !!     Beckmann, A., and R. Doscher, 1997, J. Phys.Oceanogr., 581-591.
76      !!
77      !! History :
78      !!   8.0  !  96-06  (L. Mortier)  Original code
79      !!   8.0  !  97-11  (G. Madec)  Optimization
80      !!   8.5  !  02-08  (G. Madec)  free form + modules
81      !!----------------------------------------------------------------------
82      !! * Arguments
83      INTEGER, INTENT( in ) ::   kt         ! ocean time-step
84
85      !!----------------------------------------------------------------------
86
87      IF( kt == nit000 )   CALL tra_bbl_init
88
89   END SUBROUTINE tra_bbl_dif
90
91   SUBROUTINE tra_bbl_init
92      !!----------------------------------------------------------------------
93      !!                  ***  ROUTINE tra_bbl_init  ***
94      !!
95      !! ** Purpose :   Initialization for the bottom boundary layer scheme.
96      !!
97      !! ** Method  :   Read the nam_bbl namelist and check the parameters
98      !!      called by tra_bbl at the first timestep (nit000)
99      !!
100      !! History :
101      !!    8.5  !  02-08  (G. Madec)  Original code
102      !!----------------------------------------------------------------------
103      !! * Local declarations
104      NAMELIST/nambbl/ atrbbl
105      !!----------------------------------------------------------------------
106
107      ! Read Namelist nam_bbl : bottom boundary layer scheme
108      ! --------------------
109      REWIND ( numnam )
110      READ   ( numnam, nambbl )
111
112      ! Parameter control and print
113      ! ---------------------------
114      IF(lwp) THEN
115         WRITE(numout,*)
116         WRITE(numout,*)
117         WRITE(numout,*) 'tra_bbl_init : * Diffusive Bottom Boundary Layer'
118         WRITE(numout,*) '~~~~~~~~~~~~'
119         WRITE(numout,*) '          Namelist nambbl : set bbl parameters'
120         WRITE(numout,*)
121         WRITE(numout,*) '          bottom boundary layer coef.    atrbbl = ', atrbbl
122         WRITE(numout,*)
123      ENDIF
124 
125   END SUBROUTINE tra_bbl_init
126
127#else
128   !!----------------------------------------------------------------------
129   !!   Dummy module :                      No bottom boundary layer scheme
130   !!----------------------------------------------------------------------
131CONTAINS
132   SUBROUTINE tra_bbl_dif (kt )              ! Empty routine
133      INTEGER, INTENT(in) :: kt
134      WRITE(*,*) 'tra_bbl_dif: You should not have seen this print! error?', kt
135   END SUBROUTINE tra_bbl_dif
136#endif
137
138   !!======================================================================
139END MODULE trabbl
Note: See TracBrowser for help on using the repository browser.