module_mol.f90 Source File


This file depends on

sourcefile~~module_mol.f90~~EfferentGraph sourcefile~module_mol.f90 module_mol.f90 sourcefile~module_kinds.f90 module_kinds.f90 sourcefile~module_mol.f90->sourcefile~module_kinds.f90 sourcefile~module_equations.f90 module_equations.f90 sourcefile~module_mol.f90->sourcefile~module_equations.f90 sourcefile~module_equations.f90->sourcefile~module_kinds.f90

Files dependent on this one

sourcefile~~module_mol.f90~~AfferentGraph sourcefile~module_mol.f90 module_mol.f90 sourcefile~module_abmv5.f90 module_abmv5.f90 sourcefile~module_abmv5.f90->sourcefile~module_mol.f90 sourcefile~module_rk5.f90 module_rk5.f90 sourcefile~module_rk5.f90->sourcefile~module_mol.f90 sourcefile~module_rk4.f90 module_rk4.f90 sourcefile~module_rk4.f90->sourcefile~module_mol.f90 sourcefile~submodule_rk4_implementation.f90 submodule_rk4_implementation.f90 sourcefile~submodule_rk4_implementation.f90->sourcefile~module_rk4.f90 sourcefile~module_all_integrators.f90 module_all_integrators.f90 sourcefile~module_all_integrators.f90->sourcefile~module_abmv5.f90 sourcefile~module_all_integrators.f90->sourcefile~module_rk5.f90 sourcefile~module_all_integrators.f90->sourcefile~module_rk4.f90 sourcefile~submodule_rk5_implementation.f90 submodule_rk5_implementation.f90 sourcefile~submodule_rk5_implementation.f90->sourcefile~module_rk5.f90 sourcefile~submodule_abmv5_implementation.f90 submodule_abmv5_implementation.f90 sourcefile~submodule_abmv5_implementation.f90->sourcefile~module_abmv5.f90 sourcefile~submodule_abmv5_implementation.f90->sourcefile~module_rk4.f90 sourcefile~submodule_geod_schw_implementation.f90 submodule_geod_schw_implementation.f90 sourcefile~submodule_geod_schw_implementation.f90->sourcefile~module_all_integrators.f90 sourcefile~submodule_osc_schw_implementation.f90 submodule_osc_schw_implementation.f90 sourcefile~submodule_osc_schw_implementation.f90->sourcefile~module_all_integrators.f90 sourcefile~submodule_scalar_schw_implementation.f90 submodule_scalar_schw_implementation.f90 sourcefile~submodule_scalar_schw_implementation.f90->sourcefile~module_all_integrators.f90 sourcefile~test.f90 test.f90 sourcefile~test.f90->sourcefile~module_all_integrators.f90

Contents

Source Code


Source Code

module method_of_lines
!! Module that defines an abstract class for the concept of an ODE integrator.
!! As this is just an abstract class, there is no implementation.

  use kinds
  use equations

  implicit none

  type, abstract :: integrator
  !! An abstract class that defines an equation time integrator.
    integer(ip) :: nequations
    !! The number of equations to integrate.
    class(equation_pointer), dimension(:), allocatable :: eqs
    !! A 1d array of equation pointers. Will be of length nequations.
  contains
    procedure (integrator_ntemp_interface), deferred, pass :: ntemp
    !! A procedure that allows an integrator to tell the equations how much
    !! temporary storage is needed.
    procedure (integrator_init_interface), deferred, pass :: init
    !! A procedure that initializes an integrator.
    procedure (integrator_step_interface), deferred, pass :: step
    !! A procedure that takes one time step.
    procedure (integrator_shutdown_interface), deferred, pass :: shutdown
    !! A procedure that shuts down an integrator.
  end type integrator

  abstract interface
    function integrator_ntemp_interface ( this ) result (ntemp)
    !! The return value is the number of temporary storage levels are needed.
      import :: integrator, ip
      class(integrator), intent(in) :: this
      !! The routine is called on this object.
      integer(ip) :: ntemp
      !! The number of temporary storage levels needed.
    end function integrator_ntemp_interface

    subroutine integrator_init_interface ( this, eqs )
    !! Initialize an integrator.
      import :: integrator, equation_pointer
      class(integrator), intent(inout) :: this
      !! The routine is called on this object.
      type(equation_pointer), dimension(:), intent(in) :: eqs
      !! A 1d array of pointers to the equations that will be integrated.
    end subroutine integrator_init_interface

    subroutine integrator_step_interface ( this )
    !! Take a time step.
      import :: integrator
      class(integrator), intent(inout) :: this
      !! The routine is called on this object.
    end subroutine integrator_step_interface

    subroutine integrator_shutdown_interface ( this )
    !! Shut down this integrator.
      import :: integrator
      class(integrator), intent(inout) :: this
      !! The routine is called on this object.
    end subroutine integrator_shutdown_interface
  end interface

end module method_of_lines