module Drasil.Projectile.Body (printSetting, si, srs, projectileTitle, fullSI) where
import Language.Drasil
import Drasil.SRSDocument
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.NounPhrase.Combinators as NP
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.Concepts.Computation (inValue)
import Data.Drasil.Concepts.Documentation (analysis, doccon, doccon', physics,
problem, srsDomains, assumption, goalStmt, physSyst,
requirement, typUnc)
import qualified Data.Drasil.Concepts.Documentation as Doc (srs)
import Data.Drasil.Concepts.Math (cartesian, mathcon)
import Data.Drasil.Concepts.PhysicalProperties (mass)
import Data.Drasil.Concepts.Physics (gravity, physicCon, physicCon',
rectilinear, oneD, twoD, motion)
import Data.Drasil.Concepts.Software (errMsg, program)
import Data.Drasil.Quantities.Math (pi_, piConst)
import Data.Drasil.Quantities.Physics (acceleration, constAccel,
gravitationalAccelConst, iPos, iSpeed, iVel, ixPos, iyPos, ixVel, iyVel,
position, scalarPos, time, velocity, xAccel, xConstAccel, xPos,
xVel, yAccel, yConstAccel, yPos, yVel, physicscon)
import Data.Drasil.People (brooks, samCrawford, spencerSmith)
import Data.Drasil.SI_Units (metre, radian, second)
import Data.Drasil.Theories.Physics (accelerationTM, velocityTM)
import Data.Drasil.TheoryConcepts (dataDefn, genDefn, inModel, thModel)
import Drasil.Projectile.Assumptions (assumptions)
import Drasil.Projectile.Concepts (concepts, landingPosNC,
launcher, projectile, target)
import Drasil.Projectile.DataDefs (dataDefs)
import Drasil.Projectile.Figures (figLaunch)
import Drasil.Projectile.GenDefs (genDefns)
import Drasil.Projectile.Goals (goals)
import Drasil.Projectile.IMods (iMods)
import Drasil.Projectile.References (citations)
import Drasil.Projectile.Requirements (funcReqs, nonfuncReqs)
import Drasil.Projectile.Unitals
import Theory.Drasil (TheoryModel)
srs :: Document
srs :: Document
srs = SRSDecl
-> (IdeaDict -> IdeaDict -> Sentence)
-> SystemInformation
-> Document
mkDoc SRSDecl
mkSRS ((IdeaDict -> Sentence)
-> (IdeaDict -> Sentence) -> IdeaDict -> IdeaDict -> Sentence
forall c d.
(c -> Sentence) -> (d -> Sentence) -> c -> d -> Sentence
S.forGen IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize IdeaDict -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase) SystemInformation
si
fullSI :: SystemInformation
fullSI :: SystemInformation
fullSI = SRSDecl -> SystemInformation -> SystemInformation
fillcdbSRS SRSDecl
mkSRS SystemInformation
si
printSetting :: PrintingInformation
printSetting :: PrintingInformation
printSetting = SystemInformation
-> Stage -> PrintingConfiguration -> PrintingInformation
piSys SystemInformation
fullSI Stage
Equational PrintingConfiguration
defaultConfiguration
mkSRS :: SRSDecl
mkSRS :: SRSDecl
mkSRS = [DocSection
TableOfContents,
RefSec -> DocSection
RefSec (RefSec -> DocSection) -> RefSec -> DocSection
forall a b. (a -> b) -> a -> b
$
Contents -> [RefTab] -> RefSec
RefProg Contents
intro
[ RefTab
TUnits
, [TSIntro] -> RefTab
tsymb [TSIntro
TSPurpose, [TConvention] -> TSIntro
TypogConvention [Emphasis -> TConvention
Vector Emphasis
Bold], TSIntro
SymbOrder, TSIntro
VectorUnits]
, RefTab
TAandA
],
IntroSec -> DocSection
IntroSec (IntroSec -> DocSection) -> IntroSec -> DocSection
forall a b. (a -> b) -> a -> b
$
Sentence -> Sentence -> [IntroSub] -> IntroSec
IntroProg Sentence
justification (CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase CI
projectileTitle)
[ Sentence -> IntroSub
IScope Sentence
scope ],
SSDSec -> DocSection
SSDSec (SSDSec -> DocSection) -> SSDSec -> DocSection
forall a b. (a -> b) -> a -> b
$
[SSDSub] -> SSDSec
SSDProg
[ ProblemDescription -> SSDSub
SSDProblem (ProblemDescription -> SSDSub) -> ProblemDescription -> SSDSub
forall a b. (a -> b) -> a -> b
$ Sentence -> [Section] -> [PDSub] -> ProblemDescription
PDProg Sentence
prob []
[ Maybe Sentence -> [ConceptChunk] -> PDSub
forall c. Concept c => Maybe Sentence -> [c] -> PDSub
TermsAndDefs Maybe Sentence
forall a. Maybe a
Nothing [ConceptChunk]
terms
, CI -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
forall a.
Idea a =>
a -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
PhySysDesc CI
projectileTitle [Sentence]
physSystParts LabelledContent
figLaunch []
, [Sentence] -> PDSub
Goals [(UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
iVel Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "vector") Sentence -> Sentence -> Sentence
`S.the_ofThe` ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
projectile]]
, SolChSpec -> SSDSub
SSDSolChSpec (SolChSpec -> SSDSub) -> SolChSpec -> SSDSub
forall a b. (a -> b) -> a -> b
$ [SCSSub] -> SolChSpec
SCSProg
[ SCSSub
Assumptions
, [Sentence] -> Fields -> SCSSub
TMs [] (Field
Label Field -> Fields -> Fields
forall a. a -> [a] -> [a]
: Fields
stdFields)
, [Sentence] -> Fields -> DerivationDisplay -> SCSSub
GDs [] ([Field
Label, Field
Units] Fields -> Fields -> Fields
forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation
, [Sentence] -> Fields -> DerivationDisplay -> SCSSub
DDs [] ([Field
Label, Field
Symbol, Field
Units] Fields -> Fields -> Fields
forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation
, [Sentence] -> Fields -> DerivationDisplay -> SCSSub
IMs [] ([Field
Label, Field
Input, Field
Output, Field
InConstraints, Field
OutConstraints] Fields -> Fields -> Fields
forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation
, Sentence -> [UncertQ] -> SCSSub
forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
Sentence -> [c] -> SCSSub
Constraints Sentence
EmptyS [UncertQ]
inConstraints
, [UncertQ] -> [Contents] -> SCSSub
forall c.
(Quantity c, Constrained c) =>
[c] -> [Contents] -> SCSSub
CorrSolnPpties [UncertQ]
outConstraints []
]
],
ReqrmntSec -> DocSection
ReqrmntSec (ReqrmntSec -> DocSection) -> ReqrmntSec -> DocSection
forall a b. (a -> b) -> a -> b
$
[ReqsSub] -> ReqrmntSec
ReqsProg
[ Sentence -> [LabelledContent] -> ReqsSub
FReqsSub Sentence
EmptyS []
, ReqsSub
NonFReqsSub
],
TraceabilitySec -> DocSection
TraceabilitySec (TraceabilitySec -> DocSection) -> TraceabilitySec -> DocSection
forall a b. (a -> b) -> a -> b
$ [TraceConfig] -> TraceabilitySec
TraceabilityProg ([TraceConfig] -> TraceabilitySec)
-> [TraceConfig] -> TraceabilitySec
forall a b. (a -> b) -> a -> b
$ SystemInformation -> [TraceConfig]
traceMatStandard SystemInformation
si,
AuxConstntSec -> DocSection
AuxConstntSec (AuxConstntSec -> DocSection) -> AuxConstntSec -> DocSection
forall a b. (a -> b) -> a -> b
$
CI -> [ConstQDef] -> AuxConstntSec
AuxConsProg CI
projectileTitle [ConstQDef]
constants,
DocSection
Bibliography
]
justification, scope :: Sentence
justification :: Sentence
justification = [Sentence] -> Sentence
foldlSent [ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart ConceptChunk
projectile, ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
motion, String -> Sentence
S "is a common" Sentence -> Sentence -> Sentence
+:+.
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk
problem NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`in_` NamedChunk
physics), String -> Sentence
S "Therefore, it is useful to have a",
ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
program, String -> Sentence
S "to solve and model these types of" Sentence -> Sentence -> Sentence
+:+. NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
problem,
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
program), String -> Sentence
S "documented here is called", CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase CI
projectileTitle]
scope :: Sentence
scope = [Sentence] -> Sentence
foldlSent_ [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NP -> NP
NP.the (NamedChunk
analysis NamedChunk -> CI -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofA` CI
twoD)),
Sentence -> Sentence
sParen (CI -> Sentence
getAcc CI
twoD), NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI ConceptChunk
projectile ConceptChunk
motion), NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
problem, String -> Sentence
S "with",
UnitalChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitalChunk
constAccel]
projectileTitle :: CI
projectileTitle :: CI
projectileTitle = String -> NP -> String -> [UID] -> CI
commonIdea "projectileTitle" (String -> NP
pn "Projectile") "Projectile" []
si :: SystemInformation
si :: SystemInformation
si = SI :: forall a b c e f h i j d.
(CommonIdea a, Idea a, Idea b, HasName c, Quantity e, Eq e,
MayHaveUnit e, Quantity f, MayHaveUnit f, Concept f, Eq f,
Quantity h, MayHaveUnit h, Quantity i, MayHaveUnit i, HasUID j,
Constrained j) =>
a
-> b
-> [c]
-> d
-> [e]
-> [f]
-> [InstanceModel]
-> [DataDefinition]
-> [String]
-> [h]
-> [i]
-> [Block SimpleQDef]
-> [j]
-> [ConstQDef]
-> ChunkDB
-> ChunkDB
-> ReferenceDB
-> SystemInformation
SI {
_sys :: CI
_sys = CI
projectileTitle,
_kind :: CI
_kind = CI
Doc.srs,
_authors :: [Person]
_authors = [Person
samCrawford, Person
brooks, Person
spencerSmith],
_purpose :: [Any]
_purpose = [],
_quants :: [QuantityDict]
_quants = [QuantityDict]
symbols,
_concepts :: [DefinedQuantityDict]
_concepts = [] :: [DefinedQuantityDict],
_instModels :: [InstanceModel]
_instModels = [InstanceModel]
iMods,
_datadefs :: [DataDefinition]
_datadefs = [DataDefinition]
dataDefs,
_configFiles :: [String]
_configFiles = [],
_inputs :: [QuantityDict]
_inputs = [QuantityDict]
inputs,
_outputs :: [QuantityDict]
_outputs = [QuantityDict]
outputs,
_defSequence :: [Block SimpleQDef]
_defSequence = [] :: [Block SimpleQDef],
_constraints :: [ConstrainedChunk]
_constraints = (ConstrConcept -> ConstrainedChunk)
-> [ConstrConcept] -> [ConstrainedChunk]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> ConstrainedChunk
forall c.
(Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) =>
c -> ConstrainedChunk
cnstrw [ConstrConcept]
constrained,
_constants :: [ConstQDef]
_constants = [ConstQDef]
constants,
_sysinfodb :: ChunkDB
_sysinfodb = ChunkDB
symbMap,
_usedinfodb :: ChunkDB
_usedinfodb = ChunkDB
usedDB,
refdb :: ReferenceDB
refdb = ReferenceDB
refDB
}
tMods :: [TheoryModel]
tMods :: [TheoryModel]
tMods = [TheoryModel
accelerationTM, TheoryModel
velocityTM]
symbMap :: ChunkDB
symbMap :: ChunkDB
symbMap = [QuantityDict]
-> [IdeaDict]
-> [ConceptChunk]
-> [UnitDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Section]
-> [LabelledContent]
-> [Reference]
-> ChunkDB
forall q t c u.
(Quantity q, MayHaveUnit q, Idea t, Concept c, IsUnit u) =>
[q]
-> [t]
-> [c]
-> [u]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Section]
-> [LabelledContent]
-> [Reference]
-> ChunkDB
cdb (DefinedQuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw DefinedQuantityDict
pi_ QuantityDict -> [QuantityDict] -> [QuantityDict]
forall a. a -> [a] -> [a]
: (UnitalChunk -> QuantityDict) -> [UnitalChunk] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [UnitalChunk]
physicscon [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ [QuantityDict]
unitalQuants [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ [QuantityDict]
symbols)
(CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
projectileTitle IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
mass IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw NamedChunk
inValue IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: [ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
errMsg, ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
program] [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++
(NamedChunk -> IdeaDict) -> [NamedChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [NamedChunk]
doccon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
doccon' [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
physicCon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
physicCon' [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++
(UnitalChunk -> IdeaDict) -> [UnitalChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [UnitalChunk]
physicscon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
mathcon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ [IdeaDict]
concepts [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ [IdeaDict]
unitalIdeas [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++
(CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
acronyms [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (QuantityDict -> IdeaDict) -> [QuantityDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map QuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [QuantityDict]
symbols [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (UnitDefn -> IdeaDict) -> [UnitDefn] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [UnitDefn
metre, UnitDefn
radian, UnitDefn
second]) (DefinedQuantityDict -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw DefinedQuantityDict
pi_ ConceptChunk -> [ConceptChunk] -> [ConceptChunk]
forall a. a -> [a] -> [a]
: (ConstrConcept -> ConceptChunk)
-> [ConstrConcept] -> [ConceptChunk]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw [ConstrConcept]
constrained [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
srsDomains)
((UnitDefn -> UnitDefn) -> [UnitDefn] -> [UnitDefn]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> UnitDefn
forall u. IsUnit u => u -> UnitDefn
unitWrapper [UnitDefn
metre, UnitDefn
radian, UnitDefn
second]) [DataDefinition]
dataDefs [InstanceModel]
iMods [GenDefn]
genDefns [TheoryModel]
tMods [ConceptInstance]
concIns [] [] []
usedDB :: ChunkDB
usedDB :: ChunkDB
usedDB = [QuantityDict]
-> [IdeaDict]
-> [ConceptChunk]
-> [UnitDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Section]
-> [LabelledContent]
-> [Reference]
-> ChunkDB
forall q t c u.
(Quantity q, MayHaveUnit q, Idea t, Concept c, IsUnit u) =>
[q]
-> [t]
-> [c]
-> [u]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Section]
-> [LabelledContent]
-> [Reference]
-> ChunkDB
cdb ([] :: [QuantityDict]) (DefinedQuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw DefinedQuantityDict
pi_ IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: (CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
acronyms [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (QuantityDict -> IdeaDict) -> [QuantityDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map QuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [QuantityDict]
symbols)
(DefinedQuantityDict -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw DefinedQuantityDict
pi_ ConceptChunk -> [ConceptChunk] -> [ConceptChunk]
forall a. a -> [a] -> [a]
: [ConceptChunk]
srsDomains) ([] :: [UnitDefn]) [] [] [] [] [] [] [] ([] :: [Reference])
stdFields :: Fields
stdFields :: Fields
stdFields = [Field
DefiningEquation, Verbosity -> InclUnits -> Field
Description Verbosity
Verbose InclUnits
IncludeUnits, Field
Notes, Field
Source, Field
RefBy]
refDB :: ReferenceDB
refDB :: ReferenceDB
refDB = BibRef -> [ConceptInstance] -> ReferenceDB
rdb BibRef
citations [ConceptInstance]
concIns
concIns :: [ConceptInstance]
concIns :: [ConceptInstance]
concIns = [ConceptInstance]
assumptions [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
funcReqs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
goals [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
nonfuncReqs
prob :: Sentence
prob :: Sentence
prob = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S "efficiently" Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S "correctly predict the",
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk
landingPosNC NamedChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofA` ConceptChunk
projectile)]
terms :: [ConceptChunk]
terms :: [ConceptChunk]
terms = [ConceptChunk
launcher, ConceptChunk
projectile, ConceptChunk
target, ConceptChunk
gravity, ConceptChunk
cartesian, ConceptChunk
rectilinear]
physSystParts :: [Sentence]
physSystParts :: [Sentence]
physSystParts = (Sentence -> Sentence) -> [Sentence] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map Sentence -> Sentence
(!.)
[NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
launcher),
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
projectile) Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (String -> Sentence
S "with" Sentence -> Sentence -> Sentence
+:+ UnitalChunk -> Sentence
forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
iVel Sentence -> Sentence -> Sentence
`S.and_` ConstrConcept -> Sentence
forall a. Quantity a => a -> Sentence
getTandS ConstrConcept
launAngle),
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
target)]
symbols :: [QuantityDict]
symbols :: [QuantityDict]
symbols = ConstQDef -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstQDef
gravitationalAccelConst QuantityDict -> [QuantityDict] -> [QuantityDict]
forall a. a -> [a] -> [a]
: [QuantityDict]
unitalQuants [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ (ConstQDef -> QuantityDict) -> [ConstQDef] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstQDef -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [ConstQDef]
constants [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++
(UnitalChunk -> QuantityDict) -> [UnitalChunk] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [UnitalChunk
acceleration, UnitalChunk
constAccel, UnitalChunk
iPos, UnitalChunk
iSpeed, UnitalChunk
iVel, UnitalChunk
ixPos,
UnitalChunk
iyPos, UnitalChunk
ixVel, UnitalChunk
iyVel, UnitalChunk
position, UnitalChunk
scalarPos, UnitalChunk
projSpeed, UnitalChunk
time, UnitalChunk
velocity, UnitalChunk
xAccel,
UnitalChunk
xConstAccel, UnitalChunk
xPos, UnitalChunk
xVel, UnitalChunk
yAccel, UnitalChunk
yConstAccel, UnitalChunk
yPos, UnitalChunk
yVel]
constants :: [ConstQDef]
constants :: [ConstQDef]
constants = [ConstQDef
gravitationalAccelConst, ConstQDef
piConst, ConstQDef
tol]
inputs :: [QuantityDict]
inputs :: [QuantityDict]
inputs = (ConstrConcept -> QuantityDict)
-> [ConstrConcept] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [ConstrConcept
launSpeed, ConstrConcept
launAngle, ConstrConcept
targPos]
outputs :: [QuantityDict]
outputs :: [QuantityDict]
outputs = [QuantityDict
message, ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrConcept
offset]
unitalQuants :: [QuantityDict]
unitalQuants :: [QuantityDict]
unitalQuants = QuantityDict
message QuantityDict -> [QuantityDict] -> [QuantityDict]
forall a. a -> [a] -> [a]
: (ConstrConcept -> QuantityDict)
-> [ConstrConcept] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [ConstrConcept]
constrained
unitalIdeas :: [IdeaDict]
unitalIdeas :: [IdeaDict]
unitalIdeas = QuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw QuantityDict
message IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: (ConstrConcept -> IdeaDict) -> [ConstrConcept] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConstrConcept]
constrained
inConstraints :: [UncertQ]
inConstraints :: [UncertQ]
inConstraints = [UncertQ
launAngleUnc, UncertQ
launSpeedUnc, UncertQ
targPosUnc]
outConstraints :: [UncertQ]
outConstraints :: [UncertQ]
outConstraints = [UncertQ
landPosUnc, UncertQ
offsetUnc]
constrained :: [ConstrConcept]
constrained :: [ConstrConcept]
constrained = [ConstrConcept
flightDur, ConstrConcept
landPos, ConstrConcept
launAngle, ConstrConcept
launSpeed, ConstrConcept
offset, ConstrConcept
targPos]
acronyms :: [CI]
acronyms :: [CI]
acronyms = [CI
oneD, CI
twoD, CI
assumption, CI
dataDefn, CI
genDefn, CI
goalStmt, CI
inModel,
CI
physSyst, CI
requirement, CI
Doc.srs, CI
thModel, CI
typUnc]