SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
average_rad.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_rad(PFRAC_TILE, &
7  pdir_alb_tile, psca_alb_tile, pemis_tile, ptrad_tile, &
8  pdir_alb, psca_alb, pemis, ptrad )
9 ! #################################################################
10 !
11 !
12 !!**** *AVERAGE_RAD*
13 !!
14 !! PURPOSE
15 !! -------
16 ! Average the radiative fluxes from the land and water surfaces depending on the
17 ! fraction of each surface cover type in the mesh area.
18 !
19 !!** METHOD
20 !! ------
21 !
22 !! EXTERNAL
23 !! --------
24 !!
25 !! IMPLICIT ARGUMENTS
26 !! ------------------
27 !!
28 !!
29 !! REFERENCE
30 !! ---------
31 !!
32 !! AUTHOR
33 !! ------
34 !! S. Belair * Meteo-France *
35 !!
36 !! MODIFICATIONS
37 !! -------------
38 !! Original 10/03/95
39 !! V.Masson 20/03/96 remove abnormal averages and average TS**4 instead
40 !! of TS
41 !! (J.Stein) 27/03/96 use only H and LE in the soil scheme
42 !! A. Boone 27/11/02 revised to output ALMA variables, and general applications
43 ! B. decharme 04/2013 Optimization
44 !-------------------------------------------------------------------------------
45 !
46 !* 0. DECLARATIONS
47 ! ------------
48 !
49 !
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 REAL, DIMENSION(:,:), INTENT(IN) :: pfrac_tile ! Fraction in a mesh-area of
61 ! ! a given surface
62 REAL, DIMENSION(:,:), INTENT(IN) :: pemis_tile ! emissivity
63 REAL, DIMENSION(:,:,:), INTENT(IN) :: pdir_alb_tile ! direct albedo
64 REAL, DIMENSION(:,:,:), INTENT(IN) :: psca_alb_tile ! diffuse albedo
65 REAL, DIMENSION(:,:), INTENT(IN) :: ptrad_tile ! surface radiative temp.
66 REAL, DIMENSION(:), INTENT(OUT):: pemis ! emissivity
67 REAL, DIMENSION(:,:), INTENT(OUT):: pdir_alb ! direct albedo
68 REAL, DIMENSION(:,:), INTENT(OUT):: psca_alb ! diffuse albedo
69 REAL, DIMENSION(:), INTENT(OUT):: ptrad ! surface radiative temp.
70 !
71 !
72 !* 0.2 declarations of local variables
73 !
74 REAL, PARAMETER :: zeps = 1.e-10
75 !
76 INTEGER :: ini, inp, inswb ! dimenssion
77 INTEGER :: ji, jp, jswb ! loop counter on tiles
78 !
79 REAL(KIND=JPRB) :: zhook_handle
80 !-------------------------------------------------------------------------------
81 !
82 IF (lhook) CALL dr_hook('AVERAGE_RAD',0,zhook_handle)
83 !
84 ini = SIZE(pfrac_tile,1)
85 inp = SIZE(pfrac_tile,2)
86 inswb = SIZE(pdir_alb_tile,2)
87 !
88 ! 1. Grid-Box average surface temperatures, radiative properties
89 ! -----------------------------------------------------------
90 !
91 ! albedo:
92 !
93 pdir_alb(:,:) = 0.
94 psca_alb(:,:) = 0.
95 !
96 DO jswb = 1,inswb
97  DO jp = 1,inp
98  DO ji = 1,ini
99  pdir_alb(ji,jswb) = pdir_alb(ji,jswb) + pfrac_tile(ji,jp) * pdir_alb_tile(ji,jswb,jp)
100  psca_alb(ji,jswb) = psca_alb(ji,jswb) + pfrac_tile(ji,jp) * psca_alb_tile(ji,jswb,jp)
101  END DO
102  END DO
103 END DO
104 !
105 ! emissivity
106 !
107 pemis(:) = 0.
108 !
109 DO jp = 1,inp
110  DO ji = 1,ini
111  pemis(ji) = pemis(ji) + pfrac_tile(ji,jp) * pemis_tile(ji,jp)
112  END DO
113 END DO
114 !
115 ! radiative surface temperature
116 !
117 ptrad(:) = 0.
118 !
119 DO jp = 1, inp
120  DO ji = 1,ini
121  ptrad(ji) = ptrad(ji) + (ptrad_tile(ji,jp)**4)*pfrac_tile(ji,jp)*pemis_tile(ji,jp)
122  END DO
123 END DO
124 !
125 ptrad(:) = ( ptrad(:) / max(pemis(:),zeps) )**0.25
126 !
127 IF (lhook) CALL dr_hook('AVERAGE_RAD',1,zhook_handle)
128 !
129 !-------------------------------------------------------------------------------
130 !
131 END SUBROUTINE average_rad
subroutine average_rad(PFRAC_TILE, PDIR_ALB_TILE, PSCA_ALB_TILE, PEMIS_TILE, PTRAD_TILE, PDIR_ALB, PSCA_ALB, PEMIS, PTRAD)
Definition: average_rad.F90:6