source: trunk/LMDZ.TITAN/libf/phytitan/mucorr.F @ 855

Last change on this file since 855 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,lon_sun, 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         lon_sun          solar longitude (radians!!)
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#include "comorbit.h"
32
33c     Arguments :
34c     -----------
35      INTEGER npts
36      REAL plat(npts),pmu(npts), pfract(npts)
37      REAL lon_sun
38c
39c     Local variables :
40c     -----------------
41      INTEGER j
42      REAL z,cz,sz,tz,phi,cphi,sphi,tphi
43      REAL ap,a,t,b,tp
44      real pdeclin,incl
45
46c-----------------------------------------------------------------------
47
48c verifs
49c     print*,"LATITUDES=",plat(1),plat(npts/2),plat(npts)
50c     print*,"zls=",lon_sun*180/RPI
51
52      incl=obliquit * RPI / 180.                ! obliquite en radian
53      pdeclin = ASIN (SIN(lon_sun)*SIN(incl) ) ! declin en radian
54c     print*,'npts,pdeclin',npts,pdeclin*180./RPI
55      z = pdeclin
56      cz = cos (z)
57      sz = sin (z)
58c      print*,'cz,sz',cz,sz
59
60      DO 20 j = 1, npts
61
62         phi = plat(j)*RPI/180.  ! latitude en radian
63         cphi = cos(phi)
64         if (cphi.le.1.e-9) cphi=1.e-9
65         sphi = sin(phi)
66         tphi = sphi / cphi
67         b = cphi * cz
68         t = -tphi * sz / cz
69         a = 1.0 - t*t
70         ap = a
71
72         IF(t.eq.0.) then
73            t=0.5*RPI
74         ELSE
75            IF (a.lt.0.) a = 0.
76            t = sqrt(a) / t
77            IF (t.lt.0.) then
78               tp = -atan (-t) + RPI
79            ELSE
80               tp = atan(t)
81            ENDIF
82            t = tp
83         ENDIF
84   
85         pmu(j) = (sphi*sz*t) / RPI + b*sin(t)/RPI
86         pfract(j) = t / RPI
87         IF (ap .lt.0.) then
88            pmu(j) = sphi * sz
89            pfract(j) = 1.0
90         ENDIF
91
92         IF (pmu(j).le.0.0) pmu(j) = 0.0
93         pmu(j) = pmu(j) / pfract(j)
94         IF (pmu(j).eq.0.) pfract(j) = 0.
95
96   20 CONTINUE
97c        call dump2d(48,31,pfract(2),'FRACT      ')
98c        call dump2d(48,31,pmu(2),'MU0        ')
99c        stop
100                                 
101c-----------------------------------------------------------------------
102c   correction de rotondite:
103c   ------------------------
104
105c        print*,'dans mucorr avant correction rotondite'
106c        print*,'pmu(1)=',pmu(1),' pmu(npts/2)=',pmu(npts/2)
107c        print*,'pfract(1)=',pfract(1),' pfract(npts/2)=',pfract(npts/2)
108         
109      DO 30 j=1,npts
110c !!!!!!
111         pmu(j)=sqrt(1224.*pmu(j)*pmu(j)+1.)/35.
11230    CONTINUE
113
114c        print*,'dans mucorr apres correction rotondite'
115c        print*,'pmu(1)=',pmu(1),' pmu(npts/2)=',pmu(npts/2)
116         
117c     print*,"pmu=",pmu(1),pmu(npts/2),pmu(npts)
118c     print*,"pfract=",pfract(1),pfract(npts/2),pfract(npts)
119      RETURN
120      END
Note: See TracBrowser for help on using the repository browser.