{-# LANGUAGE PostfixOperators #-}
module Drasil.GamePhysics.IMods (iMods, instModIntro) where
import Language.Drasil
import Language.Drasil.ShortHands (lJ)
import Theory.Drasil
import Utils.Drasil (weave)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S
import Drasil.GamePhysics.Assumptions (assumpDI, assumpCAJI)
import Drasil.GamePhysics.Concepts (centreMass)
import Drasil.GamePhysics.DataDefs (ctrOfMassDD, linDispDD, linVelDD, linAccDD,
angDispDD, angVelDD, angAccelDD, collisionAssump, rightHandAssump,
rigidTwoDAssump)
import Drasil.GamePhysics.Expressions
import Drasil.GamePhysics.GenDefs (accelGravityGD, impulseGD)
import Drasil.GamePhysics.Goals (linearGS, angularGS)
import Drasil.GamePhysics.TMods (newtonSL, newtonSLR)
import Drasil.GamePhysics.Unitals (accj, forcej, massA, massj, normalVect,
timeC, torquej, velA, velj, angAccj)
import Data.Drasil.TheoryConcepts (inModel)
import Data.Drasil.Concepts.Documentation (condition, goal, output_)
import Data.Drasil.Concepts.Math (equation, ode)
import Data.Drasil.Concepts.Physics (rigidBody, motion)
import Data.Drasil.Quantities.Math (orientation)
import Data.Drasil.Quantities.Physics (acceleration, angularAccel, angularVelocity,
force, gravitationalAccel, impulseS, momentOfInertia, position, time, velocity)
iMods :: [InstanceModel]
iMods :: [InstanceModel]
iMods = [InstanceModel
transMot, InstanceModel
rotMot, InstanceModel
col2D]
transMot :: InstanceModel
transMot :: InstanceModel
transMot = ModelKind Expr
-> Inputs
-> Output
-> OutputConstraints
-> Maybe Derivation
-> String
-> [Sentence]
-> InstanceModel
imNoRefs (SimpleQDef -> ModelKind Expr
forall e. QDefinition e -> ModelKind e
equationalModel' SimpleQDef
transMotQD)
[ UnitalChunk -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC UnitalChunk
velj (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
, UnitalChunk -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC UnitalChunk
time (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
, UnitalChunk -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC UnitalChunk
gravitationalAccel (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
, UnitalChunk -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC UnitalChunk
forcej (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
, UnitalChunk -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC UnitalChunk
massj (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
]
(UnitalChunk -> Output
forall q. (Quantity q, MayHaveUnit q) => q -> Output
qw UnitalChunk
accj) [] (Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
transMotDeriv)
String
"transMot" [Sentence
transMotDesc, Sentence
transMotOutputs, Sentence
rigidTwoDAssump, Sentence
noDampConsAssumps]
transMotQD :: SimpleQDef
transMotQD :: SimpleQDef
transMotQD = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
accj Expr
PExpr
transMotExpr
transMotDesc, transMotOutputs :: Sentence
transMotDesc :: Sentence
transMotDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"The above", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation, String -> Sentence
S String
"expresses the total",
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
acceleration UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofThe` ConceptChunk
rigidBody), Symbol -> Sentence
P Symbol
lJ,
String -> Sentence
S String
"as the sum" Sentence -> Sentence -> Sentence
`S.of_` UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
gravitationalAccel, GenDefn -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource GenDefn
accelGravityGD Sentence -> Sentence -> Sentence
`S.and_`
UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
acceleration, String -> Sentence
S String
"due to applied", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force, ModelExpr -> Sentence
eS (UnitalChunk -> UnitalChunk -> ModelExpr
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
forcej UnitalChunk
time) Sentence -> Sentence -> Sentence
+:+.
TheoryModel -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource TheoryModel
newtonSL, String -> Sentence
S String
"The resultant", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
output_ Sentence -> Sentence -> Sentence
`S.are`
String -> Sentence
S String
"then obtained from this", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation, String -> Sentence
S String
"using",
SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List ((DataDefinition -> Sentence) -> [DataDefinition] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS [DataDefinition
linDispDD, DataDefinition
linVelDD, DataDefinition
linAccDD])]
transMotOutputs :: Sentence
transMotOutputs = [Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict
output_ IdeaDict -> CI -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` CI
inModel),
String -> Sentence
S String
"will be the functions" Sentence -> Sentence -> Sentence
`S.of_` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
position UnitalChunk -> UnitalChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` UnitalChunk
velocity),
String -> Sentence
S String
"over time that satisfy the", CI -> Sentence
getAcc CI
ode Sentence -> Sentence -> Sentence
`S.for` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
acceleration) Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"with the given initial", (IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
condition Sentence -> Sentence -> Sentence
`S.for` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
position UnitalChunk -> UnitalChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_`
UnitalChunk
velocity) !.), NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
motion), String -> Sentence
S String
"is translational" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so the",
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
position UnitalChunk -> UnitalChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` UnitalChunk
velocity), String -> Sentence
S String
"functions are for the",
CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
centreMass, DataDefinition -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource DataDefinition
ctrOfMassDD]
transMotDeriv :: Derivation
transMotDeriv :: Derivation
transMotDeriv = Sentence -> [Sentence] -> Derivation
mkDerivName (InstanceModel -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase InstanceModel
transMot)
([[Sentence]] -> [Sentence]
forall a. [[a]] -> [a]
weave [[Sentence]
transMotDerivStmts, [Sentence]
transMotDerivEqns])
transMotDerivStmts :: [Sentence]
transMotDerivStmts :: [Sentence]
transMotDerivStmts = [
[Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"We may calculate the total acceleration" Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"rigid body",
Symbol -> Sentence
P Symbol
lJ, String -> Sentence
S String
"by calculating the derivative" Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"it's velocity with respect to time", DataDefinition -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource DataDefinition
linAccDD],
String -> Sentence
S String
"Performing the derivative, we obtain:"
]
transMotDerivEqns :: [Sentence]
transMotDerivEqns :: [Sentence]
transMotDerivEqns = (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr
forall r. (ModelExprC r, ExprC r) => r
transMotExprDeriv1, SimpleQDef -> ModelExpr
forall c. Express c => c -> ModelExpr
express SimpleQDef
transMotQD]
rotMot :: InstanceModel
rotMot :: InstanceModel
rotMot = ModelKind Expr
-> Inputs
-> Output
-> OutputConstraints
-> Maybe Derivation
-> String
-> [Sentence]
-> InstanceModel
imNoRefs (SimpleQDef -> ModelKind Expr
forall e. QDefinition e -> ModelKind e
equationalModel' SimpleQDef
rotMotQD)
[ UnitalChunk -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC UnitalChunk
angularVelocity (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
, UnitalChunk -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC UnitalChunk
time (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
, UnitalChunk -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC UnitalChunk
torquej (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
, UnitalChunk -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC UnitalChunk
momentOfInertia (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
]
(UnitalChunk -> Output
forall q. (Quantity q, MayHaveUnit q) => q -> Output
qw UnitalChunk
angAccj) [(Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)]
(Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
rotMotDeriv) String
"rotMot"
[Sentence
rotMotDesc, Sentence
rigidTwoDAssump, Sentence
rightHandAssump]
rotMotQD :: SimpleQDef
rotMotQD :: SimpleQDef
rotMotQD = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
angAccj Expr
PExpr
rotMotExpr
rotMotDesc :: Sentence
rotMotDesc :: Sentence
rotMotDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"The above", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation, String -> Sentence
S String
"for the total",
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
angularAccel UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofThe` ConceptChunk
rigidBody), Symbol -> Sentence
P Symbol
lJ Sentence -> Sentence -> Sentence
`S.is`
String -> Sentence
S String
"derived from", TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
newtonSLR Sentence -> Sentence -> Sentence
`sC` Sentence
EmptyS Sentence -> Sentence -> Sentence
`S.andThe` String -> Sentence
S String
"resultant",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
output_ Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"then obtained from this", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation, String -> Sentence
S String
"using",
SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List ((DataDefinition -> Sentence) -> [DataDefinition] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS [DataDefinition
angDispDD, DataDefinition
angVelDD, DataDefinition
angAccelDD])]
rotMotDeriv :: Derivation
rotMotDeriv :: Derivation
rotMotDeriv = Sentence -> [Sentence] -> Derivation
mkDerivName (InstanceModel -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase InstanceModel
rotMot)
([[Sentence]] -> [Sentence]
forall a. [[a]] -> [a]
weave [[Sentence]
rotMotDerivStmts, [Sentence]
rotMotDerivEqns])
rotMotDerivStmts :: [Sentence]
rotMotDerivStmts :: [Sentence]
rotMotDerivStmts = [
[Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"We may calculate the total angular acceleration" Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"rigid body",
Symbol -> Sentence
P Symbol
lJ, String -> Sentence
S String
"by calculating the derivative" Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"its angular velocity with respect to time", DataDefinition -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource DataDefinition
angAccelDD],
String -> Sentence
S String
"Performing the derivative, we obtain:"
]
rotMotDerivEqns :: [Sentence]
rotMotDerivEqns :: [Sentence]
rotMotDerivEqns = (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr
forall r. (ModelExprC r, ExprC r) => r
rotMotExprDeriv1, SimpleQDef -> ModelExpr
forall c. Express c => c -> ModelExpr
express SimpleQDef
rotMotQD]
col2D :: InstanceModel
col2D :: InstanceModel
col2D = ModelKind Expr
-> Inputs
-> Output
-> OutputConstraints
-> String
-> [Sentence]
-> InstanceModel
imNoDerivNoRefs (String -> NP -> SimpleQDef -> ModelKind Expr
forall e. String -> NP -> QDefinition e -> ModelKind e
equationalModel String
"col2DIM" NP
col2DNP SimpleQDef
col2DFD)
[UnitalChunk -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC UnitalChunk
time (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
,UnitalChunk -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC UnitalChunk
impulseS (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
,UnitalChunk -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC UnitalChunk
massA (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
,UnitalChunk -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC UnitalChunk
normalVect (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
]
(UnitalChunk -> Output
forall q. (Quantity q, MayHaveUnit q) => q -> Output
qw UnitalChunk
timeC) [(Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)] String
"col2D"
[Sentence
col2DOutputs, Sentence
rigidTwoDAssump, Sentence
rightHandAssump, Sentence
collisionAssump,
Sentence
noDampConsAssumps, Sentence
impulseNote]
col2DFD :: SimpleQDef
col2DFD :: SimpleQDef
col2DFD = UnitalChunk -> [UnitalChunk] -> Expr -> SimpleQDef
forall c i e.
(Quantity c, MayHaveUnit c, HasSpace c, Quantity i, HasSpace i) =>
c -> [i] -> e -> QDefinition e
mkFuncDefByQ UnitalChunk
velA [UnitalChunk
timeC] Expr
col2DExpr
col2DNP :: NP
col2DNP :: NP
col2DNP = String -> NP
nounPhraseSP String
"Collisions on 2D rigid bodies"
col2DExpr :: Expr
col2DExpr :: Expr
col2DExpr = UnitalChunk -> UnitalChunk -> Expr
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
velA UnitalChunk
time Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$+
((UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
impulseS Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$/ UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
massA) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
normalVect)
col2DOutputs, impulseNote :: Sentence
col2DOutputs :: Sentence
col2DOutputs = [Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict
output_ IdeaDict -> CI -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` CI
inModel),
String -> Sentence
S String
"will be the functions" Sentence -> Sentence -> Sentence
`S.of_` Sentence
vals, String -> Sentence
S String
"over time that satisfy the",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
equation, String -> Sentence
S String
"for the", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
velocity UnitalChunk -> UnitalChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` UnitalChunk
angularAccel) Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"with the given initial", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
condition, String -> Sentence
S String
"for" Sentence -> Sentence -> Sentence
+:+. Sentence
vals, NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
motion),
String -> Sentence
S String
"is translational" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so the", Sentence
vals, String -> Sentence
S String
"functions are for the",
CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
centreMass, DataDefinition -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource DataDefinition
ctrOfMassDD]
where vals :: Sentence
vals = SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List ((UnitalChunk -> Sentence) -> [UnitalChunk] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase [UnitalChunk
position, UnitalChunk
velocity,
UnitalChunk
orientation, UnitalChunk
angularAccel])
impulseNote :: Sentence
impulseNote = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
impulseS Sentence -> Sentence -> Sentence
`S.is` GenDefn -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
definedIn'' GenDefn
impulseGD
instModIntro :: Sentence
instModIntro :: Sentence
instModIntro = [Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
goal), ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
linearGS,
String -> Sentence
S String
"is met by" Sentence -> Sentence -> Sentence
+:+. (InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
transMot Sentence -> Sentence -> Sentence
`S.and_` InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
col2D),
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
goal), ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
angularGS, String -> Sentence
S String
"is met by",
InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
rotMot Sentence -> Sentence -> Sentence
`S.and_` InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
col2D]
noDampConsAssumps :: Sentence
noDampConsAssumps :: Sentence
noDampConsAssumps = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"It is currently assumed that no damping",
String -> Sentence
S String
"occurs during the simulation", ConceptInstance -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource ConceptInstance
assumpDI Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"that no",
String -> Sentence
S String
"constraints are involved", ConceptInstance -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource ConceptInstance
assumpCAJI]