SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
slope_radiative_effect.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 slope_radiative_effect(PTSTEP,PZENITH,PAZIM,PPS,PTA,PRAIN,PDIR_SW,PLW, &
6  pzs,pzs_xy,pslopang,pslopazi,psurf_triangle )
7 !##############################################################
8 !
9 !!**** *SLOPE_RADIATIVE_EFFECT* compute direct short-wave radiation modified by slopes and shadows,
10 ! BUT renormalized on the horizontal surface of the grid mesh
11 ! to serve as input for ISBA
12 !
13 !!
14 !! PURPOSE
15 !! -------
16 !!
17 !! METHOD
18 !! ------
19 !!
20 !
21 !! EXTERNAL
22 !! --------
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !! REFERENCE
28 !! ---------
29 !! Based on original package to correct shortwave radiation included in
30 !! MESO-NH (developed by V. Masson)
31 !!
32 !! AUTHOR
33 !! ------
34 !!
35 !! V. Vionnet Meteo-France
36 !!
37 !! MODIFICATION
38 !! ------------
39 !!
40 !! Original 04/11
41 !! 29/04/11 : VV implementation of adjustment of incoming longwave
42 !! radiation as a function of the slope (routine
43 !! originally implemented in operational chain SCM)
44 !! (routine meteo.f90 of Crocus)
45 !! 03/14 : M Lafaysse, modifs for optimization and parallelization
46 !----------------------------------------------------------------------------
47 !
48 !* 0. DECLARATION
49 ! -----------
50 !
51 !
52 USE modi_surf_rad_modif
53 !
54 USE modd_csts, ONLY : xpi,xstefan
56 !
57 IMPLICIT NONE
58 !
59 !* 0.1 Declaration of arguments
60 ! ------------------------
61 !
62 REAL, INTENT(IN) :: ptstep ! surface time step (s)
63 REAL, DIMENSION(:), INTENT(IN) :: pzenith ! zenithal angle (radian from the vertical)
64 REAL, DIMENSION(:), INTENT(IN) :: pazim ! azimuthal angle (radian from North, clockwise)
65 REAL, DIMENSION(:), INTENT(IN) :: pps ! pressure at atmospheric model surface (Pa)
66 REAL, DIMENSION(:), INTENT(IN) :: pta ! air temperature forcing (K)
67 REAL, DIMENSION(:), INTENT(IN) :: prain ! liquid precipitation (kg/m2/s)
68 
69 ! OROGRAPHY OF THE SUBDOMAIN (THIS PROCESSOR)
70 REAL, DIMENSION(:,:), INTENT(IN) :: pzs ! (resolved) model orography
71 REAL, DIMENSION(:,:), INTENT(IN) :: pzs_xy ! orography at vort. points
72 REAL, DIMENSION(:,:,:), INTENT(IN) :: pslopazi ! azimuthal slope angle of triangles
73 REAL, DIMENSION(:,:,:), INTENT(IN) :: pslopang ! vertical slope angle of triangles
74 REAL, DIMENSION(:,:,:), INTENT(IN) :: psurf_triangle ! surface of triangles
75 
76 REAL, DIMENSION(:,:), INTENT(INOUT) :: pdir_sw ! IN : input down (direct) short-wave radiation
77 ! OUT : down (direct) short-wave radiation modified by slopes and shadows,
78 ! BUT renormalized on the horizontal surface of the grid mesh
79 REAL, DIMENSION(:), INTENT(INOUT) :: plw ! IN : longwave radiation (on horizontal surf.)
80 ! OUT : longwave radiation modified by slopee and valley effects,
81 ! BUT renormalized on the horizontal surface of the grid mesh
82 !
83 !
84 !* 0.2 Declaration of local variables
85 ! ------------------------------
86 !
87 INTEGER :: jx ! loop counter
88 INTEGER :: jy ! loop counter
89 INTEGER :: jb ! loop counter
90 INTEGER :: inbands ! number of radiative bands
91 INTEGER :: iindy
92 
93 REAL, DIMENSION(:,:), ALLOCATABLE :: zmap ! map factor
94 REAL, DIMENSION(:,:), ALLOCATABLE :: zcoszen ! cosine of solar zenithal angle (=1 at zenith)
95 REAL, DIMENSION(:,:), ALLOCATABLE :: zsinzen ! sinus of solar zenithal angle (=0 at zenith)
96 REAL, DIMENSION(:,:), ALLOCATABLE :: zazimsol ! solar azimuthal angle
97 ! ! 0 ==> Sun from the South
98 ! ! Pi/2 ==> Sun from the East
99 ! ! Pi ==> Sun from the North
100 ! ! 3Pi/2 ==> Sun from the West
101 ! REAL, DIMENSION(:,:), ALLOCATABLE :: ZSSO_SURF ! ratio between sloping orography and horizontal surface
102 ! REAL, DIMENSION(:), ALLOCATABLE :: ZSSO_SURF_1D ! ratio between sloping orography and horizontal surface (1D vector)
103 REAL, DIMENSION(:,:,:), ALLOCATABLE :: zdirflaswd ! input down (direct) short-wave radiation
104 REAL, DIMENSION(:,:,:), ALLOCATABLE :: zdirsrfswd ! down (direct) short-wave radiation modified by slopes and shadows,
105 ! ! BUT renormalized on the horizontal surface of the grid mesh
106 ! ! For both variables, 3rd dimension is wavelength
107 REAL, DIMENSION(:), ALLOCATABLE :: zalpha ! intermediate variable
108 !
109 REAL, PARAMETER :: vpres1 = 87000.
110 !
111 
112 inbands = SIZE(pdir_sw,2)
113 
114 !-------------------------------------------------------------------------------
115 !
116 !* 1. Downwards solar radiation and solar angles
117 ! ------------------------------------------
118 !
119 ! PRINT*,"SIZE(PTA)=",SIZE(PTA)
120 
121 !
122 ! solar zenithal angle (cosine=1 : zenith)
123 ALLOCATE(zcoszen(nnxloc,nnyloc))
124 ALLOCATE(zsinzen(nnxloc,nnyloc))
125 ALLOCATE(zazimsol(nnxloc,nnyloc))
126 ALLOCATE(zmap(nnxloc,nnyloc))
127 ! ALLOCATE(ZSSO_SURF(NNX,NNY))
128 ALLOCATE(zdirflaswd(nnxloc,nnyloc,inbands))
129 ALLOCATE(zdirsrfswd(nnxloc,nnyloc,inbands))
130 ! ALLOCATE(ZSSO_SURF_1D(IX*IY))
131 ALLOCATE(zalpha(nix*niy))
132 
133 ! PRINT*,SIZE(PZENITH)
134 ! PRINT*,NNX,NNY,IX,IY
135 
136 !PRINT*,NIYLOC,NIXLOC
137 
138 IF (lrevertgrid) THEN
139  DO jy=1,niyloc
140  iindy=niyloc-jy+1
141  DO jx=1,nixloc
142  zcoszen(jx+1,iindy+1) = cos(pzenith( jx + (jy-1)*nixloc ))
143  zsinzen(jx+1,iindy+1) = sin(pzenith( jx + (jy-1)*nixloc ))
144  zazimsol(jx+1,iindy+1) = pazim( jx + (jy-1)*nixloc )
145  END DO
146  END DO
147 ELSE
148  DO jy=1,niyloc
149  DO jx=1,nixloc
150  zcoszen(jx+1,jy+1) = cos(pzenith( jx + (jy-1)*nixloc ))
151  zsinzen(jx+1,jy+1) = sin(pzenith( jx + (jy-1)*nixloc ))
152  zazimsol(jx+1,jy+1) = pazim( jx + (jy-1)*nixloc )
153  END DO
154  END DO
155 ENDIF
156 
157 
158 zcoszen(1,:) = zcoszen(2,:)
159 zcoszen(nnxloc,:) = zcoszen(nnxloc-1,:)
160 zcoszen(:,1) = zcoszen(:,2)
161 zcoszen(:,nnyloc) = zcoszen(:,nnyloc-1)
162 zsinzen(1,:) = zsinzen(2,:)
163 zsinzen(nnxloc,:) = zsinzen(nnxloc-1,:)
164 zsinzen(:,1) = zsinzen(:,2)
165 zsinzen(:,nnyloc) = zsinzen(:,nnyloc-1)
166 zazimsol(1,:) = zazimsol(2,:)
167 zazimsol(nnxloc,:) = zazimsol(nnxloc-1,:)
168 zazimsol(:,1) = zazimsol(:,2)
169 zazimsol(:,nnyloc) = zazimsol(:,nnyloc-1)
170 !
171 ! Downwards solar radiation
172 IF (lrevertgrid) THEN
173  DO jb = 1,inbands
174  DO jy=1,niyloc
175  iindy=niyloc-jy+1
176  DO jx=1,nixloc
177  zdirflaswd(jx+1,iindy+1,jb) = pdir_sw( jx + (jy-1)*nixloc,jb)
178  END DO
179  END DO
180  END DO
181 ELSE
182  DO jb = 1,inbands
183  DO jy=1,niyloc
184  DO jx=1,nixloc
185  zdirflaswd(jx+1,jy+1,jb) = pdir_sw( jx + (jy-1)*nixloc,jb)
186  END DO
187  END DO
188  END DO
189 ENDIF
190 
191 
192 zdirflaswd(1,:,:) = zdirflaswd(2,:,:)
193 zdirflaswd(nnxloc,:,:) = zdirflaswd(nnxloc-1,:,:)
194 zdirflaswd(:,1,:) = zdirflaswd(:,2,:)
195 zdirflaswd(:,nnyloc,:) = zdirflaswd(:,nnyloc-1,:)
196 
197 !
198 ! Map factor
199 !
200 zmap(:,:) = 1.
201 
202 !------------------------------------------------------------------------------------------
203 !
204 !* 2. Calls radiative computations
205 ! ----------------------------
206 !
207 ! PRINT*,XZSL
208 ! PRINT*,"in slope radiative effect",SIZE(XZSL,1),SIZE(XZSL,2)
209 
210  CALL surf_rad_modif( zmap, xxhat_thread, xyhat_thread, &
211  zcoszen, zsinzen, zazimsol,pzs,pzs_xy, &
212  pslopang,pslopazi,psurf_triangle, &
213  xxhat,xyhat,nindx1_x,nindx1_y,xzsl,xzs_xy, &
214  zdirflaswd, zdirsrfswd )
215 !
216 !
217 !-------------------------------------------------------------------------------
218 !
219 !* 3. Output field comes back into 1D vector
220 ! --------------------------------------
221 !
222 
223 IF (lrevertgrid) THEN
224  DO jb=1,inbands
225  DO jy=1,niyloc
226  iindy=niyloc-jy+1
227  DO jx=1,nixloc
228  pdir_sw( jx + (jy-1)*nixloc,jb ) = zdirsrfswd(jx+1,iindy+1,jb)
229 ! ZSSO_SURF_1D(JX + (JY-1)*IX) = ZSSO_SURF(JX+1,JY+1)
230  END DO
231  END DO
232  END DO
233 ELSE
234  DO jb=1,inbands
235  DO jy=1,niyloc
236  DO jx=1,nixloc
237  pdir_sw( jx + (jy-1)*nixloc,jb ) = zdirsrfswd(jx+1,jy+1,jb)
238 ! ZSSO_SURF_1D(JX + (JY-1)*IX) = ZSSO_SURF(JX+1,JY+1)
239  END DO
240  END DO
241  END DO
242 ENDIF
243 !
244 !
245 !
246 !-------------------------------------------------------------------------------
247 !
248 ! !* 4. Modify longwave incoming radiation due to account for the influence
249 ! ! of opposite slope and correction in case of rain
250 ! ! --------------------------------------------------------
251 ! ZALPHA(:) = MAX(0.25*(ZSSO_SURF_1D(:)/SQRT(1+ZSSO_SURF_1D(:)**2.))**2., 0.1*PPS(:)/VPRES1)
252 !
253 ! PLW(:) = (1-ZALPHA(:))*PLW(:) +ZALPHA(:)*XSTEFAN*PTA(:)**4.
254 !
255 ! WHERE(PRAIN(:)*PTSTEP>0.001)
256 ! PLW(:) = MAX(PLW(:),0.95*XSTEFAN*PTA(:)**4.)
257 ! END WHERE
258 
259 
260 DEALLOCATE(zcoszen)
261 DEALLOCATE(zsinzen)
262 DEALLOCATE(zazimsol)
263 DEALLOCATE(zmap)
264 ! DEALLOCATE(ZSSO_SURF)
265 DEALLOCATE(zdirflaswd)
266 DEALLOCATE(zdirsrfswd)
267 ! DEALLOCATE(ZSSO_SURF_1D)
268 DEALLOCATE(zalpha)
269 END SUBROUTINE slope_radiative_effect
subroutine slope_radiative_effect(PTSTEP, PZENITH, PAZIM, PPS, PTA, PRAIN, PDIR_SW, PLW, PZS, PZS_XY, PSLOPANG, PSLOPAZI, PSURF_TRIANGLE)
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)