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

Last change on this file since 3022 was 3022, checked in by jbclement, 16 months ago

Mars PEM:
Rework and correction of computation of the maximum number of iterations for PEM according to orbital parameters.
JBC

File size: 8.6 KB
Line 
1      MODULE 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
11      IMPLICIT NONE
12
13      CONTAINS
14
15      SUBROUTINE orbit_param_criterion(year_iter_max)
16#ifdef CPP_IOIPSL
17  use IOIPSL, only: getin
18#else
19  ! if not using IOIPSL, we still need to use (a local version of) getin
20  use ioipsl_getincom, only: getin
21#endif
22
23      USE temps_mod_evol, ONLY: year_bp_ini, year_PEM, var_obl, var_ex, var_lsp
24#ifndef CPP_STD
25      USE planete_h, ONLY: e_elips, obliquit, timeperi
26#else
27      use planete_mod, only: e_elips, obliquit, timeperi
28#endif
29      USE comconst_mod, ONLY: pi
30      USE lask_param_mod, only: yearlask,oblask,exlask,lsplask, &
31                                ini_lask_param_mod,last_ilask
32
33      IMPLICIT NONE
34
35!--------------------------------------------------------
36! Input Variables
37!--------------------------------------------------------
38
39!--------------------------------------------------------
40! Output Variables
41!--------------------------------------------------------
42
43      integer,intent(out) :: year_iter_max      ! Maximum number of iteration of the PEM before orb changes too much
44
45!--------------------------------------------------------
46! Local variables
47!--------------------------------------------------------
48
49      real :: Year                      ! Year of the simulation
50      real :: Lsp                       ! Year of the simulation
51      integer nlask, ilask, iylask      ! Loop variables
52      parameter (nlask = 20001)         ! Number of line in Laskar file
53
54      real max_change_obl,max_change_ex,max_change_lsp ! Percentage of change that is considered to be acceptible
55
56      real max_obl,max_ex,max_lsp       ! Maximum value of orbit param given the acceptable percentage
57      real min_obl,min_ex,min_lsp       ! Maximum value of orbit param given the acceptable percentage
58      real max_obl_iter,max_ex_iter,max_lsp_iter ! Maximum year iteration before reaching an unacceptable value
59      real xa,xb,ya,yb,yc
60
61      ! **********************************************************************
62      ! 0. Initializations
63      ! **********************************************************************
64
65          Year = year_bp_ini + year_PEM      ! We compute the current year
66          Lsp = 360. - timeperi*360./(2.*pi) ! We convert in degree
67
68          call ini_lask_param_mod(nlask) ! Allocation of variables
69
70          print*, "orbit_param_criterion, Year in pem.def=", year_bp_ini
71          print*, "orbit_param_criterion, Year in the startpem.nc =", year_PEM
72          print*, "orbit_param_criterion, Current year=", Year
73          print*, "orbit_param_criterion, Current obl=", obliquit
74          print*, "orbit_param_criterion, Current ex=", e_elips
75          print*, "orbit_param_criterion, Current lsp=", Lsp
76
77! We read the file
78
79          open(73,file='ob_ex_lsp.asc')
80          do ilask=1,nlask
81            read(73,*) yearlask(ilask),oblask(ilask),      &
82             exlask(ilask),lsplask(ilask)
83            yearlask(ilask)=yearlask(ilask)*1000
84
85            if(yearlask(ilask).GT.Year) then
86                last_ilask=ilask+1
87            endif
88          end do
89          close(73)
90
91       print*, "Coresponding line in the ob_ex_lsp.asc file=", last_ilask
92
93!Constant max change case
94
95        max_change_obl = 0.5
96        max_change_ex = 0.1
97        max_change_lsp = 40.
98
99        CALL getin('max_change_obl', max_change_obl)
100        max_obl = obliquit + max_change_obl
101        min_obl = obliquit - max_change_obl
102        print*, "Maximum obliquity accepted=", max_obl
103        print*, "Minimum obliquity accepted=", min_obl
104
105        CALL getin('max_change_ex', max_change_ex)
106        max_ex = e_elips + max_change_ex
107        min_ex = e_elips - max_change_ex
108        print*, "Maximum excentricity accepted=", max_ex
109        print*, "Minimum excentricity accepted=", min_ex
110
111        CALL getin('max_change_lsp', max_change_lsp)
112        max_lsp = Lsp + max_change_lsp
113        min_lsp = Lsp - max_change_lsp
114        print*, "Maximum lsp accepted=", max_lsp
115        print*, "Minimum lsp accepted=", min_lsp
116
117!End Constant max change case
118
119! If we do not want some orb parameter to change, they should not be a stopping criterion,
120! So the number of iteration corresponding is set to maximum
121        max_obl_iter = 999999
122        max_ex_iter = 999999
123        max_lsp_iter = 999999
124
125        ! Tendency of the orbital parameter for the considered year gives the limitation between min and max
126        do ilask = last_ilask,2,-1
127          xa = yearlask(ilask)
128          xb = yearlask(ilask - 1)
129          if (xa <= Year .and. Year < xb) then
130            ! Obliquity
131            if (var_obl) then
132              ya = oblask(ilask)
133              yb = oblask(ilask - 1)
134              if (ya < yb) then ! Increasing -> max is the limitation
135                yc = max_obl
136              else ! Decreasing -> min is the limitation
137                yc = min_obl
138              endif
139            endif
140
141            ! Excentricity
142            if (var_ex) then
143              ya = exlask(ilask)
144              yb = exlask(ilask - 1)
145              if (ya < yb) then ! Increasing -> max is the limitation
146                yc = max_ex
147              else ! Decreasing -> min is the limitation
148                yc = min_ex
149              endif
150            endif
151
152            ! Lsp
153            if (var_lsp) then
154              ya = lsplask(ilask)
155              yb = lsplask(ilask - 1)
156              if (ya < yb) then ! Increasing -> max is the limitation
157                if (yb - ya > 300.) then ! If modulo is "crossed" then it is the other way around
158                  !yb = yb - 360.
159                  yc = min_lsp
160                else
161                  yc = max_lsp
162                endif
163              else ! Decreasing -> min is the limitation
164                if (ya - yb > 300.) then ! If modulo is "crossed" then it is the other way around
165                  !yb = yb + 360.
166                  yc = max_lsp
167                else
168                  yc = min_lsp
169                endif
170              endif
171            endif
172            iylask = ilask
173            exit ! The loop is left as soon as the right interval is found
174          endif
175        enddo
176        if (ilask == 1) then
177          write(*,*) 'The year does not match with Laskar data in the file ob_ex_lsp.asc.'
178          stop
179        endif
180
181        ! Linear interpolation gives the maximum reachable year according to the limitation
182        ! Obliquity
183        if (var_obl) then
184          do ilask = iylask,2,-1
185            ya = oblask(ilask)
186            yb = oblask(ilask - 1)
187            if (ya <= yc .and. yc < yb) then
188              xa = yearlask(ilask)
189              xb = yearlask(ilask - 1)
190              max_obl_iter = int((max_obl - ya)*(xb - xa)/(yb - ya) + xa) - Year
191              exit ! The loop is left as soon as the right interval is found
192            endif
193          enddo
194        endif
195        ! Excentricity
196        if (var_ex) then
197          do ilask = iylask,2,-1
198            ya = exlask(ilask)
199            yb = exlask(ilask - 1)
200            if (ya <= yc .and. yc < yb) then
201              xa = yearlask(ilask)
202              xb = yearlask(ilask - 1)
203              max_ex_iter = int((max_ex - ya)*(xb - xa)/(yb - ya) + xa) - Year
204              exit ! The loop is left as soon as the right interval is found
205            endif           
206          enddo
207        endif
208        ! Lsp
209        if (var_lsp) then
210          do ilask = iylask,2,-1
211            ya = lsplask(ilask)
212            yb = lsplask(ilask - 1)
213            if (ya <= yc .and. yc < yb) then
214              xa = yearlask(ilask)
215              xb = yearlask(ilask - 1)
216              max_lsp_iter = int((max_lsp - ya)*(xb - xa)/(yb - ya) + xa) - Year
217              exit ! The loop is left as soon as the right interval is found
218            endif
219          enddo
220        endif
221
222      print*, "Maximum number of iteration for the obl. parameter=", max_obl_iter
223      print*, "Maximum number of iteration for the ex. parameter=", max_ex_iter
224      print*, "Maximum number of iteration for the lsp. parameter=", max_lsp_iter
225
226      year_iter_max = min(max_obl_iter,max_ex_iter,max_lsp_iter)
227      if (year_iter_max > 0) then
228        print*, "So the max. number of iteration (year) for the orbital parameter=", year_iter_max
229      else
230        write(*,*) 'The max. number of iteration (year) is not compatible with Laskar data in the file ob_ex_lsp.asc.'
231        stop
232      endif
233
234        END SUBROUTINE orbit_param_criterion
235
236!********************************************************************************   
237     
238      END MODULE orbit_param_criterion_mod
Note: See TracBrowser for help on using the repository browser.