source: dynamico_lmdz/simple_physics/phyparam/param/mufract.F @ 4187

Last change on this file since 4187 was 4176, checked in by dubos, 5 years ago

simple_physics : copy code from FH

File size: 2.2 KB
Line 
1      SUBROUTINE mufract(jjm,pdecli, plat, pmu, pfract)
2      IMPLICIT NONE
3c
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         jjm              number of points
15c         pdecli           solar declinaison
16c         plat(jjm)        latitude
17c
18c      Output :
19c      --------
20c         pmu(jjm)          equivalent cosinus of the solar angle
21c         pfract(jjm)       fractionnal day
22c
23c
24c    inclinex is the obliquity of the planet.
25c
26c=======================================================================
27c
28c-----------------------------------------------------------------------
29c
30c    0. Declarations :
31c    -----------------
32c
33c     Arguments :
34c     -----------
35
36      INTEGER jjm
37      REAL plat(jjm),pmu(jjm), pfract(jjm)
38      REAL pdecli
39c
40c     Local variables :
41c     -----------------
42
43      REAL inclinex
44      PARAMETER (inclinex=26.7)
45      INTEGER j
46      REAL pi
47      REAL z,cz,sz,tz,phi,cphi,sphi,tphi
48      REAL ap,a,t,b
49c
50c=======================================================================
51c
52      pi = 4. * atan(1.0)
53      z = pdecli
54      cz = cos (z*pi/180.)
55      sz = sin (z*pi/180.)
56c
57      DO 20 j = 1, jjm
58c
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 = -tphi * sz / cz
66         a = 1.0 - t*t
67         ap = a
68         IF(t.eq.0.) THEN
69            t=0.5*pi
70         ELSE
71            IF (a.lt.0.) a = 0.
72            t = sqrt(a) / t
73            IF (t.lt.0.) THEN
74               t = -atan (-t) + pi
75            ELSE
76               t = atan(t)
77            ENDIF
78         ENDIF
79         pmu(j) = (sphi*sz*t) / pi + b*sin(t)/pi
80         pfract(j) = t / pi
81         IF (ap .lt.0.) THEN
82            pmu(j) = sphi * sz
83            pfract(j) = 1.0
84         ENDIF
85         IF (pmu(j).le.0.0) pmu(j) = 0.0
86         pmu(j) = pmu(j) / pfract(j)
87         IF (pmu(j).eq.0.) pfract(j) = 0.
88c
89   20 CONTINUE
90c
91      RETURN
92      END
93c
94c* end of mufract
95c=======================================================================
96c
Note: See TracBrowser for help on using the repository browser.