EFTCAMB  Reference documentation for version 3.0
04p5_CPL_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 cpl_parametrization_1d
40 
41  ! ---------------------------------------------------------------------------------------------
43  type, extends ( parametrized_function_1d ) :: cpl_parametrization_1d
44 
45  real(dl) :: w0
46  real(dl) :: wa
47 
48  contains
49 
50  ! utility functions:
51  procedure :: set_param_number => cplparametrized1dsetparamnumber
52  procedure :: init_parameters => cplparametrized1dinitparams
53  procedure :: parameter_value => cplparametrized1dparametervalues
54  procedure :: feedback => cplparametrized1dfeedback
55 
56  ! evaluation procedures:
57  procedure :: value => cplparametrized1dvalue
58  procedure :: first_derivative => cplparametrized1dfirstderivative
59  procedure :: second_derivative => cplparametrized1dsecondderivative
60  procedure :: third_derivative => cplparametrized1dthirdderivative
61  procedure :: integral => cplparametrized1dintegral
62 
63  end type cpl_parametrization_1d
64 
65 contains
66 
67  ! ---------------------------------------------------------------------------------------------
68  ! Implementation of the CPL function.
69  ! ---------------------------------------------------------------------------------------------
70 
71  ! ---------------------------------------------------------------------------------------------
73  subroutine cplparametrized1dsetparamnumber( self )
74 
75  implicit none
76 
77  class(cpl_parametrization_1d) :: self
78 
79  ! initialize the number of parameters:
80  self%parameter_number = 2
81 
82  end subroutine cplparametrized1dsetparamnumber
83 
84  ! ---------------------------------------------------------------------------------------------
86  subroutine cplparametrized1dinitparams( self, array )
87 
88  implicit none
89 
90  class(cpl_parametrization_1d) :: self
91  real(dl), dimension(self%parameter_number), intent(in) :: array
92 
93  self%w0 = array(1)
94  self%wa = array(2)
95 
96  end subroutine cplparametrized1dinitparams
97 
98  ! ---------------------------------------------------------------------------------------------
100  subroutine cplparametrized1dparametervalues( self, i, value )
101 
102  implicit none
103 
104  class(cpl_parametrization_1d) :: self
105  integer , intent(in) :: i
106  real(dl) , intent(out) :: value
107 
108  select case (i)
109  case(1)
110  value = self%w0
111  case(2)
112  value = self%wa
113  case default
114  write(*,*) 'Illegal index for parameter_names.'
115  write(*,*) 'Maximum value is:', self%parameter_number
116  call mpistop('EFTCAMB error')
117  end select
118 
119  end subroutine cplparametrized1dparametervalues
120 
121  ! ---------------------------------------------------------------------------------------------
123  subroutine cplparametrized1dfeedback( self, print_params )
124 
125  implicit none
126 
127  class(cpl_parametrization_1d) :: self
128  logical, optional :: print_params
130 
131  integer :: i
132  real(dl) :: param_value
133  character(len=EFT_names_max_length) :: param_name
134  logical :: print_params_temp
135 
136  if ( present(print_params) ) then
137  print_params_temp = print_params
138  else
139  print_params_temp = .true.
140  end if
141 
142  write(*,*) 'CPL parametrization: ', self%name
143  if ( print_params_temp ) then
144  do i=1, self%parameter_number
145  call self%parameter_names( i, param_name )
146  call self%parameter_value( i, param_value )
147  write(*,'(a23,a,F12.6)') param_name, '=', param_value
148  end do
149  end if
150 
151  end subroutine cplparametrized1dfeedback
152 
153  ! ---------------------------------------------------------------------------------------------
155  function cplparametrized1dvalue( self, x, eft_cache )
156 
157  implicit none
158 
159  class(cpl_parametrization_1d) :: self
160  real(dl), intent(in) :: x
161  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
162  real(dl) :: cplparametrized1dvalue
163 
164  cplparametrized1dvalue = self%w0 +(1._dl - x)*self%wa
165  end function cplparametrized1dvalue
166 
167  ! ---------------------------------------------------------------------------------------------
169  function cplparametrized1dfirstderivative( self, x, eft_cache )
170 
171  implicit none
172 
173  class(cpl_parametrization_1d) :: self
174  real(dl), intent(in) :: x
175  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
176  real(dl) :: cplparametrized1dfirstderivative
177 
178  cplparametrized1dfirstderivative = -self%wa
179 
180  end function cplparametrized1dfirstderivative
181 
182  ! ---------------------------------------------------------------------------------------------
184  function cplparametrized1dsecondderivative( self, x, eft_cache )
185 
186  implicit none
187 
188  class(cpl_parametrization_1d) :: self
189  real(dl), intent(in) :: x
190  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
191  real(dl) :: cplparametrized1dsecondderivative
192 
193  cplparametrized1dsecondderivative = 0._dl
194 
195  end function cplparametrized1dsecondderivative
196 
197  ! ---------------------------------------------------------------------------------------------
199  function cplparametrized1dthirdderivative( self, x, eft_cache )
200 
201  implicit none
202 
203  class(cpl_parametrization_1d) :: self
204  real(dl), intent(in) :: x
205  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
206  real(dl) :: cplparametrized1dthirdderivative
207 
208  cplparametrized1dthirdderivative = 0._dl
209 
210  end function cplparametrized1dthirdderivative
211 
212  ! ---------------------------------------------------------------------------------------------
214  function cplparametrized1dintegral( self, x, eft_cache )
215 
216  implicit none
217 
218  class(cpl_parametrization_1d) :: self
219  real(dl), intent(in) :: x
220  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
221  real(dl) :: cplparametrized1dintegral
222 
223  cplparametrized1dintegral = x**(2._dl -3._dl*(1._dl +self%w0 +self%wa))*exp(3._dl*(x-1._dl)*self%wa)
224 
225  end function cplparametrized1dintegral
226 
227  ! ---------------------------------------------------------------------------------------------
228 
230 
231 !----------------------------------------------------------------------------------------
This module contains the definition of the EFTCAMB caches. These are used to store parameters that ca...
This module contains the definition of the CPL parametrization, inheriting from parametrized_function...
This module contains the definitions of all the EFTCAMB compile time flags.
Definition: 01_EFT_def.f90:25
This module contains the abstract class for generic parametrizations for 1D functions that are used b...