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

source: trunk/NEMO/OFF_SRC/TRA/trabbl.F90 @ 325

Last change on this file since 325 was 325, checked in by opalod, 19 years ago

Initial revision

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