module Drasil.Projectile.IMods (iMods, landPosIM, messageIM, offsetIM, timeIM) where
import Prelude hiding (cos, sin)
import Language.Drasil
import Theory.Drasil (InstanceModel, imNoDerivNoRefs, imNoRefs, qwC, equationalModelN)
import Utils.Drasil (weave)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S
import qualified Drasil.DocLang.SRS as SRS (valsOfAuxCons)
import Data.Drasil.Concepts.Documentation (value)
import Data.Drasil.Concepts.Math (constraint, equation, xAxis)
import Data.Drasil.Quantities.Math (pi_)
import Data.Drasil.Quantities.Physics (gravitationalAccelConst, iSpeed, ixPos,
ixVel, iyPos, iyVel, time, xConstAccel, xPos, yConstAccel, yPos)
import Drasil.Projectile.Assumptions (accelXZero, accelYGravity, gravAccelValue,
launchOrigin, posXDirection, targetXAxis, timeStartZero, yAxisGravity)
import Drasil.Projectile.Concepts (projectile, target)
import Drasil.Projectile.DataDefs (speedIX, speedIY)
import qualified Drasil.Projectile.Derivations as D
import qualified Drasil.Projectile.Expressions as E
import Drasil.Projectile.Figures (figLaunch)
import Drasil.Projectile.GenDefs (posVecGD)
import Drasil.Projectile.Unitals (flightDur, landPos, launAngle, launSpeed,
message, offset, targPos, tol)
iMods :: [InstanceModel]
iMods :: [InstanceModel]
iMods = [InstanceModel
timeIM, InstanceModel
landPosIM, InstanceModel
offsetIM, InstanceModel
messageIM]
timeIM :: InstanceModel
timeIM :: InstanceModel
timeIM = ModelKind Expr
-> Inputs
-> QuantityDict
-> OutputConstraints
-> Maybe Derivation
-> String
-> [Sentence]
-> InstanceModel
imNoRefs (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (String -> NP
nounPhraseSP String
"calculation of landing time") SimpleQDef
timeQD)
[ConstrConcept -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC ConstrConcept
launSpeed (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)
,ConstrConcept -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC ConstrConcept
launAngle (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, Expr -> Expr
forall r. (ExprC r, LiteralC r) => r -> r
half (Expr -> Expr) -> Expr -> Expr
forall a b. (a -> b) -> a -> b
$ DefinedQuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
pi_)]
(ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrConcept
flightDur) [(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
timeDeriv) String
"calOfLandingTime" [Sentence
angleConstraintNote, Sentence
gravitationalAccelConstNote, Sentence
timeConsNote]
timeQD :: SimpleQDef
timeQD :: SimpleQDef
timeQD = ConstrConcept -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef ConstrConcept
flightDur Expr
PExpr
E.flightDur'
timeDeriv :: Derivation
timeDeriv :: Derivation
timeDeriv = Sentence -> [Sentence] -> Derivation
mkDerivName (ConstrConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConstrConcept
flightDur) ([[Sentence]] -> [Sentence]
forall a. [[a]] -> [a]
weave [[Sentence]
timeDerivSents, (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr]
timeDerivEqns])
timeDerivSents :: [Sentence]
timeDerivSents :: [Sentence]
timeDerivSents = [Sentence
timeDerivSent1, Sentence
timeDerivSent2, Sentence
timeDerivSent3, Sentence
timeDerivSent4, Sentence
timeDerivSent5]
timeDerivSent1, timeDerivSent2, timeDerivSent3, timeDerivSent4, timeDerivSent5 :: Sentence
timeDerivSent1 :: Sentence
timeDerivSent1 = [Sentence] -> Sentence
foldlSentCol [String -> Sentence
S String
"We know that" Sentence -> Sentence -> Sentence
+:+.
SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List
[ModelExpr -> ConceptInstance -> Sentence
forall r.
(Referable r, HasShortName r) =>
ModelExpr -> r -> Sentence
eqnWSource (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
iyPos ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= ModelExpr
PExpr
E.iyPos) ConceptInstance
launchOrigin,
ModelExpr -> ConceptInstance -> Sentence
forall r.
(Referable r, HasShortName r) =>
ModelExpr -> r -> Sentence
eqnWSource (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
yConstAccel ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= ModelExpr
PExpr
E.yConstAccel) ConceptInstance
accelYGravity],
String -> Sentence
S String
"Substituting these", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
value, String -> Sentence
S String
"into the y-direction" Sentence -> Sentence -> Sentence
`S.of_`
GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
posVecGD, String -> Sentence
S String
"gives us"]
timeDerivSent2 :: Sentence
timeDerivSent2 = [Sentence] -> Sentence
foldlSentCol [String -> Sentence
S String
"To find the", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
time, String -> Sentence
S String
"that the",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
projectile, String -> Sentence
S String
"lands" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"we want to find the", UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
time, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
value,
Sentence -> Sentence
sParen (ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
flightDur), String -> Sentence
S String
"where", ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
yPos ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) Sentence -> Sentence -> Sentence
+:+. Sentence -> Sentence
sParen (String -> Sentence
S String
"since the" Sentence -> Sentence -> Sentence
+:+
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
target Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"on the" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
xAxis Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"from" Sentence -> Sentence -> Sentence
+:+ ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
targetXAxis),
String -> Sentence
S String
"From the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation, String -> Sentence
S String
"above we get"]
timeDerivSent3 :: Sentence
timeDerivSent3 = [Sentence] -> Sentence
foldlSentCol [String -> Sentence
S String
"Dividing by", ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
flightDur,
Sentence -> Sentence
sParen (String -> Sentence
S String
"with the" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
constraint Sentence -> Sentence -> Sentence
+:+ ModelExpr -> Sentence
eS (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
flightDur ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$> Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)),
String -> Sentence
S String
"gives us"]
timeDerivSent4 :: Sentence
timeDerivSent4 = String -> Sentence
S String
"Solving for" Sentence -> Sentence -> Sentence
+:+ ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
flightDur Sentence -> Sentence -> Sentence
+: String -> Sentence
S String
"gives us"
timeDerivSent5 :: Sentence
timeDerivSent5 = [Sentence] -> Sentence
foldlSentCol [String -> Sentence
S String
"From", DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
speedIY,
Sentence -> Sentence
sParen (String -> Sentence
S String
"with" Sentence -> Sentence -> Sentence
+:+ ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
iSpeed ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= ModelExpr
PExpr
E.iSpeed)), String -> Sentence
S String
"we can replace", UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
iyVel]
timeDerivEqns :: [ModelExpr]
timeDerivEqns :: [ModelExpr]
timeDerivEqns = [ModelExpr]
D.timeDeriv [ModelExpr] -> [ModelExpr] -> [ModelExpr]
forall a. [a] -> [a] -> [a]
++ [SimpleQDef -> ModelExpr
forall c. Express c => c -> ModelExpr
express SimpleQDef
timeQD]
landPosIM :: InstanceModel
landPosIM :: InstanceModel
landPosIM = ModelKind Expr
-> Inputs
-> QuantityDict
-> OutputConstraints
-> Maybe Derivation
-> String
-> [Sentence]
-> InstanceModel
imNoRefs (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (String -> NP
nounPhraseSP String
"calculation of landing position") SimpleQDef
landPosQD)
[ConstrConcept -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC ConstrConcept
launSpeed (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),
ConstrConcept -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC ConstrConcept
launAngle (RealInterval Expr Expr -> Input)
-> RealInterval Expr Expr -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, Expr -> Expr
forall r. (ExprC r, LiteralC r) => r -> r
half (Expr -> Expr) -> Expr -> Expr
forall a b. (a -> b) -> a -> b
$ DefinedQuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
pi_)]
(ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrConcept
landPos) [(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
landPosDeriv) String
"calOfLandingDist" [Sentence
angleConstraintNote, Sentence
gravitationalAccelConstNote, Sentence
landPosConsNote]
landPosQD :: SimpleQDef
landPosQD :: SimpleQDef
landPosQD = ConstrConcept -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef ConstrConcept
landPos Expr
PExpr
E.landPosExpr
landPosDeriv :: Derivation
landPosDeriv :: Derivation
landPosDeriv = Sentence -> [Sentence] -> Derivation
mkDerivName (ConstrConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConstrConcept
landPos) ([[Sentence]] -> [Sentence]
forall a. [[a]] -> [a]
weave [[Sentence]
landPosDerivSents, (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr]
landPosDerivEqns])
landPosDerivSents :: [Sentence]
landPosDerivSents :: [Sentence]
landPosDerivSents = [Sentence
landPosDerivSent1, Sentence
landPosDerivSent2, Sentence
landPosDerivSent3, Sentence
landPosDerivSent4]
landPosDerivSent1, landPosDerivSent2, landPosDerivSent3, landPosDerivSent4 :: Sentence
landPosDerivSent1 :: Sentence
landPosDerivSent1 = [Sentence] -> Sentence
foldlSentCol [String -> Sentence
S String
"We know that" Sentence -> Sentence -> Sentence
+:+.
SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List
[ModelExpr -> ConceptInstance -> Sentence
forall r.
(Referable r, HasShortName r) =>
ModelExpr -> r -> Sentence
eqnWSource (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
ixPos ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) ConceptInstance
launchOrigin,
ModelExpr -> ConceptInstance -> Sentence
forall r.
(Referable r, HasShortName r) =>
ModelExpr -> r -> Sentence
eqnWSource (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
xConstAccel ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) ConceptInstance
accelXZero],
String -> Sentence
S String
"Substituting these", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
value, String -> Sentence
S String
"into the x-direction" Sentence -> Sentence -> Sentence
`S.of_`
GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
posVecGD, String -> Sentence
S String
"gives us"]
landPosDerivSent2 :: Sentence
landPosDerivSent2 = [Sentence] -> Sentence
foldlSentCol [String -> Sentence
S String
"To find the", ConstrConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConstrConcept
landPos Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"we want to find the", UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
xPos, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
value, Sentence -> Sentence
sParen (ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
landPos),
String -> Sentence
S String
"at", ConstrConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConstrConcept
flightDur, InstanceModel -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource InstanceModel
timeIM]
landPosDerivSent3 :: Sentence
landPosDerivSent3 = [Sentence] -> Sentence
foldlSentCol [String -> Sentence
S String
"From", DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
speedIX,
Sentence -> Sentence
sParen (String -> Sentence
S String
"with" Sentence -> Sentence -> Sentence
+:+ ModelExpr -> Sentence
E (ModelExpr -> ModelExpr -> ModelExpr
forall r. ModelExprC r => r -> r -> r
defines (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
iSpeed) (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
launSpeed))), String -> Sentence
S String
"we can replace", UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
ixVel]
landPosDerivSent4 :: Sentence
landPosDerivSent4 = String -> Sentence
S String
"Rearranging this gives us the required" Sentence -> Sentence -> Sentence
+: ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation
landPosDerivEqns :: [ModelExpr]
landPosDerivEqns :: [ModelExpr]
landPosDerivEqns = [ModelExpr]
D.landPosDeriv [ModelExpr] -> [ModelExpr] -> [ModelExpr]
forall a. [a] -> [a] -> [a]
++ [SimpleQDef -> ModelExpr
forall c. Express c => c -> ModelExpr
express SimpleQDef
landPosQD]
offsetIM :: InstanceModel
offsetIM :: InstanceModel
offsetIM = ModelKind Expr
-> Inputs
-> QuantityDict
-> OutputConstraints
-> String
-> [Sentence]
-> InstanceModel
imNoDerivNoRefs (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (String -> NP
nounPhraseSP String
"offset") SimpleQDef
offsetQD)
[ConstrConcept -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC ConstrConcept
landPos (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)
,ConstrConcept -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC ConstrConcept
targPos (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)]
(ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrConcept
offset) [] String
"offsetIM" [Sentence
landPosNote, Sentence
landAndTargPosConsNote]
offsetQD :: SimpleQDef
offsetQD :: SimpleQDef
offsetQD = ConstrConcept -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef ConstrConcept
offset Expr
PExpr
E.offset'
messageIM :: InstanceModel
messageIM :: InstanceModel
messageIM = ModelKind Expr
-> Inputs
-> QuantityDict
-> OutputConstraints
-> String
-> [Sentence]
-> InstanceModel
imNoDerivNoRefs (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (String -> NP
nounPhraseSP String
"output message") SimpleQDef
messageQD)
[ConstrConcept -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC ConstrConcept
offset (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, Expr -> Expr
forall r. ExprC r => r -> r
neg (ConstrConcept -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
targPos))
,ConstrConcept -> RealInterval Expr Expr -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Expr Expr -> Input
qwC ConstrConcept
targPos (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)]
(QuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw QuantityDict
message)
[] String
"messageIM" [Sentence
offsetNote, Sentence
targPosConsNote, Sentence
offsetConsNote, Sentence
tolNote]
messageQD :: SimpleQDef
messageQD :: SimpleQDef
messageQD = QuantityDict -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef QuantityDict
message Expr
PExpr
E.message
angleConstraintNote, gravitationalAccelConstNote, landAndTargPosConsNote, landPosNote,
landPosConsNote, offsetNote, offsetConsNote, targPosConsNote,
timeConsNote, tolNote :: Sentence
angleConstraintNote :: Sentence
angleConstraintNote = [Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
constraint),
ModelExpr -> Sentence
eS (ConstrConcept -> RealInterval ModelExpr ModelExpr -> ModelExpr
forall c.
HasUID c =>
c -> RealInterval ModelExpr ModelExpr -> ModelExpr
forall r c. (ExprC r, HasUID c) => c -> RealInterval r r -> r
realInterval ConstrConcept
launAngle ((Inclusive, ModelExpr)
-> (Inclusive, ModelExpr) -> RealInterval ModelExpr ModelExpr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, ModelExpr -> ModelExpr
forall r. (ExprC r, LiteralC r) => r -> r
half (ModelExpr -> ModelExpr) -> ModelExpr -> ModelExpr
forall a b. (a -> b) -> a -> b
$ DefinedQuantityDict -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
pi_))) Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"from",
ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
posXDirection Sentence -> Sentence -> Sentence
`S.and_` ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
yAxisGravity Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"and is shown" Sentence -> Sentence -> Sentence
`S.in_` LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
figLaunch]
gravitationalAccelConstNote :: Sentence
gravitationalAccelConstNote = ConstQDef -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstQDef
gravitationalAccelConst Sentence -> Sentence -> Sentence
`S.is`
String -> Sentence
S String
"defined in" Sentence -> Sentence -> Sentence
+:+. ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
gravAccelValue
landAndTargPosConsNote :: Sentence
landAndTargPosConsNote = NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
constraint) Sentence -> Sentence -> Sentence
+:+
ModelExpr -> Sentence
eS (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
landPos ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$> Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) Sentence -> Sentence -> Sentence
`S.and_` ModelExpr -> Sentence
eS (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
targPos ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$> Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"from" Sentence -> Sentence -> Sentence
+:+. ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
posXDirection
landPosNote :: Sentence
landPosNote = ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
landPos Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"from" Sentence -> Sentence -> Sentence
+:+. InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
landPosIM
landPosConsNote :: Sentence
landPosConsNote = NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
constraint) Sentence -> Sentence -> Sentence
+:+
ModelExpr -> Sentence
eS (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
landPos ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$> Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"from" Sentence -> Sentence -> Sentence
+:+. ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
posXDirection
offsetNote :: Sentence
offsetNote = ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
offset Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"from" Sentence -> Sentence -> Sentence
+:+. InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
offsetIM
offsetConsNote :: Sentence
offsetConsNote = [Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
constraint), ModelExpr -> Sentence
eS (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
offset ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r
neg (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
targPos)) Sentence -> Sentence -> Sentence
`S.is`
String -> Sentence
S String
"from the fact that", ModelExpr -> Sentence
eS (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
landPos ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$> Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"from", ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
posXDirection]
targPosConsNote :: Sentence
targPosConsNote = NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
constraint) Sentence -> Sentence -> Sentence
+:+
ModelExpr -> Sentence
eS (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
targPos ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$> Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"from" Sentence -> Sentence -> Sentence
+:+. ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
posXDirection
timeConsNote :: Sentence
timeConsNote = NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
constraint) Sentence -> Sentence -> Sentence
+:+
ModelExpr -> Sentence
eS (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
flightDur ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$> Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"from" Sentence -> Sentence -> Sentence
+:+. ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
timeStartZero
tolNote :: Sentence
tolNote = ConstQDef -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstQDef
tol Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"defined in" Sentence -> Sentence -> Sentence
+:+. Section -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ([Contents] -> [Section] -> Section
SRS.valsOfAuxCons ([]::[Contents]) ([]::[Section]))