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

Last change on this file since 3860 was 3851, checked in by jbclement, 5 days ago

PEM:

  • Making the computation of CO2 mass balance more robust, especially regarding 'CO2cond_ps'.
  • Small correction about the dust tendency management for the layering algorithm.
  • Small improvement of the visualization in "visu_evol_layering.py".
  • File "log_launchPEM.txt" renamed into "launchPEM.log".

JBC

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