SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
isba_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 isba_canopy (I, &
7  ki,klvl,pz,pzf,pdz,pdzf,pheight,pcanopy_density,pu,ptke, &
8  puw_ground, pduwdu_ground, &
9  pforc_u,pdforc_udu,pforc_e,pdforc_ede)
10 ! ###############################################################################
11 !
12 !!**** *ISBA_CANOPY_n * - prepares forcing for canopy air model
13 !!
14 !! PURPOSE
15 !! -------
16 !
17 !!** METHOD
18 !! ------
19 !!
20 !! REFERENCE
21 !! ---------
22 !!
23 !!
24 !! AUTHOR
25 !! ------
26 !! V. Masson
27 !!
28 !! MODIFICATIONS
29 !! -------------
30 !! Original 07/2006
31 !!---------------------------------------------------------------
32 !
33 !
34 USE modd_isba_n, ONLY : isba_t
35 !
36 USE modd_csts, ONLY : xrd, xcpd, xp00, xg
37 USE modd_surf_par, ONLY : xundef
38 !
39 USE yomhook ,ONLY : lhook, dr_hook
40 USE parkind1 ,ONLY : jprb
41 !
42 USE modi_canopy
43 !
44 IMPLICIT NONE
45 !
46 !* 0.1 declarations of arguments
47 !
48 !
49 TYPE(isba_t), INTENT(INOUT) :: i
50 !
51 INTEGER, INTENT(IN) :: ki ! number of points
52 INTEGER, INTENT(IN) :: klvl ! number of levels in canopy
53 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pz ! heights of canopy levels (m)
54 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pzf ! heights of bottom of canopy levels (m)
55 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pdz ! depth of canopy levels (m)
56 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pdzf ! depth between canopy levels (m)
57 REAL, DIMENSION(KI), INTENT(IN) :: pheight ! canopy height (m)
58 REAL, DIMENSION(KI), INTENT(IN) :: pcanopy_density ! canopy density (-)
59 
60 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pu ! wind for each canopy layer (m/s)
61 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: ptke ! Tke for each canopy layer (m2/s2)
62 !
63 REAL, DIMENSION(KI), INTENT(IN) :: puw_ground ! friction flux for ground surface (m2/s2)
64 REAL, DIMENSION(KI), INTENT(IN) :: pduwdu_ground ! derivative of ground friction flux (m/s)
65 !
66 REAL, DIMENSION(KI,KLVL), INTENT(OUT) :: pforc_u ! tendency of wind due to canopy drag (m/s2)
67 REAL, DIMENSION(KI,KLVL), INTENT(OUT) :: pdforc_udu! formal derivative of the tendency of
68 ! ! wind due to canopy drag (1/s)
69 REAL, DIMENSION(KI,KLVL), INTENT(OUT) :: pforc_e ! tendency of TKE due to canopy drag (m2/s3)
70 REAL, DIMENSION(KI,KLVL), INTENT(OUT) :: pdforc_ede! formal derivative of the tendency of
71 ! ! TKE due to canopy drag (1/s)
72 !
73 !* 0.2 declarations of local variables
74 !
75 INTEGER :: jlayer, jj ! loop counter on canopy heights
76 !
77 REAL, DIMENSION(KI,KLVL) :: zcdrag ! drag coefficient in canopy
78 REAL, DIMENSION(KI,KLVL) :: zdensity ! vegetation density for each canopy level
79 REAL, DIMENSION(KI,KLVL) :: zsv ! vertical surface for each canopy level
80 REAL, DIMENSION(KI,KLVL) :: zforc
81 REAL, DIMENSION(KI,KLVL) :: zairvol ! Fraction of air for each canopy level total volume
82 REAL(KIND=JPRB) :: zhook_handle
83 !
84 !-------------------------------------------------------------------------------------
85 !
86 !* 1. Computations of canopy grid characteristics
87 ! -------------------------------------------
88 !
89 !
90 !* 1.1 Proportion of leaves for each canopy level
91 ! (parabolic shape, maximum at mid canopy height, with the same
92 ! total LAI on the canopy)
93 !
94 IF (lhook) CALL dr_hook('ISBA_CANOPY',0,zhook_handle)
95 zdensity(:,:) = 0.
96 DO jlayer = 1,klvl
97  DO jj = 1,ki
98  IF (pheight(jj)>0.) THEN
99  zdensity(jj,jlayer) = 1.5 * &
100  max( pcanopy_density(jj)*4.*pz(jj,jlayer)*(pheight(jj)-pz(jj,jlayer))/pheight(jj)**2, 0.)
101  ENDIF
102  ENDDO
103 END DO
104 !
105 !* 2.1 Drag coefficient by vegetation (Patton et al 2001)
106 ! ------------------------------
107 !
108 zcdrag(:,:) = i%XCDRAG
109 !
110 !* 1.4 No building volume
111 !
112 ! * in order to take into account building volume, further developments must be
113 ! done in the atmospheric model.
114 ! If these changes are not done, to take into account building volume in the
115 ! present routine alone would not be energetically coeherent (there would be
116 ! too much energy release for heat and vapor or consumed for wind).
117 !
118 zairvol(:,:) = 1.
119 !
120 !* 1.2 Discretization on each canopy level
121 !
122  CALL canopy(ki, klvl, pzf, pdz, pheight, zdensity, zcdrag, pu, zairvol, &
123  zsv, zforc, pforc_u, pdforc_udu, pforc_e, pdforc_ede )
124 !
125 !
126 !* 2.4 Drag force by ground surface
127 ! ----------------------------
128 !
129 pforc_u(:,1) = puw_ground(:) / pdz(:,1)
130 pdforc_udu(:,1) = pdforc_udu(:,1) + pduwdu_ground(:) / pdz(:,1)
131 
132 !-------------------------------------------------------------------------------------
133 !
134 !* 3.2 Destruction of TKE due to small-scale motions forced by leaves
135 ! --------------------------------------------------------------
136 !
137 ! from Kanda and Hino (1994)
138 !
139 ! Ext = - Cd * e * u * Sv trees
140 !
141 pforc_e(:,:) = pforc_e - 2.*ptke(:,:)*zforc(:,:)
142 pdforc_ede(:,:) = pdforc_ede - 2.*zforc(:,:)
143 !
144 IF (lhook) CALL dr_hook('ISBA_CANOPY',1,zhook_handle)
145 !-------------------------------------------------------------------------------------
146 !
147 END SUBROUTINE isba_canopy
subroutine isba_canopy(I, KI, KLVL, PZ, PZF, PDZ, PDZF, PHEIGHT, PCANOPY_DENSITY, PU, PTKE, PUW_GROUND, PDUWDU_GROUND, PFORC_U, PDFORC_UDU, PFORC_E, PDFORC_EDE)
Definition: isba_canopy.F90:6
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