SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
canopy_evol_temp.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_temp(KI,KLVL,PTSTEP,KIMPL,PTHA,PK,PDKDDVDZ, &
7  psflux_t,pforc_t,pdforc_tdt,pdz,pdzf,pth,pwth, &
8  palfa,pbeta )
9 ! #########################################
10 !
11 !!**** *CANOPY_EVOL_TEMP* - 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) :: ptha ! potential temp. at forcing level (K)
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_t ! surface flux w'Th' (mK/s)
67 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pforc_t ! tendency of wind due to canopy drag (K/s)
68 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pdforc_tdt! 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) :: pth ! pot. temp. at canopy levels (K)
75 REAL, DIMENSION(KI,KLVL), INTENT(OUT) :: pwth ! turbulent flux (at half levels) (mK/s)
76 REAL, DIMENSION(KI), INTENT(OUT) :: palfa ! V+(1) = alfa F(1) + beta
77 REAL, DIMENSION(KI), INTENT(OUT) :: pbeta ! V+(1) = alfa F(1) + 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) :: zdthdz ! dTh/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) :: zth ! work variable : pot. temp at futur instant
95 ! ! (or past at the end of the routine)
96 REAL, DIMENSION(KI) :: zdthadt ! dTHa/dt at forcing level
97 REAL, DIMENSION(KI) :: zdwthdz ! dw'Th'/dz at forcing level
98 LOGICAL :: limpl
99 REAL(KIND=JPRB) :: zhook_handle
100 !
101 !-------------------------------------------------------------------------------
102 !
103 !
104 !* 1. initializations
105 ! ---------------
106 !
107 !* external forces
108 !
109 IF (lhook) CALL dr_hook('CANOPY_EVOL_TEMP',0,zhook_handle)
110 zext = 0.
111 zdextdv = 0.
112 !
113 !-------------------------------------------------------------------------------
114 !
115 !* 5. Forcing due to drag (at full levels)
116 ! -------------------
117 !
118 zext = zext + pforc_t
119 zdextdv = zdextdv + pdforc_tdt
120 !
121 !-------------------------------------------------------------------------------
122 !
123 !* 6. External forcing due to large-scale forces (at full levels)
124 ! ------------------------------------------
125 !
126 !
127 !* forces due to large-scale forcing
128 !
129 ! These are computed from wind evolution equation at forcing level :
130 !
131 ! dUa/dt = Large_Scale_Forcing - d(u'w')/dz|z=forcing_level
132 !
133 ! because vertical derivative of turbulent flux is not available at forcing
134 ! level, one must make the assumption that the turbulent flux is uniform
135 ! between the forcing level and the level just below.
136 ! This means that one assume that the forcing layer is in the inertial sublayer
137 ! (where turbulent fluxes are constant).
138 !
139 zdthadt(:) = ( ptha(:) - pth(:,klvl) ) /ptstep
140 !
141 zdwthdz(:) = 0.
142 !
143 DO jlayer=1,klvl
144  zext(:,jlayer) = zext(:,jlayer) + zdwthdz(:) + zdthadt(:)
145 END DO
146 !
147  CALL canopy_evol_field(ki, klvl, ptstep, kimpl, pk, pdkddvdz, &
148  psflux_t, pforc_t, pdforc_tdt, pdz, pdzf, &
149  zext, zdextdv, pth, pwth, palfa, pbeta )
150 !
151 IF (lhook) CALL dr_hook('CANOPY_EVOL_TEMP',1,zhook_handle)
152 !----------------------------------------------------------------
153 !
154 END SUBROUTINE canopy_evol_temp
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_temp(KI, KLVL, PTSTEP, KIMPL, PTHA, PK, PDKDDVDZ, PSFLUX_T, PFORC_T, PDFORC_TDT, PDZ, PDZF, PTH, PWTH, PALFA, PBETA)