SURFEX v8.1
General documentation of Surfex
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 (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 !
59 USE yomhook ,ONLY : lhook, dr_hook
60 USE parkind1 ,ONLY : jprb
61 !
62 #ifdef AIX64
63 !$ USE OMP_LIB
64 #endif
65 !
66 IMPLICIT NONE
67 !
68 #ifndef AIX64
69 !$ INCLUDE 'omp_lib.h'
70 #endif
71 !
72 !* 0.1 Declarations of dummy arguments :
73 !
74 INTEGER, INTENT(IN) :: KYEAR ! current year
75 INTEGER, INTENT(IN) :: KMONTH ! current month
76 INTEGER, INTENT(IN) :: KDAY ! current day
77 REAL, INTENT(IN) :: PTIME ! current time
78 REAL, DIMENSION(:), INTENT(IN) :: PLON ! longitude
79 REAL, DIMENSION(:), INTENT(IN) :: PLAT ! latutude
80 !
81 REAL, DIMENSION(:), INTENT(OUT) :: PZENITH ! Solar zenithal angle
82 REAL, DIMENSION(:), INTENT(OUT) :: PAZIMSOL ! Solar azimuthal angle
83 REAL, DIMENSION(:), INTENT(OUT) :: PTSUN ! Solar time
84 !
85 !* 0.2 declarations of local variables
86 !
87 !
88 REAL :: ZUT ! Universal time
89 !
90 REAL, DIMENSION(SIZE(PLON)) :: ZTUT ,&! True (absolute) Universal Time
91  ZSOLANG ,&! Hourly solar angle
92  ZSINAZI ,&! Sine of the solar azimuthal angle
93  ZCOSAZI ,&! Cosine of the solar azimuthal angle
94  ZLAT, &
95  ZLON, &! Array of latitudes and longitudes
96  ZSINZEN, &!Sine of zenithal angle
97  ZCOSZEN !Cosine of zenithal angle
98 INTEGER, DIMENSION(0:11) :: IBIS, INOBIS ! Cumulative number of days per month
99  ! for bissextile and regular years
100 REAL :: ZDATE ! Julian day of the year
101 REAL :: ZAD ! Angular Julian day of the year
102 REAL :: ZDECSOL ! Daily solar declination angle
103 REAL :: ZA1, ZA2 ! Ancillary variables
104 REAL :: ZTSIDER, &
105  ZSINDEL, &!azimuthal angle
106  ZCOSDEL !azimuthal angle
107 !
108 INTEGER :: JI, JJ, INKPROMA
109 INTEGER :: IINDX1, IINDX2
110 REAL(KIND=JPRB) :: ZHOOK_HANDLE, ZHOOK_HANDLE_OMP
111 !
112 !-------------------------------------------------------------------------------
113 !
114 !* 1. TO COMPUTE THE TRUE SOLAR TIME
115 ! -------------------------------
116 !
117 IF (lhook) CALL dr_hook('SUNPOS_1',0,zhook_handle)
118 !
119 zut = mod( 24.0+mod(ptime/3600.,24.0),24.0 )
120 
121 inobis(:) = (/0,31,59,90,120,151,181,212,243,273,304,334/)
122 ibis(0:1) = inobis(0:1)
123 DO ji=2,11
124  ibis(ji) = inobis(ji)+1
125 END DO
126 IF( mod(kyear,4).EQ.0 .AND. (mod(kyear,100).NE.0 .OR. mod(kyear,400).EQ.0)) THEN
127  zdate = float(kday + ibis(kmonth-1)) - 1 + ptime/xday
128  zad = 2.0*xpi*zdate/366.0
129 ELSE
130  zdate = float(kday + inobis(kmonth-1)) - 1 + ptime/xday
131  zad = 2.0*xpi*zdate/365.0
132 END IF
133 
134 za1 = (1.00554*zdate- 6.28306)*(xpi/180.0)
135 za2 = (1.93946*zdate+23.35089)*(xpi/180.0)
136 ztsider = (7.67825*sin(za1)+10.09176*sin(za2)) / 60.0
137 !
138 !-------------------------------------------------------------------------------
139 !
140 !* 2. COMPUTE THE SOLAR DECLINATION ANGLE
141 ! -----------------------------------
142 !
143 zdecsol = 0.006918-0.399912*cos(zad) +0.070257*sin(zad) &
144  -0.006758*cos(2.*zad)+0.000907*sin(2.*zad) &
145  -0.002697*cos(3.*zad)+0.00148 *sin(3.*zad)
146 zsindel = sin(zdecsol)
147 zcosdel = cos(zdecsol)
148 !-------------------------------------------------------------------------------
149 !
150 IF (lhook) CALL dr_hook('SUNPOS_1',1,zhook_handle)
151 !
152 !$OMP PARALLEL PRIVATE(ZHOOK_HANDLE_OMP)
153 IF (lhook) CALL dr_hook('SUNPOS_2',0,zhook_handle_omp)
154 !$OMP DO PRIVATE(JJ)
155 DO jj = 1,SIZE(plat)
156 !
157 !* 3. LOADS THE ZLAT, ZLON ARRAYS
158 ! ---------------------------
159 !
160  zlat(jj) = plat(jj)*(xpi/180.)
161  zlon(jj) = plon(jj)*(xpi/180.)
162 !
163 !-------------------------------------------------------------------------------
164 !
165 !* 4. COMPUTE THE TRUE SOLAR TIME
166 ! ----------------------------
167 !
168  ztut(jj) = zut - ztsider + zlon(jj)*((180./xpi)/15.0)
169 !
170  ptsun(jj) = mod(ptime -ztsider*3600. +plon(jj)*240., xday)
171 !
172 !-------------------------------------------------------------------------------
173 !* 3. COMPUTES THE COSINE AND SINUS OF THE ZENITHAL SOLAR ANGLE
174 ! ---------------------------------------------------------
175 !
176  zsolang(jj) = (ztut(jj)-12.0)*15.0*(xpi/180.) ! hour angle in radians
177 !
178  zcoszen(jj) = sin(zlat(jj))*zsindel + &! Cosine of the zenithal
179  cos(zlat(jj))*zcosdel*cos(zsolang(jj)) ! solar angle
180 !
181  zsinzen(jj) = sqrt( 1. - zcoszen(jj)*zcoszen(jj) )
182 !
183 !-------------------------------------------------------------------------------
184 !
185 !* 5. ZENITHAL SOLAR ANGLE
186 ! --------------------
187 !
188  pzenith(jj) = acos(zcoszen(jj))
189 !
190 !-------------------------------------------------------------------------------
191 !
192 !* 6. COMPUTE THE AZIMUTHAL SOLAR ANGLE (PAZIMSOL)
193 ! --------------------------------------------
194 !
195  IF (zsinzen(jj)/=0.) THEN
196  !Azimuth is measured clockwise from north
197  zsinazi(jj) = - zcosdel * sin(zsolang(jj)) / zsinzen(jj)
198  zcosazi(jj) = (-sin(zlat(jj))*zcosdel*cos(zsolang(jj)) &
199  +cos(zlat(jj))*zsindel &
200  ) / zsinzen(jj)
201  pazimsol(jj) = atan2(zsinazi(jj),zcosazi(jj))
202  ELSE
203  pazimsol(jj) = xpi
204  ENDIF
205 !
206 ENDDO
207 !$OMP END DO
208 IF (lhook) CALL dr_hook('SUNPOS_2',1,zhook_handle_omp)
209 !$OMP END PARALLEL
210 !
211 !-------------------------------------------------------------------------------
212 !
213 END SUBROUTINE sunpos
real, save xpi
Definition: modd_csts.F90:43
subroutine sunpos(KYEAR, KMONTH, KDAY, PTIME, PLON, PLAT, PTSUN, PZENITH, PAZIMSOL)
Definition: sunpos.F90:8
integer, parameter jprb
Definition: parkind1.F90:32
real, save xday
Definition: modd_csts.F90:45
logical lhook
Definition: yomhook.F90:15