source: trunk/LMDZ.COMMON/libf/evolution/recomp_orb_param_mod.F90 @ 3974

Last change on this file since 3974 was 3961, checked in by jbclement, 2 months ago

PEM:
Clearing all the tags and code related to the Generic PCM.
JBC

File size: 4.3 KB
Line 
1MODULE recomp_orb_param_mod
2!=======================================================================
3!
4! Purpose: Recompute orbit parameters based on values by Laskar et al.,
5!
6! Author: RV, JBC
7!=======================================================================
8
9implicit none
10
11!=======================================================================
12contains
13!=======================================================================
14
15SUBROUTINE recomp_orb_param(i_myear,i_myear_leg)
16
17use time_evol_mod,    only: year_bp_ini, var_obl, var_ecc, var_lsp
18use lask_param_mod,   only: yearlask, obllask, ecclask, lsplask, end_lask_param_mod, last_ilask
19use comcstfi_h,       only: pi
20use planete_h,        only: e_elips, obliquit, lsperi, periheli, aphelie, p_elips, peri_day, year_day
21use call_dayperi_mod, only: call_dayperi
22
23implicit none
24
25!--------------------------------------------------------
26! Input Variables
27!--------------------------------------------------------
28real, intent(in) :: i_myear     ! Number of simulated Martian years
29real, intent(in) :: i_myear_leg ! Number of iterations of the PEM
30
31!--------------------------------------------------------
32! Output Variables
33!--------------------------------------------------------
34
35!--------------------------------------------------------
36! Local variables
37!--------------------------------------------------------
38real    :: Year           ! Year of the simulation
39real    :: Lsp            ! Ls perihelion
40integer :: ilask          ! Loop variable
41real    :: halfaxe        ! Million of km
42real    :: unitastr
43real    :: xa, xb, ya, yb ! Variables for interpolation
44logical :: found_year     ! Flag variable
45
46! **********************************************************************
47! 0. Initializations
48! **********************************************************************
49Year = year_bp_ini + i_myear ! We compute the current year
50Lsp = lsperi*180./pi         ! We convert in degree
51
52write(*,*) 'recomp_orb_param, Old year =', Year - i_myear_leg
53write(*,*) 'recomp_orb_param, Old obl. =', obliquit
54write(*,*) 'recomp_orb_param, Old ecc. =', e_elips
55write(*,*) 'recomp_orb_param, Old Lsp  =', Lsp
56write(*,*) 'recomp_orb_param, New year =', Year
57
58found_year = .false.
59if (Year < 0.) then
60    do ilask = last_ilask,2,-1
61        xa = yearlask(ilask)
62        xb = yearlask(ilask - 1)
63        if (xa <= Year .and. Year < xb) then
64            ! Obliquity
65            if (var_obl) then
66                ya = obllask(ilask)
67                yb = obllask(ilask - 1)
68                obliquit = (Year - xa)*(yb - ya)/(xb - xa) + ya
69            endif
70
71            ! Eccentricity
72            if (var_ecc) then
73                ya = ecclask(ilask)
74                yb = ecclask(ilask - 1)
75                e_elips = (Year - xa)*(yb - ya)/(xb - xa) + ya
76            endif
77
78            ! Lsp
79            if (var_lsp) then
80                ya = lsplask(ilask)
81                yb = lsplask(ilask - 1)
82                if (abs(yb - ya) > 300.) then ! If modulo is "crossed" through the interval
83                    if (ya < yb) then ! Lsp should be decreasing
84                        ya = ya + 360.
85                    else ! Lsp should be increasing
86                        yb = yb + 360.
87                    endif
88                endif
89                Lsp = modulo((Year - xa)*(yb - ya)/(xb - xa) + ya,360.)
90            endif
91            found_year = .true.
92            exit ! The loop is left as soon as the right interval is found
93        endif
94    enddo
95else if (Year >= 0 .and. Year < 100.) then ! For present orbital characteristics
96    if (var_obl) obliquit = 25.19
97    if (var_ecc) e_elips = 0.0934
98    if (var_lsp) Lsp = 251.
99    found_year = .true.
100endif
101
102if (.not. found_year) error stop 'The new year could not be found in the file "obl_ecc_lsp.asc".'
103
104write(*,*) 'recomp_orb_param, New obl. =', obliquit
105write(*,*) 'recomp_orb_param, New ecc. =', e_elips
106write(*,*) 'recomp_orb_param, New Lsp  =', Lsp
107
108halfaxe = 227.94
109Lsp = Lsp*pi/180.
110periheli = halfaxe*(1 - e_elips)
111aphelie =  halfaxe*(1 + e_elips)
112unitastr = 149.597927
113p_elips = 0.5*(periheli + aphelie)*(1. - e_elips*e_elips)/unitastr
114
115call call_dayperi(Lsp,e_elips,peri_day,year_day)
116
117END SUBROUTINE recomp_orb_param
118
119!********************************************************************************
120
121END MODULE recomp_orb_param_mod
122
Note: See TracBrowser for help on using the repository browser.