source: dynamico_lmdz/simple_physics/phyparam/param/zenang.F @ 4200

Last change on this file since 4200 was 4191, checked in by dubos, 5 years ago

simple_physics : cleanup astronomy

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