SURFEX v8.1
General documentation of Surfex
average1_cti.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_cti(UG,KLUOUT,KNBLINES,PLAT,PLON,PVALUE,PNODATA)
7 ! ################################################
8 !
9 !!**** *AVERAGE1_CTI* computes the sum of cti, squared cti
10 !! and subgrid cti characteristics
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !! METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !! AUTHOR
29 !! ------
30 !!
31 !! B. Decharme Meteo-France
32 !!
33 !! MODIFICATION
34 !! ------------
35 !!
36 !! Original 06/2009
37 !!
38 !----------------------------------------------------------------------------
39 !
40 !* 0. DECLARATION
41 ! -----------
42 !
44 !
45 USE modd_pgdwork, ONLY : xall, nsize_all, xext_all
46 !
47 USE modi_get_mesh_index
49 !!
50 !
51 USE yomhook ,ONLY : lhook, dr_hook
52 USE parkind1 ,ONLY : jprb
53 !
54 IMPLICIT NONE
55 !
56 !* 0.1 Declaration of arguments
57 ! ------------------------
58 !
59 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
60 !
61 INTEGER, INTENT(IN) :: KLUOUT
62 INTEGER, INTENT(IN) :: KNBLINES
63 REAL, DIMENSION(:), INTENT(IN) :: PLAT ! latitude of the point to add
64 REAL, DIMENSION(:), INTENT(IN) :: PLON ! longitude of the point to add
65 REAL, DIMENSION(:), INTENT(IN) :: PVALUE ! value of the point to add
66 REAL, OPTIONAL, INTENT(IN) :: PNODATA
67 !
68 !* 0.2 Declaration of other local variables
69 ! ------------------------------------
70 !
71 INTEGER, DIMENSION(NOVMX,SIZE(PLAT)) :: IINDEX ! mesh index of all input points
72  ! 0 indicates the point is out of the domain
73 !
74 REAL, DIMENSION(SIZE(PLAT)) :: ZVALUE
75 REAL :: ZNODATA
76 !
77 INTEGER :: JL, JOV ! loop index on input arrays
78 REAL(KIND=JPRB) :: ZHOOK_HANDLE
79 !----------------------------------------------------------------------------
80 !
81 !
82 !* 1. Get position
83 ! ------------
84 !
85 IF (lhook) CALL dr_hook('AVERAGE1_CTI',0,zhook_handle)
86 !
87 IF (PRESENT(pnodata)) THEN
88  zvalue(:) = pvalue(:)
89  znodata = pnodata
90  CALL get_mesh_index(ug,kluout,knblines,plat,plon,iindex,zvalue,znodata)
91 ELSE
92  zvalue(:) = 1.
93  znodata = 0.
94  CALL get_mesh_index(ug,kluout,knblines,plat,plon,iindex)
95 ENDIF
96 !
97 !* 2. Loop on all input data points
98 ! -----------------------------
99 !
100 bloop: &
101 DO jl = 1 , SIZE(plat)
102 !
103  DO jov = 1, novmx
104 !
105 !* 3. Tests on position
106 ! -----------------
107 !
108  IF (iindex(jov,jl)==0) cycle bloop
109 !
110 !* 4. Summation
111 ! ---------
112 !
113  nsize_all(iindex(jov,jl),1)=nsize_all(iindex(jov,jl),1)+1
114 !
115 !* 5. CTI
116 ! ---
117 !
118  xall(iindex(jov,jl),1,1) = xall(iindex(jov,jl),1,1)+pvalue(jl)
119 !
120 !* 6. Square of CTI
121 ! -------------
122 !
123  xall(iindex(jov,jl),2,1) = xall(iindex(jov,jl),2,1)+pvalue(jl)**2
124 !
125 !
126 !* 7. Cube of CTI
127 ! -------------
128 !
129  xall(iindex(jov,jl),3,1) = xall(iindex(jov,jl),3,1)+pvalue(jl)**3
130 !
131 !
132 !* 8. Maximum CTI in the mesh
133 ! -----------------------
134 !
135  xext_all(iindex(jov,jl),1) = max(xext_all(iindex(jov,jl),1),pvalue(jl))
136 !
137 !
138 !* 9. Minimum CTI in the mesh
139 ! -----------------------
140 !
141  xext_all(iindex(jov,jl),2) = min(xext_all(iindex(jov,jl),2),pvalue(jl))
142 !
143 !
144  ENDDO
145 !
146 ENDDO bloop
147 !
148 IF (lhook) CALL dr_hook('AVERAGE1_CTI',1,zhook_handle)
149 !
150 !-------------------------------------------------------------------------------
151 !
152 END SUBROUTINE average1_cti
integer, dimension(:,:), allocatable nsize_all
real, dimension(:,:,:), allocatable xall
integer, parameter jprb
Definition: parkind1.F90:32
subroutine average1_cti(UG, KLUOUT, KNBLINES, PLAT, PLON, PVALUE, PNODAT
Definition: average1_cti.F90:7
subroutine get_mesh_index(UG, KLUOUT, KNBLINES, PLAT, PLON, KINDEX, PVAL
logical lhook
Definition: yomhook.F90:15
real, dimension(:,:), allocatable xext_all