hamilton-0.1.0.3: Physics on generalized coordinate systems using Hamiltonian Mechanics and AD

Copyright(c) Justin Le 2016
LicenseBSD-3
Maintainerjustin@jle.im
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Numeric.Hamilton

Contents

Description

Simulate physical systems on generalized/arbitrary coordinates using Hamiltonian mechanics and automatic differentiation!

See the https://github.com/mstksg/hamilton#readme for more information on usage!

Synopsis

Systems and states

Systems

data System :: Nat -> Nat -> Type Source #

Represents a physical system in which physics happens. A System m n is a system whose state described using n generalized coordinates (an "n-dimensional" system), where the underlying cartesian coordinate space is m-dimensional.

For the most part, you are supposed to be able to ignore m. m is only provided because it's useful when plotting/drawing the system with a given state back in rectangular coordinates. (The only function that use the m at the moment is underlyingPos)

A System m n's state is described using a Config n (which describes the system in configuration space) or a Phase n (which describes the system in phase space).

mkSystem Source #

Arguments

:: (KnownNat m, KnownNat n) 
=> R m

The "inertia" of each of the m coordinates in the underlying cartesian space of the system. This should be mass for linear coordinates and rotational inertia for angular coordinates.

-> (forall a. RealFloat a => Vector n a -> Vector m a)

Conversion function to convert points in the generalized coordinate space to the underlying cartesian space of the system.

-> (forall a. RealFloat a => Vector n a -> a)

The potential energy of the system as a function of the generalized coordinate space's positions.

-> System m n 

Create a system with n generalized coordinates by describing its coordinate space (by a function from the generalized coordinates to the underlying cartesian coordinates), the inertia of each of those underlying coordinates, and the pontential energy function.

The potential energy function is expressed in terms of the genearlized coordinate space's positions.

mkSystem' Source #

Arguments

:: (KnownNat m, KnownNat n) 
=> R m

The "inertia" of each of the m coordinates in the underlying cartesian space of the system. This should be mass for linear coordinates and rotational inertia for angular coordinates.

-> (forall a. RealFloat a => Vector n a -> Vector m a)

Conversion function to convert points in the generalized coordinate space to the underlying cartesian space of the system.

-> (forall a. RealFloat a => Vector m a -> a)

The potential energy of the system as a function of the underlying cartesian coordinate space's positions.

-> System m n 

Convenience wrapper over mkSystem that allows you to specify the potential energy function in terms of the underlying cartesian coordinate space.

underlyingPos :: System m n -> R n -> R m Source #

Converts the position of generalized coordinates of a system to the coordinates of the system's underlying cartesian coordinate system. Useful for plotting/drawing the system in cartesian space.

States

data Config :: Nat -> Type where Source #

Represents the full state of a system of n generalized coordinates in configuration space (informally, "positions and velocities")

A configuration space representaiton is more directly "physically meaningful" and intuitive/understandable to humans than a phase space representation. However, it's much less mathematically ideal to work with because of the lack of some neat underlying symmetries.

You can convert a Config n into a Phase n (convert from configuration space to phase space) for a given system with toPhase. This allows you to state your system in configuration space and then convert it to phase space before handing it off to the hamiltonian machinery.

Constructors

Cfg :: {..} -> Config n 

Fields

  • cfgPositions :: !(R n)

    The current values ("positions") of each of the n generalized coordinates

  • cfgVelocities :: !(R n)

    The current rate of changes ("velocities") of each of the n generalized coordinates

Instances

KnownNat n => Show (Config n) Source # 

Methods

showsPrec :: Int -> Config n -> ShowS #

show :: Config n -> String #

showList :: [Config n] -> ShowS #

Generic (Config a) Source # 

Associated Types

type Rep (Config a) :: * -> * #

Methods

from :: Config a -> Rep (Config a) x #

to :: Rep (Config a) x -> Config a #

type Rep (Config a) Source # 
type Rep (Config a) = D1 * (MetaData "Config" "Numeric.Hamilton" "hamilton-0.1.0.3-KARukhp6LRI80NG1iE11Go" False) (C1 * (MetaCons "Cfg" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "cfgPositions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (R a))) (S1 * (MetaSel (Just Symbol "cfgVelocities") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (R a)))))

data Phase :: Nat -> Type where Source #

Represents the full state of a system of n generalized coordinates in phase space (informally, "positions and momentums").

Phase space representations are much nicer to work with mathematically because of some neat underlying symmetries. For one, positions and momentums are "interchangeable" in a system; if you swap every coordinate's positions with their momentums, and also swap them in the equations of motions, you get the same system back. This isn't the case with configuration space representations.

A hamiltonian simulation basically describes the trajectory of each coordinate through phase space, so this is the state of the simulation. However, configuration space representations are much more understandable to humans, so it might be useful to give an initial state in configuration space using Config, and then convert it to a Phase with toPhase.

Constructors

Phs :: {..} -> Phase n 

Fields

  • phsPositions :: !(R n)

    The current values ("positions") of each of the n generalized coordinates.

  • phsMomenta :: !(R n)

    The current conjugate momenta ("momentums") to each of the n generalized coordinates

Instances

KnownNat n => Show (Phase n) Source # 

Methods

showsPrec :: Int -> Phase n -> ShowS #

show :: Phase n -> String #

showList :: [Phase n] -> ShowS #

Generic (Phase a) Source # 

Associated Types

type Rep (Phase a) :: * -> * #

Methods

from :: Phase a -> Rep (Phase a) x #

to :: Rep (Phase a) x -> Phase a #

type Rep (Phase a) Source # 
type Rep (Phase a) = D1 * (MetaData "Phase" "Numeric.Hamilton" "hamilton-0.1.0.3-KARukhp6LRI80NG1iE11Go" False) (C1 * (MetaCons "Phs" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "phsPositions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (R a))) (S1 * (MetaSel (Just Symbol "phsMomenta") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (R a)))))

toPhase :: (KnownNat m, KnownNat n) => System m n -> Config n -> Phase n Source #

Convert a configuration-space representaiton of the state of the system to a phase-space representation.

Useful because the hamiltonian simulations use Phase as its working state, but Config is a much more human-understandable and intuitive representation. This allows you to state your starting state in configuration space and convert to phase space for your simulation to use.

fromPhase :: (KnownNat m, KnownNat n) => System m n -> Phase n -> Config n Source #

Invert toPhase and convert a description of a system's state in phase space to a description of the system's state in configuration space.

Possibly useful for showing the phase space representation of a system's state in a more human-readable/human-understandable way.

State functions

momenta :: (KnownNat m, KnownNat n) => System m n -> Config n -> R n Source #

Compute the generalized momenta conjugate to each generalized coordinate of a system by giving the configuration-space state of the system.

Note that getting the momenta from a Phase n involves just using phsMomenta.

velocities :: (KnownNat m, KnownNat n) => System m n -> Phase n -> R n Source #

Compute the rate of change of each generalized coordinate by giving the state of the system in phase space.

Note that getting the velocities from a Config n involves just using cfgVelocities.

keC :: (KnownNat m, KnownNat n) => System m n -> Config n -> Double Source #

The kinetic energy of a system, given the system's state in configuration space.

keP :: (KnownNat m, KnownNat n) => System m n -> Phase n -> Double Source #

The kinetic energy of a system, given the system's state in phase space.

pe :: System m n -> R n -> Double Source #

The potential energy of a system, given the position in the generalized coordinates of the system.

lagrangian :: (KnownNat m, KnownNat n) => System m n -> Config n -> Double Source #

The Lagrangian of a system (the difference between the kinetic energy and the potential energy), given the system's state in configuration space.

hamiltonian :: (KnownNat m, KnownNat n) => System m n -> Phase n -> Double Source #

The Hamiltonian of a system (the sum of kinetic energy and the potential energy), given the system's state in phase space.

hamEqs :: (KnownNat m, KnownNat n) => System m n -> Phase n -> (R n, R n) Source #

The "hamiltonian equations" for a given system at a given state in phase space. Returns the rate of change of the positions and conjugate momenta, which can be used to progress the simulation through time.

Simulating hamiltonian dynamics

Over phase space

stepHam Source #

Arguments

:: (KnownNat m, KnownNat n) 
=> Double

timestep to step through

-> System m n

system to simulate

-> Phase n

initial state, in phase space

-> Phase n 

Step a system through phase space over over a single timestep.

evolveHam Source #

Arguments

:: (KnownNat m, KnownNat n, KnownNat s, 2 <= s) 
=> System m n

system to simulate

-> Phase n

initial state, in phase space

-> Vector s Double

desired solution times

-> Vector s (Phase n) 

Evolve a system using a hamiltonian stepper, with the given initial phase space state.

evolveHam' Source #

Arguments

:: (KnownNat m, KnownNat n) 
=> System m n

system to simulate

-> Phase n

initial state, in phase space

-> [Double]

desired solution times

-> [Phase n] 

Evolve a system using a hamiltonian stepper, with the given initial phase space state.

Desired solution times provided as a list instead of a sized Vector. The output list should be the same length as the input list.

Over configuration space

Convenience wrappers over the normal phase-space steppers/simulators that allow you to provide input and expect output in configuration space instead of in phase space. Note that the simulation itself still runs in phase space, so these all require conversions to and from phase space under the hood.

stepHamC Source #

Arguments

:: (KnownNat m, KnownNat n) 
=> Double

timestep to step through

-> System m n

system to simulate

-> Config n

initial state, in phase space

-> Config n 

Step a system through configuration space over over a single timestep.

Note that the simulation itself still runs in phase space; this function just abstracts over converting to and from phase space for the input and output.

evolveHamC Source #

Arguments

:: (KnownNat m, KnownNat n, KnownNat s, 2 <= s) 
=> System m n

system to simulate

-> Config n

initial state, in configuration space

-> Vector s Double

desired solution times

-> Vector s (Config n) 

A convenience wrapper for evolveHam that works on configuration space states instead of phase space states.

Note that the simulation itself still runs in phase space; this function just abstracts over converting to and from phase space for the inputs and outputs.

evolveHamC' Source #

Arguments

:: (KnownNat m, KnownNat n) 
=> System m n

system to simulate

-> Config n

initial state, in configuration space

-> [Double]

desired solution times

-> [Config n] 

A convenience wrapper for evolveHam' that works on configuration space states instead of phase space states.

Note that the simulation itself still runs in phase space; this function just abstracts over converting to and from phase space for the inputs and outputs.