EFTCAMB  Reference documentation for version 3.0
04_abstract_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 
21 
22 
23 !----------------------------------------------------------------------------------------
27 
29 
31 
32  use precision
33  use amlutils
34  use inifile
35  use eft_def
37  use eftcamb_cache
38 
39  implicit none
40 
41  private
42 
43  public parametrized_function_1d
44 
45  !----------------------------------------------------------------------------------------
49  type, abstract :: parametrized_function_1d
50 
51  integer :: parameter_number
52  character(len=:), allocatable :: name
53  character(len=:), allocatable :: name_latex
54  type(string) , allocatable, dimension(:) :: param_names
55  type(string) , allocatable, dimension(:) :: param_names_latex
56 
57  contains
58 
59  ! initialization procedures:
60  procedure( parametrizedfunction1dsetparamnumber ), deferred :: set_param_number
61  procedure :: param_number => parametrizedfunction1dparamnumber
62  procedure :: set_name => parametrizedfunction1dsetname
63  procedure :: set_param_names => parametrizedfunction1dsetparamnames
64  procedure :: init_from_file => parametrizedfunction1dinitfromfile
65  procedure( parametrizedfunction1dinitparams ), deferred :: init_parameters
66  ! utility functions:
67  procedure :: feedback => parametrizedfunction1dfeedback
68  procedure :: parameter_names => parametrizedfunction1dparameternames
69  procedure :: parameter_names_latex => parametrizedfunction1dparameternameslatex
70  procedure( parametrizedfunction1dparametervalues ), deferred :: parameter_value
71  ! evaluation procedures:
72  procedure( parametrizedfunction1dvalue ), deferred :: value
73  procedure( parametrizedfunction1dfirstderivative ), deferred :: first_derivative
74  procedure( parametrizedfunction1dsecondderivative ), deferred :: second_derivative
75  procedure( parametrizedfunction1dthirdderivative ), deferred :: third_derivative
76  procedure( parametrizedfunction1dintegral ), deferred :: integral
77 
78  end type parametrized_function_1d
79 
80  ! ---------------------------------------------------------------------------------------------
81  ! parametrized_function_1D abstract interfaces: these are all the function procedures
82  ! that the user HAS to override when writing its own parametrized 1D function.
83  ! ---------------------------------------------------------------------------------------------
84 
85  abstract interface
86 
87  ! ---------------------------------------------------------------------------------------------
89  subroutine parametrizedfunction1dsetparamnumber( self )
90  use precision
91  import parametrized_function_1d
92  implicit none
93  class(parametrized_function_1d) :: self
94  end subroutine parametrizedfunction1dsetparamnumber
95 
96  ! ---------------------------------------------------------------------------------------------
98  subroutine parametrizedfunction1dinitparams( self, array )
99  use precision
100  import parametrized_function_1d
101  implicit none
102  class(parametrized_function_1d) :: self
103  real(dl), dimension(self%parameter_number), intent(in) :: array
104  end subroutine parametrizedfunction1dinitparams
105 
106  ! ---------------------------------------------------------------------------------------------
108  subroutine parametrizedfunction1dparametervalues( self, i, value )
109  use precision
110  import parametrized_function_1d
111  implicit none
112  class(parametrized_function_1d) :: self
113  integer , intent(in) :: i
114  real(dl), intent(out) :: value
115  end subroutine parametrizedfunction1dparametervalues
116 
117  ! ---------------------------------------------------------------------------------------------
120  function parametrizedfunction1dvalue( self, x, eft_cache )
121  use precision
122  use eftcamb_cache
123  import parametrized_function_1d
124  implicit none
125  class(parametrized_function_1d) :: self
126  real(dl), intent(in) :: x
127  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
128  real(dl) :: parametrizedfunction1dvalue
129  end function parametrizedfunction1dvalue
130 
131  ! ---------------------------------------------------------------------------------------------
135  function parametrizedfunction1dfirstderivative( self, x, eft_cache )
136  use precision
137  use eftcamb_cache
138  import parametrized_function_1d
139  implicit none
140  class(parametrized_function_1d) :: self
141  real(dl), intent(in) :: x
142  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
143  real(dl) :: parametrizedfunction1dfirstderivative
144  end function parametrizedfunction1dfirstderivative
145 
146  ! ---------------------------------------------------------------------------------------------
150  function parametrizedfunction1dsecondderivative( self, x, eft_cache )
151  use precision
152  use eftcamb_cache
153  import parametrized_function_1d
154  implicit none
155  class(parametrized_function_1d) :: self
156  real(dl), intent(in) :: x
157  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
158  real(dl) :: parametrizedfunction1dsecondderivative
159  end function parametrizedfunction1dsecondderivative
160 
161  ! ---------------------------------------------------------------------------------------------
165  function parametrizedfunction1dthirdderivative( self, x, eft_cache )
166  use precision
167  use eftcamb_cache
168  import parametrized_function_1d
169  implicit none
170  class(parametrized_function_1d) :: self
171  real(dl), intent(in) :: x
172  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
173  real(dl) :: parametrizedfunction1dthirdderivative
174  end function parametrizedfunction1dthirdderivative
175 
176  ! ---------------------------------------------------------------------------------------------
179  function parametrizedfunction1dintegral( self, x, eft_cache )
180  use precision
181  use eftcamb_cache
182  import parametrized_function_1d
183  implicit none
184  class(parametrized_function_1d) :: self
185  real(dl), intent(in) :: x
186  type(eftcamb_timestep_cache), intent(in), optional :: eft_cache
187  real(dl) :: parametrizedfunction1dintegral
188  end function parametrizedfunction1dintegral
189 
190  ! ---------------------------------------------------------------------------------------------
191 
192  end interface
193 
194  ! ---------------------------------------------------------------------------------------------
195 
196 contains
197 
198  ! ---------------------------------------------------------------------------------------------
200  function parametrizedfunction1dparamnumber( self )
202  implicit none
203 
204  class(parametrized_function_1d) :: self
205  integer :: ParametrizedFunction1DParamNumber
206 
207  parametrizedfunction1dparamnumber = self%parameter_number
208 
210 
211  ! ---------------------------------------------------------------------------------------------
213  subroutine parametrizedfunction1dsetname( self, name, latexname )
214 
215  implicit none
216 
217  class(parametrized_function_1d) :: self
218  character(*), intent(in) :: name
219  character(*), intent(in), optional :: latexname
220 
221  ! ensure that the number of parameters is properly associated:
222  call self%set_param_number()
223 
224  ! store the name of the function:
225  self%name = trim( name )
226  ! store the latex name of the function:
227  if ( present(latexname) ) then
228  self%name_latex = trim( latexname )
229  else
230  self%name_latex = trim( name )
231  end if
232 
233  end subroutine parametrizedfunction1dsetname
234 
235  ! ---------------------------------------------------------------------------------------------
238  subroutine parametrizedfunction1dsetparamnames( self, param_names, param_names_latex )
239 
240  implicit none
241 
242  class(parametrized_function_1d) :: self
243  character(*), intent(in), dimension(:) :: param_names
244  character(*), intent(in), dimension(:), optional :: param_names_latex
245 
246  character(len=:), allocatable :: string_array(:)
247 
248  integer :: num_params, ind
249 
250  ! ensure that the number of parameters is properly associated:
251  call self%set_param_number()
252 
253  ! check the number of parameters:
254  num_params = self%param_number()
255  if ( num_params /= size(param_names) ) then
256  write(*,*) 'In parametrized_function_1D:', self%name
257  write(*,*) 'Length of param_names and number of parameters do not coincide.'
258  write(*,*) 'Parameter number:', num_params
259  write(*,*) 'Size of the param_names array:', size(param_names)
260  call mpistop('EFTCAMB error')
261  end if
262  if ( present(param_names_latex) ) then
263  ! check length:
264  if ( num_params /= size(param_names_latex) ) then
265  write(*,*) 'In parametrized_function_1D:', self%name
266  write(*,*) 'Length of param_names_latex and number of parameters do not coincide.'
267  write(*,*) 'Parameter number:', self%parameter_number
268  write(*,*) 'Size of the param_names array:', size(param_names_latex)
269  call mpistop('EFTCAMB error')
270  end if
271  end if
272 
273  ! allocate self%param_names and self%param_names_latex:
274  if ( allocated(self%param_names) ) deallocate(self%param_names)
275  allocate( self%param_names(num_params) )
276  if ( allocated(self%param_names_latex) ) deallocate(self%param_names_latex)
277  allocate( self%param_names_latex(num_params) )
278 
279  ! store the parameter names and latex param names:
280  do ind=1, num_params
281  self%param_names(ind)%string = param_names(ind)
282  if ( present(param_names_latex) ) then
283  self%param_names_latex(ind)%string = param_names_latex(ind)
284  else
285  self%param_names_latex(ind)%string = param_names(ind)
286  end if
287  end do
288 
289  end subroutine parametrizedfunction1dsetparamnames
290 
291  ! ---------------------------------------------------------------------------------------------
293  subroutine parametrizedfunction1dinitfromfile( self, Ini )
294 
295  implicit none
296 
297  class(parametrized_function_1d) :: self
298  type(tinifile) :: Ini
299 
300  character(len=EFT_names_max_length) :: param_name
301  real(dl), dimension( self%parameter_number ) :: parameters
302 
303  integer :: i
304 
305  ! ensure that the number of parameters is properly associated:
306  call self%set_param_number()
307 
308  ! read the parameters and store them in a vector:
309  do i=1, self%parameter_number
310  call self%parameter_names( i, param_name )
311  parameters(i) = ini_read_double_file( ini, trim(param_name), 0._dl )
312  end do
313  ! initialize the function parameters from the vector:
314  call self%init_parameters( parameters )
315 
316  end subroutine parametrizedfunction1dinitfromfile
317 
318  ! ---------------------------------------------------------------------------------------------
320  subroutine parametrizedfunction1dfeedback( self, print_params )
321 
322  implicit none
323 
324  class(parametrized_function_1d) :: self
325  logical, optional :: print_params
327 
328  integer :: i
329  real(dl) :: param_value
330  character(len=EFT_names_max_length) :: param_name
331  logical :: print_params_temp
332 
333  if ( present(print_params) ) then
334  print_params_temp = print_params
335  else
336  print_params_temp = .true.
337  end if
338 
339  if ( self%parameter_number>0 ) then
340  write(*,*) 'Parametrized function 1D: ', self%name
341  if ( print_params_temp ) then
342  do i=1, self%parameter_number
343  call self%parameter_names( i, param_name )
344  call self%parameter_value( i, param_value )
345  write(*,'(a23,a,F12.6)') param_name, '=', param_value
346  end do
347  end if
348  end if
349 
350  end subroutine parametrizedfunction1dfeedback
351 
352  ! ---------------------------------------------------------------------------------------------
354  subroutine parametrizedfunction1dparameternames( self, i, name )
355 
356  implicit none
357 
358  class(parametrized_function_1d) :: self
359  integer , intent(in) :: i
360  character(*), intent(out) :: name
361 
362  ! check the input index:
363  if ( i>self%parameter_number ) then
364  write(*,*) 'In parametrized_function_1D:', self%name
365  write(*,*) 'Illegal index for parameter_names.'
366  write(*,*) 'Maximum value is:', self%parameter_number
367  call mpistop('EFTCAMB error')
368  end if
369  ! return the parameter name:
370  if ( allocated(self%param_names) ) then
371  name = self%param_names(i)%string
372  else
373  name = trim(self%name)//integer_to_string(i-1)
374  end if
375 
376  end subroutine parametrizedfunction1dparameternames
377 
378  ! ---------------------------------------------------------------------------------------------
380  subroutine parametrizedfunction1dparameternameslatex( self, i, latexname )
381 
382  implicit none
383 
384  class(parametrized_function_1d) :: self
385  integer , intent(in) :: i
386  character(*), intent(out) :: latexname
387 
388  ! check the input index:
389  if ( i>self%parameter_number ) then
390  write(*,*) 'In parametrized_function_1D:', self%name
391  write(*,*) 'Illegal index for parameter_names.'
392  write(*,*) 'Maximum value is:', self%parameter_number
393  call mpistop('EFTCAMB error')
394  end if
395  ! return the parameter name:
396  if ( allocated(self%param_names_latex) ) then
397  latexname = self%param_names_latex(i)%string
398  else
399  latexname = trim(self%name)//'_'//integer_to_string(i-1)
400  end if
401 
402  end subroutine parametrizedfunction1dparameternameslatex
403 
404  ! ---------------------------------------------------------------------------------------------
405 
407 
408 !----------------------------------------------------------------------------------------
This module contains the definition of the EFTCAMB caches. These are used to store parameters that ca...
This module contains various generic algorithms that are useful to EFTCAMB.
character(10) function, public integer_to_string(number)
This function converts an integer to a string. Usefull for numbered files output. ...
This module contains the definitions of all the EFTCAMB compile time flags.
Definition: 01_EFT_def.f90:25
integer function parametrizedfunction1dparamnumber(self)
Function that returns the number of parameters of the parametrized function.
This module contains the abstract class for generic parametrizations for 1D functions that are used b...