source: trunk/LMDZ.PLUTO/libf/phypluto/mucorr.F @ 3380

Last change on this file since 3380 was 3184, checked in by afalco, 10 months ago

Pluto PCM:
Added LMDZ.PLUTO, a copy of the generic model,
cleaned from some unnecessary modules (water, ...)
AF

File size: 2.8 KB
Line 
1      SUBROUTINE mucorr(npts,pdeclin, plat, pmu,pfract,phaut,prad)
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         pdeclin          solar declinaison
16c         plat(npts)        latitude
17c         phaut            hauteur typique de l'atmosphere
18c         prad             rayon planetaire
19c
20c      Output :
21c      --------
22c         pmu(npts)          equivalent cosinus of the solar angle
23c         pfract(npts)       fractionnal day
24c
25c=======================================================================
26
27c-----------------------------------------------------------------------
28c
29c    0. Declarations :
30c    -----------------
31
32c     Arguments :
33c     -----------
34      INTEGER npts
35      REAL plat(npts),pmu(npts), pfract(npts)
36      REAL phaut,prad,pdeclin
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, rap
44      REAL alph
45
46c-----------------------------------------------------------------------
47
48c----- SG: geometry adapted to a flattened planet (Feb2014)
49c----- AF24: replaced flat param by 0
50
51      pi = 4. * atan(1.0)
52      z = pdeclin
53      cz = cos (z)
54      sz = sin (z)
55      rap = 1./((1.-0)**2)
56
57      DO 20 j = 1, npts
58
59         phi = plat(j)
60         cphi = cos(phi)
61         if (cphi.le.1.e-9) cphi=1.e-9
62         sphi = sin(phi)
63         tphi = sphi / cphi
64         b = cphi * cz
65         t = -rap*tphi * sz / cz
66         a = 1.0 - t*t
67         ap = a
68   
69         IF(t.eq.0.) then
70            tp=0.5*pi
71         ELSE
72            IF (a.lt.0.) a = 0.
73            t = sqrt(a) / t
74            IF (t.lt.0.) then
75               tp = -atan (-t) + pi
76            ELSE
77               tp = atan(t)
78            ENDIF
79         ENDIF
80         t = tp
81   
82         pmu(j) = (sphi*sz*t*rap) / pi + b*sin(t)/pi
83         pfract(j) = t / pi
84         IF (ap .lt.0.) then
85            pmu(j) = sphi * sz*rap
86            pfract(j) = 1.0
87         ENDIF
88         IF (pmu(j).le.0.0) pmu(j) = 0.0
89         pmu(j) = pmu(j) / pfract(j)
90         IF (pmu(j).eq.0.) pfract(j) = 0.
91
92         pmu(j)=pmu(j)/SQRT(cphi**2 + (rap**2) * (sphi**2))
93
94   20 CONTINUE
95
96c-----------------------------------------------------------------------
97c   correction de rotondite:
98c   ------------------------
99
100      ! condition added to avoid errors when rad is not set (e.g. 1D runs)
101      IF (prad.ne.0) THEN
102 
103      alph=phaut/prad
104      DO 30 j=1,npts
105c !!!!!!
106 !!!!!!! AS: how generic is this???
107         pmu(j)=sqrt(1224.*pmu(j)*pmu(j)+1.)/35.
108c    $          (sqrt(alph*alph*pmu(j)*pmu(j)+2.*alph+1.)-alph*pmu(j))
10930    CONTINUE
110
111      ENDIF
112
113      RETURN
114      END
Note: See TracBrowser for help on using the repository browser.