SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
average2_mesh.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_mesh(PPGDARRAY)
7 ! #########################################
8 !
9 !!**** *AVERAGE2_MESH* computes a PGD field
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!
15 !! AUTHOR
16 !! ------
17 !!
18 !! V. Masson Meteo-France
19 !!
20 !! MODIFICATION
21 !! ------------
22 !!
23 !! Original 12/09/95
24 !! V. Masson 03/2004 externalization
25 !!
26 !----------------------------------------------------------------------------
27 !
28 !* 0. DECLARATION
29 ! -----------
30 !
31 USE modd_pgdwork, ONLY : nsize, xsumval, catype, &
32  nvalnbr, nvalcount, xvallist
33 USE modd_data_cover_par, ONLY : xcdref
34 !
35 !
36 USE yomhook ,ONLY : lhook, dr_hook
37 USE parkind1 ,ONLY : jprb
38 !
39 IMPLICIT NONE
40 !
41 !* 0.1 Declaration of arguments
42 ! ------------------------
43 !
44 REAL, DIMENSION(:), INTENT(INOUT) :: ppgdarray ! Mesonh field
45 REAL(KIND=JPRB) :: zhook_handle
46 !
47 !* 0.2 Declaration of other local variables
48 ! ------------------------------------
49 !
50 INTEGER :: jloop ! loop counter on grid points
51 INTEGER :: jval ! loop counter on values encountered in grid mesh
52 INTEGER :: imax ! Maximum of times a value has been encountered in the grid mesh
53 INTEGER :: ival ! Index of this value
54 !-------------------------------------------------------------------------------
55 !
56 IF (lhook) CALL dr_hook('AVERAGE2_MESH',0,zhook_handle)
57 SELECT CASE (catype)
58 
59  CASE ('ARI')
60  WHERE (nsize(:)/=0)
61  ppgdarray(:)=xsumval(:)/nsize(:)
62  ENDWHERE
63 
64  CASE ('INV')
65  WHERE (nsize(:)/=0)
66  ppgdarray(:)=nsize(:)/xsumval(:)
67  ENDWHERE
68 
69  CASE ('CDN')
70  WHERE (nsize(:)/=0)
71  ppgdarray(:)=xcdref/exp(sqrt(nsize(:)/xsumval(:)))
72  ENDWHERE
73 
74  CASE ('MAJ')
75  DO jloop=1,SIZE(nsize)
76  IF(nsize(jloop)==0) cycle
77  !* determines the index of the value which has been the most encountered
78  ! in the grid mesh
79  imax=0
80  DO jval=1,nvalnbr(jloop)
81  IF (nvalcount(jloop,jval)>imax) THEN
82  imax=nvalcount(jloop,jval)
83  ival = jval
84  END IF
85  END DO
86  !* sets this value to the PGD field
87  ppgdarray(jloop)=xvallist(jloop,ival)
88  END DO
89 
90 END SELECT
91 IF (lhook) CALL dr_hook('AVERAGE2_MESH',1,zhook_handle)
92 
93 !-------------------------------------------------------------------------------
94 !
95 END SUBROUTINE average2_mesh
subroutine average2_mesh(PPGDARRAY)