SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
average2_orography.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 average2_orography (USS)
7 ! #########################
8 !
9 !!**** *AVERAGE2_OROGRAPHY* computes the cover fractions
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !! EXTERNAL
18 !! --------
19 !!
20 !! IMPLICIT ARGUMENTS
21 !! ------------------
22 !!
23 !! REFERENCE
24 !! ---------
25 !!
26 !! AUTHOR
27 !! ------
28 !!
29 !! V. Masson Meteo-France
30 !!
31 !! MODIFICATION
32 !! ------------
33 !!
34 !! Original 10/12/97
35 !!
36 !----------------------------------------------------------------------------
37 !
38 !* 0. DECLARATION
39 ! -----------
40 !
41 !
43 !
44 USE modd_pgdwork, ONLY : nsize, xsumval, xsumval2, lssqo, xssqo, nsso
45 !
46 !
47 USE yomhook ,ONLY : lhook, dr_hook
48 USE parkind1 ,ONLY : jprb
49 !
50 IMPLICIT NONE
51 !
52 !* 0.1 Declaration of arguments
53 ! ------------------------
54 !
55 !
56 !* 0.2 Declaration of other local variables
57 ! ------------------------------------
58 !
59 !
60 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
61 !
62 INTEGER :: jl
63 REAL, DIMENSION(NSSO) :: zmaxx
64 REAL, DIMENSION(NSSO) :: zmaxy
65 LOGICAL, DIMENSION(NSSO) :: gsegx
66 LOGICAL, DIMENSION(NSSO) :: gsegy
67 REAL(KIND=JPRB) :: zhook_handle
68 !
69 !----------------------------------------------------------------------------
70 !
71 !* 1. Mean orography
72 ! --------------
73 !
74 IF (lhook) CALL dr_hook('AVERAGE2_OROGRAPHY',0,zhook_handle)
75 WHERE (nsize(:)/=0)
76  uss%XAVG_ZS(:)=xsumval(:)/nsize(:)
77 END WHERE
78 !
79 !-------------------------------------------------------------------------------
80 !
81 !* 2. Standard deviation
82 ! ------------------
83 !
84 WHERE (nsize(:)/=0)
85  uss%XSSO_STDEV(:)=sqrt( max(0.,xsumval2(:)/nsize(:) - uss%XAVG_ZS(:)*uss%XAVG_ZS(:)) )
86 END WHERE
87 !
88 !-------------------------------------------------------------------------------
89 !
90 !* 3. Silhouette orography
91 ! --------------------
92 !
93 DO jl=1,SIZE(uss%XSIL_ZS)
94  IF (nsize(jl)==0) cycle
95  zmaxx(:) = maxval(xssqo(:,:,jl),dim=2)
96  gsegx(:) = any(lssqo(:,:,jl),dim=2)
97  zmaxy(:) = maxval(xssqo(:,:,jl),dim=1)
98  gsegy(:) = any(lssqo(:,:,jl),dim=1)
99  uss%XSIL_ZS(jl) =0.5*( sum(zmaxx(:),mask=gsegx(:)) / count(gsegx(:)) &
100  + sum(zmaxy(:),mask=gsegy(:)) / count(gsegy(:)) )
101 
102 END DO
103 IF (lhook) CALL dr_hook('AVERAGE2_OROGRAPHY',1,zhook_handle)
104 !
105 !-------------------------------------------------------------------------------
106 !
107 END SUBROUTINE average2_orography
subroutine average2_orography(USS)