source: trunk/LMDZ.MARS/libf/phymars/mucorr.F @ 3807

Last change on this file since 3807 was 3740, checked in by emillour, 7 weeks ago

Mars PCM:
Code tidying; removed unused mufract.F (mucorr.F does the job); turned
ambiguously named sig.F to sig_h2o.F90 and make it a module.
EM

File size: 2.6 KB
Line 
1      MODULE mucorr_mod
2     
3      IMPLICIT NONE
4     
5      CONTAINS
6     
7      SUBROUTINE mucorr(npts,pdeclin, plat, pmu, pfract,phaut,prad)
8      IMPLICIT NONE
9
10c=======================================================================
11c
12c   Compute equivalent solar angle and fraction of day whithout
13c   diurnal cycle.
14c
15c   parmeters :
16c   -----------
17c
18c      Input :
19c      -------
20c         npts             number of points
21c         pdeclin          solar declinaison
22c         plat(npts)       latitude
23c         phaut            thickness of atmosphere
24c         prad             planet radius
25c
26c      Output :
27c      --------
28c         pmu(npts)          equivalent cosine of the solar angle
29c         pfract(npts)       fractionnal day
30c
31c=======================================================================
32
33c-----------------------------------------------------------------------
34c
35c    0. Declarations :
36c    -----------------
37
38c     Arguments :
39c     -----------
40      INTEGER,INTENT(IN) :: npts
41      REAL,INTENT(IN) :: plat(npts)
42      REAL,INTENT(IN) :: phaut,prad,pdeclin
43      REAL,INTENT(OUT) :: pmu(npts), pfract(npts)
44c
45c     Local variables :
46c     -----------------
47      INTEGER j
48      REAL pi
49      REAL z,cz,sz,tz,phi,cphi,sphi,tphi
50      REAL ap,a,t,b, tp
51      REAL alph
52
53c-----------------------------------------------------------------------
54
55      pi = 4. * atan(1.0)
56      z = pdeclin
57      cz = cos (z)
58      sz = sin (z)
59
60      DO j = 1, npts
61
62         phi = plat(j)
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            tp=0.5*pi
74         ELSE
75            IF (a.lt.0.) a = 0.
76            t = sqrt(a) / t
77            IF (t.lt.0.) then
78               tp = -atan (-t) + pi
79            ELSE
80               tp = atan(t)
81            ENDIF
82         ENDIF
83         t = tp
84   
85         pmu(j) = (sphi*sz*t) / pi + b*sin(t)/pi
86         pfract(j) = t / pi
87         IF (ap .lt.0.) then
88            pmu(j) = sphi * sz
89            pfract(j) = 1.0
90         ENDIF
91         IF (pmu(j).le.0.0) pmu(j) = 0.0
92         pmu(j) = pmu(j) / pfract(j)
93         IF (pmu(j).eq.0.) pfract(j) = 0.
94
95      ENDDO
96
97c-----------------------------------------------------------------------
98c   correction de rotondite:
99c   ------------------------
100
101      alph=phaut/prad
102      DO j=1,npts
103c !!!!!!
104         pmu(j)=sqrt(1224.*pmu(j)*pmu(j)+1.)/35.
105c    $          (sqrt(alph*alph*pmu(j)*pmu(j)+2.*alph+1.)-alph*pmu(j))
106      ENDDO
107
108      END SUBROUTINE mucorr
109
110      END MODULE mucorr_mod
Note: See TracBrowser for help on using the repository browser.