SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modd_surf_atm_sson.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 ! ####################
7 ! ######################
8 !
9 !!**** *MODD_SURF_ATM_SSO - declaration of surface parameters related to orography
10 !!
11 !! PURPOSE
12 !! -------
13 ! Declaration of surface parameters
14 !
15 !!
16 !!** IMPLICIT ARGUMENTS
17 !! ------------------
18 !! None
19 !!
20 !! REFERENCE
21 !! ---------
22 !!
23 !! AUTHOR
24 !! ------
25 !! V. Masson *Meteo France*
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 01/2004
30 !
31 !* 0. DECLARATIONS
32 ! ------------
33 !
34 !
35 USE yomhook ,ONLY : lhook, dr_hook
36 USE parkind1 ,ONLY : jprb
37 !
38 IMPLICIT NONE
39 
41 !
42 !-----------------------------------------------------------------------------------------------------
43 !
44 ! Type of roughness
45 !
46  CHARACTER(LEN=4) :: CROUGH ! type of orographic roughness
47 ! ! 'NONE'
48  ! 'Z01D'
49  ! 'Z04D'
50  ! 'BE04'
51 
52 !-----------------------------------------------------------------------------------------------------
53 !
54 ! Subgrid orography parameters
55 !
56  REAL, DIMENSION(:), POINTER :: XAOSIP,XAOSIM,XAOSJP,XAOSJM
57 ! directional A/S quantities in 4 coordinate directions
58 ! (IP: i index up; IM: i index down; JP: j index up; JM: j index down)
59 ! They are used in soil routines to compute effective roughness length
60 !
61  REAL, DIMENSION(:), POINTER :: XHO2IP,XHO2IM,XHO2JP,XHO2JM
62 ! directional h/2 quantities in 4 coordinate directions
63 ! (IP: i index up; IM: i index down; JP: j index up; JM: j index down)
64 ! They are used in soil routines to compute effective roughness length
65 !
66  REAL, DIMENSION(:), POINTER :: XZ0EFFIP,XZ0EFFIM,XZ0EFFJP,XZ0EFFJM
67 ! directional total roughness lenghts in 4 coordinate directions
68 ! (IP: i index up; IM: i index down; JP: j index up; JM: j index down)
69 !
70  REAL, DIMENSION(:), POINTER :: XZ0EFFJPDIR ! heading of J direction (deg from N clockwise)
71 
72  REAL, DIMENSION(:), POINTER :: XZ0REL ! relief roughness length (m)
73 !
74  REAL, DIMENSION(:), POINTER :: XSSO_SLOPE ! slope of S.S.O.
75  REAL, DIMENSION(:), POINTER :: XSSO_ANIS ! anisotropy of S.S.O.
76  REAL, DIMENSION(:), POINTER :: XSSO_DIR ! direction of S.S.O. (deg from N clockwise)
77  REAL, DIMENSION(:), POINTER :: XSSO_STDEV ! S.S.O. standard deviation (m)
78 !
79 !
80  REAL, DIMENSION(:), POINTER :: XAVG_ZS ! averaged orography (m)
81  REAL, DIMENSION(:), POINTER :: XSIL_ZS ! silhouette orography (m)
82  REAL, DIMENSION(:), POINTER :: XMAX_ZS ! maximum subgrid orography (m)
83  REAL, DIMENSION(:), POINTER :: XMIN_ZS ! minimum subgrid orography (m)
84 ! Zo threshold
85  REAL :: XFRACZ0 ! Z0=Min(Z0, Href/XFRACZ0)
86  REAL :: XCOEFBE ! Beljaars coefficient
87 !-----------------------------------------------------------------------------------------------------
88 !
89 !
90 
91 
92 END TYPE surf_atm_sso_t
93 
94 
95 
96  CONTAINS
97 
98 !
99 
100 
101 
102 
103 SUBROUTINE surf_atm_sso_init(YSURF_ATM_SSO)
104 TYPE(surf_atm_sso_t), INTENT(INOUT) :: ysurf_atm_sso
105 REAL(KIND=JPRB) :: zhook_handle
106 IF (lhook) CALL dr_hook("MODD_SURF_ATM_SSO_N:SURF_ATM_SSO_INIT",0,zhook_handle)
107  nullify(ysurf_atm_sso%XAOSIP)
108  nullify(ysurf_atm_sso%XAOSIM)
109  nullify(ysurf_atm_sso%XAOSJP)
110  nullify(ysurf_atm_sso%XAOSJM)
111  nullify(ysurf_atm_sso%XHO2IP)
112  nullify(ysurf_atm_sso%XHO2IM)
113  nullify(ysurf_atm_sso%XHO2JP)
114  nullify(ysurf_atm_sso%XHO2JM)
115  nullify(ysurf_atm_sso%XZ0EFFIP)
116  nullify(ysurf_atm_sso%XZ0EFFIM)
117  nullify(ysurf_atm_sso%XZ0EFFJP)
118  nullify(ysurf_atm_sso%XZ0EFFJM)
119  nullify(ysurf_atm_sso%XZ0EFFJPDIR)
120  nullify(ysurf_atm_sso%XZ0REL)
121  nullify(ysurf_atm_sso%XSSO_SLOPE)
122  nullify(ysurf_atm_sso%XSSO_ANIS)
123  nullify(ysurf_atm_sso%XSSO_DIR)
124  nullify(ysurf_atm_sso%XSSO_STDEV)
125  nullify(ysurf_atm_sso%XAVG_ZS)
126  nullify(ysurf_atm_sso%XSIL_ZS)
127  nullify(ysurf_atm_sso%XMAX_ZS)
128  nullify(ysurf_atm_sso%XMIN_ZS)
129 ysurf_atm_sso%CROUGH=' '
130 ysurf_atm_sso%XFRACZ0=2.
131 ysurf_atm_sso%XCOEFBE=2.
132 IF (lhook) CALL dr_hook("MODD_SURF_ATM_SSO_N:SURF_ATM_SSO_INIT",1,zhook_handle)
133 END SUBROUTINE surf_atm_sso_init
134 
135 
136 END MODULE modd_surf_atm_sso_n
subroutine surf_atm_sso_init(YSURF_ATM_SSO)