SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
sunpos.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 sunpos (KSIZE_OMP, KYEAR, KMONTH, KDAY, PTIME, &
7  plon, plat, ptsun, pzenith, pazimsol)
8 ! ####################################################################################
9 !
10 !!**** *SUNPOS * - routine to compute the position of the sun
11 !!
12 !! PURPOSE
13 !! -------
14 !! The purpose of this routine is to compute the cosine and sinus of the
15 !! solar zenithal angle (angle defined by the local vertical at the position
16 !! XLAT, XLON and the direction of the sun) and the azimuthal solar
17 !! angle (angle between an horizontal direction (south or north according
18 !! to the terrestrial hemisphere) and the horizontal projection of the
19 !! direction of the sun.
20 !!
21 !!** METHOD
22 !! ------
23 !! The cosine and sinus of the zenithal solar angle and the azimuthal
24 !! solar angle are computed from the true universal time, valid for the (XLAT,
25 !! XLON) location, and from the solar declination aPD_ICE(:)ngle of the day. There
26 !! is a special convention to define the azimuthal solar angle.
27 !!
28 !! EXTERNAL
29 !! --------
30 !! NONE
31 !!
32 !! IMPLICIT ARGUMENTS
33 !! ------------------
34 !!
35 !! REFERENCE
36 !! ---------
37 !! "Radiative Processes in Meteorology and Climatology"
38 !! (1976) Paltridge and Platt
39 !!
40 !! AUTHOR
41 !! ------
42 !! J.-P. Pinty * Laboratoire d'Aerologie*
43 !!
44 !! MODIFICATIONS
45 !! -------------
46 !! Original 16/10/94
47 !! Revised 12/09/95
48 !! (J.Stein) 01:04/96 bug correction for ZZEANG
49 !! (K. Suhre) 14/02/97 bug correction for ZLON0
50 !! (V. Masson) 01/03/03 add zenithal angle output
51 !! (V. Masson) 14/03/14 avoid discontinuous declination at 00UTC each day
52 !-------------------------------------------------------------------------------
53 !
54 !* 0. DECLARATIONS
55 ! ------------
56 !
57 USE modd_csts, ONLY : xpi, xday
58 USE modd_surfex_omp, ONLY : nblock, nblocktot, init_dim
59 !
60 USE yomhook ,ONLY : lhook, dr_hook
61 USE parkind1 ,ONLY : jprb
62 !
63 #ifdef AIX64
64 !$ USE OMP_LIB
65 #endif
66 !
67 IMPLICIT NONE
68 !
69 #ifndef AIX64
70 !$ INCLUDE 'omp_lib.h'
71 #endif
72 !
73 !* 0.1 Declarations of dummy arguments :
74 !
75 INTEGER, DIMENSION(:), INTENT(IN) :: ksize_omp
76 INTEGER, INTENT(IN) :: kyear ! current year
77 INTEGER, INTENT(IN) :: kmonth ! current month
78 INTEGER, INTENT(IN) :: kday ! current day
79 REAL, INTENT(IN) :: ptime ! current time
80 REAL, DIMENSION(:), INTENT(IN) :: plon ! longitude
81 REAL, DIMENSION(:), INTENT(IN) :: plat ! latutude
82 !
83 REAL, DIMENSION(:), INTENT(OUT) :: pzenith ! Solar zenithal angle
84 REAL, DIMENSION(:), INTENT(OUT) :: pazimsol ! Solar azimuthal angle
85 REAL, DIMENSION(:), INTENT(OUT) :: ptsun ! Solar time
86 !
87 !* 0.2 declarations of local variables
88 !
89 !
90 REAL :: zut ! Universal time
91 !
92 REAL, DIMENSION(SIZE(PLON)) :: ztut ,&! True (absolute) Universal Time
93  zsolang ,&! Hourly solar angle
94  zsinazi ,&! Sine of the solar azimuthal angle
95  zcosazi ,&! Cosine of the solar azimuthal angle
96  zlat, &
97  zlon, &! Array of latitudes and longitudes
98  zsinzen, &!Sine of zenithal angle
99  zcoszen !Cosine of zenithal angle
100 INTEGER, DIMENSION(0:11) :: ibis, inobis ! Cumulative number of days per month
101  ! for bissextile and regular years
102 REAL :: zdate ! Julian day of the year
103 REAL :: zad ! Angular Julian day of the year
104 REAL :: zdecsol ! Daily solar declination angle
105 REAL :: za1, za2 ! Ancillary variables
106 REAL :: ztsider, &
107  zsindel, &!azimuthal angle
108  zcosdel !azimuthal angle
109 !
110 INTEGER :: ji, jj, inkproma
111 INTEGER :: iindx1, iindx2
112 REAL(KIND=JPRB) :: zhook_handle
113 !
114 !-------------------------------------------------------------------------------
115 !
116 !* 1. TO COMPUTE THE TRUE SOLAR TIME
117 ! -------------------------------
118 !
119 IF (lhook) CALL dr_hook('SUNPOS',0,zhook_handle)
120 zut = mod( 24.0+mod(ptime/3600.,24.0),24.0 )
121 
122 inobis(:) = (/0,31,59,90,120,151,181,212,243,273,304,334/)
123 ibis(0:1) = inobis(0:1)
124 DO ji=2,11
125  ibis(ji) = inobis(ji)+1
126 END DO
127 IF( mod(kyear,4).EQ.0 .AND. (mod(kyear,100).NE.0 .OR. mod(kyear,400).EQ.0)) THEN
128  zdate = float(kday + ibis(kmonth-1)) - 1 + ptime/xday
129  zad = 2.0*xpi*zdate/366.0
130 ELSE
131  zdate = float(kday + inobis(kmonth-1)) - 1 + ptime/xday
132  zad = 2.0*xpi*zdate/365.0
133 END IF
134 
135 za1 = (1.00554*zdate- 6.28306)*(xpi/180.0)
136 za2 = (1.93946*zdate+23.35089)*(xpi/180.0)
137 ztsider = (7.67825*sin(za1)+10.09176*sin(za2)) / 60.0
138 !
139 !-------------------------------------------------------------------------------
140 !
141 !* 2. COMPUTE THE SOLAR DECLINATION ANGLE
142 ! -----------------------------------
143 !
144 zdecsol = 0.006918-0.399912*cos(zad) +0.070257*sin(zad) &
145  -0.006758*cos(2.*zad)+0.000907*sin(2.*zad) &
146  -0.002697*cos(3.*zad)+0.00148 *sin(3.*zad)
147 zsindel = sin(zdecsol)
148 zcosdel = cos(zdecsol)
149 !-------------------------------------------------------------------------------
150 !
151 !$OMP PARALLEL PRIVATE(INKPROMA,IINDX1,IINDX2)
152 !
153 !$ NBLOCK = OMP_GET_THREAD_NUM()
154 !
155 IF (nblock==nblocktot) THEN
156  CALL init_dim(ksize_omp,0,inkproma,iindx1,iindx2)
157 ELSE
158  CALL init_dim(ksize_omp,nblock,inkproma,iindx1,iindx2)
159 ENDIF
160 !
161 DO jj = iindx1,iindx2
162 !
163 !* 3. LOADS THE ZLAT, ZLON ARRAYS
164 ! ---------------------------
165 !
166  zlat(jj) = plat(jj)*(xpi/180.)
167  zlon(jj) = plon(jj)*(xpi/180.)
168 !
169 !-------------------------------------------------------------------------------
170 !
171 !* 4. COMPUTE THE TRUE SOLAR TIME
172 ! ----------------------------
173 !
174  ztut(jj) = zut - ztsider + zlon(jj)*((180./xpi)/15.0)
175 !
176  ptsun(jj) = mod(ptime -ztsider*3600. +plon(jj)*240., xday)
177 !
178 !-------------------------------------------------------------------------------
179 !* 3. COMPUTES THE COSINE AND SINUS OF THE ZENITHAL SOLAR ANGLE
180 ! ---------------------------------------------------------
181 !
182  zsolang(jj) = (ztut(jj)-12.0)*15.0*(xpi/180.) ! hour angle in radians
183 !
184  zcoszen(jj) = sin(zlat(jj))*zsindel + &! Cosine of the zenithal
185  cos(zlat(jj))*zcosdel*cos(zsolang(jj)) ! solar angle
186 !
187  zsinzen(jj) = sqrt( 1. - zcoszen(jj)*zcoszen(jj) )
188 !
189 !-------------------------------------------------------------------------------
190 !
191 !* 5. ZENITHAL SOLAR ANGLE
192 ! --------------------
193 !
194  pzenith(jj) = acos(zcoszen(jj))
195 !
196 !-------------------------------------------------------------------------------
197 !
198 !* 6. COMPUTE THE AZIMUTHAL SOLAR ANGLE (PAZIMSOL)
199 ! --------------------------------------------
200 !
201  IF (zsinzen(jj)/=0.) THEN
202  !Azimuth is measured clockwise from north
203  zsinazi(jj) = - zcosdel * sin(zsolang(jj)) / zsinzen(jj)
204  zcosazi(jj) = (-sin(zlat(jj))*zcosdel*cos(zsolang(jj)) &
205  +cos(zlat(jj))*zsindel &
206  ) / zsinzen(jj)
207  pazimsol(jj) = atan2(zsinazi(jj),zcosazi(jj))
208  ELSE
209  pazimsol(jj) = xpi
210  ENDIF
211 !
212 ENDDO
213 !
214 !$OMP END PARALLEL
215 !
216 IF (lhook) CALL dr_hook('SUNPOS',1,zhook_handle)
217 !-------------------------------------------------------------------------------
218 !
219 END SUBROUTINE sunpos
subroutine sunpos(KSIZE_OMP, KYEAR, KMONTH, KDAY, PTIME, PLON, PLAT, PTSUN, PZENITH, PAZIMSOL)
Definition: sunpos.F90:6
subroutine init_dim(KSIZE_OMP, KBLOCK, KKPROMA, KINDX1, KINDX2)