/[lmdze]/trunk/phylmd/orbite.f90
ViewVC logotype

Diff of /trunk/phylmd/orbite.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 254 by guez, Mon Feb 5 10:39:38 2018 UTC revision 317 by guez, Tue Dec 11 14:12:45 2018 UTC
# Line 6  CONTAINS Line 6  CONTAINS
6    
7    pure SUBROUTINE orbite(xjour, longi, dist)    pure SUBROUTINE orbite(xjour, longi, dist)
8    
9      ! From phylmd/orbite.F, version 1.1.1.1 2004/05/19 12:53:08      ! From phylmd/orbite.F, version 1.1.1.1, 2004/05/19 12:53:08
10    
11      ! Author: Z.X. Li (LMD/CNRS)      ! Author: Z. X. Li (LMD/CNRS)
12      ! Date: 1993/08/18      ! Date: 1993/08/18
13    
14      ! Pour un jour donn\'e, calcule la longitude vraie de la Terre et la      ! Pour un jour donn\'e, calcule la longitude vraie de la Terre et
15      ! distance Terre-Soleil, c'est-\`a-dire l'unit\'e astronomique.      ! la distance Terre-Soleil.
16    
17      use nr_util, only: pi      use nr_util, only: deg_to_rad
18      USE yomcst, ONLY: r_ecc, r_peri      USE yomcst, ONLY: r_ecc, r_peri
19    
20      REAL, INTENT (IN):: xjour ! jour de l'ann\'ee \`a compter du premier janvier      REAL, INTENT (IN):: xjour ! jour de l'ann\'ee \`a compter du premier janvier
# Line 27  CONTAINS Line 27  CONTAINS
27      ! distance terre-soleil (par rapport \`a la moyenne)      ! distance terre-soleil (par rapport \`a la moyenne)
28    
29      ! Local:      ! Local:
30      REAL pir, xl, xllp, xee, xse, ranm      REAL xl, xllp, xee, xse, ranm
31    
32      !----------------------------------------------------------------------      !----------------------------------------------------------------------
33    
     pir = pi / 180.  
34      xl = r_peri + 180.      xl = r_peri + 180.
35      xllp = xl * pir      xllp = xl * deg_to_rad
36      xee = r_ecc**2      xee = r_ecc**2
37      xse = sqrt(1. - xee)      xse = sqrt(1. - xee)
38      ranm = 2. * ((r_ecc / 2 + r_ecc * xee / 8.) * (1. + xse) * sin(xllp) &      ranm = 2. * ((r_ecc / 2 + r_ecc * xee / 8.) * (1. + xse) * sin(xllp) &
39           - xee / 4. * (0.5 + xse) * sin(2.*xllp) + r_ecc * xee / 8. &           - xee / 4. * (0.5 + xse) * sin(2.*xllp) + r_ecc * xee / 8. &
40           * (1. / 3. + xse) * sin(3. * xllp)) + (xjour - 81.) * pir - xllp           * (1. / 3. + xse) * sin(3. * xllp)) + (xjour - 81.) * deg_to_rad - xllp
41      xee = xee * r_ecc      xee = xee * r_ecc
42      longi = (ranm + (2. * r_ecc - xee / 4.) * sin(ranm) + 5. / 4. * r_ecc**2 &      longi = (ranm + (2. * r_ecc - xee / 4.) * sin(ranm) + 5. / 4. * r_ecc**2 &
43           * sin(2 * ranm) + 13. / 12. * xee * sin(3. * ranm)) / pir + xl           * sin(2 * ranm) + 13. / 12. * xee * sin(3. * ranm)) / deg_to_rad + xl
44    
45      IF (present(dist)) dist = (1 - r_ecc * r_ecc) &      IF (present(dist)) dist = (1 - r_ecc**2) &
46           / (1 + r_ecc * cos(pir * (longi - (r_peri + 180.))))           / (1 + r_ecc * cos(deg_to_rad * (longi - (r_peri + 180.))))
47    
48    END SUBROUTINE orbite    END SUBROUTINE orbite
49    

Legend:
Removed from v.254  
changed lines
  Added in v.317

  ViewVC Help
Powered by ViewVC 1.1.21