SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
average_flux.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_flux(PFRAC_TILE, &
7  psfth_tile, psftq_tile, &
8  psfts_tile, psfco2_tile, &
9  psfu_tile, psfv_tile, &
10  psfth, psftq, psfts, psfco2, &
11  psfu, psfv )
12 ! ######################################################################
13 !
14 !
15 !!**** *AVERAGE_FLUX*
16 !!
17 !! PURPOSE
18 !! -------
19 ! Average the fluxes from the land and water surfaces depending on the
20 ! fraction of each surface cover type in the mesh area.
21 !
22 !!** METHOD
23 !! ------
24 !
25 !! EXTERNAL
26 !! --------
27 !!
28 !! IMPLICIT ARGUMENTS
29 !! ------------------
30 !!
31 !!
32 !! REFERENCE
33 !! ---------
34 !!
35 !! AUTHOR
36 !! ------
37 !! S. Belair * Meteo-France *
38 !!
39 !! MODIFICATIONS
40 !! -------------
41 !! Original 10/03/95
42 !! V.Masson 20/03/96 remove abnormal averages and average TS**4 instead
43 !! of TS
44 !! (J.Stein) 27/03/96 use only H and LE in the soil scheme
45 !! A. Boone 27/11/02 revised to output ALMA variables, and general applications
46 !-------------------------------------------------------------------------------
47 !
48 !* 0. DECLARATIONS
49 ! ------------
50 !
51 !
52 USE modd_surf_par, ONLY : xundef
53 !
54 !
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 IMPLICIT NONE
60 !
61 !* 0.1 declarations of arguments
62 !
63 !
64 !* 0.1 declarations of arguments
65 !
66 REAL, DIMENSION(:,:), INTENT(IN) :: pfrac_tile ! Fraction in a mesh-area of
67 ! ! a given surface
68 REAL, DIMENSION(:,:), INTENT(IN) :: psfth_tile ! pot. temp. flux (mK/s)
69 REAL, DIMENSION(:,:), INTENT(IN) :: psftq_tile ! water vapor flux (m kg/kg/s)
70 REAL, DIMENSION(:,:), INTENT(IN) :: psfco2_tile! CO2 flux (m kg/kg/s)
71 REAL, DIMENSION(:,:,:),INTENT(IN):: psfts_tile ! scalar flux (m kg/kg/s)
72 REAL, DIMENSION(:,:), INTENT(IN) :: psfu_tile ! zonal momentum flux (pa)
73 REAL, DIMENSION(:,:), INTENT(IN) :: psfv_tile ! meridian momentum flux (pa)
74 REAL, DIMENSION(:), INTENT(OUT):: psfth ! pot. temp. flux (mK/s)
75 REAL, DIMENSION(:), INTENT(OUT):: psftq ! water vapor flux (m kg/kg/s)
76 REAL, DIMENSION(:,:), INTENT(OUT):: psfts ! scalar flux (m kg/kg/s)
77 REAL, DIMENSION(:), INTENT(OUT):: psfco2 ! CO2 flux (m kg/kg/s)
78 REAL, DIMENSION(:), INTENT(OUT):: psfu ! zonal momentum flux (pa)
79 REAL, DIMENSION(:), INTENT(OUT):: psfv ! meridian momentum flux (pa)
80 !
81 !* 0.2 declarations of local variables
82 !
83 INTEGER :: jsv ! scalar loop counter
84 INTEGER :: jtile ! tile loop counter
85 REAL(KIND=JPRB) :: zhook_handle
86 !-------------------------------------------------------------------------------
87 !
88 ! 0. Initialization
89 ! --------------
90 !
91 IF (lhook) CALL dr_hook('AVERAGE_FLUX',0,zhook_handle)
92 psfth(:) = 0.
93 psftq(:) = 0.
94 psfco2(:) = 0.
95 psfu(:) = 0.
96 psfv(:) = 0.
97 psfts(:,:) = 0.
98 !
99 ! 1. Grid-Box average 1d fluxes
100 ! --------------------------
101 !
102 !
103 DO jtile = 1, SIZE(psfth_tile,2)
104 !
105 ! potential temperature flux:
106 !
107  psfth(:) = psfth(:) + pfrac_tile(:,jtile) * psfth_tile(:,jtile)
108 !
109 ! water vapor flux:
110 !
111  psftq(:) = psftq(:) + pfrac_tile(:,jtile) * psftq_tile(:,jtile)
112 !
113 ! carbon flux:
114 !
115  psfco2(:) = psfco2(:) + pfrac_tile(:,jtile) * psfco2_tile(:,jtile)
116 !
117 ! wind surface friction:
118 !
119  psfu(:) = psfu(:) + pfrac_tile(:,jtile) * psfu_tile(:,jtile)
120  psfv(:) = psfv(:) + pfrac_tile(:,jtile) * psfv_tile(:,jtile)
121 !
122 END DO
123 !
124 !
125 !
126 ! 2. Grid-Box average 2d fluxes
127 ! --------------------------
128 !
129 DO jsv = 1, SIZE(psfts_tile,2)
130 !
131  DO jtile = 1, SIZE(psfts_tile,3)
132 !
133 ! scalar flux
134 !
135  psfts(:,jsv) = psfts(:,jsv) + pfrac_tile(:,jtile) * psfts_tile(:,jsv,jtile)
136 !
137  END DO
138 !
139 END DO
140 IF (lhook) CALL dr_hook('AVERAGE_FLUX',1,zhook_handle)
141 
142 !-------------------------------------------------------------------------------
143 !
144 END SUBROUTINE average_flux
subroutine average_flux(PFRAC_TILE, PSFTH_TILE, PSFTQ_TILE, PSFTS_TILE, PSFCO2_TILE, PSFU_TILE, PSFV_TILE, PSFTH, PSFTQ, PSFTS, PSFCO2, PSFU, PSFV)
Definition: average_flux.F90:6