SURFEX v8.1
General documentation of Surfex
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, SB, KI, PSSO_STDEV, PFORC_U, PDFORC_UDU)
7 ! ###############################################################################
8 !
9 !!**** *SSO_BELJAARS04_n * - prepares forcing for canopy air model
10 !!
11 !! SB%XURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !!
21 !! AUTHOR
22 !! ------
23 !! V. Masson
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 07/2006
28 !!---------------------------------------------------------------
29 !
30 USE modd_canopy_n, ONLY : canopy_t
31 USE modd_sso_n, ONLY : sso_t
32 !
33 USE yomhook ,ONLY : lhook, dr_hook
34 USE parkind1 ,ONLY : jprb
35 !
36 IMPLICIT NONE
37 !
38 !* 0.1 declarations of arguments
39 !
40 TYPE(sso_t), INTENT(INOUT) :: USS
41 TYPE(canopy_t), INTENT(INOUT) :: SB
42 !
43 INTEGER, INTENT(IN) :: KI ! number of points
44 REAL, DIMENSION(KI), INTENT(IN) :: PSSO_STDEV! Subgrid scale orography standard dev. (m)
45 !
46 REAL, DIMENSION(KI,SB%NLVL), INTENT(INOUT) :: PFORC_U ! tendency of wind due to canopy drag (m/s2)
47 REAL, DIMENSION(KI,SB%NLVL), INTENT(INOUT) :: PDFORC_UDU! formal derivative of the tendency of
48 ! ! wind due to canopy drag (1/s)
49 !
50 !* 0.2 declarations of local variables
51 !
52 !
53 !* BERJLAARS et al 2004 constants
54 !
55 REAL, PARAMETER :: C_ALPHA = 12.
56 REAL, PARAMETER :: C_BETA = 1.
57 REAL, PARAMETER :: C_CMD = 0.005
58 REAL, PARAMETER :: C_COR = 0.6
59 REAL, PARAMETER :: C_IH = 0.00102 ! (m-1)
60 REAL, PARAMETER :: C_KFLT = 0.00035 ! (m-1)
61 REAL, PARAMETER :: C_K1 = 0.003 ! (m-1)
62 REAL, PARAMETER :: C_N1 = -1.9
63 REAL, PARAMETER :: C_N2 = -2.8
64 REAL :: C_AVAR ! = C_K1**(C_N1-C_N2) / (C_IH * C_KFLT**C_N1)
65 ! ! (unit: m^{1+C_N2} = m^-1.8)
66 !
67 INTEGER :: JL ! loop counter on canopy heights
68 REAL, DIMENSION(KI,SB%NLVL) :: ZSSO_DRAG ! drag due to subgrid-scale orogaphy
69 REAL(KIND=JPRB) :: ZHOOK_HANDLE
70 !
71 !-------------------------------------------------------------------------------------
72 !-------------------------------------------------------------------------------------
73 IF (lhook) CALL dr_hook('SSO_BELJAARS04',0,zhook_handle)
74 !
75 !* 2. Computations of wind tendency due to orographic drag
76 ! ----------------------------------------------------
77 !
78 c_avar = c_k1**(c_n1-c_n2) / (c_ih * c_kflt**c_n1) ! (unit: m^{1+C_N2} = m^-1.8)
79 !
80 !
81 !* 2.1 Drag coefficient in drag force by subscale orography
82 ! -----------------------------------------------------
83 !
84 ! unit : m-1 (m^-1.8 . m ^2 . m^-1.2)
85 !
86 zsso_drag = 0.
87 DO jl=1,sb%NLVL
88  zsso_drag(:,jl) = uss%XCOEFBE * c_alpha * c_beta * c_cor * c_cmd * 2.109 * &
89  exp( -(sb%XZ(:,jl)/1500.)**1.5) * c_avar * psso_stdev(:)**2 * sb%XZ(:,jl)**(-1.2)
90 END DO
91 !
92 !
93 !* 2.2 Impact on each SBL layer
94 ! ------------------------
95 !
96 ! Ext = - Cdrag(z) * u- * u- (unit : m s-2) subscale orgraphy drag
97 !
98 pforc_u(:,:) = pforc_u(:,:) - zsso_drag(:,:) * sb%XU(:,:)**2
99 !
100 pdforc_udu(:,:) = pdforc_udu(:,:) - 2. * zsso_drag(:,:) * sb%XU(:,:)
101 !
102 IF (lhook) CALL dr_hook('SSO_BELJAARS04',1,zhook_handle)
103 !-------------------------------------------------------------------------------------
104 !
105 END SUBROUTINE sso_beljaars04
subroutine sso_beljaars04(USS, SB, KI, PSSO_STDEV, PFORC_U, PDFORC_UDU)
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15