module Drasil.Projectile.Lesson.Motion where
import Utils.Drasil (weave)
import qualified Drasil.DocLang.Notebook as NB (summary, hormotion, vermotion)
import Data.Drasil.Concepts.Physics (motion, acceleration, velocity, force, time,
constAccel, horizontalMotion, verticalMotion)
import Data.Drasil.Units.Physics (accelU)
import Data.Drasil.Concepts.Math (xDir, yAxis)
import Drasil.Projectile.Concepts (projectile, projMotion)
import Drasil.Projectile.Derivations
import Drasil.Projectile.Expressions
import qualified Data.Drasil.Quantities.Physics as QP (iSpeed, ixSpeed, iySpeed, speed,
constAccel, gravitationalAccel, xAccel, yAccel, time, xVel, yVel)
import Data.Drasil.Concepts.Documentation (coordinateSystem)
import Language.Drasil
import Language.Drasil.ShortHands
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.SI_Units (s_2)
motionContextP1, motionContextP2 :: Contents
motionContextP1 :: Contents
motionContextP1
= [Sentence] -> Contents
foldlSP
[String -> Sentence
S "The free flight", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
motion Sentence -> Sentence -> Sentence
`S.ofA` ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
projectile,
String -> Sentence
S "is often studied in terms of its rectangular components, since the",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrasePoss ConceptChunk
projectile, ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
acceleration Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S "always acts in the vertical direciton",
String -> Sentence
S "To illustrate the kinematic analysis, consider a ", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
projectile,
String -> Sentence
S "launched at point", Sentence -> Sentence
sParen (Symbol -> Sentence
P Symbol
lX Sentence -> Sentence -> Sentence
`sC` Symbol -> Sentence
P Symbol
lY),
String -> Sentence
S "as shown in" Sentence -> Sentence -> Sentence
+:+. LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
figCSandA,
String -> Sentence
S "The path is defined in the", Symbol -> Sentence
P Symbol
lX Sentence -> Sentence -> Sentence
`sDash` Symbol -> Sentence
P Symbol
lY, String -> Sentence
S "plane such that the initial",
ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
velocity, String -> Sentence
S "is", ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.iSpeed) Sentence -> Sentence -> Sentence
:+: String -> Sentence
S ", having components",
ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.ixSpeed) Sentence -> Sentence -> Sentence
`S.and_` ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.iySpeed),
String -> Sentence
S "When air resistance is neglected, the only", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
force, String -> Sentence
S "acting on the",
ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
projectile, String -> Sentence
S"is its weight, which causes the", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
projectile,
String -> Sentence
S "to have a *constant downward acceleration* of approximately",
ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.constAccel ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.gravitationalAccel ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= Double -> ModelExpr
forall r. LiteralC r => Double -> r
dbl 9.81), USymb -> Sentence
Sy (UnitDefn -> USymb
forall u. HasUnitSymbol u => u -> USymb
usymb UnitDefn
accelU) Sentence -> Sentence -> Sentence
`S.or_`
ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.gravitationalAccel ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= Double -> ModelExpr
forall r. LiteralC r => Double -> r
dbl 32.2), USymb -> Sentence
Sy (UnitDefn -> USymb
forall u. HasUnitSymbol u => u -> USymb
usymb UnitDefn
accelinftU)]
motionContextP2 :: Contents
motionContextP2
= [Sentence] -> Contents
foldlSP_
[String -> Sentence
S "The equations for rectilinear kinematics given above", LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
lcrectVel, String -> Sentence
S "are in one dimension.",
String -> Sentence
S "These equations can be applied for both the", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
verticalMotion Sentence -> Sentence -> Sentence
`S.andThe`
ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
horizontalMotion Sentence -> Sentence -> Sentence
:+: String -> Sentence
S ", as follows:"]
horMotion, verMotion, summary :: Section
horMotion :: Section
horMotion = [Contents] -> [Section] -> Section
NB.hormotion [Contents
intro, Contents
equations, Contents
concl] []
where intro :: Contents
intro = [Sentence] -> Contents
foldlSP_ [
String -> Sentence
S "For", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
projMotion Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "the", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
acceleration,
String -> Sentence
S "in the horizontal direction is and equal to zero" Sentence -> Sentence -> Sentence
+:+.
Sentence -> Sentence
sParen(ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.xAccel ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl 0)), Sentence
motionSent]
equations :: Contents
equations = [Sentence] -> Contents
foldlSP_ ([Sentence] -> Contents) -> [Sentence] -> Contents
forall a b. (a -> b) -> a -> b
$ [[Sentence]] -> [Sentence]
forall a. [[a]] -> [a]
weave [[Sentence]
equationsSents, (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr]
horMotionEqns]
concl :: Contents
concl = [Sentence] -> Contents
foldlSP [
String -> Sentence
S "Since the", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
acceleration, String -> Sentence
S "in the" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
xDir,
Sentence -> Sentence
sParen (ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.xAccel)), String -> Sentence
S "is zero, the horizontal component of ", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
velocity,
String -> Sentence
S "always remains constant during" Sentence -> Sentence -> Sentence
+:+. ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
motion,
String -> Sentence
S "In addition to knowing this, we have one more equation"]
verMotion :: Section
verMotion = [Contents] -> [Section] -> Section
NB.vermotion [Contents
intro, Contents
equations, Contents
concl] []
where intro :: Contents
intro = [Sentence] -> Contents
foldlSP_ [
String -> Sentence
S "Since the positive", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
yAxis, String -> Sentence
S "is directed upward, the", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
acceleration,
String -> Sentence
S "in the vertical direction is" Sentence -> Sentence -> Sentence
+:+. ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.yAccel ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= ModelExpr -> ModelExpr
forall r. ExprC r => r -> r
neg (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.gravitationalAccel)), Sentence
motionSent]
equations :: Contents
equations = [Sentence] -> Contents
foldlSP_ ([Sentence] -> Contents) -> [Sentence] -> Contents
forall a b. (a -> b) -> a -> b
$ [[Sentence]] -> [Sentence]
forall a. [[a]] -> [a]
weave [[Sentence]
equationsSents, (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr]
verMotionDeriv]
concl :: Contents
concl = [Sentence] -> Contents
foldlSP [
String -> Sentence
S "Recall that the last equation can be formulated on the basis of eliminating the",
ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
time Sentence -> Sentence -> Sentence
+:+ ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.time), String -> Sentence
S "between the first two equations, and therefore only ",
String -> Sentence
S "two of the above three equations are independent of one another"]
summary :: Section
summary = [Contents] -> [Section] -> Section
NB.summary [Contents
smmryCon] []
where smmryCon :: Contents
smmryCon = [Sentence] -> Contents
foldlSP [
String -> Sentence
S "In addition to knowing that the horizontal component of", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
velocity,
String -> Sentence
S "is constant [Hibbler doesn't say this, but it seems necessary for completeness],",
String -> Sentence
S "problems involving the", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
motion Sentence -> Sentence -> Sentence
`S.ofA` ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
projectile Sentence -> Sentence -> Sentence
+:
String -> Sentence
S "can have at most three unknowns since only three independent equations can be written",
String -> Sentence
S "that is, one equation in the horizontal direction and two in the vertical direction.",
String -> Sentence
S "Once", ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.xVel) Sentence -> Sentence -> Sentence
`S.and_` ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.yVel), String -> Sentence
S "are obtained, the resultant",
ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
velocity Sentence -> Sentence -> Sentence
+:+ ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.speed), String -> Sentence
S "which is always tangent to the path,",
String -> Sentence
S "is defined by the vector sum as shown in", LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
figCSandA]
resourcePath :: String
resourcePath :: String
resourcePath = "../../../datafiles/Projectile/"
figCSandA :: LabelledContent
figCSandA :: LabelledContent
figCSandA = Reference -> RawContent -> LabelledContent
llcc (String -> Reference
makeFigRef "CoordSystAndAssumpts") (RawContent -> LabelledContent) -> RawContent -> LabelledContent
forall a b. (a -> b) -> a -> b
$ Sentence -> String -> RawContent
fig (NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NP -> Sentence) -> NP -> Sentence
forall a b. (a -> b) -> a -> b
$ NamedChunk -> NP
forall t. NamedIdea t => t -> NP
the NamedChunk
coordinateSystem)
(String
resourcePath String -> String -> String
forall a. [a] -> [a] -> [a]
++ "CoordSystAndAssumpts.png")
equationsSents :: [Sentence]
equationsSents :: [Sentence]
equationsSents = [String -> Sentence
S "From Equation" Sentence -> Sentence -> Sentence
+: LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
lcrectVel,
String -> Sentence
S "From Equation" Sentence -> Sentence -> Sentence
+: LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
lcrectPos,
String -> Sentence
S "From Equation" Sentence -> Sentence -> Sentence
+: LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
lcrectNoTime]
horMotionEqns :: [ModelExpr]
horMotionEqns :: [ModelExpr]
horMotionEqns = [ModelExpr
horMotionEqn1, ModelExpr
horMotionEqn2, ModelExpr
horMotionEqn1]
motionSent :: Sentence
motionSent :: Sentence
motionSent = String -> Sentence
S "This value can be substituted in the equations for" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
constAccel Sentence -> Sentence -> Sentence
+:
String -> Sentence
S "given above (ref) to yield the following"
figRefs :: [Reference]
figRefs :: [Reference]
figRefs = [LabelledContent -> Reference
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Reference
ref LabelledContent
figCSandA]
foot, accelinftU :: UnitDefn
= String -> String -> String -> UnitDefn
fund "foot" "length" "ft"
accelinftU :: UnitDefn
accelinftU = String -> UnitEquation -> UnitDefn
newUnit "acceleration" (UnitEquation -> UnitDefn) -> UnitEquation -> UnitDefn
forall a b. (a -> b) -> a -> b
$ UnitDefn
foot UnitDefn -> UnitDefn -> UnitEquation
/: UnitDefn
s_2