Copyright | (c) Scott N. Walck 2023 |
---|---|
License | BSD3 (see LICENSE) |
Maintainer | Scott N. Walck <walck@lvc.edu> |
Stability | stable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Code from chapter 15 of the book Learn Physics with Functional Programming
Synopsis
- type Time = R
- type TimeStep = R
- type Mass = R
- type Position = R
- type Velocity = R
- type Force = R
- type State1D = (Time, Position, Velocity)
- newtonSecond1D :: Mass -> [State1D -> Force] -> State1D -> (R, R, R)
- euler1D :: R -> (State1D -> (R, R, R)) -> State1D -> State1D
- updateTXV :: R -> Mass -> [State1D -> Force] -> State1D -> State1D
- statesTXV :: R -> Mass -> State1D -> [State1D -> Force] -> [State1D]
- velocity1D :: [State1D] -> Time -> Velocity
- velocityFtxv :: R -> Mass -> State1D -> [State1D -> Force] -> Time -> Velocity
- position1D :: [State1D] -> Time -> Position
- positionFtxv :: R -> Mass -> State1D -> [State1D -> Force] -> Time -> Position
- springForce :: R -> State1D -> Force
- dampedHOForces :: [State1D -> Force]
- dampedHOStates :: [State1D]
- pingpongPosition :: Time -> Position
- pingpongVelocity :: Time -> Velocity
- eulerCromer1D :: R -> (State1D -> (R, R, R)) -> State1D -> State1D
- updateTXVEC :: R -> Mass -> [State1D -> Force] -> State1D -> State1D
- type UpdateFunction s = s -> s
- type DifferentialEquation s ds = s -> ds
- type NumericalMethod s ds = DifferentialEquation s ds -> UpdateFunction s
- solver :: NumericalMethod s ds -> DifferentialEquation s ds -> s -> [s]
- class RealVectorSpace ds where
- class RealVectorSpace ds => Diff s ds where
- euler :: Diff s ds => R -> (s -> ds) -> s -> s
- rungeKutta4 :: Diff s ds => R -> (s -> ds) -> s -> s
- exponential :: DifferentialEquation (R, R, R) (R, R, R)
- update2 :: (R, R, R) -> (R, R, R)
- earthGravity :: Mass -> State1D -> Force
- type MState = (Time, Mass, Position, Velocity)
- earthGravity2 :: MState -> Force
- positionFtxv2 :: R -> MState -> [MState -> Force] -> Time -> Position
- statesTXV2 :: R -> MState -> [MState -> Force] -> [MState]
- updateTXV2 :: R -> [MState -> Force] -> MState -> MState
- updateTV' :: R -> Mass -> [(Time, Velocity) -> Force] -> (Time, Velocity) -> (Time, Velocity)
- forces :: R -> [State1D -> R]
- vdp :: R -> [(R, R)]
Documentation
dampedHOForces :: [State1D -> Force] Source #
dampedHOStates :: [State1D] Source #
pingpongPosition :: Time -> Position Source #
pingpongVelocity :: Time -> Velocity Source #
type UpdateFunction s = s -> s Source #
An update function takes a state as input and returns an updated state as output.
type DifferentialEquation s ds = s -> ds Source #
A differential equation takes a state as input and returns as output the rate at which the state is changing.
type NumericalMethod s ds = DifferentialEquation s ds -> UpdateFunction s Source #
A numerical method turns a differential equation into a state-update function.
solver :: NumericalMethod s ds -> DifferentialEquation s ds -> s -> [s] Source #
Given a numerical method, a differential equation, and an initial state, return a list of states.
class RealVectorSpace ds where Source #
A real vector space allows vector addition and scalar multiplication by reals.
Instances
RealVectorSpace DParticleFieldState Source # | |
Defined in LPFPCore.Lorentz | |
RealVectorSpace DParticleState Source # | |
Defined in LPFPCore.Mechanics3D (+++) :: DParticleState -> DParticleState -> DParticleState Source # scale :: R -> DParticleState -> DParticleState Source # | |
RealVectorSpace DMultiParticleState Source # | |
Defined in LPFPCore.MultipleObjects | |
RealVectorSpace (R, R) Source # | |
RealVectorSpace (R, R, R) Source # | A triple of real numbers is a real vector space. |
class RealVectorSpace ds => Diff s ds where Source #
A type class that expresses a relationship between a state space and a time-derivative-state space.
Instances
Diff ParticleFieldState DParticleFieldState Source # | |
Defined in LPFPCore.Lorentz shift :: R -> DParticleFieldState -> ParticleFieldState -> ParticleFieldState Source # | |
Diff ParticleState DParticleState Source # | |
Defined in LPFPCore.Mechanics3D shift :: R -> DParticleState -> ParticleState -> ParticleState Source # | |
Diff MultiParticleState DMultiParticleState Source # | |
Defined in LPFPCore.MultipleObjects shift :: R -> DMultiParticleState -> MultiParticleState -> MultiParticleState Source # | |
Diff State1D (R, R, R) Source # | A triple of real numbers can serve as the time derivative of a |
Diff (Time, Velocity) (R, R) Source # | |
euler :: Diff s ds => R -> (s -> ds) -> s -> s Source #
Given a step size, return the numerical method that uses the Euler method with that step size.
rungeKutta4 :: Diff s ds => R -> (s -> ds) -> s -> s Source #
Given a step size, return the numerical method that uses the 4th order Runge Kutta method with that step size.
exponential :: DifferentialEquation (R, R, R) (R, R, R) Source #
earthGravity2 :: MState -> Force Source #