SURFEX v8.1
General documentation of Surfex
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 !
42 USE modd_sso_n, ONLY : sso_t
43 !
44 USE modd_surf_par, ONLY : xundef
45 USE modd_surfex_mpi, ONLY : nrank
47 !
48 !
49 USE yomhook ,ONLY : lhook, dr_hook
50 USE parkind1 ,ONLY : jprb
51 !
52 IMPLICIT NONE
53 !
54 !* 0.1 Declaration of arguments
55 ! ------------------------
56 !
57 !
58 !* 0.2 Declaration of other local variables
59 ! ------------------------------------
60 !
61 !
62 TYPE(sso_t), INTENT(INOUT) :: USS
63 !
64 REAL :: ZINT
65 INTEGER :: JL, JI
66 REAL, DIMENSION(NSSO) :: ZMAXX
67 REAL, DIMENSION(NSSO) :: ZMAXY
68 LOGICAL, DIMENSION(NSSO) :: GSEGX
69 LOGICAL, DIMENSION(NSSO) :: GSEGY
70 REAL(KIND=JPRB) :: ZHOOK_HANDLE
71 !
72 !----------------------------------------------------------------------------
73 !
74 !* 1. Mean orography
75 ! --------------
76 !
77 IF (lhook) CALL dr_hook('AVERAGE2_OROGRAPHY',0,zhook_handle)
78 WHERE (nsize(:,1)/=0)
79  uss%XAVG_ZS(:) = xsumval(:,1)/nsize(:,1)
80 END WHERE
81 !
82 !-------------------------------------------------------------------------------
83 !
84 !* 2. Standard deviation
85 ! ------------------
86 !
87 WHERE (nsize(:,1)/=0)
88  uss%XSSO_STDEV(:) = sqrt( max(0.,xsumval(:,2)/nsize(:,1) - uss%XAVG_ZS(:)*uss%XAVG_ZS(:)) )
89 END WHERE
90 !
91 !-------------------------------------------------------------------------------
92 !
93 !* 3. Silhouette orography
94 ! --------------------
95 !
96 DO jl=1,SIZE(uss%XSIL_ZS)
97  IF (nsize(jl,1)==0) cycle
98  zmaxx(:) = maxval(xssqo(jl,:,:),dim=2)
99  gsegx(:) = any(lssqo(jl,:,:),dim=2)
100  zmaxy(:) = maxval(xssqo(jl,:,:),dim=1)
101  gsegy(:) = any(lssqo(jl,:,:),dim=1)
102  uss%XSIL_ZS(jl) =0.5*( sum(zmaxx(:),mask=gsegx(:)) / count(gsegx(:)) &
103  + sum(zmaxy(:),mask=gsegy(:)) / count(gsegy(:)) )
104 
105 END DO
106 !
107 !
108 DO ji = 1,SIZE(uss%XAVG_ZS)
109 
110  IF (uss%XAVG_ZS(ji)/=xundef) THEN
111 
112  zint = aint(uss%XAVG_ZS(ji))
113  IF (uss%XAVG_ZS(ji)/=zint) &
114  uss%XAVG_ZS(ji) = zint + anint((uss%XAVG_ZS(ji)-zint)*xprec)/xprec
115 
116  zint = aint(uss%XSSO_STDEV(ji))
117  IF (uss%XSSO_STDEV(ji)/=zint) &
118  uss%XSSO_STDEV(ji) = zint + anint((uss%XSSO_STDEV(ji)-zint)*xprec)/xprec
119 
120  zint = aint(uss%XSIL_ZS(ji))
121  IF (uss%XSIL_ZS(ji)/=zint) &
122  uss%XSIL_ZS(ji) = zint + anint((uss%XSIL_ZS(ji)-zint)*xprec)/xprec
123 
124  ENDIF
125 
126 ENDDO
127 !
128 IF (lhook) CALL dr_hook('AVERAGE2_OROGRAPHY',1,zhook_handle)
129 !
130 !-------------------------------------------------------------------------------
131 !
132 END SUBROUTINE average2_orography
subroutine average2_orography(USS)
real, parameter xprec
logical, dimension(:,:,:), allocatable lssqo
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
real, dimension(:,:), allocatable xsumval
real, dimension(:,:,:), allocatable xssqo
intent(out) overrides sub arrays one Sort by the least significant key first sum(iindex(1:n))
logical lhook
Definition: yomhook.F90:15
integer, dimension(:,:), allocatable nsize
static int mask
Definition: ifssig.c:38
static int count
Definition: memory_hook.c:21