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