source: trunk/LMDZ.COMMON/libf/evolution/orbit_param_criterion_mod.F90 @ 3985

Last change on this file since 3985 was 3985, checked in by jbclement, 6 days ago

PEM:
Addition of a module "phys_constants" to read and store physical parameter of the planet properly, i.e. without going through the module "comcstfi_h" and/or "comconst_mod".
JBC

File size: 8.7 KB
Line 
1MODULE orbit_param_criterion_mod
2
3!=======================================================================
4!
5! Purpose: Compute the maximum number of iteration for PEM based on the
6! stopping criterion given by the orbital parameters
7!
8! Author: RV, JBC
9!=======================================================================
10
11implicit none
12
13!=======================================================================
14contains
15!=======================================================================
16
17SUBROUTINE orbit_param_criterion(i_myear,n_myear_leg)
18
19#ifdef CPP_IOIPSL
20    use IOIPSL,          only: getin
21#else
22    ! if not using IOIPSL, we still need to use (a local version of) getin
23    use ioipsl_getincom, only: getin
24#endif
25use planete_h,      only: e_elips, obliquit, lsperi
26use phys_constants, only: pi
27use time_evol_mod,  only: year_bp_ini, var_obl, var_ecc, var_lsp, convert_years
28use lask_param_mod, only: yearlask, obllask, ecclask, lsplask, ini_lask_param_mod, last_ilask
29
30implicit none
31
32!--------------------------------------------------------
33! Input Variables
34!--------------------------------------------------------
35real, intent(in) :: i_myear ! Martian year of the simulation
36
37!--------------------------------------------------------
38! Output Variables
39!--------------------------------------------------------
40real, intent(out) :: n_myear_leg ! Maximum number of iteration of the PEM before orb changes too much
41
42!--------------------------------------------------------
43! Local variables
44!--------------------------------------------------------
45real                            :: Year                                           ! Year of the simulation
46real                            :: Lsp                                            ! Ls perihelion
47real                            :: max_change_obl, max_change_ecc, max_change_lsp ! Maximum admissible change
48real                            :: max_obl, max_ecc, max_lsp                      ! Maximum value of orbit param given the admissible change
49real                            :: min_obl, min_ecc, min_lsp                      ! Minimum value of orbit param given the admissible change
50real                            :: max_obl_iter, max_ecc_iter, max_lsp_iter       ! Maximum year iteration before reaching an inadmissible value of orbit param
51integer                         :: ilask                                          ! Loop variable
52real                            :: xa, xb, ya, yb                                 ! Variables for interpolation
53logical                         :: found_obl, found_ecc, found_lsp                ! Flag variables for orbital parameters
54real                            :: lsp_corr                                       ! Lsp corrected if the "modulo is crossed"
55real                            :: delta                                          ! Intermediate variable
56real, dimension(:), allocatable :: lsplask_unwrap                                 ! Unwrapped sequence of Lsp from Laskar's file
57
58! **********************************************************************
59! 0. Initializations
60! **********************************************************************
61Year = year_bp_ini + i_myear ! We compute the current year
62Lsp = lsperi*180./pi         ! We convert in degree
63
64call ini_lask_param_mod() ! Allocation of variables
65
66write(*,*) 'orbit_param_criterion, Current year =', Year
67write(*,*) 'orbit_param_criterion, Current obl. =', obliquit
68write(*,*) 'orbit_param_criterion, Current ecc. =', e_elips
69write(*,*) 'orbit_param_criterion, Current Lsp  =', Lsp
70
71! We read the file
72open(73,file = 'obl_ecc_lsp.asc',status = 'old',action = 'read')
73last_ilask = 0
74do ilask = 1,size(yearlask,1)
75    read(73,*) yearlask(ilask), obllask(ilask), ecclask(ilask), lsplask(ilask)
76    yearlask(ilask) = yearlask(ilask)*1000./convert_years ! Conversion from Laskar's kilo Earth years to PEM Martian years
77    if (yearlask(ilask) > Year) last_ilask = ilask + 1
78enddo
79close(73)
80if (last_ilask == 0 .or. last_ilask == size(yearlask,1) + 1) then
81    error stop 'The current year could not be found in the file "obl_ecc_lsp.asc".'
82else
83    write(*,*) 'The current year in the "obl_ecc_lsp.asc" file is at line:', last_ilask
84endif
85
86! Unwrap the Lsp changes in Laskar's file
87allocate(lsplask_unwrap(last_ilask))
88lsplask_unwrap(last_ilask) = lsplask(last_ilask)
89do ilask = last_ilask,2,-1
90    delta = lsplask(ilask - 1) - lsplask(ilask)
91    if (delta > 180.) then
92        lsp_corr = lsplask(ilask - 1) - 360.
93    else if (delta < -180.) then
94        lsp_corr = lsplask(ilask - 1) + 360.
95    else
96        lsp_corr = lsplask(ilask - 1)
97    endif
98    lsplask_unwrap(ilask - 1) = lsplask_unwrap(ilask) + lsp_corr - lsplask(ilask)
99enddo
100
101! Correct the current Lsp according to the unwrapping
102delta = Lsp - lsplask_unwrap(last_ilask)
103if (delta > 180.) then
104    Lsp = Lsp - 360.
105else if (delta < -180.) then
106    Lsp = Lsp + 360.
107endif
108
109! Constant max change case
110max_change_obl = 1.
111max_change_ecc = 5.e-3
112max_change_lsp = 20.
113
114call getin('max_change_obl',max_change_obl)
115max_obl = obliquit + max_change_obl
116min_obl = obliquit - max_change_obl
117write(*,*) 'Maximum obliquity accepted =', max_obl
118write(*,*) 'Minimum obliquity accepted =', min_obl
119
120call getin('max_change_ecc',max_change_ecc)
121max_ecc = min(e_elips + max_change_ecc,1. - 1.e-10) ! ecc < 1.
122min_ecc = max(e_elips - max_change_ecc,0.) ! ecc >= 0.
123write(*,*) 'Maximum eccentricity accepted =', max_ecc
124write(*,*) 'Minimum eccentricity accepted =', min_ecc
125
126call getin('max_change_lsp',max_change_lsp)
127max_lsp = Lsp + max_change_lsp
128min_lsp = Lsp - max_change_lsp
129write(*,*) 'Maximum Lsp accepted =', max_lsp
130write(*,*) 'Minimum Lsp accepted =', min_lsp
131! End Constant max change case
132
133! If we do not want some orb parameter to change, they should not be a stopping criterion,
134! So the number of iteration corresponding is set to maximum
135max_obl_iter = 1000000.
136max_ecc_iter = 1000000.
137max_lsp_iter = 1000000.
138
139! The maximum reachable year is found by interpolation according to the maximum admissible change of orbital parameters
140found_obl = .false.
141found_ecc = .false.
142found_lsp = .false.
143if (.not. var_obl) found_obl = .true.
144if (.not. var_ecc) found_ecc = .true.
145if (.not. var_lsp) found_lsp = .true.
146
147do ilask = last_ilask,2,-1
148    xa = yearlask(ilask)
149    xb = yearlask(ilask - 1)
150
151    ! Obliquity
152    if (var_obl .and. .not. found_obl) then
153        ya = obllask(ilask)
154        yb = obllask(ilask - 1)
155        if (yb < min_obl) then ! The minimum accepted is overtaken
156            max_obl_iter = (min_obl - ya)*(xb - xa)/(yb - ya) + xa - Year
157            found_obl = .true.
158        else if (max_obl < yb) then ! The maximum accepted is overtaken
159            max_obl_iter = (max_obl - ya)*(xb - xa)/(yb - ya) + xa - Year
160            found_obl = .true.
161        endif
162    endif
163
164    ! Eccentricity
165    if (var_ecc .and. .not. found_ecc) then
166        ya = ecclask(ilask)
167        yb = ecclask(ilask - 1)
168        if (yb < min_ecc) then ! The minimum accepted is overtaken
169            max_ecc_iter = (min_ecc - ya)*(xb - xa)/(yb - ya) + xa - Year
170            found_ecc = .true.
171        else if (max_ecc < yb) then ! The maximum accepted is overtaken
172            max_ecc_iter = (max_ecc - ya)*(xb - xa)/(yb - ya) + xa - Year
173            found_ecc = .true.
174        endif
175    endif
176
177    ! Lsp
178    if (var_lsp .and. .not. found_lsp) then
179        ya = lsplask_unwrap(ilask)
180        yb = lsplask_unwrap(ilask - 1)
181        if (yb < min_lsp) then ! The minimum accepted is overtaken
182            max_lsp_iter = (min_lsp - ya)*(xb - xa)/(yb - ya) + xa - Year
183            found_lsp = .true.
184        else if (max_lsp < yb) then ! The maximum accepted is overtaken
185            max_lsp_iter = (max_lsp - ya)*(xb - xa)/(yb - ya) + xa - Year
186            found_lsp = .true.
187        endif
188    endif
189
190    if (found_obl .and. found_ecc .and. found_lsp) exit ! The loop is left as soon as everything is found
191enddo
192
193deallocate(lsplask_unwrap)
194
195if (.not. found_obl) write(*,*) 'The maximum reachable year for obl. could not be found in the file "obl_ecc_lsp.asc".'
196if (.not. found_ecc) write(*,*) 'The maximum reachable year for ecc. could not be found in the file "obl_ecc_lsp.asc".'
197if (.not. found_lsp) write(*,*) 'The maximum reachable year for Lsp could not be found in the file "obl_ecc_lsp.asc".'
198
199write(*,*) 'Max. number of iterations for the obl. parameter =', max_obl_iter
200write(*,*) 'Max. number of iterations for the ecc. parameter =', max_ecc_iter
201write(*,*) 'Max. number of iterations for the Lsp parameter  =', max_lsp_iter
202
203n_myear_leg = min(max_obl_iter,max_ecc_iter,max_lsp_iter)
204if (n_myear_leg < 1.) n_myear_leg = 1. ! n_myear_leg should be at least equal to 1
205write(*,*) 'So the max. number of iterations for the orbital criteria =', n_myear_leg
206
207END SUBROUTINE orbit_param_criterion
208
209!***********************************************************************
210
211END MODULE orbit_param_criterion_mod
212
Note: See TracBrowser for help on using the repository browser.