SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
average_phy.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 average_phy(PFRAC_TILE, &
7  ptsurf_tile, pz0_tile, &
8  pz0h_tile, pqsurf_tile, &
9  puref, pzref, &
10  ptsurf, pz0, pz0h, pqsurf )
11 ! ######################################################################
12 !
13 !
14 !!**** *AVERAGE_PHY*
15 !!
16 !! PURPOSE
17 !! -------
18 ! Average the physical properties from the land and water surfaces depending on the
19 ! fraction of each surface cover type in the mesh area.
20 !
21 !!** METHOD
22 !! ------
23 !
24 !! EXTERNAL
25 !! --------
26 !!
27 !! IMPLICIT ARGUMENTS
28 !! ------------------
29 !!
30 !!
31 !! REFERENCE
32 !! ---------
33 !!
34 !! AUTHOR
35 !! ------
36 !! B. Decharme * Meteo-France *
37 !!
38 !! MODIFICATIONS
39 !! -------------
40 !! Original 23/04/2013
41 !
42 ! B. Decharme 07/2015 - Modification to deal with E-zone points in Arome/Aladin
43 !-----------------------------------------------------------------------------------
44 !
45 !* 0. DECLARATIONS
46 ! ------------
47 !
48 !
49 USE modd_surf_par, ONLY : xundef
50 !
51 !
52 !
53 USE yomhook ,ONLY : lhook, dr_hook
54 USE parkind1 ,ONLY : jprb
55 !
56 IMPLICIT NONE
57 !
58 !* 0.1 declarations of arguments
59 !
60 !
61 !* 0.1 declarations of arguments
62 !
63 REAL, DIMENSION(:,:), INTENT(IN) :: pfrac_tile ! Fraction in a mesh-area of
64 !
65 REAL, DIMENSION(:,:), INTENT(IN) :: ptsurf_tile ! surface effective temperature (K)
66 REAL, DIMENSION(:,:), INTENT(IN) :: pz0_tile ! roughness length for momentum (m)
67 REAL, DIMENSION(:,:), INTENT(IN) :: pz0h_tile ! roughness length for heat (m)
68 REAL, DIMENSION(:,:), INTENT(IN) :: pqsurf_tile ! specific humidity at surface (kg/kg)
69 !
70 REAL, DIMENSION(:), INTENT(IN) :: puref ! height of wind forcing (m)
71 REAL, DIMENSION(:), INTENT(IN) :: pzref ! height of T,q forcing (m)
72 REAL, DIMENSION(:), INTENT(OUT):: ptsurf ! surface effective temperature (K)
73 REAL, DIMENSION(:), INTENT(OUT):: pz0 ! roughness length for momentum (m)
74 REAL, DIMENSION(:), INTENT(OUT):: pz0h ! roughness length for heat (m)
75 REAL, DIMENSION(:), INTENT(OUT):: pqsurf ! specific humidity at surface (kg/kg)
76 !
77 !* 0.2 declarations of local variables
78 !
79 REAL, DIMENSION(SIZE(PUREF)) :: zwork_z0 ! work array for roughness length for momentum
80 REAL, DIMENSION(SIZE(PUREF)) :: zwork_z0h ! work array for roughness length for heat
81 !
82 INTEGER :: ini, inp ! dimenssion
83 INTEGER :: ji, jp ! loop counter
84 REAL(KIND=JPRB) :: zhook_handle
85 !-------------------------------------------------------------------------------
86 !
87 ! 0. Initialization
88 ! --------------
89 !
90 IF (lhook) CALL dr_hook('AVERAGE_PHY',0,zhook_handle)
91 !
92 ini = SIZE(pfrac_tile,1)
93 inp = SIZE(pfrac_tile,2)
94 !
95 ptsurf(:) = 0.
96 pz0(:) = 0.
97 pz0h(:) = 0.
98 pqsurf(:) = 0.
99 !
100 zwork_z0(:) = 0.
101 zwork_z0h(:) = 0.
102 !
103 ! 1. Grid-Box average
104 ! ----------------
105 DO jp = 1, inp
106 !
107  DO ji = 1, ini
108 !
109 ! surface effective temperature
110 !
111  ptsurf(ji) = ptsurf(ji) + pfrac_tile(ji,jp) * ptsurf_tile(ji,jp)
112 !
113 ! specific humidity at surface
114 !
115  pqsurf(ji) = pqsurf(ji) + pfrac_tile(ji,jp) * pqsurf_tile(ji,jp)
116 !
117 ! roughness length for momentum and heat
118 !
119  zwork_z0(ji) = zwork_z0(ji) + pfrac_tile(ji,jp) * 1.0/(log(puref(ji)/pz0_tile(ji,jp)))**2
120  zwork_z0h(ji) = zwork_z0h(ji) + pfrac_tile(ji,jp) * 1.0/(log(pzref(ji)/pz0h_tile(ji,jp)))**2
121 !
122  ENDDO
123 !
124 ENDDO
125 !
126 
127 DO ji = 1, ini
128  IF(zwork_z0(ji) /= 0 ) then
129  pz0(ji) = puref(ji) * exp( - sqrt(1./zwork_z0(ji)) )
130  pz0h(ji) = pzref(ji) * exp( - sqrt(1./zwork_z0h(ji)) )
131  ELSE
132  pz0(ji) = xundef
133  pz0h(ji) = xundef
134  ENDIF
135 ENDDO
136 !
137 IF (lhook) CALL dr_hook('AVERAGE_PHY',1,zhook_handle)
138 
139 !-------------------------------------------------------------------------------
140 !
141 END SUBROUTINE average_phy
subroutine average_phy(PFRAC_TILE, PTSURF_TILE, PZ0_TILE, PZ0H_TILE, PQSURF_TILE, PUREF, PZREF, PTSURF, PZ0, PZ0H, PQSURF)
Definition: average_phy.F90:6