Copyright | (c) Scott N. Walck 2023 |
---|---|
License | BSD3 (see LICENSE) |
Maintainer | Scott N. Walck <walck@lvc.edu> |
Stability | stable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Code from the book Learn Physics with Functional Programming
Synopsis
- type R = Double
- type Time = R
- data Vec
- type PosVec = Vec
- type Velocity = Vec
- type Acceleration = Vec
- vec :: R -> R -> R -> Vec
- (^+^) :: Vec -> Vec -> Vec
- (^-^) :: Vec -> Vec -> Vec
- (*^) :: R -> Vec -> Vec
- (^*) :: Vec -> R -> Vec
- (^/) :: Vec -> R -> Vec
- (<.>) :: Vec -> Vec -> R
- (><) :: Vec -> Vec -> Vec
- magnitude :: Vec -> R
- zeroV :: Vec
- negateV :: Vec -> Vec
- sumV :: [Vec] -> Vec
- xComp :: Vec -> R
- yComp :: Vec -> R
- zComp :: Vec -> R
- iHat :: Vec
- jHat :: Vec
- kHat :: Vec
- positionCV :: PosVec -> Velocity -> Time -> PosVec
- velocityCA :: Velocity -> Acceleration -> Time -> Velocity
- positionCA :: PosVec -> Velocity -> Acceleration -> Time -> PosVec
- aParallel :: Vec -> Vec -> Vec
- aPerp :: Vec -> Vec -> Vec
- speedRateChange :: Vec -> Vec -> R
- type Derivative = (R -> R) -> R -> R
- type VecDerivative = (R -> Vec) -> R -> Vec
- derivative :: R -> Derivative
- vecDerivative :: R -> VecDerivative
- integral :: R -> (R -> R) -> R -> R -> R
- antiDerivative :: R -> R -> (R -> R) -> R -> R
- velFromPos :: R -> (Time -> PosVec) -> Time -> Velocity
- accFromVel :: R -> (Time -> Velocity) -> Time -> Acceleration
- type UpdateFunction s = s -> s
- type DifferentialEquation s ds = s -> ds
- type NumericalMethod s ds = DifferentialEquation s ds -> UpdateFunction s
- class RealVectorSpace ds where
- class RealVectorSpace ds => Diff s ds where
- solver :: NumericalMethod s ds -> DifferentialEquation s ds -> s -> [s]
- euler :: Diff s ds => R -> (s -> ds) -> s -> s
- rungeKutta4 :: Diff s ds => R -> (s -> ds) -> s -> s
- data ParticleState = ParticleState {}
- data DParticleState = DParticleState {}
- class HasTime s where
- defaultParticleState :: ParticleState
- newtonSecondPS :: [OneBodyForce] -> ParticleState -> DParticleState
- relativityPS :: [OneBodyForce] -> ParticleState -> DParticleState
- eulerCromerPS :: TimeStep -> NumericalMethod ParticleState DParticleState
- statesPS :: NumericalMethod ParticleState DParticleState -> [OneBodyForce] -> ParticleState -> [ParticleState]
- updatePS :: NumericalMethod ParticleState DParticleState -> [OneBodyForce] -> ParticleState -> ParticleState
- type OneBodyForce = ParticleState -> Vec
- earthSurfaceGravity :: OneBodyForce
- sunGravity :: OneBodyForce
- airResistance :: R -> R -> R -> OneBodyForce
- windForce :: Vec -> R -> R -> R -> OneBodyForce
- uniformLorentzForce :: Vec -> Vec -> OneBodyForce
- fixedLinearSpring :: R -> R -> Vec -> OneBodyForce
- data Force
- data MultiParticleState = MPS {}
- data DMultiParticleState = DMPS [DParticleState]
- type TwoBodyForce = ParticleState -> ParticleState -> ForceVector
- universalGravity :: TwoBodyForce
- linearSpring :: R -> R -> TwoBodyForce
- centralForce :: (R -> R) -> TwoBodyForce
- billiardForce :: R -> R -> TwoBodyForce
- newtonSecondMPS :: [Force] -> MultiParticleState -> DMultiParticleState
- eulerCromerMPS :: TimeStep -> NumericalMethod MultiParticleState DMultiParticleState
- updateMPS :: NumericalMethod MultiParticleState DMultiParticleState -> [Force] -> MultiParticleState -> MultiParticleState
- statesMPS :: NumericalMethod MultiParticleState DMultiParticleState -> [Force] -> MultiParticleState -> [MultiParticleState]
- data Justification
- data Table a = Table Justification [[a]]
- kineticEnergy :: ParticleState -> R
- systemKE :: MultiParticleState -> R
- momentum :: ParticleState -> Vec
- systemP :: MultiParticleState -> Vec
- linearSpringPE :: R -> R -> ParticleState -> ParticleState -> R
- earthSurfaceGravityPE :: ParticleState -> R
- tenths :: R -> Float
- sigFigs :: Int -> R -> Float
- elementaryCharge :: Charge
- coulombForce :: TwoBodyForce
- data Position
- type Displacement = Vec
- type ScalarField = Position -> R
- type VectorField = Position -> Vec
- type CoordinateSystem = (R, R, R) -> Position
- cartesian :: CoordinateSystem
- cylindrical :: CoordinateSystem
- spherical :: CoordinateSystem
- cart :: R -> R -> R -> Position
- cyl :: R -> R -> R -> Position
- sph :: R -> R -> R -> Position
- cartesianCoordinates :: Position -> (R, R, R)
- cylindricalCoordinates :: Position -> (R, R, R)
- sphericalCoordinates :: Position -> (R, R, R)
- displacement :: Position -> Position -> Displacement
- shiftPosition :: Displacement -> Position -> Position
- rHat :: VectorField
- thetaHat :: VectorField
- phiHat :: VectorField
- sHat :: VectorField
- xHat :: VectorField
- yHat :: VectorField
- zHat :: VectorField
- origin :: Position
- xSF :: ScalarField
- ySF :: ScalarField
- rSF :: ScalarField
- rVF :: VectorField
- fst3 :: (a, b, c) -> a
- snd3 :: (a, b, c) -> b
- thd3 :: (a, b, c) -> c
- addScalarFields :: [ScalarField] -> ScalarField
- addVectorFields :: [VectorField] -> VectorField
- sfTable :: ((R, R) -> Position) -> [R] -> [R] -> ScalarField -> Table Int
- data Curve = Curve {
- curveFunc :: R -> Position
- startingCurveParam :: R
- endingCurveParam :: R
- unitCircle :: Curve
- straightLine :: Position -> Position -> Curve
- data Surface = Surface {
- surfaceFunc :: (R, R) -> Position
- lowerLimit :: R
- upperLimit :: R
- lowerCurve :: R -> R
- upperCurve :: R -> R
- unitSphere :: Surface
- centeredSphere :: R -> Surface
- sphere :: R -> Position -> Surface
- northernHemisphere :: Surface
- disk :: R -> Surface
- shiftSurface :: Vec -> Surface -> Surface
- data Volume = Volume {}
- unitBall :: Volume
- centeredBall :: R -> Volume
- northernHalfBall :: Volume
- centeredCylinder :: R -> R -> Volume
- type Charge = R
- data ChargeDistribution
- totalCharge :: ChargeDistribution -> Charge
- electricDipoleMoment :: ChargeDistribution -> Vec
- epsilon0 :: R
- cSI :: R
- mu0 :: R
- eField :: ChargeDistribution -> VectorField
- type ScalarLineIntegral = ScalarField -> Curve -> R
- type ScalarSurfaceIntegral = ScalarField -> Surface -> R
- type ScalarVolumeIntegral = ScalarField -> Volume -> R
- type VectorLineIntegral = VectorField -> Curve -> Vec
- type VectorSurfaceIntegral = VectorField -> Surface -> Vec
- type VectorVolumeIntegral = VectorField -> Volume -> Vec
- type CurveApprox = Curve -> [(Position, Vec)]
- type SurfaceApprox = Surface -> [(Position, Vec)]
- type VolumeApprox = Volume -> [(Position, R)]
- scalarLineIntegral :: CurveApprox -> ScalarField -> Curve -> R
- scalarSurfaceIntegral :: SurfaceApprox -> ScalarField -> Surface -> R
- scalarVolumeIntegral :: VolumeApprox -> ScalarField -> Volume -> R
- vectorLineIntegral :: CurveApprox -> VectorField -> Curve -> Vec
- vectorSurfaceIntegral :: SurfaceApprox -> VectorField -> Surface -> Vec
- vectorVolumeIntegral :: VolumeApprox -> VectorField -> Volume -> Vec
- dottedLineIntegral :: CurveApprox -> VectorField -> Curve -> R
- dottedSurfaceIntegral :: SurfaceApprox -> VectorField -> Surface -> R
- curveSample :: Int -> Curve -> [(Position, Vec)]
- surfaceSample :: Int -> Surface -> [(Position, Vec)]
- volumeSample :: Int -> Volume -> [(Position, R)]
- type Field a = Position -> a
- type Current = R
- data CurrentDistribution
- crossedLineIntegral :: CurveApprox -> VectorField -> Curve -> Vec
- totalCurrent :: VectorField -> Surface -> Current
- magneticDipoleMoment :: CurrentDistribution -> Vec
- bField :: CurrentDistribution -> VectorField
- lorentzForce :: ParticleFieldState -> Vec
- newtonSecondPFS :: ParticleFieldState -> DParticleFieldState
- defaultPFS :: ParticleFieldState
- directionalDerivative :: Vec -> ScalarField -> ScalarField
- curl :: R -> VectorField -> VectorField
- type FieldState = (R, VectorField, VectorField)
(Approximations to) Real numbers
Vectors
A type for three-dimensional vectors.
type Acceleration = Vec Source #
Acceleration is a vector.
Form a vector by giving its x, y, and z components.
positionCV :: PosVec -> Velocity -> Time -> PosVec Source #
Given initial position and a constant velocity, return a position function.
velocityCA :: Velocity -> Acceleration -> Time -> Velocity Source #
Given initial velocity and a constant acceleration, return a velocity function.
positionCA :: PosVec -> Velocity -> Acceleration -> Time -> PosVec Source #
Given initial position, initial velocity, and a constant acceleration, return a position function.
aParallel :: Vec -> Vec -> Vec Source #
Given a nonzero velocity and an acceleration, return the component of acceleration parallel to the velocity.
aPerp :: Vec -> Vec -> Vec Source #
Given a nonzero velocity and an acceleration, return the component of acceleration perpendicular to the velocity.
speedRateChange :: Vec -> Vec -> R Source #
Given velocity and acceleration, return the rate at which speed is changing.
Calculus
type Derivative = (R -> R) -> R -> R Source #
A derivative takes a real-valued function of a real variable (often time) as input, and produces a real-valued function of a real variable as output.
type VecDerivative = (R -> Vec) -> R -> Vec Source #
A vector derivative takes a vector-valued function of a real variable (usually time) as input, and produces a vector-valued function of a real variable as output.
derivative :: R -> Derivative Source #
Given a step size, calculate the derivative of a real-valued function of a real variable (often time).
vecDerivative :: R -> VecDerivative Source #
Given a step size, calculate the vector derivative of a vector-valued function of a real variable (usually time).
integral :: R -> (R -> R) -> R -> R -> R Source #
Given a step size, a function, a lower limit, and an upper limit, return the definite integral of the function.
antiDerivative :: R -> R -> (R -> R) -> R -> R Source #
Given a step size, a y-intercept, and a function, return a function with the given y-intercept whose derivative is the given function.
Given a time step and a position function, return a velocity function.
accFromVel :: R -> (Time -> Velocity) -> Time -> Acceleration Source #
Given a time step and a velocity function, return an acceleration function.
Differential equations
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.
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 # | |
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.
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.
3D Mechanics
Single particle state
data ParticleState Source #
Data type for the state of a single particle in three-dimensional space.
Instances
HasTime ParticleState Source # | |
Defined in LPFPCore.Mechanics3D timeOf :: ParticleState -> Time Source # | |
Show ParticleState Source # | |
Defined in LPFPCore.Mechanics3D showsPrec :: Int -> ParticleState -> ShowS # show :: ParticleState -> String # showList :: [ParticleState] -> ShowS # | |
Diff ParticleState DParticleState Source # | |
Defined in LPFPCore.Mechanics3D shift :: R -> DParticleState -> ParticleState -> ParticleState Source # |
data DParticleState Source #
Data type for the time-derivative of a particle state.
Instances
RealVectorSpace DParticleState Source # | |
Defined in LPFPCore.Mechanics3D (+++) :: DParticleState -> DParticleState -> DParticleState Source # scale :: R -> DParticleState -> DParticleState Source # | |
Show DParticleState Source # | |
Defined in LPFPCore.Mechanics3D showsPrec :: Int -> DParticleState -> ShowS # show :: DParticleState -> String # showList :: [DParticleState] -> ShowS # | |
Diff ParticleState DParticleState Source # | |
Defined in LPFPCore.Mechanics3D shift :: R -> DParticleState -> ParticleState -> ParticleState Source # |
class HasTime s where Source #
Instances
HasTime ParticleFieldState Source # | |
Defined in LPFPCore.Lorentz timeOf :: ParticleFieldState -> Time Source # | |
HasTime ParticleState Source # | |
Defined in LPFPCore.Mechanics3D timeOf :: ParticleState -> Time Source # | |
HasTime MultiParticleState Source # | |
Defined in LPFPCore.MultipleObjects timeOf :: MultiParticleState -> Time Source # |
defaultParticleState :: ParticleState Source #
A default particle state.
:: [OneBodyForce] | |
-> ParticleState | |
-> DParticleState | a differential equation |
Given a list of forces, return a differential equation based on Newton's second law.
relativityPS :: [OneBodyForce] -> ParticleState -> DParticleState Source #
Given a list of forces, return a differential equation based on the theory of special relativity.
eulerCromerPS :: TimeStep -> NumericalMethod ParticleState DParticleState Source #
Euler-Cromer method for the ParticleState
data type.
:: NumericalMethod ParticleState DParticleState | numerical method |
-> [OneBodyForce] | list of force funcs |
-> ParticleState | |
-> [ParticleState] | evolver |
Given a numerical method, a list of one-body forces, and an initial state, return a list of states describing how the particle evolves in time.
updatePS :: NumericalMethod ParticleState DParticleState -> [OneBodyForce] -> ParticleState -> ParticleState Source #
Given a numerical method and a list of one-body forces, return a state-update function.
One-body forces
type OneBodyForce = ParticleState -> Vec Source #
Data type for a one-body force.
earthSurfaceGravity :: OneBodyForce Source #
The force of gravity near Earth's surface. The z direction is toward the sky. Assumes SI units.
sunGravity :: OneBodyForce Source #
The force of the Sun's gravity on an object. The origin is at center of the Sun. Assumes SI units.
:: R | drag coefficient |
-> R | air density |
-> R | cross-sectional area of object |
-> OneBodyForce |
The force of air resistance on an object.
:: Vec | wind velocity |
-> R | drag coefficient |
-> R | air density |
-> R | cross-sectional area of object |
-> OneBodyForce |
The force of wind on an object.
:: Vec | E |
-> Vec | B |
-> OneBodyForce |
The force of uniform electric and magnetic fields on an object.
fixedLinearSpring :: R -> R -> Vec -> OneBodyForce Source #
Force provided by a spring that is fixed at one end.
Interacting particles
data MultiParticleState Source #
Instances
HasTime MultiParticleState Source # | |
Defined in LPFPCore.MultipleObjects timeOf :: MultiParticleState -> Time Source # | |
Show MultiParticleState Source # | |
Defined in LPFPCore.MultipleObjects showsPrec :: Int -> MultiParticleState -> ShowS # show :: MultiParticleState -> String # showList :: [MultiParticleState] -> ShowS # | |
Diff MultiParticleState DMultiParticleState Source # | |
Defined in LPFPCore.MultipleObjects shift :: R -> DMultiParticleState -> MultiParticleState -> MultiParticleState Source # |
data DMultiParticleState Source #
Instances
RealVectorSpace DMultiParticleState Source # | |
Defined in LPFPCore.MultipleObjects | |
Show DMultiParticleState Source # | |
Defined in LPFPCore.MultipleObjects showsPrec :: Int -> DMultiParticleState -> ShowS # show :: DMultiParticleState -> String # showList :: [DMultiParticleState] -> ShowS # | |
Diff MultiParticleState DMultiParticleState Source # | |
Defined in LPFPCore.MultipleObjects shift :: R -> DMultiParticleState -> MultiParticleState -> MultiParticleState Source # |
Two-body forces
type TwoBodyForce = ParticleState -> ParticleState -> ForceVector Source #
linearSpring :: R -> R -> TwoBodyForce Source #
centralForce :: (R -> R) -> TwoBodyForce Source #
billiardForce :: R -> R -> TwoBodyForce Source #
newtonSecondMPS :: [Force] -> MultiParticleState -> DMultiParticleState Source #
updateMPS :: NumericalMethod MultiParticleState DMultiParticleState -> [Force] -> MultiParticleState -> MultiParticleState Source #
statesMPS :: NumericalMethod MultiParticleState DMultiParticleState -> [Force] -> MultiParticleState -> [MultiParticleState] Source #
data Justification Source #
Instances
Show Justification Source # | |
Defined in LPFPCore.MOExamples showsPrec :: Int -> Justification -> ShowS # show :: Justification -> String # showList :: [Justification] -> ShowS # |
Table Justification [[a]] |
kineticEnergy :: ParticleState -> R Source #
systemKE :: MultiParticleState -> R Source #
momentum :: ParticleState -> Vec Source #
systemP :: MultiParticleState -> Vec Source #
linearSpringPE :: R -> R -> ParticleState -> ParticleState -> R Source #
Electricity
Coordinate Systems
type Displacement = Vec Source #
type ScalarField = Position -> R Source #
type VectorField = Position -> Vec Source #
displacement :: Position -> Position -> Displacement Source #
shiftPosition :: Displacement -> Position -> Position Source #
rHat :: VectorField Source #
phiHat :: VectorField Source #
sHat :: VectorField Source #
xHat :: VectorField Source #
yHat :: VectorField Source #
zHat :: VectorField Source #
xSF :: ScalarField Source #
ySF :: ScalarField Source #
rSF :: ScalarField Source #
rVF :: VectorField Source #
addScalarFields :: [ScalarField] -> ScalarField Source #
addVectorFields :: [VectorField] -> VectorField Source #
Geometry
unitCircle :: Curve Source #
Surface | |
|
unitSphere :: Surface Source #
centeredSphere :: R -> Surface Source #
centeredBall :: R -> Volume Source #
Electromagnetic Theory
Charge
data ChargeDistribution Source #
Electric Field
type ScalarLineIntegral = ScalarField -> Curve -> R Source #
type ScalarSurfaceIntegral = ScalarField -> Surface -> R Source #
type ScalarVolumeIntegral = ScalarField -> Volume -> R Source #
type VectorLineIntegral = VectorField -> Curve -> Vec Source #
type VectorSurfaceIntegral = VectorField -> Surface -> Vec Source #
type VectorVolumeIntegral = VectorField -> Volume -> Vec Source #
scalarLineIntegral :: CurveApprox -> ScalarField -> Curve -> R Source #
scalarSurfaceIntegral :: SurfaceApprox -> ScalarField -> Surface -> R Source #
scalarVolumeIntegral :: VolumeApprox -> ScalarField -> Volume -> R Source #
vectorLineIntegral :: CurveApprox -> VectorField -> Curve -> Vec Source #
vectorSurfaceIntegral :: SurfaceApprox -> VectorField -> Surface -> Vec Source #
vectorVolumeIntegral :: VolumeApprox -> VectorField -> Volume -> Vec Source #
dottedLineIntegral :: CurveApprox -> VectorField -> Curve -> R Source #
dottedSurfaceIntegral :: SurfaceApprox -> VectorField -> Surface -> R Source #
Current
data CurrentDistribution Source #
crossedLineIntegral :: CurveApprox -> VectorField -> Curve -> Vec Source #
totalCurrent :: VectorField -> Surface -> Current Source #
Magnetic Field
Lorentz Force Law
lorentzForce :: ParticleFieldState -> Vec Source #
Maxwell Equations
directionalDerivative :: Vec -> ScalarField -> ScalarField Source #
curl :: R -> VectorField -> VectorField Source #
type FieldState = (R, VectorField, VectorField) Source #