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

Last change on this file since 2927 was 2894, checked in by romain.vande, 2 years ago

Mars PEM:
New Boolean options for following orbital parameters of ob_ex_lsp.asc: var_obl, var_ex, var_lsp.
If using evol_orbit_pem=true, you can specify which parameter to follow.
True by default: Do you want to change the parameter XXX during the PEM run as prescribed in ob_ex_lsp.asc.
If false, it is set to constant (to the value of the tab_cntrl in the start)
RV

File size: 6.6 KB
Line 
1      MODULE orbit_param_criterion_mod
2
3      IMPLICIT NONE
4
5      CONTAINS
6
7      SUBROUTINE orbit_param_criterion(year_iter_max)
8
9      USE temps_mod_evol, ONLY: year_bp_ini, year_PEM, var_obl, var_ex, var_lsp
10#ifndef CPP_STD
11      USE planete_h, ONLY: e_elips, obliquit, timeperi
12#else
13      use planete_mod, only: e_elips, obliquit, timeperi
14#endif
15      USE comconst_mod, ONLY: pi
16      USE lask_param_mod, only: yearlask,oblask,exlask,lsplask, &
17                                ini_lask_param_mod,last_ilask
18
19      IMPLICIT NONE
20
21!--------------------------------------------------------
22! Input Variables
23!--------------------------------------------------------
24
25!--------------------------------------------------------
26! Output Variables
27!--------------------------------------------------------
28
29      integer,intent(out) :: year_iter_max      ! Maximum number of iteration of the PEM before orb changes too much
30
31!--------------------------------------------------------
32! Local variables
33!--------------------------------------------------------
34
35      real :: Year                      ! Year of the simulation
36      real :: timeperi_ls                       ! Year of the simulation
37      integer nlask,ilask!,last_ilask !Loop variable
38      parameter (nlask = 20001)
39
40      real max_change_obl,max_change_ex,max_change_lsp ! Percentage of change that is considered to be acceptible
41
42      real max_obl,max_ex,max_lsp !Maximum value of orbit param given the acceptable percentage
43      real min_obl,min_ex,min_lsp !Maximum value of orbit param given the acceptable percentage
44
45      real max_obl_iter,max_ex_iter,max_lsp_iter !Maximum year iteration before reaching an unacceptable value
46
47      logical obl_not_found, ex_not_found,lsp_not_found !Loop variable (first call)
48
49      ! **********************************************************************
50      ! 0. Initializations
51      ! **********************************************************************
52
53          Year=year_bp_ini+year_PEM
54          timeperi_ls=timeperi*360/2/pi
55
56          call ini_lask_param_mod(nlask)
57
58          print *, "orbit_param_criterion, Year in pem.def=", year_bp_ini
59          print *, "orbit_param_criterion, Year in the startpem.nc =", year_PEM
60          print *, "orbit_param_criterion, Current year=", Year
61          print *, "orbit_param_criterion, Current obl=", obliquit
62          print *, "orbit_param_criterion, Current ex=", e_elips
63          print *, "orbit_param_criterion, Current lsp=", timeperi_ls
64
65          open(73,file='ob_ex_lsp.asc')
66          do ilask=1,nlask
67            read(73,*) yearlask(ilask),oblask(ilask),      &
68             exlask(ilask),lsplask(ilask)
69            yearlask(ilask)=yearlask(ilask)*1000
70
71            if(yearlask(ilask).GT.Year) then
72                last_ilask=ilask+1
73            endif
74          end do
75          close(73)
76
77       print *, "Coresponding line in the ob_ex_lsp.asc file=", last_ilask
78
79! 5% max change case
80
81        max_change_obl=0.05
82        max_change_ex=0.05
83        max_change_lsp=0.05
84
85        max_obl=obliquit*(1+max_change_obl)
86        min_obl=obliquit*(1-max_change_obl)
87
88        max_ex=e_elips*(1+max_change_ex)
89        min_ex=e_elips*(1-max_change_ex)
90
91        max_lsp=timeperi_ls*(1+max_change_lsp)
92        min_lsp=timeperi_ls*(1-max_change_lsp)
93
94!End of 5% max change case
95
96!Constant max change case
97
98        max_change_obl=0.1
99        max_change_ex=0.1
100        max_change_lsp=40.
101
102        max_obl=obliquit+max_change_obl
103        min_obl=obliquit-max_change_obl
104
105        max_ex=e_elips+max_change_ex
106        min_ex=e_elips-max_change_ex
107
108        max_lsp=timeperi_ls+max_change_lsp
109        min_lsp=timeperi_ls-max_change_lsp
110
111!End Constant max change case
112
113! If we do not want some orb parameter to change, they should not be a stopping criterion,
114! So the number of iteration corresponding is set to maximum
115        if(.not.var_obl) then
116           obl_not_found=.FALSE.
117        else
118           obl_not_found=.TRUE.
119        endif
120        if(.not.var_ex) then
121           ex_not_found=.FALSE.
122        else
123           ex_not_found=.TRUE.
124        endif
125        if(.not.var_lsp) then
126           lsp_not_found=.FALSE.
127        else
128           lsp_not_found=.TRUE.
129        endif
130
131        max_obl_iter=999999999999
132        max_ex_iter =999999999999
133        max_lsp_iter=999999999999
134
135        do ilask=last_ilask+1,1,-1
136           if((oblask(ilask).GT.max_obl).and. obl_not_found ) then
137              max_obl_iter=(max_obl-oblask(ilask)) * (yearlask(ilask-1)-yearlask(ilask)) &
138                               / (oblask(ilask-1)-oblask(ilask))
139              obl_not_found=.FALSE.
140           elseif((oblask(ilask).LT.min_obl).and. obl_not_found ) then
141              max_obl_iter=(min_obl-oblask(ilask)) * (yearlask(ilask-1)-yearlask(ilask)) &
142                               / (oblask(ilask-1)-oblask(ilask))
143              obl_not_found=.FALSE.
144           endif
145           if((exlask(ilask).GT.max_ex).and. ex_not_found ) then
146              max_ex_iter=(max_ex-exlask(ilask)) * (yearlask(ilask-1)-yearlask(ilask)) &
147                               / (exlask(ilask-1)-exlask(ilask))
148              ex_not_found=.FALSE.
149           elseif((exlask(ilask).LT.min_ex ).and. ex_not_found ) then
150              max_ex_iter=(min_ex-exlask(ilask)) * (yearlask(ilask-1)-yearlask(ilask)) &
151                               / (exlask(ilask-1)-exlask(ilask))
152              ex_not_found=.FALSE.
153           endif
154           if((lsplask(ilask).GT.max_lsp).and. lsp_not_found ) then
155              max_lsp_iter=(max_lsp-lsplask(ilask)) * (yearlask(ilask-1)-yearlask(ilask)) &
156                               / (lsplask(ilask-1)-lsplask(ilask))
157              lsp_not_found=.FALSE.
158           elseif((lsplask(ilask).LT.min_lsp ).and. lsp_not_found ) then
159              max_lsp_iter=(min_lsp-lsplask(ilask)) * (yearlask(ilask-1)-yearlask(ilask)) &
160                               / (lsplask(ilask-1)-lsplask(ilask))
161              lsp_not_found=.FALSE.
162           endif
163        enddo
164
165      print *, "Maximum obliquity accepted=", max_obl
166      print *, "Minimum obliquity accepted=", min_obl
167      print *, "Maximum number of iteration for the obl. parameter=", max_obl_iter
168
169      print *, "Maximum excentricity accepted=", max_ex
170      print *, "Minimum excentricity accepted=", min_ex
171      print *, "Maximum number of iteration for the ex. parameter=", max_ex_iter
172
173      print *, "Maximum lsp accepted=", max_obl
174      print *, "Minimum lsp accepted=", min_obl
175      print *, "Maximum number of iteration for the lsp. parameter=", max_lsp_iter
176
177      year_iter_max=min(max_obl_iter,max_ex_iter,max_lsp_iter)
178
179      print *, "So the max. number of iteration (year) for the orbital parameter=", year_iter_max
180
181        END SUBROUTINE orbit_param_criterion
182
183!********************************************************************************   
184     
185      END MODULE orbit_param_criterion_mod
Note: See TracBrowser for help on using the repository browser.