source: trunk/LMDZ.TITAN/libf/phytitan/zenang.F @ 1524

Last change on this file since 1524 was 119, checked in by slebonnois, 14 years ago

Sebastien Lebonnois: apres validation des versions Venus et Titan,
correction d'un certain nombre de bugs.

File size: 5.8 KB
Line 
1c====================================================================
2      SUBROUTINE zenang(longi,gmtime,pdtrad,lat,long,
3     s                  pmu0,frac)
4c=============================================================
5c Auteur : O. Boucher (LMD/CNRS)
6c          d'apres les routines zenith et angle de Z.X. Li
7c Objet  : calculer les valeurs moyennes du cos de l'angle zenithal
8c          et l'ensoleillement moyen entre gmtime1 et gmtime2
9c          connaissant la declinaison, la latitude et la longitude.
10c Rque   : Different de la routine angle en ce sens que zenang
11c          fournit des moyennes de pmu0 et non des valeurs
12c          instantanees, du coup frac prend toutes les valeurs
13c          entre 0 et 1.
14c Date   : premiere version le 13 decembre 1994
15c          revu pour  GCM  le 30 septembre 1996
16c===============================================================
17c longi----INPUT : la longitude vraie de la terre dans son plan
18c                  solaire a partir de l'equinoxe de printemps (degre)
19c gmtime---INPUT : temps universel en fraction de jour
20c pdtrad---INPUT : pas de temps du rayonnement (secondes)
21c lat------INPUT : latitude en degres
22c long-----INPUT : longitude en degres
23c pmu0-----OUTPUT: angle zenithal moyen entre gmtime et gmtime+(pdtrad/RDAY)
24c frac-----OUTPUT: ensoleillement moyen entre gmtime et gmtime+(pdtrad/RDAY)
25c================================================================
26      use dimphy
27      IMPLICIT none
28#include "dimensions.h"
29#include "YOMCST.h"
30#include "comorbit.h"
31c================================================================
32      real longi, gmtime, pdtrad
33      real lat(klon), long(klon), pmu0(klon), frac(klon)
34c================================================================
35      integer i
36      real gmtime1, gmtime2
37      real pi_local, deux_pi_local, incl
38      real omega1, omega2, omega
39c omega1, omega2 : temps 1 et 2 exprime en radian avec 0 a midi.
40c omega : heure en radian du coucher de soleil
41c -omega est donc l'heure en radian de lever du soleil
42      real omegadeb, omegafin
43      real zfrac1, zfrac2, z1_mu, z2_mu
44      real lat_sun          ! declinaison en radian
45      real lon_sun          ! longitude solaire en radian
46      real latr             ! latitude du pt de grille en radian
47c================================================================
48c
49      pi_local = 4.0 * ATAN(1.0)
50      deux_pi_local = 2.0 * pi_local
51      incl=obliquit * pi_local / 180.
52c
53      lon_sun = longi * pi_local / 180.0
54      lat_sun = ASIN (SIN(lon_sun)*SIN(incl) )
55c
56      gmtime1=gmtime*RDAY
57      gmtime2=gmtime*RDAY+pdtrad
58c
59      DO i = 1, klon
60c
61      latr = lat(i) * pi_local / 180.
62c
63c--pose probleme quand lat=+/-90 degres
64c
65c      omega = -TAN(latr)*TAN(lat_sun)
66c      omega = ACOS(omega)
67c      IF (latr.GE.(pi_local/2.+lat_sun)
68c     .    .OR. latr.LE.(-pi_local/2.+lat_sun)) THEN
69c         omega = 0.0       ! nuit polaire
70c      ENDIF
71c      IF (latr.GE.(pi_local/2.-lat_sun)
72c     .          .OR. latr.LE.(-pi_local/2.-lat_sun)) THEN
73c         omega = pi_local  ! journee polaire
74c      ENDIF
75c
76c--remplace par cela (le cas par defaut est different)
77c
78      omega=0.0  !--nuit polaire
79      IF (latr.GE.(pi_local/2.-lat_sun)
80     .          .OR. latr.LE.(-pi_local/2.-lat_sun)) THEN
81         omega = pi_local  ! journee polaire
82      ENDIF
83      IF (latr.LT.(pi_local/2.+lat_sun).AND.
84     .    latr.GT.(-pi_local/2.+lat_sun).AND.
85     .    latr.LT.(pi_local/2.-lat_sun).AND.
86     .    latr.GT.(-pi_local/2.-lat_sun)) THEN
87      omega = -TAN(latr)*TAN(lat_sun)
88      omega = ACOS(omega)
89      ENDIF
90c
91         omega1 = gmtime1 + long(i)*RDAY/360.0
92         omega1 = omega1 / RDAY*deux_pi_local
93         omega1 = MOD (omega1+deux_pi_local, deux_pi_local)
94         omega1 = omega1 - pi_local
95c
96         omega2 = gmtime2 + long(i)*RDAY/360.0
97         omega2 = omega2 / RDAY*deux_pi_local
98         omega2 = MOD (omega2+deux_pi_local, deux_pi_local)
99         omega2 = omega2 - pi_local
100c
101      IF (omega1.LE.omega2) THEN  !--on est dans la meme journee locale
102c
103      IF (omega2.LE.-omega .OR. omega1.GE.omega
104     .                     .OR. omega.LT.1e-5) THEN   !--nuit
105         frac(i)=0.0
106         pmu0(i)=0.0
107      ELSE                                              !--jour+nuit/jour
108        omegadeb=MAX(-omega,omega1)
109        omegafin=MIN(omega,omega2)
110        frac(i)=(omegafin-omegadeb)/(omega2-omega1)
111        pmu0(i)=SIN(latr)*SIN(lat_sun) +
112     .          COS(latr)*COS(lat_sun)*
113     .          (SIN(omegafin)-SIN(omegadeb))/
114     .          (omegafin-omegadeb)       
115      ENDIF
116c
117      ELSE  !---omega1 GT omega2 -- a cheval sur deux journees
118c
119c-------------------entre omega1 et pi
120      IF (omega1.GE.omega) THEN  !--nuit
121         zfrac1=0.0
122         z1_mu =0.0
123      ELSE                       !--jour+nuit
124        omegadeb=MAX(-omega,omega1)
125        omegafin=omega
126        zfrac1=omegafin-omegadeb
127        z1_mu =SIN(latr)*SIN(lat_sun) +
128     .          COS(latr)*COS(lat_sun)*
129     .          (SIN(omegafin)-SIN(omegadeb))/
130     .          (omegafin-omegadeb)
131      ENDIF
132c---------------------entre -pi et omega2
133      IF (omega2.LE.-omega) THEN   !--nuit
134         zfrac2=0.0
135         z2_mu =0.0
136      ELSE                         !--jour+nuit
137         omegadeb=-omega
138         omegafin=MIN(omega,omega2)
139         zfrac2=omegafin-omegadeb
140         z2_mu =SIN(latr)*SIN(lat_sun) +
141     .           COS(latr)*COS(lat_sun)*
142     .           (SIN(omegafin)-SIN(omegadeb))/
143     .           (omegafin-omegadeb)
144c
145      ENDIF
146c-----------------------moyenne
147      frac(i)=(zfrac1+zfrac2)/(omega2+deux_pi_local-omega1)
148      pmu0(i)=(zfrac1*z1_mu+zfrac2*z2_mu)/MAX(zfrac1+zfrac2,1.E-10)
149c
150      ENDIF   !---comparaison omega1 et omega2
151c
152c Petit test rajoute pour les cas pathologiques aux poles
153      if (pmu0(i).lt.0.) pmu0(i) = -1.*pmu0(i)
154
155      ENDDO
156c
157      END
Note: See TracBrowser for help on using the repository browser.