learn-physics-0.6.0.2: Haskell code for learning physics

Copyright(c) Scott N. Walck 2014
LicenseBSD3 (see LICENSE)
MaintainerScott N. Walck <walck@lvc.edu>
Stabilityexperimental
Safe HaskellTrustworthy
LanguageHaskell98

Physics.Learn.StateSpace

Contents

Description

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

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.

Minimal complete definition

(.-.), (.+^)

Associated Types

type Diff p Source #

Associated vector space

Methods

(.-.) :: p -> p -> Diff p infix 6 Source #

Subtract points

(.+^) :: p -> Diff p -> p infixl 6 Source #

Point plus vector

Instances

StateSpace Double Source # 

Associated Types

type Diff Double :: * Source #

StateSpace Vec Source # 

Associated Types

type Diff Vec :: * Source #

Methods

(.-.) :: Vec -> Vec -> Diff Vec Source #

(.+^) :: Vec -> Diff Vec -> Vec Source #

StateSpace Position Source #

Position is not a vector, but displacement (difference in position) is a vector.

StateSpace St Source # 

Associated Types

type Diff St :: * Source #

Methods

(.-.) :: St -> St -> Diff St Source #

(.+^) :: St -> Diff St -> St Source #

StateSpace p => StateSpace [p] Source # 

Associated Types

type Diff [p] :: * Source #

Methods

(.-.) :: [p] -> [p] -> Diff [p] Source #

(.+^) :: [p] -> Diff [p] -> [p] Source #

(StateSpace p, StateSpace q, (~) * (Time p) (Time q)) => StateSpace (p, q) Source # 

Associated Types

type Diff (p, q) :: * Source #

Methods

(.-.) :: (p, q) -> (p, q) -> Diff (p, q) Source #

(.+^) :: (p, q) -> Diff (p, q) -> (p, q) Source #

(StateSpace p, StateSpace q, StateSpace r, (~) * (Time p) (Time q), (~) * (Time q) (Time r)) => StateSpace (p, q, r) Source # 

Associated Types

type Diff (p, q, r) :: * Source #

Methods

(.-.) :: (p, q, r) -> (p, q, r) -> Diff (p, q, r) Source #

(.+^) :: (p, q, r) -> Diff (p, q, r) -> (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 #

Arguments

 = 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.

Orphan instances

VectorSpace v => VectorSpace [v] Source # 

Associated Types

type Scalar [v] :: * #

Methods

(*^) :: Scalar [v] -> [v] -> [v] #

AdditiveGroup v => AdditiveGroup [v] Source # 

Methods

zeroV :: [v] #

(^+^) :: [v] -> [v] -> [v] #

negateV :: [v] -> [v] #

(^-^) :: [v] -> [v] -> [v] #