SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
canopy_evol_wind.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_evol_wind(KI,KLVL,PTSTEP,KIMPL,PWIND,PK,PDKDDVDZ, &
7  psflux_u,pforc_u,pdforc_udu,pdz,pdzf,pu,puw, &
8  palfa,pbeta )
9 ! #########################################
10 !
11 !!**** *CANOPY_EVOL_WIND* - evolution of wind in canopy
12 !!
13 !!
14 !! PURPOSE
15 !! -------
16 !!
17 !!** METHOD
18 !! ------
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !! REFERENCE
28 !! ---------
29 !!
30 !!
31 !! AUTHOR
32 !! ------
33 !! V. Masson *Meteo France*
34 !!
35 !! MODIFICATIONS
36 !! -------------
37 !! Original 07/2006
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 USE modi_canopy_evol_field
44 !
45 USE yomhook ,ONLY : lhook, dr_hook
46 USE parkind1 ,ONLY : jprb
47 !
48 IMPLICIT NONE
49 !
50 !* 0.1 Declarations of arguments
51 ! -------------------------
52 !
53 INTEGER, INTENT(IN) :: ki ! number of horizontal points
54 INTEGER, INTENT(IN) :: klvl ! number of levels in canopy
55 REAL, INTENT(IN) :: ptstep ! time-step (s)
56 INTEGER, INTENT(IN) :: kimpl ! implicitation code:
57 ! ! 1 : computes only alfa and beta coupling
58 ! ! coefficients for all variables
59 ! ! 2 : computes temporal evolution of the
60 ! ! variables
61 REAL, DIMENSION(KI), INTENT(IN) :: pwind ! wind at forcing level (m/s)
62 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pk ! mixing exchange coefficient (m2/s)
63 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pdkddvdz ! derivative of mixing coefficient as a
64 ! ! function of vertical gradient of wind
65 ! ! (at mid levels) (m2)
66 REAL, DIMENSION(KI), INTENT(IN) :: psflux_u ! Surface flux u'w' (m2/s2)
67 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pforc_u ! tendency of wind due to canopy drag (m/s2)
68 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pdforc_udu! formal derivative of the tendency of
69 ! ! wind due to canopy drag (1/s)
70 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pdz ! deltaZ between canopy half levels,
71 ! ! located at full levels (m)
72 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pdzf ! deltaZ between canopy (full) levels,
73 ! ! located at half levels (m)
74 REAL, DIMENSION(KI,KLVL), INTENT(INOUT) :: pu ! wind speed at canopy levels (m/s)
75 REAL, DIMENSION(KI,KLVL), INTENT(OUT) :: puw ! turbulent flux (at half levels) (m2/s2)
76 REAL, DIMENSION(KI), INTENT(OUT) :: palfa ! V+(1) = alfa u'w' + beta
77 REAL, DIMENSION(KI), INTENT(OUT) :: pbeta ! V+(1) = alfa u'w' + beta
78 !
79 !
80 !* 0.2 Declarations of local variables
81 ! -------------------------------
82 !
83 INTEGER :: jlayer ! loop counter on layers
84 !
85 REAL, DIMENSION(KI,KLVL) :: zdudz ! dU/dz at mid levels
86 REAL, DIMENSION(KI,KLVL) :: zf ! turbulent flux at mid levels
87 REAL, DIMENSION(KI,KLVL) :: zdfddvdz ! derivative of turbulent flux as a
88 ! ! function of vertical gradient of wind variable
89 ! ! (at mid levels)
90 REAL, DIMENSION(KI,KLVL) :: zext ! external forcing at full levels
91 REAL, DIMENSION(KI,KLVL) :: zdextdv ! derivative of external forcing as a
92 ! ! function of vertical variable
93 ! ! (at full levels)
94 REAL, DIMENSION(KI,KLVL) :: zu ! work variable : wind at futur instant
95 ! ! (or past at the end of the routine)
96 REAL, DIMENSION(KI) :: zduadt ! dUa/dt at forcing level
97 LOGICAL :: limpl
98 REAL(KIND=JPRB) :: zhook_handle
99 !
100 !-------------------------------------------------------------------------------
101 !
102 !
103 !* 1. initializations
104 ! ---------------
105 !
106 !* external forces
107 !
108 IF (lhook) CALL dr_hook('CANOPY_EVOL_WIND',0,zhook_handle)
109 zext = 0.
110 zdextdv = 0.
111 !
112 !* coupling coefficient with the surface
113 !
114 palfa(:)=0.
115 pbeta(:)=pu(:,1)
116 !
117 !-------------------------------------------------------------------------------
118 !
119 !* 5. Forcing due to drag (at full levels)
120 ! -------------------
121 !
122 !* drag force by canopy
123 !
124 zext = zext + pforc_u(:,:)
125 !
126 zdextdv = zdextdv + pdforc_udu(:,:)
127 !
128 !-------------------------------------------------------------------------------
129 !
130 !* 6. External forcing due to large-scale forces (at full levels)
131 ! ------------------------------------------
132 !
133 !
134 !* forces due to large-scale forcing
135 !
136 ! These are computed from wind evolution equation at forcing level :
137 !
138 ! dUa/dt = Large_Scale_Forcing - d(u'w')/dz|z=forcing_level
139 !
140 ! because vertical derivative of turbulent flux is not available at forcing
141 ! level, one must make the assumption that the turbulent flux is uniform
142 ! between the forcing level and the level just below.
143 ! This means that one assume that the forcing layer is in the inertail sublayer
144 ! (where turbulent fluxes are constant).
145 !
146 zduadt(:) = ( pwind(:) - pu(:,klvl) ) /ptstep
147 !
148 !* for smoother evolution at large time steps, does not include explicitely
149 ! forcing term in lower layers
150 DO jlayer=1,klvl-1
151  zext(:,jlayer) = zext(:,jlayer)
152 END DO
153 
154 !* evolution of forcing layer forced by forcing...
155 zext(:,klvl) = zduadt(:)
156 !
157  CALL canopy_evol_field(ki, klvl, ptstep, kimpl, pk, pdkddvdz, &
158  psflux_u, pforc_u, pdforc_udu, pdz, pdzf, &
159  zext, zdextdv, pu, puw, palfa, pbeta )
160 !
161 !-------------------------------------------------------------------------------
162 !
163 !* 10. Security at all levels : positivity of wind speed
164 ! ----------------------
165 !
166 pu(:,:) = max(pu,0.)
167 IF (lhook) CALL dr_hook('CANOPY_EVOL_WIND',1,zhook_handle)
168 !
169 !----------------------------------------------------------------
170 !
171 END SUBROUTINE canopy_evol_wind
subroutine canopy_evol_field(KI, KLVL, PTSTEP, KIMPL, PK, PDKDDVDZ, PSFLUX_F, PFORC_F, PDFORC_FDF, PDZ, PDZF, PEXT, PDEXTDV, PF, PWF, PALFA, PBETA)
subroutine canopy_evol_wind(KI, KLVL, PTSTEP, KIMPL, PWIND, PK, PDKDDVDZ, PSFLUX_U, PFORC_U, PDFORC_UDU, PDZ, PDZF, PU, PUW, PALFA, PBETA)