source: trunk/LMDZ.GENERIC/libf/phystd/rings.F90 @ 1145

Last change on this file since 1145 was 1133, checked in by aslmd, 11 years ago

LMDZ.GENERIC. LMDZ.UNIVERSAL. A first version of ring shadowing subroutine. Authors: M. Sylvestre, M. Capderou, S. Guerlet, A. Spiga.

File size: 5.5 KB
Line 
1SUBROUTINE rings(ngrid, declin, ptime, rad, flat, eclipse)
2! Calculates Saturn's rings shadowing
3! Authors: M. Sylvestre, M. Capderou, S. Guerlet, A. Spiga
4
5    use comdiurn_h
6    use comgeomfi_h
7 
8    implicit none   
9
10    INTEGER, INTENT(IN) :: ngrid  ! horizontal grid dimension
11    REAL, INTENT(IN) :: declin    ! latitude of the subsolar point
12    REAL, INTENT(IN) :: ptime     ! UTC time in sol fraction : ptime=0.5 at noon
13    REAL, INTENT(IN) :: rad       ! equatorial radius of the planet
14    REAL, INTENT(IN) :: flat      ! flattening of the planet
15    REAL, DIMENSION(ngrid), INTENT(OUT) :: eclipse ! absorption of the light by the rings   
16   
17    REAL :: rpol   ! polar radius of the planet
18    REAL :: e      ! shape excentricity of the planet : (1-e*e) = (1-f)*(1-f)   
19    INTEGER, PARAMETER :: nb_a=1 ! number of subdivisions of the A ring
20    INTEGER, PARAMETER :: nb_b=3 ! number of subdivisions of the B ring
21    INTEGER, PARAMETER :: nb_c=1 ! number of subdivisions of the C ring
22    INTEGER :: i
23
24    ! arrays for the rings. TBD: dynamical?
25    REAL, DIMENSION(nb_a) :: A_Rint ! internal radii of the subdivisions of the A ring
26    REAL, DIMENSION(nb_a) :: A_Rext ! external radii of the subdivisions of the A ring
27    REAL, DIMENSION(nb_b) :: B_Rint ! internal radii of the subdivisions of the B ring
28    REAL, DIMENSION(nb_b) :: B_Rext ! external radii of the subdivisions of the B ring
29    REAL, DIMENSION(nb_c) :: C_Rint ! internal radii of the subdivisions of the C ring
30    REAL, DIMENSION(nb_c) :: C_Rext ! external radii of the subdivisions of the C ring
31               
32    ! Opacities of the rings : for each one we can give different opacities for each part
33    REAL, DIMENSION(nb_a) :: tau_A ! opacity of the A ring
34    REAL, DIMENSION(nb_b) :: tau_B ! opacity of the B ring
35    REAL, DIMENSION(nb_c) :: tau_C ! opacity of the C ring
36               
37    ! Parameters used to calculate if a point is under a ring subdivision's shadow
38    REAL :: phi_S                             ! subsolar point longitude
39    REAL, PARAMETER :: pi=acos(-1.0)   
40    REAL, DIMENSION(:), ALLOCATABLE:: x, y, z ! cartesian coordinates of the points on the planet
41    REAL :: xs, ys, zs                        ! cartesian coordinates of the points of the subsolar point
42    REAL, DIMENSION(:), ALLOCATABLE :: k      ! parameter (?)
43    REAL, DIMENSION(:), ALLOCATABLE :: N      ! parameter to compute cartesian coordinates on a ellipsoidal planet
44    REAL, DIMENSION(:), ALLOCATABLE :: r      ! distance at which the incident ray of sun crosses the equatorial plane
45                                              ! measured from the center of the planet   
46    REAL :: Ns                                ! (same for the subsolar point)
47   
48    ! equinox --> no shadow (AS: why is this needed?)
49    if(declin .eq. 0.) then
50        eclipse = 0.
51        return
52    endif
53
54! 1) INITIALIZATION
55
56    ! Generic
57    rpol = (1.- flat)*rad
58    e = sqrt(2*flat - flat**2)
59    ALLOCATE(x(ngrid))
60    ALLOCATE(y(ngrid))
61    ALLOCATE(z(ngrid))
62    ALLOCATE(k(ngrid))
63    ALLOCATE(N(ngrid))
64    ALLOCATE(r(ngrid))
65    eclipse = 2000.
66
67    ! Size of the rings
68    A_Rint(1) = 2.01*rad
69    A_Rext(1) = 2.26*rad
70    B_Rint(1) = 1.55*rad
71    B_Rext(1) = 1.67*rad
72    B_Rint(2) = 1.67*rad
73    B_Rext(2) = 1.83*rad
74    B_Rint(3) = 1.83*rad
75    B_Rext(3) = 1.92*rad
76    C_Rint(1) = 1.21*rad
77    C_Rext(1) = 1.53*rad
78   
79    ! Opacities of the rings (TBD: update with most recent values?)
80    tau_A(1) = 0.4
81    tau_B(1) = 0.8
82    tau_B(2) = 2.
83    tau_B(3) = 1.4
84    tau_C(1) = 0.08
85
86    ! Convert to cartesian coordinates
87    N = rad/sqrt(1-(e**2)*sinlat**2)
88    x = N*coslat*coslon
89    y = N*coslat*sinlon
90    z = N*(1-e**2)*sinlat
91
92! 2) LOCATION OF THE SUBSOLAR POINT
93 
94    ! subsolar longitude is deduced from time fraction ptime
95    ! SG: the minus sign is important! ... otherwise subsolar point adopts a reverse rotation
96    phi_S = -(ptime - 0.5)*2.*pi
97    write(*,*) 'subsol point coords : ', declin*180./pi, phi_S*180./pi
98
99    ! subsolar latitude is declin (declination of the sun)
100    ! now convert in cartesian coordinates :
101    Ns = rad/sqrt(1-(e**2)*sin(declin)**2)
102    xs = Ns*cos(declin)*cos(phi_S)
103    ys = Ns*cos(declin)*sin(phi_S)
104    zs = Ns*(1-e**2)*sin(declin)
105
106! 3) WHERE DOES THE INCIDENT RAY OF SUN CROSS THE EQUATORIAL PLAN ?
107
108    k = -z/zs
109    r = (k*xs + x)**2 + (k*ys + y)**2
110    r = sqrt(r)
111
112! 4) SO WHERE ARE THE SHADOW OF THESE RINGS ?
113
114    ! Summer hemisphere is not under the shadow of the rings
115    where(lati*declin .gt. 0.)
116       eclipse = 1000.
117    end where
118
119    ! No shadow of the rings by night
120    where(x*xs + y*ys + z*zs .lt. 0.)
121       eclipse = 1000.
122    end where
123
124    ! if the incident rays of sun cross a ring, there is a shadow
125    do i=1, nb_A
126        where(r .ge. A_Rint(i) .and. r .le. A_Rext(i) .and. eclipse .ne. 1000.)
127            eclipse = 1. - exp(-tau_A(i)/cos(declin))
128        end where
129    end do
130
131    do i=1, nb_B
132        where(r .ge. B_Rint(i) .and. r .le. B_Rext(i) .and. eclipse .ne. 1000.)
133            eclipse = 1. - exp(-tau_B(i)/cos(declin))
134        end where
135    enddo
136   
137    do i=1, nb_C
138        where(r .ge. C_Rint(i) .and. r .le. C_Rext(i) .and. eclipse .ne. 1000.)
139            eclipse = 1. - exp(-tau_C(i)/cos(declin))
140        end where
141    enddo
142
143    ! At the other places and the excluded ones, eclipse is 0.
144    where(eclipse .eq. 2000. .or. eclipse .eq. 1000.)
145        eclipse = 0.
146    end where
147
148! 5) CLEAN THE PLACE
149    DEALLOCATE(x)
150    DEALLOCATE(y)
151    DEALLOCATE(z)
152    DEALLOCATE(k)
153    DEALLOCATE(N)
154    DEALLOCATE(r)
155
156END SUBROUTINE rings
Note: See TracBrowser for help on using the repository browser.