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.
abl.F90 in NEMO/trunk/src/ABL – NEMO

source: NEMO/trunk/src/ABL/abl.F90 @ 13237

Last change on this file since 13237 was 13214, checked in by smasson, 4 years ago

trunk: Mid-year merge, merge back dev_r12563_ASINTER-06_ABL_improvement

File size: 4.3 KB
Line 
1MODULE abl
2   !!======================================================================
3   !!                      ***  MODULE  abl  ***
4   !! Abl        :  ABL dynamics and active tracers defined in memory
5   !!======================================================================
6   !! History :  4.0  !  2019-03  (F. Lemarié & G. Samson)  Original code
7   !!----------------------------------------------------------------------
8   USE par_abl        ! abl parameters
9   USE lib_mpp        ! MPP library
10   USE dom_oce, ONLY: glamt, gphit               ! latitude/longitude
11   USE dom_oce, ONLY: e1t, e1u, e1v, e1f         ! scale factors for horizontal grid
12   USE dom_oce, ONLY: e2t, e2u, e2v, e2f         !
13   USE dom_oce, ONLY: rn_Dt                      ! oceanic time-step
14   USE sbc_oce, ONLY: ght_abl, ghw_abl, e3t_abl, e3w_abl, jpka   ! scale factors and altitudes of ABL grid points in the vertical
15 
16   IMPLICIT NONE
17   PRIVATE
18
19   PUBLIC abl_alloc ! routine called by nemo_init in nemogcm.F90
20
21   !! ABL dynamics and tracer fields                            !
22   !! --------------------------                            !
23   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:,:)   ::   u_abl        !: i-horizontal velocity   [m/s]
24   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:,:)   ::   v_abl        !: j-horizontal velocity   [m/s]
25   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:,:,:) ::   tq_abl       !: 4D T-q fields           [Kelvin,kg/kg]
26   
27   !! ABL TKE closure scheme                            !
28   !! --------------------------       
29   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:)     ::   avm_abl      !: turbulent viscosity   [m2/s]
30   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:)     ::   avt_abl      !: turbulent diffusivity [m2/s]
31   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:)     ::   mxld_abl     !: dissipative mixing length    [m]
32   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:)     ::   mxlm_abl     !: master mixing length         [m]
33   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:,:)   ::   tke_abl      !: turbulent kinetic energy [m2/s2]
34   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)       ::   fft_abl      !: Coriolis parameter    [1/s]
35   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)       ::   pblh         !: PBL height            [m]
36
37   !! ABL Land/sea mask and restoring term                           !
38   !! --------------------------     
39   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)       ::   msk_abl
40   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)       ::   rest_eq
41   !
42   INTEGER , PUBLIC :: nt_n, nt_a       !: now / after indices (equal 1 or 2)
43   !
44   !!----------------------------------------------------------------------
45   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
46   !! $Id: abl.F90 4990 2014-12-15 16:42:49Z timgraham $
47   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
48   !!----------------------------------------------------------------------
49CONTAINS
50
51   INTEGER FUNCTION abl_alloc()
52      !!----------------------------------------------------------------------
53      !!                   ***  FUNCTION abl_alloc  ***
54      !!----------------------------------------------------------------------
55      INTEGER :: ierr
56      !!----------------------------------------------------------------------
57      !
58      ALLOCATE( u_abl   (1:jpi,1:jpj,1:jpka,jptime     ), &
59         &      v_abl   (1:jpi,1:jpj,1:jpka,jptime     ), &
60         &      tq_abl  (1:jpi,1:jpj,1:jpka,jptime,jptq), &
61         &      tke_abl (1:jpi,1:jpj,1:jpka,jptime     ), &
62         &      avm_abl (1:jpi,1:jpj,1:jpka            ), &
63         &      avt_abl (1:jpi,1:jpj,1:jpka            ), &
64         &      mxld_abl(1:jpi,1:jpj,1:jpka            ), &
65         &      mxlm_abl(1:jpi,1:jpj,1:jpka            ), &
66         &      fft_abl (1:jpi,1:jpj                   ), &
67         &      pblh    (1:jpi,1:jpj                   ), &
68         &      msk_abl (1:jpi,1:jpj                   ), &
69         &      rest_eq (1:jpi,1:jpj                   ), &
70         &      e3t_abl (1:jpka), e3w_abl(1:jpka)       , &
71         &      ght_abl (1:jpka), ghw_abl(1:jpka)       , STAT=ierr )
72         !
73      abl_alloc = ierr
74      IF( abl_alloc /= 0 )   CALL ctl_warn('abl_alloc: failed to allocate arrays')
75      !
76   END FUNCTION abl_alloc
77
78   !!======================================================================
79END MODULE abl
Note: See TracBrowser for help on using the repository browser.