SURFEX v8.1
General documentation of Surfex
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_surfex_mpi, ONLY : nrank
32 USE modd_surf_par, ONLY : xundef
33 USE modd_pgdwork, ONLY : nsize, xsumval, catype, xprec
34 USE modd_data_cover_par, ONLY : xcdref
35 !
36 !
37 USE yomhook ,ONLY : lhook, dr_hook
38 USE parkind1 ,ONLY : jprb
39 !
40 IMPLICIT NONE
41 !
42 !* 0.1 Declaration of arguments
43 ! ------------------------
44 !
45 REAL, DIMENSION(:,:), INTENT(INOUT) :: PPGDARRAY ! Mesonh field
46 !
47 !* 0.2 Declaration of other local variables
48 ! ------------------------------------
49 !
50 REAL :: ZINT
51 INTEGER :: JI, JJ
52 REAL(KIND=JPRB) :: ZHOOK_HANDLE
53 !-------------------------------------------------------------------------------
54 !
55 IF (lhook) CALL dr_hook('AVERAGE2_MESH',0,zhook_handle)
56 SELECT CASE (catype)
57 
58  CASE ('ARI')
59  WHERE (nsize(:,:)/=0)
60  ppgdarray(:,:) = xsumval(:,:)/nsize(:,:)
61  ENDWHERE
62 
63  CASE ('INV')
64  WHERE (nsize(:,:)/=0)
65  ppgdarray(:,:) = nsize(:,:)/xsumval(:,:)
66  ENDWHERE
67 
68  CASE ('CDN')
69  WHERE (nsize(:,:)/=0)
70  ppgdarray(:,:) = xcdref/exp(sqrt(nsize(:,:)/xsumval(:,:)))
71  ENDWHERE
72 
73  CASE ('MAJ')
74  WHERE (nsize(:,:)/=0)
75  ppgdarray(:,:) = xsumval(:,:)
76  ENDWHERE
77 
78 END SELECT
79 !
80 !
81 DO jj=1,SIZE(ppgdarray,2)
82  DO ji = 1,SIZE(ppgdarray,1)
83 
84  IF (ppgdarray(ji,jj)/=xundef) THEN
85  zint = aint(ppgdarray(ji,jj),8)
86  IF (ppgdarray(ji,jj)/=zint) THEN
87  ppgdarray(ji,jj) = zint + anint((ppgdarray(ji,jj)-zint)*xprec)/xprec
88  ENDIF
89  ENDIF
90 
91  ENDDO
92 ENDDO
93 !
94 IF (lhook) CALL dr_hook('AVERAGE2_MESH',1,zhook_handle)
95 
96 !-------------------------------------------------------------------------------
97 !
98 END SUBROUTINE average2_mesh
character(len=3) catype
real, parameter xprec
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
real, dimension(:,:), allocatable xsumval
subroutine average2_mesh(PPGDARRAY)
logical lhook
Definition: yomhook.F90:15
integer, dimension(:,:), allocatable nsize