wenoof_polynomials.F90 Source File

Abstract polynomials object.

This File Depends On

sourcefile~~wenoof_polynomials.f90~~EfferentGraph sourcefile~wenoof_polynomials.f90 wenoof_polynomials.F90 sourcefile~penf.f90 penf.F90 sourcefile~penf.f90->sourcefile~wenoof_polynomials.f90 sourcefile~wenoof_base_object.f90 wenoof_base_object.f90 sourcefile~wenoof_base_object.f90->sourcefile~wenoof_polynomials.f90 sourcefile~penf_b_size.f90 penf_b_size.F90 sourcefile~penf_b_size.f90->sourcefile~penf.f90 sourcefile~penf_stringify.f90 penf_stringify.F90 sourcefile~penf_b_size.f90->sourcefile~penf_stringify.f90 sourcefile~penf_global_parameters_variables.f90 penf_global_parameters_variables.F90 sourcefile~penf_global_parameters_variables.f90->sourcefile~penf.f90 sourcefile~penf_global_parameters_variables.f90->sourcefile~penf_b_size.f90 sourcefile~penf_global_parameters_variables.f90->sourcefile~penf_stringify.f90 sourcefile~penf_stringify.f90->sourcefile~penf.f90
Help

Files Dependent On This One

sourcefile~~wenoof_polynomials.f90~~AfferentGraph sourcefile~wenoof_polynomials.f90 wenoof_polynomials.F90 sourcefile~wenoof.f90 wenoof.f90 sourcefile~wenoof_polynomials.f90->sourcefile~wenoof.f90 sourcefile~wenoof_objects_factory.f90 wenoof_objects_factory.f90 sourcefile~wenoof_polynomials.f90->sourcefile~wenoof_objects_factory.f90 sourcefile~wenoof_interpolator_js.f90 wenoof_interpolator_js.f90 sourcefile~wenoof_polynomials.f90->sourcefile~wenoof_interpolator_js.f90 sourcefile~wenoof_interpolator.f90 wenoof_interpolator.F90 sourcefile~wenoof_polynomials.f90->sourcefile~wenoof_interpolator.f90 sourcefile~wenoof_polynomials_js.f90 wenoof_polynomials_js.f90 sourcefile~wenoof_polynomials.f90->sourcefile~wenoof_polynomials_js.f90 sourcefile~sin_reconstruction.f90 sin_reconstruction.f90 sourcefile~wenoof.f90->sourcefile~sin_reconstruction.f90 sourcefile~wenoof_objects_factory.f90->sourcefile~wenoof_interpolator.f90 sourcefile~wenoof_interpolator_js.f90->sourcefile~wenoof.f90 sourcefile~wenoof_interpolator.f90->sourcefile~wenoof.f90 sourcefile~wenoof_interpolator.f90->sourcefile~wenoof_interpolator_js.f90 sourcefile~wenoof_polynomials_js.f90->sourcefile~wenoof.f90 sourcefile~wenoof_polynomials_js.f90->sourcefile~wenoof_objects_factory.f90 sourcefile~wenoof_polynomials_js.f90->sourcefile~wenoof_interpolator_js.f90
Help


Source Code

!< Abstract polynomials object.
module wenoof_polynomials
!< Abstract polynomials object.

use penf, only : I_P, R_P
use wenoof_base_object

implicit none
private
public :: polynomials
public :: polynomials_constructor

type, extends(base_object_constructor) :: polynomials_constructor
  !< Abstract polynomials object constructor.
  integer(I_P) :: S = 0 !< Stencils dimension.
endtype polynomials_constructor

type, extends(base_object) :: polynomials
  !< Abstract polynomials object.
  real(R_P), allocatable :: poly(:,:)   !< Polynomial reconstructions [1:2,0:S-1].
  contains
    ! deferred public methods
    procedure, pass(self) :: compute     !< Compute polynomials.
    procedure, nopass     :: description !< Return polynomials string-description.
    ! public methods
    procedure, pass(self) :: create  !< Createte polynomials.
    procedure, pass(self) :: destroy !< Destroy polynomials.
endtype polynomials

contains
  ! deferred public methods
  pure subroutine compute(self, S, stencil, f1, f2, ff)
  !< Compute polynomials.
  class(polynomials), intent(inout) :: self                !< Polynomials.
  integer(I_P),       intent(in)    :: S                   !< Number of stencils used.
  real(R_P),          intent(in)    :: stencil(1:, 1 - S:) !< Stencil used for the interpolation, [1:2, 1-S:-1+S].
  integer(I_P),       intent(in)    :: f1, f2, ff          !< Faces to be computed.

#ifndef DEBUG
  ! error stop in pure procedure is a F2015 feature not yet supported in debug mode
  error stop 'polynomials%compute to be implemented by your concrete polynomials object'
#endif
  endsubroutine compute

  pure function description() result(string)
  !< Return polynomials string-description.
  character(len=:), allocatable  :: string !< String-description.

#ifndef DEBUG
  ! error stop in pure procedure is a F2015 feature not yet supported in debug mode
  error stop 'polynomials%description to be implemented by your concrete polynomials object'
#endif
  endfunction description

  ! public methods
  pure subroutine create(self, constructor)
  !< Create polynomials.
  class(polynomials),             intent(inout) :: self        !< Polynomials.
  class(base_object_constructor), intent(in)    :: constructor !< Polynomials constructor.

  call self%destroy
  select type(constructor)
  class is(polynomials_constructor)
    allocate(self%poly(1:2, 0:constructor%S - 1))
  class default
    ! @TODO add error handling
  endselect
  self%poly = 0._R_P
  endsubroutine create

  elemental subroutine destroy(self)
  !< Destroy polynomials.
  class(polynomials), intent(inout) :: self !< Polynomials.

  if (allocated(self%poly)) deallocate(self%poly)
  endsubroutine destroy
endmodule wenoof_polynomials