Copyright | (c) Scott N. Walck 2014-2019 |
---|---|
License | BSD3 (see LICENSE) |
Maintainer | Scott N. Walck <walck@lvc.edu> |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell98 |
A StateSpace
is an affine space where the associated vector space
has scalars that are instances of Fractional
.
If p is an instance of StateSpace
, then the associated vectorspace
Diff
p is intended to represent the space of (time) derivatives
of paths in p.
StateSpace
is very similar to Conal Elliott's AffineSpace
.
Synopsis
- class (VectorSpace (Diff p), Fractional (Scalar (Diff p))) => StateSpace p where
- (.-^) :: StateSpace p => p -> Diff p -> p
- type Time p = Scalar (Diff p)
- type DifferentialEquation state = state -> Diff state
- type InitialValueProblem state = (DifferentialEquation state, state)
- type EvolutionMethod state = DifferentialEquation state -> Time state -> state -> state
- type SolutionMethod state = InitialValueProblem state -> [state]
- stepSolution :: EvolutionMethod state -> Time state -> SolutionMethod state
- eulerMethod :: StateSpace state => EvolutionMethod state
Documentation
class (VectorSpace (Diff p), Fractional (Scalar (Diff p))) => StateSpace p where Source #
An instance of StateSpace
is a data type that can serve as the state
of some system. Alternatively, a StateSpace
is a collection of dependent
variables for a differential equation.
A StateSpace
has an associated vector space for the (time) derivatives
of the state. The associated vector space is a linearized version of
the StateSpace
.
(.-.) :: p -> p -> Diff p infix 6 Source #
Subtract points
(.+^) :: p -> Diff p -> p infixl 6 Source #
Point plus vector
Instances
StateSpace Double Source # | |
StateSpace Vec Source # | |
StateSpace Position Source # | Position is not a vector, but displacement (difference in position) is a vector. |
StateSpace St Source # | |
StateSpace p => StateSpace [p] Source # | |
(StateSpace p, StateSpace q, Time p ~ Time q) => StateSpace (p, q) Source # | |
(StateSpace p, StateSpace q, StateSpace r, Time p ~ Time q, Time q ~ Time r) => StateSpace (p, q, r) Source # | |
(.-^) :: StateSpace p => p -> Diff p -> p infixl 6 Source #
Point minus vector
type Time p = Scalar (Diff p) Source #
The scalars of the associated vector space can be thought of as time intervals.
type DifferentialEquation state = state -> Diff state Source #
A differential equation expresses how the dependent variables (state) change with the independent variable (time). A differential equation is specified by giving the (time) derivative of the state as a function of the state. The (time) derivative of a state is an element of the associated vector space.
type InitialValueProblem state = (DifferentialEquation state, state) Source #
An initial value problem is a differential equation along with an initial state.
type EvolutionMethod state Source #
= DifferentialEquation state | differential equation |
-> Time state | time interval |
-> state | initial state |
-> state | evolved state |
An evolution method is a way of approximating the state after advancing a finite interval in the independent variable (time) from a given state.
type SolutionMethod state = InitialValueProblem state -> [state] Source #
A (numerical) solution method is a way of converting an initial value problem into a list of states (a solution). The list of states need not be equally spaced in time.
stepSolution :: EvolutionMethod state -> Time state -> SolutionMethod state Source #
Given an evolution method and a time step, return the solution method which applies the evolution method repeatedly with with given time step. The solution method returned will produce an infinite list of states.
eulerMethod :: StateSpace state => EvolutionMethod state Source #
The Euler method is the simplest evolution method. It increments the state by the derivative times the time step.