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 10 of the book Learn Physics with Functional Programming
Synopsis
- type VecDerivative = (R -> Vec) -> R -> Vec
- vecDerivative :: R -> VecDerivative
- v1 :: R -> Vec
- xCompFunc :: (R -> Vec) -> R -> R
- type Derivative = (R -> R) -> R -> R
- derivative :: R -> Derivative
- type Time = R
- type PosVec = Vec
- type Velocity = Vec
- type Acceleration = Vec
- velFromPos :: R -> (Time -> PosVec) -> Time -> Velocity
- accFromVel :: R -> (Time -> Velocity) -> Time -> Acceleration
- 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
- radiusOfCurvature :: Vec -> Vec -> R
- projectilePos :: PosVec -> Velocity -> Time -> PosVec
- type R = Double
- data Mass = Mass R
- data Grade = Grade String Int
- grades :: [Grade]
- data GradeRecord = GradeRecord {}
- gradeRecords1 :: [GradeRecord]
- gradeRecords2 :: [GradeRecord]
- data MyBool
- data MyMaybe a
- data Vec = Vec {}
- showDouble :: R -> String
- vec :: R -> R -> R -> Vec
- iHat :: Vec
- jHat :: Vec
- kHat :: Vec
- zeroV :: Vec
- negateV :: Vec -> Vec
- (^+^) :: Vec -> Vec -> Vec
- (^-^) :: Vec -> Vec -> Vec
- sumV :: [Vec] -> Vec
- (*^) :: R -> Vec -> Vec
- (^*) :: Vec -> R -> Vec
- (<.>) :: Vec -> Vec -> R
- (><) :: Vec -> Vec -> Vec
- (^/) :: Vec -> R -> Vec
- magnitude :: Vec -> R
- vecIntegral :: R -> (R -> Vec) -> R -> R -> Vec
- maxHeight :: PosVec -> Velocity -> R
- speedCA :: Velocity -> Acceleration -> Time -> R
- xyProj :: Vec -> Vec
- magAngles :: Vec -> (R, R, R)
- gEarth :: Vec
- vBall :: R -> Vec
- speedRateChangeBall :: R -> R
- rNCM :: (R, R -> R) -> R -> Vec
- aPerpFromPosition :: R -> (R -> Vec) -> R -> Vec
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).
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 Acceleration = Vec Source #
Acceleration is a vector.
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.
data GradeRecord Source #
Instances
Show GradeRecord Source # | |
Defined in LPFPCore.SimpleVec showsPrec :: Int -> GradeRecord -> ShowS # show :: GradeRecord -> String # showList :: [GradeRecord] -> ShowS # | |
Eq GradeRecord Source # | |
Defined in LPFPCore.SimpleVec (==) :: GradeRecord -> GradeRecord -> Bool # (/=) :: GradeRecord -> GradeRecord -> Bool # |
gradeRecords1 :: [GradeRecord] Source #
gradeRecords2 :: [GradeRecord] Source #
A type for three-dimensional vectors.
showDouble :: R -> String Source #
Form a vector by giving its x, y, and z components.
Definite integral of a vector-valued function of a real number.
speedRateChangeBall :: R -> R Source #