SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
canopy.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 canopy(KI, KLVL, PZF, PDZ, PHEIGHT, PDENSITY, PCDRAG, PU, PAIRVOL, &
7  psv, pforc, pforc_u, pdforc_udu, pforc_e, pdforc_ede )
8 ! ###############################################################################
9 !
10 !!**** *ISBA_CANOPY_n * - prepares forcing for canopy air model
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!** METHOD
16 !! ------
17 !!
18 !! REFERENCE
19 !! ---------
20 !!
21 !!
22 !! AUTHOR
23 !! ------
24 !! V. Masson
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 07/2006
29 !!---------------------------------------------------------------
30 !
31 !
32 USE modd_csts, ONLY : xrd, xcpd, xp00, xg
33 USE modd_surf_par, ONLY : xundef
34 !
35 !
36 USE yomhook ,ONLY : lhook, dr_hook
37 USE parkind1 ,ONLY : jprb
38 !
39 IMPLICIT NONE
40 !
41 !* 0.1 declarations of arguments
42 !
43 INTEGER, INTENT(IN) :: ki ! number of points
44 INTEGER, INTENT(IN) :: klvl ! number of levels in canopy
45 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pzf ! heights of bottom of canopy levels (m)
46 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pdz ! depth of canopy levels (m)
47 REAL, DIMENSION(KI), INTENT(IN) :: pheight ! canopy height (m)
48 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pdensity ! canopy density (-)
49 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pcdrag
50 !
51 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pu ! wind for each canopy layer (m/s)
52 !
53 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pairvol ! Fraction of air for each canopy level total volume
54 !
55 REAL, DIMENSION(KI,KLVL), INTENT(OUT) :: psv ! vertical surface of building
56  ! (walls) for each canopy level
57 REAL, DIMENSION(KI,KLVL), INTENT(OUT) :: pforc !
58 !
59 REAL, DIMENSION(KI,KLVL), INTENT(OUT) :: pforc_u ! tendency of wind due to canopy drag (m/s2)
60 REAL, DIMENSION(KI,KLVL), INTENT(OUT) :: pdforc_udu! formal derivative of the tendency of
61 ! ! wind due to canopy drag (1/s)
62 REAL, DIMENSION(KI,KLVL), INTENT(OUT) :: pforc_e ! tendency of TKE due to canopy drag (m2/s3)
63 REAL, DIMENSION(KI,KLVL), INTENT(OUT) :: pdforc_ede! formal derivative of the tendency of
64 ! ! TKE due to canopy drag (1/s)
65 !
66 !* 0.2 declarations of local variables
67 !
68 INTEGER :: jlayer ! loop counter on canopy heights
69 REAL(KIND=JPRB) :: zhook_handle
70 !
71 !-------------------------------------------------------------------------------------
72 !
73 IF (lhook) CALL dr_hook('CANOPY',0,zhook_handle)
74 !
75 !* 1. Computations of canopy grid characteristics
76 ! -------------------------------------------
77 !
78 !
79 !* 1.2 Discretization on each canopy level
80 !
81 psv(:,:) = 0.
82 DO jlayer = 1,klvl-1
83  !
84  WHERE ( pzf(:,jlayer) < pheight(:) )
85  psv(:,jlayer) = pdensity(:,jlayer) / pheight(:)
86  WHERE ( pzf(:,jlayer+1) > pheight(:) )
87  psv(:,jlayer) = psv(:,jlayer) * ( pheight(:) - pzf(:,jlayer) )
88  ELSEWHERE
89  psv(:,jlayer) = psv(:,jlayer) * pdz(:,jlayer)
90  END WHERE
91  END WHERE
92  !
93 END DO
94 !
95 pforc(:,:) = pcdrag(:,:) * pu(:,:) * psv(:,:)/pairvol(:,:)/pdz(:,:)
96 !
97 !-------------------------------------------------------------------------------------
98 !
99 !* 2. Computations of wind tendency due to canopy drag
100 ! ------------------------------------------------
101 !
102 pforc_u = 0.
103 pdforc_udu = 0.
104 !
105 ! Ext = - Cdrag * u- * u- * Sv tree canopy drag
106 ! - u'w'(ground) * Sh horizontal surfaces (ground)
107 !
108 !
109 !* 2.2 Drag force by wall surfaces
110 ! ---------------------------
111 !
112 !* drag force by vertical surfaces
113 !
114 pforc_u(:,:) = pforc_u - pforc(:,:) * pu(:,:)
115 pdforc_udu(:,:) = pdforc_udu - 2. * pforc(:,:)
116 !
117 !-------------------------------------------------------------------------------------
118 !
119 !* 3. Computations of TKE tendency due to canopy drag
120 ! ------------------------------------------------
121 !
122 !* Tendency due to drag for TKE
123 !
124 pforc_e(:,:) = 0.
125 pdforc_ede(:,:) = 0.
126 !
127 !* 3.1 Creation of TKE by wake
128 ! -----------------------
129 !
130 ! from Kanda and Hino (1994)
131 !
132 ! Ext = + Cd * u+^3 * Sv/Vair vertical surfaces or trees
133 !
134 ! with Vair = Vair/Vtot * Vtot = (Vair/Vtot) * Stot * Dz
135 ! and Sv/Vair = (Sv/Stot) * Stot/Vair = (Sv/Stot) / (Vair/Vtot) / Dz
136 !
137 pforc_e = pforc_e + pforc(:,:) * pu(:,:)**2
138 pdforc_ede = pdforc_ede + 0.
139 !
140 !
141 IF (lhook) CALL dr_hook('CANOPY',1,zhook_handle)
142 !
143 !-------------------------------------------------------------------------------------
144 !
145 END SUBROUTINE canopy
subroutine canopy(KI, KLVL, PZF, PDZ, PHEIGHT, PDENSITY, PCDRAG, PU, PAIRVOL, PSV, PFORC, PFORC_U, PDFORC_UDU, PFORC_E, PDFORC_EDE)
Definition: canopy.F90:6