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 HaskellSafe-Inferred
LanguageHaskell2010

LPFPCore.SimpleVec

Description

Code from chapter 10 of the book Learn Physics with Functional Programming

Synopsis

Documentation

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.

vecDerivative :: R -> VecDerivative Source #

Given a step size, calculate the vector derivative of a vector-valued function of a real variable (usually time).

v1 :: R -> Vec Source #

xCompFunc :: (R -> Vec) -> R -> R Source #

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.

derivative :: R -> Derivative Source #

Given a step size, calculate the derivative of a real-valued function of a real variable (often time).

type Time = R Source #

Time is a real number.

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.

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.

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.

type R = Double Source #

An approximation to a real number.

data Mass Source #

Constructors

Mass R 

Instances

Instances details
Show Mass Source # 
Instance details

Defined in LPFPCore.SimpleVec

Methods

showsPrec :: Int -> Mass -> ShowS #

show :: Mass -> String #

showList :: [Mass] -> ShowS #

Eq Mass Source # 
Instance details

Defined in LPFPCore.SimpleVec

Methods

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

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

data Grade Source #

Constructors

Grade String Int 

Instances

Instances details
Show Grade Source # 
Instance details

Defined in LPFPCore.SimpleVec

Methods

showsPrec :: Int -> Grade -> ShowS #

show :: Grade -> String #

showList :: [Grade] -> ShowS #

Eq Grade Source # 
Instance details

Defined in LPFPCore.SimpleVec

Methods

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

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

data GradeRecord Source #

Constructors

GradeRecord 

Fields

Instances

Instances details
Show GradeRecord Source # 
Instance details

Defined in LPFPCore.SimpleVec

Eq GradeRecord Source # 
Instance details

Defined in LPFPCore.SimpleVec

data MyBool Source #

Constructors

MyFalse 
MyTrue 

Instances

Instances details
Show MyBool Source # 
Instance details

Defined in LPFPCore.SimpleVec

Eq MyBool Source # 
Instance details

Defined in LPFPCore.SimpleVec

Methods

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

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

data MyMaybe a Source #

Constructors

MyNothing 
MyJust a 

Instances

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

Defined in LPFPCore.SimpleVec

Methods

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

show :: MyMaybe a -> String #

showList :: [MyMaybe a] -> ShowS #

Eq a => Eq (MyMaybe a) Source # 
Instance details

Defined in LPFPCore.SimpleVec

Methods

(==) :: MyMaybe a -> MyMaybe a -> Bool #

(/=) :: MyMaybe a -> MyMaybe a -> Bool #

data Vec Source #

A type for three-dimensional vectors.

Constructors

Vec 

Fields

  • xComp :: R

    x component of a vector

  • yComp :: R

    y component of a vector

  • zComp :: R

    z component of a vector

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 #

vec Source #

Arguments

:: R

x component

-> R

y component

-> R

z component

-> Vec 

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

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.

zeroV :: Vec Source #

The zero vector.

negateV :: Vec -> Vec Source #

Negate a vector.

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

Vector addition.

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

Vector subtraction.

sumV :: [Vec] -> Vec Source #

Add a list of vectors.

(*^) :: 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 -> Vec -> R infixr 7 Source #

Dot product of two vectors.

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

Cross product of two vectors.

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

Division of a vector by a number.

magnitude :: Vec -> R Source #

Magnitude of a vector.

vecIntegral Source #

Arguments

:: R

step size dt

-> (R -> Vec)

vector-valued function

-> R

lower limit

-> R

upper limit

-> Vec

result

Definite integral of a vector-valued function of a real number.

magAngles :: Vec -> (R, R, R) Source #

rNCM :: (R, R -> R) -> R -> Vec Source #

aPerpFromPosition :: R -> (R -> Vec) -> R -> Vec Source #