SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
surf_rad_modif.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 SUBROUTINE surf_rad_modif (PMAP,PXHAT,PYHAT,PCOSZEN,PSINZEN,PAZIMSOL, &
6  pzs,pzs_xy,pslopang,pslopazi,psurf_triangle,&
7  zxhat_ll,zyhat_ll,iior_ll,ijor_ll,zzs_ll, &
8  zzs_xy_ll,pdirflaswd, pdirsrfswd )
9 !###################################################################
10 !
11 !!**** * SURF_RAD_MODIF * - computes the modifications to the downwards
12 !! radiative fluxes at the surface, due to
13 !! orientation and shape of this surface.
14 !!
15 !! PURPOSE
16 !! -------
17 !!
18 !! 1) defines a continuous shape of the orography using triangles
19 !! (SURF_SOLAR_GEOM)
20 !!
21 !! 2) modification of direct SW downwards flux due to the
22 !! slope and orientation of the surface (SURF_SOLAR_SLOPES).
23 !! The surface characteristics are compared to the azimuthal
24 !! and zenithal solar angles.
25 !!
26 !! 3) modification of direct SW by shadowing from other grid points orography.
27 !!
28 !! 4) A procedure is added to insure energy conservation after these modifications.
29 !!
30 !! Only the RESOLVED orography is taken into account for these (4) effects.
31 !! Therefore, these modifications will have an impact only for fine
32 !! resolutions (large resolved slopes).
33 !!
34 !!
35 !!
36 !!** METHOD
37 !! ------
38 !!
39 !! EXTERNAL
40 !! --------
41 !!
42 !! IMPLICIT ARGUMENTS
43 !! ------------------
44 !!
45 !!
46 !! REFERENCE
47 !! ---------
48 !!
49 !!
50 !! AUTHOR
51 !! ------
52 !! V. Masson * Meteo-France *
53 !!
54 !! MODIFICATIONS
55 !! -------------
56 !! Original 28/02/00
57 !! V. Masson 28/02/00 extract the surface modifications of the
58 !! RADIATIONS routine, and add the subgrid solar
59 !! computations and the resolved shadows.
60 !! V. Masson 18/02/02 rewrites the routine to add shadows from
61 !! one grid point to another
62 !! V. Masson 03/03/03 moves local computations to surface schemes
63 !! and add multiple SW wavelengths
64 !!
65 !! 03/14 : M Lafaysse, modifs for optimization and parallelization
66 !! + comment spatial energy conservation
67 !-------------------------------------------------------------------------------
68 !
69 !* 0. DECLARATIONS
70 ! ------------
71 !
72 !USE MODI_SURF_SOLAR_SUM
73 USE modi_surf_solar_slopes
74 USE modi_surf_solar_shadows
75 !
76 !
77 IMPLICIT NONE
78 !
79 !* 0.1 DECLARATIONS OF DUMMY ARGUMENTS :
80 !
81 !
82 REAL, DIMENSION(:,:), INTENT(IN) :: pmap ! map factor
83 REAL, DIMENSION(:), INTENT(IN) :: pxhat ! X coordinate
84 REAL, DIMENSION(:), INTENT(IN) :: pyhat ! Y coordinate
85 REAL, DIMENSION(:,:), INTENT(IN) :: pcoszen ! COS(zenithal solar angle)
86 REAL, DIMENSION(:,:), INTENT(IN) :: psinzen ! SIN(zenithal solar angle)
87 REAL, DIMENSION(:,:), INTENT(IN) :: pazimsol ! azimuthal solar angle
88 REAL, DIMENSION(:,:), INTENT(IN) :: pzs ! (resolved) model orography
89 REAL, DIMENSION(:,:), INTENT(IN) :: pzs_xy ! orography at vort. points
90 REAL, DIMENSION(:,:,:), INTENT(IN) :: pslopazi ! azimuthal slope angle of triangles
91 REAL, DIMENSION(:,:,:), INTENT(IN) :: pslopang ! vertical slope angle of triangles
92 REAL, DIMENSION(:,:,:), INTENT(IN) :: psurf_triangle ! surface of triangles
93 REAL, DIMENSION(:), INTENT(IN) :: zxhat_ll ! X coordinate (all processors)
94 REAL, DIMENSION(:), INTENT(IN) :: zyhat_ll ! Y coordinate (all processors)
95 INTEGER, INTENT(IN) :: iior_ll ! position of SW corner of current processor domain
96 ! ! in the entire domain (I index along X coordinate)
97 ! ! (both including the 1 point border)
98 INTEGER, INTENT(IN) :: ijor_ll ! position of SW corner of current processor domain
99 ! ! in the entire domain (J index along Y coordinate)
100 ! ! (both including the 1 point border)
101 REAL, DIMENSION(:,:), INTENT(IN) :: zzs_ll ! orography at center of grid meshes
102 ! ! (all processors)
103 REAL, DIMENSION(:,:), INTENT(IN) :: zzs_xy_ll ! orography at SW corner of grid meshes
104  ! (all processors)
105 !
106 REAL, DIMENSION(:,:,:), INTENT(IN) :: pdirflaswd ! Downward DIR SW Flux on flat surf
107 REAL, DIMENSION(:,:,:), INTENT(OUT):: pdirsrfswd ! Downward SuRF. DIRect SW Flux
108 
109 !
110 !
111 !* 0.2 DECLARATIONS OF LOCAL VARIABLES
112 !
113 REAL, DIMENSION(SIZE(PZS,1),SIZE(PZS,2),SIZE(PDIRFLASWD,3)) :: zdirswd
114  ! down SW on grid mesh
115 REAL, DIMENSION(SIZE(PZS,1),SIZE(PZS,2),4,SIZE(PDIRFLASWD,3)) :: zdirswdt
116 ! ! down SW on triangles
117 ! ! (4 per grid mesh)
118 !
119 !REAL, DIMENSION(SIZE(PDIRFLASWD,3)) :: ZENERGY1
120 ! energy received by the surface by direct solar radiation
121 !REAL, DIMENSION(SIZE(PDIRFLASWD,3)) :: ZENERGY2
122 ! before and after modification of radiation by terrain slopes
123 !REAL, DIMENSION(SIZE(PDIRFLASWD,3)) :: ZENERGYP
124 ! idem except taking into account only positive variations of energy
125 !
126 INTEGER :: iswb ! number of SW spectral bands
127 INTEGER :: jswb ! loop on SW spectral bands
128 !-------------------------------------------------------------------------------
129 !
130 !* initializations
131 !
132 iswb = SIZE(pdirflaswd,3)
133 !
134 !-------------------------------------------------------------------------------
135 !
136 ! DO JSWB = 1, ISWB
137 ! CALL SURF_SOLAR_SUM (PXHAT, PYHAT, PMAP, PDIRFLASWD(:,:,JSWB), ZENERGY1(JSWB) )
138 ! END DO
139 !
140 !
141 !* 2. Slope direction direct SW effects
142 ! ---------------------------------
143 !
144 
145  CALL surf_solar_slopes( pcoszen, psinzen, pazimsol, &
146  pslopang,pslopazi,psurf_triangle,&
147  pdirflaswd, zdirswdt )
148 
149 
150 !
151 !* 3. RESOLVED shadows for direct solar radiation
152 ! -------------------------------------------
153 
154  CALL surf_solar_shadows(pmap, pxhat, pyhat, pcoszen, psinzen, pazimsol, pzs, pzs_xy,&
155  zxhat_ll,zyhat_ll,iior_ll,ijor_ll,zzs_ll,zzs_xy_ll, &
156  zdirswdt, zdirswd )
157 
158 !
159 !
160 !* 4. Energy conservation
161 ! -------------------
162 !
163 !! M Lafaysse : comment the spatial energy conservation
164 pdirsrfswd(:,:,:) = zdirswd(:,:,:)
165 
166 
167 
168 ! DO JSWB = 1, ISWB
169 ! CALL SURF_SOLAR_SUM(PXHAT, PYHAT, PMAP, &
170 ! ZDIRSWD(:,:,JSWB), &
171 ! ZENERGY2(JSWB) )
172 ! !
173 ! CALL SURF_SOLAR_SUM(PXHAT, PYHAT, PMAP, &
174 ! MAX(ZDIRSWD(:,:,JSWB)-PDIRFLASWD(:,:,JSWB),0.), &
175 ! ZENERGYP(JSWB) )
176 ! !
177 ! IF (ZENERGYP(JSWB)>0.) THEN
178 ! PDIRSRFSWD(:,:,JSWB) = ZDIRSWD(:,:,JSWB) &
179 ! + (ZENERGY1(JSWB)-ZENERGY2(JSWB))/ZENERGYP(JSWB) &
180 ! * MAX(ZDIRSWD(:,:,JSWB)-PDIRFLASWD(:,:,JSWB),0.)
181 ! ELSE
182 ! PDIRSRFSWD(:,:,JSWB) = PDIRFLASWD(:,:,JSWB)
183 ! END IF
184 ! END DO
185 !
186 !-------------------------------------------------------------------------------
187 !
188 END SUBROUTINE surf_rad_modif
subroutine surf_rad_modif(PMAP, PXHAT, PYHAT, PCOSZEN, PSINZEN, PAZIMSOL, PZS, PZS_XY, PSLOPANG, PSLOPAZI, PSURF_TRIANGLE, ZXHAT_ll, ZYHAT_ll, IIOR_ll, IJOR_ll, ZZS_ll, ZZS_XY_ll, PDIRFLASWD, PDIRSRFSWD)
subroutine surf_solar_shadows(PMAP, PXHAT, PYHAT, PCOSZEN, PSINZEN, PAZIMSOL, PZS, PZS_XY, ZXHAT_ll, ZYHAT_ll, IIOR_ll, IJOR_ll, ZZS_ll, ZZS_XY_ll, PDIRSWDT, PDIRSRFSWD)
subroutine surf_solar_slopes(PCOSZEN, PSINZEN, PAZIMSOL, PSLOPANG, PSLOPAZI, PSURF_TRIANGLE, PDIRSRFSWD, PDIRSWDT)