module Drasil.GamePhysics.DataDefs (dataDefs, ctrOfMassDD,
linDispDD, linVelDD, linAccDD, angDispDD, angVelDD, angAccelDD, torqueDD,
kEnergyDD, coeffRestitutionDD, reVelInCollDD, impulseVDD, momentOfInertiaDD,
collisionAssump, rightHandAssump, rigidTwoDAssump, potEnergyDD,) where
import Language.Drasil
import Theory.Drasil
import Utils.Drasil (weave)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S
import Control.Lens ((^.))
import Drasil.GamePhysics.Assumptions (assumpOT, assumpOD, assumpAD, assumpCT, assumpDI)
import Drasil.GamePhysics.Derivations (impulseVDerivEqns)
import Drasil.GamePhysics.References (chaslesWiki)
import Drasil.GamePhysics.Unitals (finRelVel, initRelVel, mTot, massj,
normalVect, posCM, posj, rOB, rRot, velAP, velB, velBP, velO)
import Data.Drasil.Concepts.Math (rightHand)
import Data.Drasil.Concepts.Physics (rigidBody, twoD)
import qualified Data.Drasil.Quantities.Math as QM (orientation)
import qualified Data.Drasil.Quantities.Physics as QP
import qualified Data.Drasil.Quantities.PhysicalProperties as QPP (mass)
import Data.Drasil.Theories.Physics (torqueDD)
dataDefs :: [DataDefinition]
dataDefs :: [DataDefinition]
dataDefs = [DataDefinition
ctrOfMassDD, DataDefinition
linDispDD, DataDefinition
linVelDD, DataDefinition
linAccDD, DataDefinition
angDispDD,
DataDefinition
angVelDD, DataDefinition
angAccelDD, DataDefinition
chaslesDD, DataDefinition
torqueDD, DataDefinition
kEnergyDD, DataDefinition
coeffRestitutionDD,
DataDefinition
reVelInCollDD, DataDefinition
impulseVDD, DataDefinition
potEnergyDD, DataDefinition
momentOfInertiaDD]
ctrOfMassDD :: DataDefinition
ctrOfMassDD :: DataDefinition
ctrOfMassDD = ModelQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddMENoRefs ModelQDef
ctrOfMass forall a. Maybe a
Nothing String
"ctrOfMass" [Sentence
rigidBodyAssump]
ctrOfMass :: ModelQDef
ctrOfMass :: ModelQDef
ctrOfMass = forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
posCM ModelExpr
ctrOfMassEqn
ctrOfMassEqn :: ModelExpr
ctrOfMassEqn :: ModelExpr
ctrOfMassEqn = forall r. ModelExprC r => Symbol -> r -> r
sumAll (String -> Symbol
variable String
"j") (forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
massj forall r. ExprC r => r -> r -> r
`mulRe` forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
posj) forall r. ExprC r => r -> r -> r
$/ forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
mTot
linDispDD :: DataDefinition
linDispDD :: DataDefinition
linDispDD = ModelQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddMENoRefs ModelQDef
linDisp forall a. Maybe a
Nothing String
"linDisp" [Sentence
rigidBodyAssump]
linDisp :: ModelQDef
linDisp :: ModelQDef
linDisp = forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.linearDisplacement ModelExpr
dispEqn
dispEqn :: ModelExpr
dispEqn :: ModelExpr
dispEqn = forall r c. (ModelExprC r, HasUID c, HasSymbol c) => r -> c -> r
deriv (forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
QP.position UnitalChunk
QP.time) UnitalChunk
QP.time
linVelDD :: DataDefinition
linVelDD :: DataDefinition
linVelDD = ModelQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddMENoRefs ModelQDef
linVel forall a. Maybe a
Nothing String
"linVel" [Sentence
rigidBodyAssump]
linVel :: ModelQDef
linVel :: ModelQDef
linVel = forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.linearVelocity ModelExpr
velEqn
velEqn :: ModelExpr
velEqn :: ModelExpr
velEqn = forall r c. (ModelExprC r, HasUID c, HasSymbol c) => r -> c -> r
deriv (forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
QP.displacement UnitalChunk
QP.time) UnitalChunk
QP.time
linAccDD :: DataDefinition
linAccDD :: DataDefinition
linAccDD = ModelQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddMENoRefs ModelQDef
linAcc forall a. Maybe a
Nothing String
"linAcc" [Sentence
rigidBodyAssump]
linAcc :: ModelQDef
linAcc :: ModelQDef
linAcc = forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.linearAccel ModelExpr
accelEqn
accelEqn :: ModelExpr
accelEqn :: ModelExpr
accelEqn = forall r c. (ModelExprC r, HasUID c, HasSymbol c) => r -> c -> r
deriv (forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
QP.velocity UnitalChunk
QP.time) UnitalChunk
QP.time
angDispDD :: DataDefinition
angDispDD :: DataDefinition
angDispDD = ModelQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddMENoRefs ModelQDef
angDisp forall a. Maybe a
Nothing String
"angDisp" [Sentence
rigidTwoDAssump]
angDisp :: ModelQDef
angDisp :: ModelQDef
angDisp = forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.angularDisplacement ModelExpr
angDispEqn
angDispEqn :: ModelExpr
angDispEqn :: ModelExpr
angDispEqn = forall r c. (ModelExprC r, HasUID c, HasSymbol c) => r -> c -> r
deriv (forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
QM.orientation UnitalChunk
QP.time) UnitalChunk
QP.time
angVelDD :: DataDefinition
angVelDD :: DataDefinition
angVelDD = ModelQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddMENoRefs ModelQDef
angVel forall a. Maybe a
Nothing String
"angVel" [Sentence
rigidTwoDAssump]
angVel :: ModelQDef
angVel :: ModelQDef
angVel = forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.angularVelocity ModelExpr
angVelEqn
angVelEqn :: ModelExpr
angVelEqn :: ModelExpr
angVelEqn = forall r c. (ModelExprC r, HasUID c, HasSymbol c) => r -> c -> r
deriv (forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
QP.angularDisplacement UnitalChunk
QP.time) UnitalChunk
QP.time
angAccelDD :: DataDefinition
angAccelDD :: DataDefinition
angAccelDD = ModelQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddMENoRefs ModelQDef
angAccel forall a. Maybe a
Nothing String
"angAccel" [Sentence
rigidTwoDAssump]
angAccel :: ModelQDef
angAccel :: ModelQDef
angAccel = forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.angularAccel ModelExpr
angAccelEqn
angAccelEqn :: ModelExpr
angAccelEqn :: ModelExpr
angAccelEqn = forall r c. (ModelExprC r, HasUID c, HasSymbol c) => r -> c -> r
deriv (forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
QP.angularVelocity UnitalChunk
QP.time) UnitalChunk
QP.time
chaslesDD :: DataDefinition
chaslesDD :: DataDefinition
chaslesDD = SimpleQDef
-> [DecRef]
-> Maybe Derivation
-> String
-> [Sentence]
-> DataDefinition
ddE SimpleQDef
chasles [forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
chaslesWiki] forall a. Maybe a
Nothing String
"chaslesThm"
[Sentence
chaslesThmNote, Sentence
rigidBodyAssump]
chasles :: SimpleQDef
chasles :: SimpleQDef
chasles = forall c e.
(Quantity c, MayHaveUnit c) =>
c -> NP -> e -> QDefinition e
mkQuantDef' UnitalChunk
velB (String -> NP
nounPhraseSP String
"Chasles' theorem") Expr
chaslesEqn
chaslesEqn :: Expr
chaslesEqn :: Expr
chaslesEqn = forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
velO forall r. ExprC r => r -> r -> r
`addRe` forall r. ExprC r => r -> r -> r
cross (forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.angularVelocity) (forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
rOB)
chaslesThmNote :: Sentence
chaslesThmNote :: Sentence
chaslesThmNote = [Sentence] -> Sentence
foldlSent [forall n. NounPhrase n => n -> Sentence
atStartNP (forall t. NamedIdea t => t -> NP
the UnitalChunk
QP.linearVelocity),
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
velB Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"any point B in a", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
rigidBody Sentence -> Sentence -> Sentence
`S.isThe` String -> Sentence
S String
"sum" Sentence -> Sentence -> Sentence
`S.ofThe`
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.linearVelocity Sentence -> Sentence -> Sentence
+:+ forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
velO Sentence -> Sentence -> Sentence
`S.ofThe` forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
rigidBody,
String -> Sentence
S String
"at the origin (axis of rotation)" Sentence -> Sentence -> Sentence
`S.andThe` String -> Sentence
S String
"resultant vector from",
String -> Sentence
S String
"cross product" Sentence -> Sentence -> Sentence
`S.the_ofThe` forall n. NamedIdea n => n -> Sentence
phrasePoss ConceptChunk
rigidBody,
forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
QP.angularVelocity Sentence -> Sentence -> Sentence
`S.andThe` forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
rOB]
impulseVDD :: DataDefinition
impulseVDD :: DataDefinition
impulseVDD = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
impulseV (forall a. a -> Maybe a
Just Derivation
impulseVDeriv) String
"impulseV"
[Sentence
impulseVDesc, Sentence
rigidBodyAssump]
impulseV :: SimpleQDef
impulseV :: SimpleQDef
impulseV = forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.impulseV Expr
impulseVEqn
impulseVEqn :: Expr
impulseVEqn :: Expr
impulseVEqn = forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QPP.mass forall r. ExprC r => r -> r -> r
`mulRe` forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.chgInVelocity
impulseVDesc :: Sentence
impulseVDesc :: Sentence
impulseVDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"An", forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
QP.impulseV, String -> Sentence
S String
"occurs when a",
forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
QP.force, String -> Sentence
S String
"acts over a body over an interval" Sentence -> Sentence -> Sentence
`S.of_` forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.time]
impulseVDeriv :: Derivation
impulseVDeriv :: Derivation
impulseVDeriv = Sentence -> [Sentence] -> Derivation
mkDerivName (forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.impulseV) (forall a. [[a]] -> [a]
weave [[Sentence]
impulseVDerivSentences, forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr]
impulseVDerivEqns])
impulseVDerivSentences :: [Sentence]
impulseVDerivSentences :: [Sentence]
impulseVDerivSentences = forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSentCol [[Sentence]
impulseVDerivSentence1,
[Sentence]
impulseVDerivSentence2, [Sentence]
impulseVDerivSentence3]
impulseVDerivSentence1 :: [Sentence]
impulseVDerivSentence1 :: [Sentence]
impulseVDerivSentence1 = [String -> Sentence
S String
"Newton's second law of motion states"]
impulseVDerivSentence2 :: [Sentence]
impulseVDerivSentence2 :: [Sentence]
impulseVDerivSentence2 = [String -> Sentence
S String
"Rearranging"]
impulseVDerivSentence3 :: [Sentence]
impulseVDerivSentence3 :: [Sentence]
impulseVDerivSentence3 = [String -> Sentence
S String
"Integrating the right hand side"]
reVelInCollDD :: DataDefinition
reVelInCollDD :: DataDefinition
reVelInCollDD = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
reVelInColl forall a. Maybe a
Nothing String
"reVeInColl"
[Sentence
reVelInCollDesc, Sentence
rigidBodyAssump]
reVelInColl :: SimpleQDef
reVelInColl :: SimpleQDef
reVelInColl = forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
initRelVel Expr
reVelInCollEqn
reVelInCollEqn :: Expr
reVelInCollEqn :: Expr
reVelInCollEqn = forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
velAP forall r. ExprC r => r -> r -> r
`vSub` forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
velBP
reVelInCollDesc :: Sentence
reVelInCollDesc :: Sentence
reVelInCollDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"In a collision, the", forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
QP.velocity
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofA` ConceptChunk
rigidBody), String -> Sentence
S String
"A colliding with another", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
rigidBody,
String -> Sentence
S String
"B relative to that body", forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
initRelVel Sentence -> Sentence -> Sentence
`S.isThe` String -> Sentence
S String
"difference between the",
forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
QP.velocity, String -> Sentence
S String
"of A and B at point P"]
coeffRestitutionDD :: DataDefinition
coeffRestitutionDD :: DataDefinition
coeffRestitutionDD = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
coeffRestitution forall a. Maybe a
Nothing String
"coeffRestitution"
[Sentence
coeffRestitutionDesc]
coeffRestitution :: SimpleQDef
coeffRestitution :: SimpleQDef
coeffRestitution = forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
QP.restitutionCoef Expr
coeffRestitutionEqn
coeffRestitutionEqn :: Expr
coeffRestitutionEqn :: Expr
coeffRestitutionEqn = forall r. ExprC r => r -> r
neg forall a b. (a -> b) -> a -> b
$ forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
finRelVel forall r. ExprC r => r -> r -> r
$.
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
normalVect forall r. ExprC r => r -> r -> r
$/ forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
initRelVel forall r. ExprC r => r -> r -> r
$.
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
normalVect
coeffRestitutionDesc :: Sentence
coeffRestitutionDesc :: Sentence
coeffRestitutionDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"The", forall a. Quantity a => a -> Sentence
getTandS DefinedQuantityDict
QP.restitutionCoef,
String -> Sentence
S String
"determines the elasticity of a collision between two" Sentence -> Sentence -> Sentence
+:+. forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
rigidBody,
SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List [
ModelExpr -> Sentence
eS (forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
QP.restitutionCoef forall r. ExprC r => r -> r -> r
$= forall r. LiteralC r => Integer -> r
exactDbl Integer
1) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"results in an elastic collision",
ModelExpr -> Sentence
eS (forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
QP.restitutionCoef forall r. ExprC r => r -> r -> r
$< forall r. LiteralC r => Integer -> r
exactDbl Integer
1) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"results in an inelastic collision",
ModelExpr -> Sentence
eS (forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
QP.restitutionCoef forall r. ExprC r => r -> r -> r
$= forall r. LiteralC r => Integer -> r
exactDbl Integer
0) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"results in a totally inelastic collision"]]
kEnergyDD :: DataDefinition
kEnergyDD :: DataDefinition
kEnergyDD = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
kEnergy forall a. Maybe a
Nothing String
"kEnergy"
[Sentence
kEnergyDesc, Sentence
rigidTwoDAssump, Sentence
noDampingAssump]
kEnergy :: SimpleQDef
kEnergy :: SimpleQDef
kEnergy = forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.kEnergy Expr
kEnergyEqn
kEnergyEqn :: Expr
kEnergyEqn :: Expr
kEnergyEqn = forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QPP.mass forall r. ExprC r => r -> r -> r
`mulRe` forall r. (ExprC r, LiteralC r) => r -> r
half (forall r. (ExprC r, LiteralC r) => r -> r
square (forall r. ExprC r => r -> r
norm (forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.velocity)))
kEnergyDesc :: Sentence
kEnergyDesc :: Sentence
kEnergyDesc = [Sentence] -> Sentence
foldlSent [forall n. NamedIdea n => n -> Sentence
atStart UnitalChunk
QP.kEnergy Sentence -> Sentence -> Sentence
`S.is` (UnitalChunk
QP.kEnergy forall s a. s -> Getting a s a -> a
^. forall c. Definition c => Lens' c Sentence
defn)]
momentOfInertiaDD :: DataDefinition
momentOfInertiaDD :: DataDefinition
momentOfInertiaDD = ModelQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddMENoRefs ModelQDef
momentOfInertia forall a. Maybe a
Nothing String
"momentOfInertia"
[Sentence
momentOfInertiaDesc, Sentence
rigidBodyAssump]
momentOfInertia :: ModelQDef
momentOfInertia :: ModelQDef
momentOfInertia = forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.momentOfInertia ModelExpr
momentOfInertiaEqn
momentOfInertiaEqn :: ModelExpr
momentOfInertiaEqn :: ModelExpr
momentOfInertiaEqn = forall r. ModelExprC r => Symbol -> r -> r
sumAll (String -> Symbol
variable String
"j") forall a b. (a -> b) -> a -> b
$ forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
massj forall r. ExprC r => r -> r -> r
`mulRe` forall r. (ExprC r, LiteralC r) => r -> r
square (forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
rRot)
momentOfInertiaDesc :: Sentence
momentOfInertiaDesc :: Sentence
momentOfInertiaDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"The", forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
QP.momentOfInertia,
String -> Sentence
S String
"of a body measures how much", forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.torque,
String -> Sentence
S String
"is needed for the body to achieve angular acceleration about the axis of rotation"]
potEnergyDD :: DataDefinition
potEnergyDD :: DataDefinition
potEnergyDD = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
potEnergy forall a. Maybe a
Nothing String
"potEnergy"
[Sentence
potEnergyDesc, Sentence
rigidTwoDAssump, Sentence
noDampingAssump]
potEnergy :: SimpleQDef
potEnergy :: SimpleQDef
potEnergy = forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.potEnergy Expr
potEnergyEqn
potEnergyEqn :: Expr
potEnergyEqn :: Expr
potEnergyEqn = forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QPP.mass forall r. ExprC r => r -> r -> r
`mulRe` forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.gravitationalAccel forall r. ExprC r => r -> r -> r
`mulRe` forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.height
potEnergyDesc :: Sentence
potEnergyDesc :: Sentence
potEnergyDesc = [Sentence] -> Sentence
foldlSent [forall n. NounPhrase n => n -> Sentence
atStartNP (forall t. NamedIdea t => t -> NP
the UnitalChunk
QP.potEnergy) Sentence -> Sentence -> Sentence
`S.of_`
String -> Sentence
S String
"an object" Sentence -> Sentence -> Sentence
`S.isThe` forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.energy, String -> Sentence
S String
"held by an object because of its",
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.position, String -> Sentence
S String
"to other objects"]
collisionAssump, noDampingAssump, rightHandAssump, rigidBodyAssump, rigidTwoDAssump :: Sentence
collisionAssump :: Sentence
collisionAssump = String -> Sentence
S String
"All collisions are vertex-to-edge" Sentence -> Sentence -> Sentence
+:+. forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource ConceptInstance
assumpCT
noDampingAssump :: Sentence
noDampingAssump = String -> Sentence
S String
"No damping occurs during the simulation" Sentence -> Sentence -> Sentence
+:+. forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource ConceptInstance
assumpDI
rightHandAssump :: Sentence
rightHandAssump = String -> Sentence
S String
"A" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
rightHand Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"used" Sentence -> Sentence -> Sentence
+:+. forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource ConceptInstance
assumpAD
rigidBodyAssump :: Sentence
rigidBodyAssump = String -> Sentence
S String
"All bodies are assumed to be rigid" Sentence -> Sentence -> Sentence
+:+. forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource ConceptInstance
assumpOT
rigidTwoDAssump :: Sentence
rigidTwoDAssump = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"All bodies are assumed to be rigid",
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource ConceptInstance
assumpOT Sentence -> Sentence -> Sentence
`S.and_` forall n. NamedIdea n => n -> Sentence
phrase CI
twoD, forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource ConceptInstance
assumpOD]