SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
surf_solar_slopes.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 surf_solar_slopes (PCOSZEN,PSINZEN,PAZIMSOL,PSLOPANG, PSLOPAZI, &
7  psurf_triangle,pdirsrfswd,pdirswdt )
8 !#########################################################################
9 !
10 !!**** * SURF_SOLAR_SLOPES * - computes the modifications to the downwards
11 !! direct solar flux at the surface, due to
12 !! orientation and shape of this surface.
13 !!
14 !! PURPOSE
15 !! -------
16 !!
17 !!
18 !!** METHOD
19 !! ------
20 !!
21 !! EXTERNAL
22 !! --------
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !!
28 !! REFERENCE
29 !! ---------
30 !!
31 !!
32 !! AUTHOR
33 !! ------
34 !! V. Masson * Meteo-France *
35 !!
36 !! MODIFICATIONS
37 !! -------------
38 !! Original 15/01/02
39 !! V. Masson 01/03/03 add multiple wavelengths
40 !!
41 !! 03/14 : M Lafaysse, modifs for optimization and parallelization
42 !-------------------------------------------------------------------------------
43 !
44 !* 0. DECLARATIONS
45 ! ------------
46 !
47 USE modd_slope_effect, ONLY:nnxloc,nnyloc
48 !
49 IMPLICIT NONE
50 !
51 !* 0.1 DECLARATIONS OF DUMMY ARGUMENTS :
52 !
53 
54 REAL, DIMENSION(:,:), INTENT(IN) :: pcoszen ! COS(zenithal solar angle)
55 REAL, DIMENSION(:,:), INTENT(IN) :: psinzen ! SIN(zenithal solar angle)
56 REAL, DIMENSION(:,:), INTENT(IN) :: pazimsol! azimuthal solar angle
57 
58 REAL, DIMENSION(:,:,:), INTENT(IN) :: pslopazi ! azimuthal slope angle of triangles
59 REAL, DIMENSION(:,:,:), INTENT(IN) :: pslopang ! vertical slope angle of triangles
60 REAL, DIMENSION(:,:,:), INTENT(IN) :: psurf_triangle ! surface of triangles
61 !
62 REAL, DIMENSION(:,:,:), INTENT(IN) :: pdirsrfswd!Downward SuRF. DIRect SW Flux
63 REAL, DIMENSION(:,:,:,:), INTENT(OUT):: pdirswdt ! shortwave flux received by
64 ! ! each subgrid triangle
65 !
66 !
67 !* 0.2 DECLARATIONS OF LOCAL VARIABLES
68 !
69 REAL, PARAMETER :: xpi=4.*atan(1.) ! Pi
70 INTEGER, PARAMETER :: jphext = 1 ! number of points around the physical domain
71 !
72 INTEGER :: iib, iie, ijb, ije
73 INTEGER :: ji, jj, jb
74 INTEGER :: jt
75 !
76 REAL :: zdzsdx ! slope in X and Y direction
77 REAL :: zdzsdy ! of a triangle surface
78 REAL :: zslopazi ! azimuthal slope angle
79 REAL :: zslopang ! vertical slope angle
80 !
81 !-------------------------------------------------------------------------------
82 !
83 iib= 1+jphext
84 iie=nnxloc-jphext
85 ijb=1+jphext
86 ije=nnyloc-jphext
87 !
88 pdirswdt(:,:,:,:)=0.
89 !
90 !-------------------------------------------------------------------------------
91 !
92 !* 1. LOOP ON GRID MESHES
93 ! -------------------
94 !
95 !* discretization of the grid mesh in four triangles
96 !
97 DO jt=1,4
98 !
99  DO jj=ijb,ije
100  DO ji=iib,iie
101 !
102 !* If zenithal angle greater than Pi/2, sun is down.
103 !
104  IF (pcoszen(ji,jj)<0.) cycle
105 !
106 !-------------------------------------------------------------------------------
107 !
108 !* 2. MODIFICATION OF RADIATION DUE TO LOCAL SLOPE
109 ! --------------------------------------------
110 !* modification of radiation received by 1 square meter of surface
111 ! (of the triangle) because of its orientation relative to the sun
112 !
113 
114 ! Modif Matthieu Lafaysse :
115 ! threshold 0.001 on zenithal angle cosinus to avoid numerical problems at sunset and sunrise
116 
117  pdirswdt(ji,jj,jt,:) = max( 0.0 , pdirsrfswd(ji,jj,:) * ( &
118  cos(pslopang(ji,jj,jt)) &
119  + sin(pslopang(ji,jj,jt)) * psinzen(ji,jj) / max(pcoszen(ji,jj),0.001) &
120  * cos(pazimsol(ji,jj)-pslopazi(ji,jj,jt))))
121 !
122 !* normalizes received radiation by the surface of the triangle to obtain
123 ! radiation representative of an horizontal surface.
124 !
125  pdirswdt(ji,jj,jt,:) = pdirswdt(ji,jj,jt,:) * psurf_triangle(ji,jj,jt)
126 !
127 ! DO JB=1,SIZE(PDIRSWDT(JI,JJ,JT,:))
128 ! IF (PDIRSWDT(JI,JJ,JT,JB)>15000) THEN
129 ! PRINT*,"warning >10000"
130 ! PRINT*,ASIN(PSINZEN(JI,JJ)),ACOS(PCOSZEN(JI,JJ)),ZSLOPANG,ZSLOPAZI,PAZIMSOL(JI,JJ),&
131 ! PDIRSRFSWD(JI,JJ,JB),PDIRSWDT(JI,JJ,JT,JB)
132 ! END IF
133 ! END DO
134  END DO
135  END DO
136 END DO
137 !
138 !-------------------------------------------------------------------------------
139 !
140 END SUBROUTINE surf_solar_slopes
subroutine surf_solar_slopes(PCOSZEN, PSINZEN, PAZIMSOL, PSLOPANG, PSLOPAZI, PSURF_TRIANGLE, PDIRSRFSWD, PDIRSWDT)