SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
average1_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 average1_orography (USS, &
7  kluout,knblines,plat,plon,pvalue,pnodata)
8 ! #######################################################
9 !
10 !!**** *AVERAGE1_OROGRAPHY* computes the sum of orography, squared orography
11 !! and subgrid orography characteristics
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !! METHOD
17 !! ------
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !! AUTHOR
30 !! ------
31 !!
32 !! V. Masson Meteo-France
33 !!
34 !! MODIFICATION
35 !! ------------
36 !!
37 !! Original 12/09/95
38 !!
39 !----------------------------------------------------------------------------
40 !
41 !* 0. DECLARATION
42 ! -----------
43 !
44 !
46 !
47 USE modd_pgdwork, ONLY : xsumval, xsumval2, nsize, xssqo, lssqo, nsso
48 !
49 USE modi_get_mesh_index
50 USE modd_point_overlay, ONLY : novmx
51 !
52 !
53 USE yomhook ,ONLY : lhook, dr_hook
54 USE parkind1 ,ONLY : jprb
55 !
56 IMPLICIT NONE
57 !
58 !* 0.1 Declaration of arguments
59 ! ------------------------
60 !
61 !
62 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
63 !
64 INTEGER, INTENT(IN) :: kluout
65 INTEGER, INTENT(IN) :: knblines
66 REAL, DIMENSION(:), INTENT(IN) :: plat ! latitude of the point to add
67 REAL, DIMENSION(:), INTENT(IN) :: plon ! longitude of the point to add
68 REAL, DIMENSION(:), INTENT(IN) :: pvalue ! value of the point to add
69 REAL, OPTIONAL, INTENT(IN) :: pnodata
70 !
71 !* 0.2 Declaration of other local variables
72 ! ------------------------------------
73 !
74 INTEGER, DIMENSION(NOVMX,SIZE(PLAT)) :: iindex ! mesh index of all input points
75  ! 0 indicates the point is out of the domain
76 INTEGER, DIMENSION(NOVMX,SIZE(PLAT)) :: issox ! X submesh index in their mesh of all input points
77 INTEGER, DIMENSION(NOVMX,SIZE(PLAT)) :: issoy ! Y submesh index in their mesh of all input points
78 !
79 INTEGER :: jloop, jover ! loop index on input arrays
80 REAL, DIMENSION(SIZE(PLAT)) :: zvalue
81 REAL :: znodata
82 REAL(KIND=JPRB) :: zhook_handle
83 !----------------------------------------------------------------------------
84 !
85 !
86 !* 1. Get position
87 ! ------------
88 !
89 IF (lhook) CALL dr_hook('AVERAGE1_OROGRAPHY',0,zhook_handle)
90 !
91 IF (present(pnodata)) THEN
92  zvalue(:) = pvalue(:)
93  znodata = pnodata
94  CALL get_mesh_index(kluout,knblines,plat,plon,iindex,zvalue,znodata,nsso,issox,issoy)
95 ELSE
96  zvalue(:) = 1.
97  znodata = 0.
98  CALL get_mesh_index(kluout,knblines,plat,plon,iindex,ksso=nsso,kissox=issox,kissoy=issoy)
99 ENDIF
100 !
101 !* 2. Loop on all input data points
102 ! -----------------------------
103 !
104 bloop: &
105 DO jloop = 1 , SIZE(plat)
106 !
107  DO jover = 1, novmx
108 !
109 !* 3. Tests on position
110 ! -----------------
111 !
112  IF (iindex(jover,jloop)==0) cycle bloop
113 !
114 !* 4. Summation
115 ! ---------
116 !
117  nsize(iindex(jover,jloop))=nsize(iindex(jover,jloop))+1
118 !
119 !* 5. Orography
120 ! ---------
121 !
122  xsumval(iindex(jover,jloop))=xsumval(iindex(jover,jloop))+pvalue(jloop)
123 !
124 !* 6. Square of Orography
125 ! -------------------
126 !
127  xsumval2(iindex(jover,jloop))=xsumval2(iindex(jover,jloop))+pvalue(jloop)**2
128 !
129 !* 7. Maximum orography in a subgrid square
130 ! -------------------------------------
131 !
132  lssqo(issox(jover,jloop),issoy(jover,jloop),iindex(jover,jloop)) = .true.
133  xssqo(issox(jover,jloop),issoy(jover,jloop),iindex(jover,jloop)) = &
134  max( xssqo(issox(jover,jloop),issoy(jover,jloop),iindex(jover,jloop)) , pvalue(jloop) )
135 !
136 !
137 !* 8. Maximum orography in the mesh
138 ! -----------------------------
139 !
140  uss%XMAX_ZS(iindex(jover,jloop))=max(uss%XMAX_ZS(iindex(jover,jloop)),pvalue(jloop))
141 !
142 !
143 !* 9. Minimum orography in the mesh
144 ! -----------------------------
145 !
146  uss%XMIN_ZS(iindex(jover,jloop))=min(uss%XMIN_ZS(iindex(jover,jloop)),pvalue(jloop))
147 !
148 !
149  END DO
150 !
151 ENDDO bloop
152 IF (lhook) CALL dr_hook('AVERAGE1_OROGRAPHY',1,zhook_handle)
153 !
154 !-------------------------------------------------------------------------------
155 !
156 END SUBROUTINE average1_orography
subroutine get_mesh_index(KLUOUT, KNBLINES, PLAT, PLON, KINDEX, PVALUE, PNODATA, KSSO, KISSOX, KISSOY)
subroutine average1_orography(USS, KLUOUT, KNBLINES, PLAT, PLON, PVALUE, PNODATA)