source: LMDZ6/trunk/libf/phylmd/iniorbit.f90

Last change on this file was 5274, checked in by abarral, 33 hours ago

Replace yomcst.h by existing module

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 3.4 KB
Line 
1SUBROUTINE iniorbit(paphelie, pperiheli, pyear_day, pperi_day, pobliq)
2  USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
3          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
4          , R_ecc, R_peri, R_incl                                      &
5          , RA, RG, R1SA                                         &
6          , RSIGMA                                                     &
7          , R, RMD, RMV, RD, RV, RCPD                    &
8          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
9          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
10          , RCW, RCS                                                 &
11          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
12          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
13          , RALPD, RBETD, RGAMD
14IMPLICIT NONE
15
16  ! =======================================================================
17
18  ! Auteur:
19  ! -------
20  ! Frederic Hourdin      22 Fevrier 1991
21
22  ! Objet:
23  ! ------
24  ! Initialisation du sous programme orbite qui calcule
25  ! a une date donnee de l'annee de duree year_day commencant
26  ! a l'equinoxe de printemps et dont le perihelie se situe
27  ! a la date peri_day, la distance au soleil et la declinaison.
28
29  ! Interface:
30  ! ----------
31  ! - Doit etre appele avant d'utiliser orbite.
32  ! - initialise une partie du common planete.h
33
34  ! Arguments:
35  ! ----------
36
37  ! Input:
38  ! ------
39  ! aphelie       \   aphelie et perihelie de l'orbite
40  ! periheli      /   en millions de kilometres.
41
42  ! =======================================================================
43
44  ! -----------------------------------------------------------------------
45  ! Declarations:
46  ! -------------
47
48  include "planete.h"
49
50
51  ! Arguments:
52  ! ----------
53
54  REAL paphelie, pperiheli, pyear_day, pperi_day, pobliq
55
56  ! Local:
57  ! ------
58
59  REAL zxref, zanom, zz, zx0, zdx, pi
60  INTEGER iter
61
62  ! -----------------------------------------------------------------------
63
64  pi = 2.*asin(1.)
65
66  aphelie = paphelie
67  periheli = pperiheli
68  year_day = pyear_day
69  obliquit = pobliq
70  peri_day = pperi_day
71
72  PRINT *, 'Perihelie en Mkm  ', periheli
73  PRINT *, 'Aphelie  en Mkm   ', aphelie
74  PRINT *, 'obliquite en degres  :', obliquit
75  PRINT *, 'Jours dans l annee : ', year_day
76  PRINT *, 'Date perihelie : ', peri_day
77  unitastr = 149.597870
78  e_elips = (aphelie-periheli)/(periheli+aphelie)
79  p_elips = 0.5*(periheli+aphelie)*(1-e_elips*e_elips)/unitastr
80
81  PRINT *, 'e_elips', e_elips
82  PRINT *, 'p_elips', p_elips
83
84  ! -----------------------------------------------------------------------
85  ! calcul de l'angle polaire et de la distance au soleil :
86  ! -------------------------------------------------------
87
88  ! calcul de l'zanomalie moyenne
89
90  zz = (year_day-pperi_day)/year_day
91  zanom = 2.*pi*(zz-nint(zz))
92  zxref = abs(zanom)
93  PRINT *, 'zanom  ', zanom
94
95  ! resolution de l'equation horaire  zx0 - e * sin (zx0) = zxref
96  ! methode de Newton
97
98  zx0 = zxref + r_ecc*sin(zxref)
99  DO iter = 1, 100
100    zdx = -(zx0-r_ecc*sin(zx0)-zxref)/(1.-r_ecc*cos(zx0))
101    IF (abs(zdx)<=(1.E-12)) GO TO 120
102    zx0 = zx0 + zdx
103  END DO
104120 CONTINUE
105  zx0 = zx0 + zdx
106  IF (zanom<0.) zx0 = -zx0
107  PRINT *, 'zx0   ', zx0
108
109  ! zteta est la longitude solaire
110
111  timeperi = 2.*atan(sqrt((1.+r_ecc)/(1.-r_ecc))*tan(zx0/2.))
112  PRINT *, 'longitude solaire du perihelie timeperi = ', timeperi
113
114  RETURN
115END SUBROUTINE iniorbit
Note: See TracBrowser for help on using the repository browser.