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

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

Mars PCM/PEM 1D:
Small fixes to be able to run the Mars PCM 1D without "water" + Improvements/addition of scripts in deftank/pem to run the PEM 1D model according to Laskar orbital parameters.
JBC

File size: 8.5 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), exlask(ilask), lsplask(ilask)
82            yearlask(ilask) = yearlask(ilask)*1000.
83            if (yearlask(ilask) > Year) last_ilask = ilask + 1
84          enddo
85          close(73)
86
87       print*, "Coresponding line in the ob_ex_lsp.asc file=", last_ilask
88
89!Constant max change case
90
91        max_change_obl = 0.5
92        max_change_ex = 0.1
93        max_change_lsp = 40.
94
95        CALL getin('max_change_obl', max_change_obl)
96        max_obl = obliquit + max_change_obl
97        min_obl = obliquit - max_change_obl
98        print*, "Maximum obliquity accepted=", max_obl
99        print*, "Minimum obliquity accepted=", min_obl
100
101        CALL getin('max_change_ex', max_change_ex)
102        max_ex = e_elips + max_change_ex
103        min_ex = e_elips - max_change_ex
104        print*, "Maximum excentricity accepted=", max_ex
105        print*, "Minimum excentricity accepted=", min_ex
106
107        CALL getin('max_change_lsp', max_change_lsp)
108        max_lsp = Lsp + max_change_lsp
109        min_lsp = Lsp - max_change_lsp
110        print*, "Maximum lsp accepted=", max_lsp
111        print*, "Minimum lsp accepted=", min_lsp
112
113!End Constant max change case
114
115! If we do not want some orb parameter to change, they should not be a stopping criterion,
116! So the number of iteration corresponding is set to maximum
117        max_obl_iter = 999999
118        max_ex_iter = 999999
119        max_lsp_iter = 999999
120
121        ! Tendency of the orbital parameter for the considered year gives the limitation between min and max
122        do ilask = last_ilask,2,-1
123          xa = yearlask(ilask)
124          xb = yearlask(ilask - 1)
125          if (xa <= Year .and. Year < xb) then
126            ! Obliquity
127            if (var_obl) then
128              ya = oblask(ilask)
129              yb = oblask(ilask - 1)
130              if (ya < yb) then ! Increasing -> max is the limitation
131                yc = max_obl
132              else ! Decreasing -> min is the limitation
133                yc = min_obl
134              endif
135            endif
136
137            ! Excentricity
138            if (var_ex) then
139              ya = exlask(ilask)
140              yb = exlask(ilask - 1)
141              if (ya < yb) then ! Increasing -> max is the limitation
142                yc = max_ex
143              else ! Decreasing -> min is the limitation
144                yc = min_ex
145              endif
146            endif
147
148            ! Lsp
149            if (var_lsp) then
150              ya = lsplask(ilask)
151              yb = lsplask(ilask - 1)
152              if (ya < yb) then ! Increasing -> max is the limitation
153                if (yb - ya > 300.) then ! If modulo is "crossed" then it is the other way around
154                  !yb = yb - 360.
155                  yc = min_lsp
156                else
157                  yc = max_lsp
158                endif
159              else ! Decreasing -> min is the limitation
160                if (ya - yb > 300.) then ! If modulo is "crossed" then it is the other way around
161                  !yb = yb + 360.
162                  yc = max_lsp
163                else
164                  yc = min_lsp
165                endif
166              endif
167            endif
168            iylask = ilask
169            exit ! The loop is left as soon as the right interval is found
170          endif
171        enddo
172        if (ilask == 1) then
173          write(*,*) 'The year does not match with Laskar data in the file ob_ex_lsp.asc.'
174          stop
175        endif
176
177        ! Linear interpolation gives the maximum reachable year according to the limitation
178        ! Obliquity
179        if (var_obl) then
180          do ilask = iylask,2,-1
181            ya = oblask(ilask)
182            yb = oblask(ilask - 1)
183            if (ya <= yc .and. yc < yb) then
184              xa = yearlask(ilask)
185              xb = yearlask(ilask - 1)
186              max_obl_iter = int((max_obl - ya)*(xb - xa)/(yb - ya) + xa) - Year
187              exit ! The loop is left as soon as the right interval is found
188            endif
189          enddo
190        endif
191        ! Excentricity
192        if (var_ex) then
193          do ilask = iylask,2,-1
194            ya = exlask(ilask)
195            yb = exlask(ilask - 1)
196            if (ya <= yc .and. yc < yb) then
197              xa = yearlask(ilask)
198              xb = yearlask(ilask - 1)
199              max_ex_iter = int((max_ex - ya)*(xb - xa)/(yb - ya) + xa) - Year
200              exit ! The loop is left as soon as the right interval is found
201            endif           
202          enddo
203        endif
204        ! Lsp
205        if (var_lsp) then
206          do ilask = iylask,2,-1
207            ya = lsplask(ilask)
208            yb = lsplask(ilask - 1)
209            if (ya <= yc .and. yc < yb) then
210              xa = yearlask(ilask)
211              xb = yearlask(ilask - 1)
212              max_lsp_iter = int((max_lsp - ya)*(xb - xa)/(yb - ya) + xa) - Year
213              exit ! The loop is left as soon as the right interval is found
214            endif
215          enddo
216        endif
217
218      print*, "Maximum number of iteration for the obl. parameter=", max_obl_iter
219      print*, "Maximum number of iteration for the ex. parameter=", max_ex_iter
220      print*, "Maximum number of iteration for the lsp. parameter=", max_lsp_iter
221
222      year_iter_max = min(max_obl_iter,max_ex_iter,max_lsp_iter)
223      if (year_iter_max > 0) then
224        print*, "So the max. number of iteration (year) for the orbital parameter=", year_iter_max
225      else
226        write(*,*) 'The max. number of iteration (year) is not compatible with Laskar data in the file ob_ex_lsp.asc.'
227        stop
228      endif
229
230        END SUBROUTINE orbit_param_criterion
231
232!********************************************************************************   
233     
234      END MODULE orbit_param_criterion_mod
Note: See TracBrowser for help on using the repository browser.