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

Last change on this file since 3303 was 1530, checked in by emillour, 9 years ago

Venus and Titan GCMs:
Updates in the physics to keep up with updates in LMDZ5 (up to
LMDZ5 trunk, rev 2350) concerning dynamics/physics separation:

  • Adapted makelmdz and makelmdz_fcm script to stop if trying to compile 1d model or newstart or start2archive in parallel.
  • got rid of references to "dimensions.h" in physics. Within physics packages, use nbp_lon (=iim), nbp_lat (=jjmp1) and nbp_lev (=llm) from module mod_grid_phy_lmdz (in phy_common) instead. Only partially done for Titan, because of many hard-coded commons; a necessary first step will be to clean these up (using modules).

EM

File size: 5.7 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 "YOMCST.h"
29#include "comorbit.h"
30c================================================================
31      real longi, gmtime, pdtrad
32      real lat(klon), long(klon), pmu0(klon), frac(klon)
33c================================================================
34      integer i
35      real gmtime1, gmtime2
36      real pi_local, deux_pi_local, incl
37      real omega1, omega2, omega
38c omega1, omega2 : temps 1 et 2 exprime en radian avec 0 a midi.
39c omega : heure en radian du coucher de soleil
40c -omega est donc l'heure en radian de lever du soleil
41      real omegadeb, omegafin
42      real zfrac1, zfrac2, z1_mu, z2_mu
43      real lat_sun          ! declinaison en radian
44      real lon_sun          ! longitude solaire en radian
45      real latr             ! latitude du pt de grille en radian
46c================================================================
47c
48      pi_local = 4.0 * ATAN(1.0)
49      deux_pi_local = 2.0 * pi_local
50      incl=obliquit * pi_local / 180.
51c
52      lon_sun = longi * pi_local / 180.0
53      lat_sun = ASIN (SIN(lon_sun)*SIN(incl) )
54c
55      gmtime1=gmtime*RDAY
56      gmtime2=gmtime*RDAY+pdtrad
57c
58      DO i = 1, klon
59c
60      latr = lat(i) * pi_local / 180.
61c
62c--pose probleme quand lat=+/-90 degres
63c
64c      omega = -TAN(latr)*TAN(lat_sun)
65c      omega = ACOS(omega)
66c      IF (latr.GE.(pi_local/2.+lat_sun)
67c     .    .OR. latr.LE.(-pi_local/2.+lat_sun)) THEN
68c         omega = 0.0       ! nuit polaire
69c      ENDIF
70c      IF (latr.GE.(pi_local/2.-lat_sun)
71c     .          .OR. latr.LE.(-pi_local/2.-lat_sun)) THEN
72c         omega = pi_local  ! journee polaire
73c      ENDIF
74c
75c--remplace par cela (le cas par defaut est different)
76c
77      omega=0.0  !--nuit polaire
78      IF (latr.GE.(pi_local/2.-lat_sun)
79     .          .OR. latr.LE.(-pi_local/2.-lat_sun)) THEN
80         omega = pi_local  ! journee polaire
81      ENDIF
82      IF (latr.LT.(pi_local/2.+lat_sun).AND.
83     .    latr.GT.(-pi_local/2.+lat_sun).AND.
84     .    latr.LT.(pi_local/2.-lat_sun).AND.
85     .    latr.GT.(-pi_local/2.-lat_sun)) THEN
86      omega = -TAN(latr)*TAN(lat_sun)
87      omega = ACOS(omega)
88      ENDIF
89c
90         omega1 = gmtime1 + long(i)*RDAY/360.0
91         omega1 = omega1 / RDAY*deux_pi_local
92         omega1 = MOD (omega1+deux_pi_local, deux_pi_local)
93         omega1 = omega1 - pi_local
94c
95         omega2 = gmtime2 + long(i)*RDAY/360.0
96         omega2 = omega2 / RDAY*deux_pi_local
97         omega2 = MOD (omega2+deux_pi_local, deux_pi_local)
98         omega2 = omega2 - pi_local
99c
100      IF (omega1.LE.omega2) THEN  !--on est dans la meme journee locale
101c
102      IF (omega2.LE.-omega .OR. omega1.GE.omega
103     .                     .OR. omega.LT.1e-5) THEN   !--nuit
104         frac(i)=0.0
105         pmu0(i)=0.0
106      ELSE                                              !--jour+nuit/jour
107        omegadeb=MAX(-omega,omega1)
108        omegafin=MIN(omega,omega2)
109        frac(i)=(omegafin-omegadeb)/(omega2-omega1)
110        pmu0(i)=SIN(latr)*SIN(lat_sun) +
111     .          COS(latr)*COS(lat_sun)*
112     .          (SIN(omegafin)-SIN(omegadeb))/
113     .          (omegafin-omegadeb)       
114      ENDIF
115c
116      ELSE  !---omega1 GT omega2 -- a cheval sur deux journees
117c
118c-------------------entre omega1 et pi
119      IF (omega1.GE.omega) THEN  !--nuit
120         zfrac1=0.0
121         z1_mu =0.0
122      ELSE                       !--jour+nuit
123        omegadeb=MAX(-omega,omega1)
124        omegafin=omega
125        zfrac1=omegafin-omegadeb
126        z1_mu =SIN(latr)*SIN(lat_sun) +
127     .          COS(latr)*COS(lat_sun)*
128     .          (SIN(omegafin)-SIN(omegadeb))/
129     .          (omegafin-omegadeb)
130      ENDIF
131c---------------------entre -pi et omega2
132      IF (omega2.LE.-omega) THEN   !--nuit
133         zfrac2=0.0
134         z2_mu =0.0
135      ELSE                         !--jour+nuit
136         omegadeb=-omega
137         omegafin=MIN(omega,omega2)
138         zfrac2=omegafin-omegadeb
139         z2_mu =SIN(latr)*SIN(lat_sun) +
140     .           COS(latr)*COS(lat_sun)*
141     .           (SIN(omegafin)-SIN(omegadeb))/
142     .           (omegafin-omegadeb)
143c
144      ENDIF
145c-----------------------moyenne
146      frac(i)=(zfrac1+zfrac2)/(omega2+deux_pi_local-omega1)
147      pmu0(i)=(zfrac1*z1_mu+zfrac2*z2_mu)/MAX(zfrac1+zfrac2,1.E-10)
148c
149      ENDIF   !---comparaison omega1 et omega2
150c
151c Petit test rajoute pour les cas pathologiques aux poles
152      if (pmu0(i).lt.0.) pmu0(i) = -1.*pmu0(i)
153
154      ENDDO
155c
156      END
Note: See TracBrowser for help on using the repository browser.