EFTCAMB  Reference documentation for version 3.0
04p6_JBP_parametrizations_1D.f90
Go to the documentation of this file.
1 !----------------------------------------------------------------------------------------
2 !
3 ! This file is part of EFTCAMB.
4 !
5 ! Copyright (C) 2013-2016 by the EFTCAMB authors
6 !
7 ! The EFTCAMB code is free software;
8 ! You can use it, redistribute it, and/or modify it under the terms
9 ! of the GNU General Public License as published by the Free Software Foundation;
10 ! either version 3 of the License, or (at your option) any later version.
11 ! The full text of the license can be found in the file eftcamb/LICENSE at
12 ! the top level of the EFTCAMB distribution.
13 !
14 !----------------------------------------------------------------------------------------
15 
19 
20 
21 !----------------------------------------------------------------------------------------
24 
26 
28 
29  use precision
30  use amlutils
31  use eft_def
32  use eftcamb_cache
34 
35  implicit none
36 
37  private
38 
39  public jbp_parametrization_1d
40 
41  ! ---------------------------------------------------------------------------------------------
43  type, extends ( parametrized_function_1d ) :: jbp_parametrization_1d
44 
45  real(dl) :: w0
46  real(dl) :: wa
47  real(dl) :: wn
48 
49  contains
50 
51  ! utility functions:
52  procedure :: set_param_number => jbpparametrized1dsetparamnumber
53  procedure :: init_parameters => jbpparametrized1dinitparams
54  procedure :: parameter_value => jbpparametrized1dparametervalues
55  procedure :: feedback => jbpparametrized1dfeedback
56 
57  ! evaluation procedures:
58  procedure :: value => jbpparametrized1dvalue
59  procedure :: first_derivative => jbpparametrized1dfirstderivative
60  procedure :: second_derivative => jbpparametrized1dsecondderivative
61  procedure :: third_derivative => jbpparametrized1dthirdderivative
62  procedure :: integral => jbpparametrized1dintegral
63 
64  end type jbp_parametrization_1d
65 
66 contains
67 
68  ! ---------------------------------------------------------------------------------------------
69  ! Implementation of the JBP function.
70  ! ---------------------------------------------------------------------------------------------
71 
72  ! ---------------------------------------------------------------------------------------------
74  subroutine jbpparametrized1dsetparamnumber( self )
75 
76  implicit none
77 
78  class(jbp_parametrization_1d) :: self
79 
80  ! initialize the number of parameters:
81  self%parameter_number = 3
82 
83  end subroutine jbpparametrized1dsetparamnumber
84 
85  ! ---------------------------------------------------------------------------------------------
87  subroutine jbpparametrized1dinitparams( self, array )
88 
89  implicit none
90 
91  class(jbp_parametrization_1d) :: self
92  real(dl), dimension(self%parameter_number), intent(in) :: array
93 
94  self%w0 = array(1)
95  self%wa = array(2)
96  self%wn = array(3)
97 
98  end subroutine jbpparametrized1dinitparams
99 
100  ! ---------------------------------------------------------------------------------------------
102  subroutine jbpparametrized1dparametervalues( self, i, value )
103 
104  implicit none
105 
106  class(jbp_parametrization_1d) :: self
107  integer , intent(in) :: i
108  real(dl) , intent(out) :: value
109 
110  select case (i)
111  case(1)
112  value = self%w0
113  case(2)
114  value = self%wa
115  case(3)
116  value = self%wn
117  case default
118  write(*,*) 'Illegal index for parameter_names.'
119  write(*,*) 'Maximum value is:', self%parameter_number
120  call mpistop('EFTCAMB error')
121  end select
122 
123  end subroutine jbpparametrized1dparametervalues
124 
125  ! ---------------------------------------------------------------------------------------------
127  subroutine jbpparametrized1dfeedback( self, print_params )
128 
129  implicit none
130 
131  class(jbp_parametrization_1d) :: self
132  logical, optional :: print_params
134 
135  integer :: i
136  real(dl) :: param_value
137  character(len=EFT_names_max_length) :: param_name
138  logical :: print_params_temp
139 
140  if ( present(print_params) ) then
141  print_params_temp = print_params
142  else
143  print_params_temp = .true.
144  end if
145 
146  write(*,*) 'Generalized JBP parametrization: ', self%name
147  if ( print_params_temp ) then
148  do i=1, self%parameter_number
149  call self%parameter_names( i, param_name )
150  call self%parameter_value( i, param_value )
151  write(*,'(a23,a,F12.6)') param_name, '=', param_value
152  end do
153  end if
154 
155  end subroutine jbpparametrized1dfeedback
156 
157  ! ---------------------------------------------------------------------------------------------
159  function jbpparametrized1dvalue( self, x, eft_cache )
160 
161  implicit none
162 
163  class(jbp_parametrization_1d) :: self
164  real(dl), intent(in) :: x
165  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
166  real(dl) :: jbpparametrized1dvalue
167 
168  jbpparametrized1dvalue = self%w0 +(1._dl - x)*self%wa*x**(self%wn -1._dl)
169  end function jbpparametrized1dvalue
170 
171  ! ---------------------------------------------------------------------------------------------
173  function jbpparametrized1dfirstderivative( self, x, eft_cache )
174 
175  implicit none
176 
177  class(jbp_parametrization_1d) :: self
178  real(dl), intent(in) :: x
179  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
180  real(dl) :: jbpparametrized1dfirstderivative
181 
182  jbpparametrized1dfirstderivative = x**(-2.0_dl +self%wn)*(-1._dl +self%wn -x*self%wn)*self%wa
183 
184  end function jbpparametrized1dfirstderivative
185 
186  ! ---------------------------------------------------------------------------------------------
188  function jbpparametrized1dsecondderivative( self, x, eft_cache )
189 
190  implicit none
191 
192  class(jbp_parametrization_1d) :: self
193  real(dl), intent(in) :: x
194  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
195  real(dl) :: jbpparametrized1dsecondderivative
196 
197  jbpparametrized1dsecondderivative = -x**(-3._dl +self%wn)*(-1.0_dl +self%wn)*(2._dl +self%wn*(-1._dl +x))*self%wa
198 
199  end function jbpparametrized1dsecondderivative
200 
201  ! ---------------------------------------------------------------------------------------------
203  function jbpparametrized1dthirdderivative( self, x, eft_cache )
204 
205  implicit none
206 
207  class(jbp_parametrization_1d) :: self
208  real(dl), intent(in) :: x
209  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
210  real(dl) :: jbpparametrized1dthirdderivative
211 
212  jbpparametrized1dthirdderivative = -x**(-4._dl +self%wn)*(-2.0_dl +self%wn)*(-1._dl +self%wn)*(3._dl +self%wn*(-1._dl +x))*self%wa
213 
214  end function jbpparametrized1dthirdderivative
215 
216  ! ---------------------------------------------------------------------------------------------
218  function jbpparametrized1dintegral( self, x, eft_cache )
219 
220  implicit none
221 
222  class(jbp_parametrization_1d) :: self
223  real(dl), intent(in) :: x
224  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
225  real(dl) :: jbpparametrized1dintegral
226 
227  jbpparametrized1dintegral = x**(-1._dl -3._dl*self%w0)*exp(3._dl*(x +x**self%wn*(x*(self%wn -1._dl) -self%wn))*self%wa/(x*self%wn*(self%wn -1._dl)))
228 
229  end function jbpparametrized1dintegral
230 
231  ! ---------------------------------------------------------------------------------------------
232 
234 
235 !----------------------------------------------------------------------------------------
This module contains the definition of the EFTCAMB caches. These are used to store parameters that ca...
This module contains the definitions of all the EFTCAMB compile time flags.
Definition: 01_EFT_def.f90:25
This module contains the definition of the generalized Jassal-Bagla-Padmanabhan (JBP) parametrization...
This module contains the abstract class for generic parametrizations for 1D functions that are used b...