source: trunk/LMDZ.VENUS/libf/phyvenus/mucorr.F @ 1543

Last change on this file since 1543 was 3, checked in by slebonnois, 14 years ago

Creation de repertoires:

  • chantiers : pour communiquer sur nos projets de modifs
  • documentation : pour stocker les docs

Ajout de:

  • libf/phytitan : physique de Titan
  • libf/chimtitan: chimie de Titan
  • libf/phyvenus : physique de Venus
File size: 3.2 KB
Line 
1      SUBROUTINE mucorr(npts,plongi, plat, pmu, pfract)
2      IMPLICIT NONE
3
4c=======================================================================
5c
6c   Calcul of equivalent solar angle and and fraction of day whithout
7c   diurnal cycle.
8c
9c   parmeters :
10c   -----------
11c
12c      Input :
13c      -------
14c         npts             number of points
15c         plongi           solar longitude (degres)
16c         plat(npts)       latitude (en degres)
17c
18c      Output :
19c      --------
20c         pmu(npts)          equivalent cosinus of the solar angle
21c         pfract(npts)       fractionnal day
22c
23c=======================================================================
24
25c-----------------------------------------------------------------------
26c
27c    0. Declarations :
28c    -----------------
29
30#include "YOMCST.h"
31
32c     Arguments :
33c     -----------
34      INTEGER npts
35      REAL plat(npts),pmu(npts), pfract(npts)
36      REAL plongi
37c
38c     Local variables :
39c     -----------------
40      INTEGER j
41      REAL pi
42      REAL z,cz,sz,tz,phi,cphi,sphi,tphi
43      REAL ap,a,t,b,tp
44      real pdeclin,incl,lon_sun
45
46c-----------------------------------------------------------------------
47
48c     pi = 4. * atan(1.0)
49c     print*,'PI=',pi
50      pi=2.*asin(1.)
51c     print*,'PI=B',pi
52
53      incl=R_incl * pi / 180.                  ! obliquite en radian
54      lon_sun = plongi * pi / 180.0            ! Ls en radian
55      pdeclin = ASIN (SIN(lon_sun)*SIN(incl) ) ! declin en radian
56c     print*,'npts,pdeclin',npts,pdeclin*180./pi
57      z = pdeclin
58      cz = cos (z)
59      sz = sin (z)
60c      print*,'cz,sz',cz,sz
61
62      DO 20 j = 1, npts
63
64         phi = plat(j)*pi/180.  ! latitude en radian
65         cphi = cos(phi)
66         if (cphi.le.1.e-9) cphi=1.e-9
67         sphi = sin(phi)
68         tphi = sphi / cphi
69         b = cphi * cz
70         t = -tphi * sz / cz
71         a = 1.0 - t*t
72         ap = a
73
74         IF(t.eq.0.) then
75            t=0.5*pi
76         ELSE
77            IF (a.lt.0.) a = 0.
78            t = sqrt(a) / t
79            IF (t.lt.0.) then
80               tp = -atan (-t) + pi
81            ELSE
82               tp = atan(t)
83            ENDIF
84            t = tp
85         ENDIF
86   
87         pmu(j) = (sphi*sz*t) / pi + b*sin(t)/pi
88         pfract(j) = t / pi
89         IF (ap .lt.0.) then
90            pmu(j) = sphi * sz
91            pfract(j) = 1.0
92         ENDIF
93
94         IF (pmu(j).le.0.0) pmu(j) = 0.0
95         pmu(j) = pmu(j) / pfract(j)
96         IF (pmu(j).eq.0.) pfract(j) = 0.
97
98   20 CONTINUE
99c        call dump2d(48,31,pfract(2),'FRACT      ')
100c        call dump2d(48,31,pmu(2),'MU0        ')
101c        stop
102                                 
103c-----------------------------------------------------------------------
104c   correction de rotondite:
105c   ------------------------
106
107c        print*,'dans mucorr avant correction rotondite'
108c        print*,'pmu(1)=',pmu(1),' pmu(npts/2)=',pmu(npts/2)
109c        print*,'pfract(1)=',pfract(1),' pfract(npts/2)=',pfract(npts/2)
110         
111      DO 30 j=1,npts
112c !!!!!!
113         pmu(j)=sqrt(1224.*pmu(j)*pmu(j)+1.)/35.
11430    CONTINUE
115
116c        print*,'dans mucorr apres correction rotondite'
117c        print*,'pmu(1)=',pmu(1),' pmu(npts/2)=',pmu(npts/2)
118         
119      RETURN
120      END
Note: See TracBrowser for help on using the repository browser.