SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
sso_beljaars04.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 sso_beljaars04 (USS, &
7  ki,klvl,pz,psso_stdev,pu,pforc_u,pdforc_udu)
8 ! ###############################################################################
9 !
10 !!**** *SSO_BELJAARS04_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 !
33 !
34 USE yomhook ,ONLY : lhook, dr_hook
35 USE parkind1 ,ONLY : jprb
36 !
37 IMPLICIT NONE
38 !
39 !* 0.1 declarations of arguments
40 !
41 !
42 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
43 !
44 INTEGER, INTENT(IN) :: ki ! number of points
45 INTEGER, INTENT(IN) :: klvl ! number of levels in canopy
46 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pz ! heights of canopy levels (m)
47 REAL, DIMENSION(KI), INTENT(IN) :: psso_stdev! Subgrid scale orography standard dev. (m)
48 
49 REAL, DIMENSION(KI,KLVL), INTENT(IN) :: pu ! wind for each canopy layer (m/s)
50 !
51 REAL, DIMENSION(KI,KLVL), INTENT(INOUT) :: pforc_u ! tendency of wind due to canopy drag (m/s2)
52 REAL, DIMENSION(KI,KLVL), INTENT(INOUT) :: pdforc_udu! formal derivative of the tendency of
53 ! ! wind due to canopy drag (1/s)
54 !
55 !* 0.2 declarations of local variables
56 !
57 !
58 !* BERJLAARS et al 2004 constants
59 !
60 REAL, PARAMETER :: c_alpha = 12.
61 REAL, PARAMETER :: c_beta = 1.
62 REAL, PARAMETER :: c_cmd = 0.005
63 REAL, PARAMETER :: c_cor = 0.6
64 REAL, PARAMETER :: c_ih = 0.00102 ! (m-1)
65 REAL, PARAMETER :: c_kflt = 0.00035 ! (m-1)
66 REAL, PARAMETER :: c_k1 = 0.003 ! (m-1)
67 REAL, PARAMETER :: c_n1 = -1.9
68 REAL, PARAMETER :: c_n2 = -2.8
69 REAL :: c_avar ! = C_K1**(C_N1-C_N2) / (C_IH * C_KFLT**C_N1)
70 ! ! (unit: m^{1+C_N2} = m^-1.8)
71 !
72 INTEGER :: jl ! loop counter on canopy heights
73 REAL, DIMENSION(KI,KLVL) :: zsso_drag ! drag due to subgrid-scale orogaphy
74 REAL(KIND=JPRB) :: zhook_handle
75 !
76 !-------------------------------------------------------------------------------------
77 !-------------------------------------------------------------------------------------
78 IF (lhook) CALL dr_hook('SSO_BELJAARS04',0,zhook_handle)
79 !
80 !* 2. Computations of wind tendency due to orographic drag
81 ! ----------------------------------------------------
82 !
83  c_avar = c_k1**(c_n1-c_n2) / (c_ih * c_kflt**c_n1) ! (unit: m^{1+C_N2} = m^-1.8)
84 !
85 !
86 !* 2.1 Drag coefficient in drag force by subscale orography
87 ! -----------------------------------------------------
88 !
89 ! unit : m-1 (m^-1.8 . m ^2 . m^-1.2)
90 !
91 zsso_drag = 0.
92 DO jl=1,klvl
93  zsso_drag(:,jl) = uss%XCOEFBE * c_alpha * c_beta * c_cor * c_cmd * 2.109 * exp( -(pz(:,jl)/1500.)**1.5) &
94  * c_avar * psso_stdev(:)**2 * pz(:,jl)**(-1.2)
95 END DO
96 !
97 !
98 !* 2.2 Impact on each SBL layer
99 ! ------------------------
100 !
101 ! Ext = - Cdrag(z) * u- * u- (unit : m s-2) subscale orgraphy drag
102 !
103 pforc_u(:,:) = pforc_u(:,:) - zsso_drag(:,:) * pu(:,:)**2
104 !
105 pdforc_udu(:,:) = pdforc_udu(:,:) - 2. * zsso_drag(:,:) * pu(:,:)
106 !
107 IF (lhook) CALL dr_hook('SSO_BELJAARS04',1,zhook_handle)
108 !-------------------------------------------------------------------------------------
109 !
110 END SUBROUTINE sso_beljaars04
subroutine sso_beljaars04(USS, KI, KLVL, PZ, PSSO_STDEV, PU, PFORC_U, PDFORC_UDU)