source: trunk/LMDZ.GENERIC/libf/phystd/iniorbit.F @ 2176

Last change on this file since 2176 was 1384, checked in by emillour, 10 years ago

Generic GCM:

  • Some code cleanup: turning comcstfi.h into module comcstfi_mod.F90

EM

File size: 2.8 KB
RevLine 
[135]1      SUBROUTINE iniorbit
[253]2     $     (papoastr,pperiastr,pyear_day,pperi_day,pobliq)
[1308]3     
4      USE planete_mod, only: apoastr, periastr, year_day, obliquit,
5     &                       peri_day, e_elips, p_elips, timeperi
[1384]6      use comcstfi_mod, only: pi
[135]7      IMPLICIT NONE
8
[1384]9!=======================================================================
10! Initialisation of orbital parameters (stored in planete_h module)
11!=======================================================================
[135]12
13c   Arguments:
14c   ----------
15
[1384]16      REAL,INTENT(IN) :: papoastr,pperiastr,pyear_day,pperi_day,pobliq
[135]17
18c   Local:
19c   ------
20
21      REAL zxref,zanom,zz,zx0,zdx
22      INTEGER iter
23
24c-----------------------------------------------------------------------
25
26      pi=2.*asin(1.)
27
[253]28      apoastr =papoastr
29      periastr=pperiastr
[135]30      year_day=pyear_day
31      obliquit=pobliq
32      peri_day=pperi_day
33
[590]34
35      !!!! SPARADRAP TEMPORAIRE !!!!
36      !!!! SPARADRAP TEMPORAIRE !!!!
37      !!!! We hope that all cases are above 25 Mkm [OK with Gliese 581d]
38      IF ( apoastr .gt. 25.) THEN
39        PRINT*,'!!!!! WARNING !!!!!'
40        PRINT*,'!!!!! YOU ARE ABOUT TO WITNESS A DIRT HACK !!!!!'
41        PRINT*,'This must be an old start file.'
42        PRINT*,'The code changed 19/03/2012: we now use AU.'
43        PRINT*,'So I am assuming units are in Mkm here'
44        PRINT*,'and I am performing a conversion towards AU.'
45        periastr = periastr / 149.598 ! Mkm to AU
46        apoastr = apoastr / 149.598 ! Mkm to AU
47      ENDIF
48      !!!! SPARADRAP TEMPORAIRE !!!!
49      !!!! SPARADRAP TEMPORAIRE !!!!
50
51 
[1384]52      PRINT*,'iniorbit: Periastron in AU  ',periastr
53      PRINT*,'iniorbit: Apoastron in AU  ',apoastr
54      PRINT*,'iniorbit: Obliquity in degrees  :',obliquit
[590]55
56
[253]57      e_elips=(apoastr-periastr)/(periastr+apoastr)
[590]58      p_elips=0.5*(periastr+apoastr)*(1-e_elips*e_elips)
[135]59
[1384]60      print*,'iniorbit: e_elips',e_elips
61      print*,'iniorbit: p_elips',p_elips
[135]62
[1384]63!-----------------------------------------------------------------------
64! compute polar angle and distance to the Sun:
65! -------------------------------------------------------
[135]66
[1384]67!  compute mean anomaly zanom
[135]68
69      zz=(year_day-pperi_day)/year_day
70      zanom=2.*pi*(zz-nint(zz))
71      zxref=abs(zanom)
[1384]72      PRINT*,'iniorbit: zanom  ',zanom
[135]73
[1384]74!  solve equation  zx0 - e * sin (zx0) = zxref for eccentric anomaly zx0
75!  using Newton method
[135]76
77      zx0=zxref+e_elips*sin(zxref)
[1384]78      DO iter=1,100
[135]79         zdx=-(zx0-e_elips*sin(zx0)-zxref)/(1.-e_elips*cos(zx0))
[1384]80         if(abs(zdx).le.(1.e-12)) exit
[135]81         zx0=zx0+zdx
[1384]82      ENDDO
83
[135]84      zx0=zx0+zdx
85      if(zanom.lt.0.) zx0=-zx0
[1384]86      PRINT*,'iniorbit: zx0   ',zx0
[135]87
88      timeperi=2.*atan(sqrt((1.+e_elips)/(1.-e_elips))*tan(zx0/2.))
[1384]89      PRINT*,'iniorbit: Perihelion solar long. Ls (deg)=',
90     &       360.-timeperi*180./pi
[135]91
92      END
Note: See TracBrowser for help on using the repository browser.