SURFEX v8.1
General documentation of Surfex
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 (UG,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 USE modd_sso_n, ONLY : sso_t
47 !
49 !
50 USE modi_get_mesh_index
51 USE modd_point_overlay, ONLY : novmx
52 !
53 !
54 USE yomhook ,ONLY : lhook, dr_hook
55 USE parkind1 ,ONLY : jprb
56 !
57 IMPLICIT NONE
58 !
59 !* 0.1 Declaration of arguments
60 ! ------------------------
61 !
62 !
63 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
64 TYPE(sso_t), INTENT(INOUT) :: USS
65 !
66 INTEGER, INTENT(IN) :: KLUOUT
67 INTEGER, INTENT(IN) :: KNBLINES
68 REAL, DIMENSION(:), INTENT(IN) :: PLAT ! latitude of the point to add
69 REAL, DIMENSION(:), INTENT(IN) :: PLON ! longitude of the point to add
70 REAL, DIMENSION(:), INTENT(IN) :: PVALUE ! value of the point to add
71 REAL, OPTIONAL, INTENT(IN) :: PNODATA
72 !
73 !* 0.2 Declaration of other local variables
74 ! ------------------------------------
75 !
76 INTEGER, DIMENSION(NOVMX,SIZE(PLAT)) :: IINDEX ! mesh index of all input points
77  ! 0 indicates the point is out of the domain
78 INTEGER, DIMENSION(NOVMX,SIZE(PLAT)) :: ISSOX ! X submesh index in their mesh of all input points
79 INTEGER, DIMENSION(NOVMX,SIZE(PLAT)) :: ISSOY ! Y submesh index in their mesh of all input points
80 !
81 INTEGER :: JL, JOV ! loop index on input arrays
82 REAL, DIMENSION(SIZE(PLAT)) :: ZVALUE
83 REAL :: ZNODATA
84 REAL(KIND=JPRB) :: ZHOOK_HANDLE
85 !----------------------------------------------------------------------------
86 !
87 !
88 !* 1. Get position
89 ! ------------
90 !
91 IF (lhook) CALL dr_hook('AVERAGE1_OROGRAPHY',0,zhook_handle)
92 !
93 IF (PRESENT(pnodata)) THEN
94  zvalue(:) = pvalue(:)
95  znodata = pnodata
96  CALL get_mesh_index(ug,kluout,knblines,plat,plon,iindex,zvalue,znodata,nsso,issox,issoy)
97 ELSE
98  zvalue(:) = 1.
99  znodata = 0.
100  CALL get_mesh_index(ug,kluout,knblines,plat,plon,iindex,ksso=nsso,kissox=issox,kissoy=issoy)
101 ENDIF
102 !
103 !* 2. Loop on all input data points
104 ! -----------------------------
105 !
106 bloop: &
107 DO jl = 1 , SIZE(plat)
108 !
109  DO jov = 1, novmx
110 !
111 !* 3. Tests on position
112 ! -----------------
113 !
114  IF (iindex(jov,jl)==0) cycle bloop
115 !
116 !* 4. Summation
117 ! ---------
118 !
119  nsize_all(iindex(jov,jl),1) = nsize_all(iindex(jov,jl),1)+1
120 !
121 !* 5. Orography
122 ! ---------
123 !
124  xall(iindex(jov,jl),1,1) = xall(iindex(jov,jl),1,1)+pvalue(jl)
125 !
126 !* 6. Square of Orography
127 ! -------------------
128 !
129  xall(iindex(jov,jl),2,1) = xall(iindex(jov,jl),2,1)+pvalue(jl)**2
130 !
131 !* 7. Maximum orography in a subgrid square
132 ! -------------------------------------
133 !
134  nsso_all(iindex(jov,jl),issox(jov,jl),issoy(jov,jl)) = 1
135  xsso_all(iindex(jov,jl),issox(jov,jl),issoy(jov,jl)) = &
136  max( xsso_all(iindex(jov,jl),issox(jov,jl),issoy(jov,jl)) , pvalue(jl) )
137 !
138 !
139 !* 8. Maximum orography in the mesh
140 ! -----------------------------
141 !
142  xext_all(iindex(jov,jl),1) = max(xext_all(iindex(jov,jl),1),pvalue(jl))
143 !
144 !
145 !* 9. Minimum orography in the mesh
146 ! -----------------------------
147 !
148  xext_all(iindex(jov,jl),2) = min(xext_all(iindex(jov,jl),2),pvalue(jl))
149 !
150 !
151  END DO
152 !
153 ENDDO bloop
154 IF (lhook) CALL dr_hook('AVERAGE1_OROGRAPHY',1,zhook_handle)
155 !
156 !-------------------------------------------------------------------------------
157 !
158 END SUBROUTINE average1_orography
subroutine average1_orography(UG, USS, KLUOUT, KNBLINES, PLAT, PLON, PVALUE, PN
integer, dimension(:,:), allocatable nsize_all
real, dimension(:,:,:), allocatable xall
integer, dimension(:,:,:), allocatable nsso_all
integer, parameter jprb
Definition: parkind1.F90:32
subroutine get_mesh_index(UG, KLUOUT, KNBLINES, PLAT, PLON, KINDEX, PVAL
logical lhook
Definition: yomhook.F90:15
real, dimension(:,:,:), allocatable xsso_all
real, dimension(:,:), allocatable xext_all