SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
sm10.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! ###############################################################################
6 SUBROUTINE sm10(PZ,PBLD_HEIGHT,PLAMBDA_F,PL)
7 ! ###############################################################################
8 !
9 !!**** *SM10* computes the shape for the mixing length according to Santiago and Martilli 2010
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !!
21 !! AUTHOR
22 !! ------
23 !! V. Masson
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 06/2010
28 !!---------------------------------------------------------------
29 !
30 !
31 USE yomhook ,ONLY : lhook, dr_hook
32 USE parkind1 ,ONLY : jprb
33 !
34 IMPLICIT NONE
35 !
36 !* 0.1 declarations of arguments
37 !
38 REAL, DIMENSION(:,:), INTENT(IN) :: pz ! canopy levels (m)
39 REAL, DIMENSION(:), INTENT(IN) :: pbld_height ! building height (m)
40 REAL, DIMENSION(:), INTENT(IN) :: plambda_f ! frontal area density (-)
41 REAL, DIMENSION(:,:), INTENT(OUT) :: pl ! base profile for mixing
42 ! ! length computations (m)
43 !
44 !
45 !* 0.2 declarations of local variables
46 !
47 REAL, DIMENSION(SIZE(PZ,1)) :: zz_can ! mixing length generic profile in canopy
48 REAL, DIMENSION(SIZE(PZ,1),SIZE(PZ,2)):: zz_surf ! Mixing length generic profile at mid levels (near the surface)
49 REAL, DIMENSION(SIZE(PZ,1),SIZE(PZ,2)):: zz_isbl ! Mixing length generic profile at mid levels (in the inertial SBL)
50 REAL, DIMENSION(SIZE(PZ,1)) :: zz_base_isbl ! Mixing length generic at the base of the ISBL
51 REAL, DIMENSION(SIZE(PZ,1)) :: zdisp_h ! displacement height
52 REAL, PARAMETER :: zalpha_can = 1.12 ! value to compute lengths in the canyon
53 
54 INTEGER :: jlayer ! vertical loop counter
55 INTEGER :: ilvl ! number of layers
56 REAL(KIND=JPRB) :: zhook_handle
57 !
58 !-------------------------------------------------------------------------------------
59 !* Preliminaries:
60 IF (lhook) CALL dr_hook('SM10',0,zhook_handle)
61 ilvl = SIZE(pz,2)
62 !
63 !* Typical uniform value in the canopy (after Santiago and Martilli 2010)
64 ! Threshold at 3/4 of hte height of the building is added to avoid unphysical
65 ! values for large lambda_f.
66 !
67 zdisp_h(:) = min( plambda_f(:)**0.13 * pbld_height(:) , 0.75 * pbld_height )
68 zz_can(:) = zalpha_can * (pbld_height(:) - zdisp_h(:))
69 !
70 !* Lengths near the surface (road, gardens)
71 zz_surf(:,:) = pz(:,:)
72 !
73 !* Lengths in the inertial sublayer (z/h>1.5)
74 DO jlayer=1,ilvl
75  zz_isbl(:,jlayer) = max(zz_can(:), pz(:,jlayer) - zdisp_h(:))
76 END DO
77 ! first point is used to compute the value at the base of the ISBL (z/h=1.5)
78 zz_base_isbl(:) = max(pz(:,1), 1.5 * pbld_height(:) )
79 !
80 !* Composition of all these mixing lengths
81 DO jlayer=1,ilvl
82  WHERE (pz(:,jlayer)<=pbld_height(:))
83 !* inside canopy, lengths are equal to minimum between uniform value and value limited by the surface
84  pl(:,jlayer) = min(zz_surf(:,jlayer), zz_can(:))
85  END WHERE
86  WHERE (pz(:,jlayer)>zz_base_isbl(:) )
87 !* in the inertial sublayer
88  pl(:,jlayer) = zz_isbl(:,jlayer)
89  END WHERE
90  WHERE (pz(:,jlayer)>pbld_height(:) .AND. pz(:,jlayer)<=1.5*pbld_height(:))
91 !* in the transition sublayer
92  pl(:,jlayer) = zz_can(:) + (zz_isbl(:,jlayer)-zz_can(:)) &
93  * (pz(:,jlayer)-pbld_height(:)) / (zz_base_isbl(:) - pbld_height(:))
94  END WHERE
95 END DO
96 !
97 ! check if mixing length scale increases with height
98 !
99 DO jlayer=2,ilvl
100  pl(:,jlayer) = max(pl(:,jlayer-1),pl(:,jlayer))
101 END DO
102 IF (lhook) CALL dr_hook('SM10',1,zhook_handle)
103 !
104 !-------------------------------------------------------------------------------------
105 !
106 END SUBROUTINE sm10
subroutine sm10(PZ, PBLD_HEIGHT, PLAMBDA_F, PL)
Definition: sm10.F90:6