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 qualified Drasil.DocLang.SRS as SRS
import Data.Drasil.Concepts.Computation (inValue, algorithm, inDatum, compcon)
import Data.Drasil.Concepts.Documentation (analysis, doccon, doccon', physics,
problem, srsDomains, assumption, goalStmt, physSyst, sysCont, software, user,
requirement, refBy, refName, typUnc, example, softwareSys, system, environment,
product_, interface, condition, physical, datum, input_, softwareConstraint,
output_, endUser)
import qualified Data.Drasil.Concepts.Documentation as Doc (srs, physics, variable)
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.Software.Products (sciCompS)
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 Data.Drasil.Concepts.Education(calculus, educon, undergraduate,
highSchoolPhysics, highSchoolCalculus)
import Drasil.Projectile.Assumptions (assumptions)
import Drasil.Projectile.Concepts (concepts, launcher, projectile, target)
import Drasil.Projectile.DataDefs (dataDefs)
import Drasil.Projectile.Figures (figLaunch, sysCtxFig1)
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. 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. NamedIdea n => n -> Sentence
phrase CI
projectileTitle)
[ [Sentence] -> IntroSub
IPurpose ([Sentence] -> IntroSub) -> [Sentence] -> IntroSub
forall a b. (a -> b) -> a -> b
$ CI -> Verbosity -> [Sentence]
purpDoc CI
projectileTitle Verbosity
Verbose
, Sentence -> IntroSub
IScope Sentence
scope
, [Sentence] -> [Sentence] -> [Sentence] -> IntroSub
IChar [] [Sentence]
charsOfReader []
, CI -> Section -> Sentence -> IntroSub
IOrgSec CI
inModel ([Contents] -> [Section] -> Section
SRS.inModel [] []) Sentence
EmptyS],
GSDSec -> DocSection
GSDSec (GSDSec -> DocSection) -> GSDSec -> DocSection
forall a b. (a -> b) -> a -> b
$
[GSDSub] -> GSDSec
GSDProg
[ [Contents] -> GSDSub
SysCntxt [Contents
sysCtxIntro, LabelledContent -> Contents
LlC LabelledContent
sysCtxFig1, Contents
sysCtxDesc, Contents
sysCtxList]
, [Contents] -> GSDSub
UsrChars [Contents
userCharacteristicsIntro]
, [Contents] -> [Section] -> GSDSub
SystCons [] []],
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
purp []
[ 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. NamedIdea n => n -> Sentence
phrase UnitalChunk
iVel Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"vector") Sentence -> Sentence -> Sentence
`S.the_ofThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
projectile,
String -> Sentence
S String
"geometric layout" Sentence -> Sentence -> Sentence
`S.the_ofThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
launcher Sentence -> Sentence -> Sentence
`S.and_` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
target]]
, 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. NamedIdea n => n -> Sentence
phrase ConceptChunk
motion, String -> Sentence
S String
"is a common" Sentence -> Sentence -> Sentence
+:+.
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
problem IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`in_` IdeaDict
physics), String -> Sentence
S String
"Therefore" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"it is useful to have a",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
program, String -> Sentence
S String
"to solve and model these types of" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
problem,
String -> Sentence
S String
"Common", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
example Sentence -> Sentence -> Sentence
`S.of_` 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),
String -> Sentence
S String
"include" Sentence -> Sentence -> Sentence
+:+. SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List [Sentence]
projectileExamples,
String -> Sentence
S String
"The document describes the program called", CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
projectileTitle,
String -> Sentence
S String
", which is based" Sentence -> Sentence -> Sentence
`S.onThe` String -> Sentence
S String
"original, manually created version of" Sentence -> Sentence -> Sentence
+:+
Reference -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Reference
externalLinkRef (String -> Sentence
S String
"Projectile")]
scope :: Sentence
scope = [Sentence] -> Sentence
foldlSent_ [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NP -> NP
NP.the (IdeaDict
analysis IdeaDict -> 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), IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem,
String -> Sentence
S String
"with", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
constAccel]
externalLinkRef :: Reference
externalLinkRef :: Reference
externalLinkRef = String -> String -> ShortName -> Reference
makeURI String
"projectileSRSLink"
String
"https://github.com/smiths/caseStudies/tree/master/CaseStudies/projectile"
(Sentence -> ShortName
shortname' (Sentence -> ShortName) -> Sentence -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"projectileSRSLink")
projectileExamples :: [Sentence]
projectileExamples :: [Sentence]
projectileExamples = [String -> Sentence
S String
"ballistics" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
problem Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (String -> Sentence
S String
"missiles" Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"bullets" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"etc."), String -> Sentence
S String
"the flight" Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"balls" Sentence -> Sentence -> Sentence
`S.in_`
String -> Sentence
S String
"various sports" Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (String -> Sentence
S String
"baseball" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"golf" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"football" Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"etc.")]
projectileTitle :: CI
projectileTitle :: CI
projectileTitle = String -> NP -> String -> [UID] -> CI
commonIdea String
"projectileTitle" (String -> NP
pn String
"Projectile") String
"Projectile" []
si :: SystemInformation
si :: SystemInformation
si = SI {
_sys :: CI
_sys = CI
projectileTitle,
_kind :: CI
_kind = CI
Doc.srs,
_authors :: People
_authors = [Person
samCrawford, Person
brooks, Person
spencerSmith],
_purpose :: [Sentence]
_purpose = [Sentence
purp],
_background :: [Sentence]
_background = [Sentence
background],
_motivation :: [Sentence]
_motivation = [Sentence
motivation],
_scope :: [Sentence]
_scope = [Sentence
scope],
_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
}
purp :: Sentence
purp :: Sentence
purp = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"predict whether a launched", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
projectile, String -> Sentence
S String
"hits its", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
target]
motivation :: Sentence
motivation :: Sentence
motivation = [Sentence] -> Sentence
foldlSent_ [ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
projectile, ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
motion, String -> Sentence
S String
"is a common" Sentence -> Sentence -> Sentence
+:+
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
problem IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`in_` IdeaDict
physics)]
background :: Sentence
background :: Sentence
background = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"Common examples of", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
projectile, ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
motion, String -> Sentence
S String
"include",
String -> Sentence
S String
"ballistics", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
problem, String -> Sentence
S String
"(missiles and bullets)" Sentence -> Sentence -> Sentence
`S.andThe` String -> Sentence
S String
"flight of the balls",
String -> Sentence
S String
"in various sports (baseball, golf, football, etc.)"]
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]
: IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw IdeaDict
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]
++
(IdeaDict -> IdeaDict) -> [IdeaDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
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]
++ [ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
algorithm] [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ [IdeaDict]
concepts [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++
[IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw IdeaDict
sciCompS] [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]
++
(IdeaDict -> IdeaDict) -> [IdeaDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
educon [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] [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (IdeaDict -> IdeaDict) -> [IdeaDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
compcon)
(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 [] [] [Reference]
allRefs
allRefs :: [Reference]
allRefs :: [Reference]
allRefs = [Reference
externalLinkRef]
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
charsOfReader :: [Sentence]
charsOfReader :: [Sentence]
charsOfReader = [IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
undergraduate Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"level 1" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
Doc.physics,
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
undergraduate Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"level 1" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
calculus]
sysCtxIntro :: Contents
sysCtxIntro :: Contents
sysCtxIntro = [Sentence] -> Contents
foldlSP
[LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
sysCtxFig1, String -> Sentence
S String
"shows the" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
sysCont,
String -> Sentence
S String
"A circle represents an entity external" Sentence -> Sentence -> Sentence
`S.toThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
software
Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
user), String -> Sentence
S String
"in this case. A rectangle represents the",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
softwareSys, String -> Sentence
S String
"itself" Sentence -> Sentence -> Sentence
+:+. Sentence -> Sentence
sParen (CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
projectileTitle),
String -> Sentence
S String
"Arrows are used to show the data flow between the", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
system
IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andIts` IdeaDict
environment)]
sysCtxDesc :: Contents
sysCtxDesc :: Contents
sysCtxDesc = [Sentence] -> Contents
foldlSPCol [String -> Sentence
S String
"The interaction between the", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
product_
IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` IdeaDict
user), String -> Sentence
S String
"is through an application programming" Sentence -> Sentence -> Sentence
+:+.
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
interface, String -> Sentence
S String
"responsibilities" Sentence -> Sentence -> Sentence
`S.the_ofTheC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
user
IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` IdeaDict
system), String -> Sentence
S String
"are as follows"]
sysCtxUsrResp :: [Sentence]
sysCtxUsrResp :: [Sentence]
sysCtxUsrResp = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent [[String -> Sentence
S String
"Provide initial", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict
condition IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofThePS`
IdeaDict
physical), String -> Sentence
S String
"state" Sentence -> Sentence -> Sentence
`S.ofThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
motion Sentence -> Sentence -> Sentence
`S.andThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
inDatum, String -> Sentence
S String
"related" Sentence -> Sentence -> Sentence
`S.toThe`
CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
projectileTitle Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"ensuring no errors" Sentence -> Sentence -> Sentence
`S.inThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
datum, String -> Sentence
S String
"entry"],
[String -> Sentence
S String
"Ensure that consistent units" Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"used for", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI IdeaDict
input_ IdeaDict
Doc.variable)],
[String -> Sentence
S String
"Ensure required", Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
SRS.assumpt ([]::[Contents]) ([]::[Section]))
(IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
software Sentence -> Sentence -> Sentence
+:+ CI -> Sentence
forall n. NamedIdea n => n -> Sentence
plural CI
assumption), String -> Sentence
S String
"are appropriate for any particular",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
input_ Sentence -> Sentence -> Sentence
`S.toThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
software]]
sysCtxSysResp :: [Sentence]
sysCtxSysResp :: [Sentence]
sysCtxSysResp = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent [[String -> Sentence
S String
"Detect data type mismatch" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"such as a string of characters",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
input_, String -> Sentence
S String
"instead of a floating point number"],
[String -> Sentence
S String
"Determine if the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
input_, String -> Sentence
S String
"satisfy the required",
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict
physical IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` IdeaDict
softwareConstraint)],
[String -> Sentence
S String
"Calculate the required", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
output_]]
sysCtxResp :: [Sentence]
sysCtxResp :: [Sentence]
sysCtxResp = (Sentence -> Sentence) -> [Sentence] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map (\Sentence
x -> Sentence
x Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"Responsibilities")
[IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
user, CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
projectileTitle]
sysCtxList :: Contents
sysCtxList :: Contents
sysCtxList = UnlabelledContent -> Contents
UlC (UnlabelledContent -> Contents) -> UnlabelledContent -> Contents
forall a b. (a -> b) -> a -> b
$ RawContent -> UnlabelledContent
ulcc (RawContent -> UnlabelledContent)
-> RawContent -> UnlabelledContent
forall a b. (a -> b) -> a -> b
$ ListType -> RawContent
Enumeration (ListType -> RawContent) -> ListType -> RawContent
forall a b. (a -> b) -> a -> b
$ [Sentence] -> [ListType] -> ListType
bulletNested [Sentence]
sysCtxResp ([ListType] -> ListType) -> [ListType] -> ListType
forall a b. (a -> b) -> a -> b
$
([Sentence] -> ListType) -> [[Sentence]] -> [ListType]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> ListType
bulletFlat [[Sentence]
sysCtxUsrResp, [Sentence]
sysCtxSysResp]
userCharacteristicsIntro :: Contents
userCharacteristicsIntro :: Contents
userCharacteristicsIntro = [Sentence] -> Contents
foldlSP
[String -> Sentence
S String
"The", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
endUser Sentence -> Sentence -> Sentence
`S.of_` CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
projectileTitle,
String -> Sentence
S String
"should have an understanding of",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
highSchoolPhysics Sentence -> Sentence -> Sentence
`S.and_` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
highSchoolCalculus]
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 String
"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
projPos, 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, ConstrConcept -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrConcept
flightDur]
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, UncertQ
flightDurUnc]
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
refBy, CI
refName, CI
thModel, CI
typUnc]