LPFP-core-1.1.1: Code for the book Learn Physics with Functional Programming
Copyright(c) Scott N. Walck 2023
LicenseBSD3 (see LICENSE)
MaintainerScott N. Walck <walck@lvc.edu>
Stabilitystable
Safe HaskellTrustworthy
LanguageHaskell2010

LPFPCore

Description

Code from the book Learn Physics with Functional Programming

Synopsis

(Approximations to) Real numbers

type R = Double Source #

An approximation to a real number.

type Time = R Source #

Time is a real number.

Vectors

data Vec Source #

A type for three-dimensional vectors.

Instances

Instances details
Show Vec Source # 
Instance details

Defined in LPFPCore.SimpleVec

Methods

showsPrec :: Int -> Vec -> ShowS #

show :: Vec -> String #

showList :: [Vec] -> ShowS #

Eq Vec Source # 
Instance details

Defined in LPFPCore.SimpleVec

Methods

(==) :: Vec -> Vec -> Bool #

(/=) :: Vec -> Vec -> Bool #

type PosVec = Vec Source #

The position of a particle can be represented as a vector.

type Velocity = Vec Source #

Velocity is a vector.

type Acceleration = Vec Source #

Acceleration is a vector.

vec Source #

Arguments

:: R

x component

-> R

y component

-> R

z component

-> Vec 

Form a vector by giving its x, y, and z components.

(^+^) :: Vec -> Vec -> Vec infixl 6 Source #

Vector addition.

(^-^) :: Vec -> Vec -> Vec infixl 6 Source #

Vector subtraction.

(*^) :: R -> Vec -> Vec infixr 7 Source #

Scalar multiplication of a number and a vector.

(^*) :: Vec -> R -> Vec infixl 7 Source #

Scalar multiplication of a vector and a number.

(^/) :: Vec -> R -> Vec infixr 7 Source #

Division of a vector by a number.

(<.>) :: Vec -> Vec -> R infixr 7 Source #

Dot product of two vectors.

(><) :: Vec -> Vec -> Vec infixl 7 Source #

Cross product of two vectors.

magnitude :: Vec -> R Source #

Magnitude of a vector.

zeroV :: Vec Source #

The zero vector.

negateV :: Vec -> Vec Source #

Negate a vector.

sumV :: [Vec] -> Vec Source #

Add a list of vectors.

xComp :: Vec -> R Source #

x component of a vector

yComp :: Vec -> R Source #

y component of a vector

zComp :: Vec -> R Source #

z component of a vector

iHat :: Vec Source #

A unit vector in the x direction.

jHat :: Vec Source #

A unit vector in the y direction.

kHat :: Vec Source #

A unit vector in the z direction.

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.

velFromPos Source #

Arguments

:: R

dt

-> (Time -> PosVec)

position function

-> Time -> Velocity

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

Methods

(+++) :: ds -> ds -> ds Source #

scale :: R -> ds -> ds Source #

Instances

Instances details
RealVectorSpace DParticleFieldState Source # 
Instance details

Defined in LPFPCore.Lorentz

RealVectorSpace DParticleState Source # 
Instance details

Defined in LPFPCore.Mechanics3D

RealVectorSpace DMultiParticleState Source # 
Instance details

Defined in LPFPCore.MultipleObjects

RealVectorSpace (R, R) Source # 
Instance details

Defined in LPFPCore.Mechanics1D

Methods

(+++) :: (R, R) -> (R, R) -> (R, R) Source #

scale :: R -> (R, R) -> (R, R) Source #

RealVectorSpace (R, R, R) Source #

A triple of real numbers is a real vector space.

Instance details

Defined in LPFPCore.Mechanics1D

Methods

(+++) :: (R, R, R) -> (R, R, R) -> (R, R, R) Source #

scale :: R -> (R, R, R) -> (R, R, R) Source #

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.

Methods

shift :: R -> ds -> s -> s Source #

Instances

Instances details
Diff ParticleFieldState DParticleFieldState Source # 
Instance details

Defined in LPFPCore.Lorentz

Diff ParticleState DParticleState Source # 
Instance details

Defined in LPFPCore.Mechanics3D

Diff MultiParticleState DMultiParticleState Source # 
Instance details

Defined in LPFPCore.MultipleObjects

Diff State1D (R, R, R) Source #

A triple of real numbers can serve as the time derivative of a State1D.

Instance details

Defined in LPFPCore.Mechanics1D

Methods

shift :: R -> (R, R, R) -> State1D -> State1D Source #

Diff (Time, Velocity) (R, R) Source # 
Instance details

Defined in LPFPCore.Mechanics1D

Methods

shift :: R -> (R, R) -> (Time, Velocity) -> (Time, Velocity) 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.

Constructors

ParticleState 

Fields

Instances

Instances details
HasTime ParticleState Source # 
Instance details

Defined in LPFPCore.Mechanics3D

Show ParticleState Source # 
Instance details

Defined in LPFPCore.Mechanics3D

Diff ParticleState DParticleState Source # 
Instance details

Defined in LPFPCore.Mechanics3D

data DParticleState Source #

Data type for the time-derivative of a particle state.

Constructors

DParticleState 

Fields

class HasTime s where Source #

Methods

timeOf :: s -> Time Source #

Instances

Instances details
HasTime ParticleFieldState Source # 
Instance details

Defined in LPFPCore.Lorentz

HasTime ParticleState Source # 
Instance details

Defined in LPFPCore.Mechanics3D

HasTime MultiParticleState Source # 
Instance details

Defined in LPFPCore.MultipleObjects

defaultParticleState :: ParticleState Source #

A default particle state.

newtonSecondPS Source #

Arguments

:: [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.

statesPS Source #

Arguments

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

airResistance Source #

Arguments

:: R

drag coefficient

-> R

air density

-> R

cross-sectional area of object

-> OneBodyForce 

The force of air resistance on an object.

windForce Source #

Arguments

:: Vec

wind velocity

-> R

drag coefficient

-> R

air density

-> R

cross-sectional area of object

-> OneBodyForce 

The force of wind on an object.

uniformLorentzForce Source #

Arguments

:: 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

Two-body forces

data Justification Source #

Constructors

LJ 
RJ 

Instances

Instances details
Show Justification Source # 
Instance details

Defined in LPFPCore.MOExamples

data Table a Source #

Constructors

Table Justification [[a]] 

Instances

Instances details
Show a => Show (Table a) Source # 
Instance details

Defined in LPFPCore.MOExamples

Methods

showsPrec :: Int -> Table a -> ShowS #

show :: Table a -> String #

showList :: [Table a] -> ShowS #

Electricity

Coordinate Systems

data Position Source #

Instances

Instances details
Show Position Source # 
Instance details

Defined in LPFPCore.CoordinateSystems

cart :: R -> R -> R -> Position Source #

cyl :: R -> R -> R -> Position Source #

sph :: R -> R -> R -> Position Source #

fst3 :: (a, b, c) -> a Source #

snd3 :: (a, b, c) -> b Source #

thd3 :: (a, b, c) -> c Source #

sfTable :: ((R, R) -> Position) -> [R] -> [R] -> ScalarField -> Table Int Source #

Geometry

data Curve Source #

Constructors

Curve 

data Surface Source #

Constructors

Surface 

Fields

data Volume Source #

Constructors

Volume 

Fields

Electromagnetic Theory

Charge

type Charge = R Source #

Electric Field

type Field a = Position -> a Source #

Current

type Current = R Source #

Magnetic Field

Lorentz Force Law

Maxwell Equations