{-# LANGUAGE PostfixOperators #-}
module Drasil.DblPend.Body where
import Control.Lens ((^.))
import Language.Drasil hiding (organization, section)
import Theory.Drasil (TheoryModel, output)
import Drasil.SRSDocument
import qualified Drasil.DocLang.SRS as SRS
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.People (dong)
import Data.Drasil.SI_Units (metre, second, newton, kilogram, degree, radian, hertz)
import Data.Drasil.Concepts.Computation (inDatum, compcon, inValue, algorithm)
import qualified Data.Drasil.Concepts.Documentation as Doc (srs, physics, variable)
import Data.Drasil.Concepts.Documentation (assumption, condition, endUser,
environment, datum, input_, interface, output_, problem, product_,
physical, sysCont, software, softwareConstraint, softwareSys, srsDomains,
system, user, doccon, doccon', analysis)
import Data.Drasil.Concepts.Education (highSchoolPhysics, highSchoolCalculus, calculus, undergraduate, educon, )
import Data.Drasil.Concepts.Math (mathcon, cartesian, ode, mathcon', graph)
import Data.Drasil.Concepts.Physics (gravity, physicCon, physicCon', pendulum, twoD, motion)
import Data.Drasil.Concepts.PhysicalProperties (mass, len, physicalcon)
import Data.Drasil.Concepts.Software (program, errMsg)
import Data.Drasil.Quantities.Physics (physicscon)
import Data.Drasil.Quantities.Math (unitVect, unitVectj)
import Data.Drasil.Software.Products (prodtcon)
import Data.Drasil.Theories.Physics (newtonSL, accelerationTM, velocityTM, newtonSLR)
import Data.Drasil.TheoryConcepts (inModel)
import Drasil.DblPend.Figures (figMotion, sysCtxFig1)
import Drasil.DblPend.Assumptions (assumpDouble)
import Drasil.DblPend.Concepts (rod, concepts, pendMotion, progName, firstRod, secondRod, firstObject, secondObject)
import Drasil.DblPend.Goals (goals, goalsInputs)
import Drasil.DblPend.DataDefs (dataDefs)
import Drasil.DblPend.IMods (iMods)
import Drasil.DblPend.GenDefs (genDefns)
import Drasil.DblPend.Unitals (lenRod_1, lenRod_2, symbols, inputs, outputs,
inConstraints, outConstraints, acronyms, pendDisAngle, constants)
import Drasil.DblPend.Requirements (funcReqs, nonFuncReqs)
import Drasil.DblPend.References (citations)
import Data.Drasil.ExternalLibraries.ODELibraries (scipyODESymbols,
osloSymbols, apacheODESymbols, odeintSymbols, arrayVecDepVar)
import Language.Drasil.Code (quantvar)
import Drasil.DblPend.ODEs (dblPenODEInfo)
srs :: Document
srs :: Document
srs = SRSDecl
-> (IdeaDict -> IdeaDict -> Sentence)
-> SystemInformation
-> Document
mkDoc SRSDecl
mkSRS (forall c d.
(c -> Sentence) -> (d -> Sentence) -> c -> d -> Sentence
S.forGen forall n. NamedIdea n => n -> Sentence
titleize 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 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 forall a b. (a -> b) -> a -> b
$
Sentence -> Sentence -> [IntroSub] -> IntroSec
IntroProg (CI -> Sentence
justification CI
progName) (forall n. NamedIdea n => n -> Sentence
phrase CI
progName)
[[Sentence] -> IntroSub
IPurpose forall a b. (a -> b) -> a -> b
$ CI -> Verbosity -> [Sentence]
purpDoc CI
progName 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 forall a b. (a -> b) -> a -> b
$
[GSDSub] -> GSDSec
GSDProg [
[Contents] -> GSDSub
SysCntxt [CI -> Contents
sysCtxIntro CI
progName, LabelledContent -> Contents
LlC LabelledContent
sysCtxFig1, Contents
sysCtxDesc, CI -> Contents
sysCtxList CI
progName],
[Contents] -> GSDSub
UsrChars [CI -> Contents
userCharacteristicsIntro CI
progName],
[Contents] -> [Section] -> GSDSub
SystCons [] []],
SSDSec -> DocSection
SSDSec forall a b. (a -> b) -> a -> b
$
[SSDSub] -> SSDSec
SSDProg
[ ProblemDescription -> SSDSub
SSDProblem forall a b. (a -> b) -> a -> b
$ Sentence -> [Section] -> [PDSub] -> ProblemDescription
PDProg Sentence
purp []
[ forall c. Concept c => Maybe Sentence -> [c] -> PDSub
TermsAndDefs forall a. Maybe a
Nothing [ConceptChunk]
terms
, forall a.
Idea a =>
a -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
PhySysDesc CI
progName [Sentence]
physSystParts LabelledContent
figMotion []
, [Sentence] -> PDSub
Goals [Sentence]
goalsInputs]
, SolChSpec -> SSDSub
SSDSolChSpec forall a b. (a -> b) -> a -> b
$ [SCSSub] -> SolChSpec
SCSProg
[ SCSSub
Assumptions
, [Sentence] -> Fields -> SCSSub
TMs [] (Field
Label forall a. a -> [a] -> [a]
: Fields
stdFields)
, [Sentence] -> Fields -> DerivationDisplay -> SCSSub
GDs [] ([Field
Label, Field
Units] forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation
, [Sentence] -> Fields -> DerivationDisplay -> SCSSub
DDs [] ([Field
Label, Field
Symbol, Field
Units] forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation
, [Sentence] -> Fields -> DerivationDisplay -> SCSSub
IMs [] ([Field
Label, Field
Input, Field
Output, Field
InConstraints, Field
OutConstraints] forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation
, forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
Sentence -> [c] -> SCSSub
Constraints Sentence
EmptyS [UncertQ]
inConstraints
, forall c.
(Quantity c, Constrained c) =>
[c] -> [Contents] -> SCSSub
CorrSolnPpties [UncertQ]
outConstraints []
]
],
ReqrmntSec -> DocSection
ReqrmntSec forall a b. (a -> b) -> a -> b
$ [ReqsSub] -> ReqrmntSec
ReqsProg
[ Sentence -> [LabelledContent] -> ReqsSub
FReqsSub Sentence
EmptyS []
, ReqsSub
NonFReqsSub
],
TraceabilitySec -> DocSection
TraceabilitySec forall a b. (a -> b) -> a -> b
$ [TraceConfig] -> TraceabilitySec
TraceabilityProg forall a b. (a -> b) -> a -> b
$ SystemInformation -> [TraceConfig]
traceMatStandard SystemInformation
si,
AuxConstntSec -> DocSection
AuxConstntSec forall a b. (a -> b) -> a -> b
$
CI -> [ConstQDef] -> AuxConstntSec
AuxConsProg CI
progName [],
DocSection
Bibliography
]
si :: SystemInformation
si :: SystemInformation
si = SI {
_sys :: CI
_sys = CI
progName,
_kind :: CI
_kind = CI
Doc.srs,
_authors :: [Person]
_authors = [Person
dong],
_purpose :: [Sentence]
_purpose = [Sentence
purp],
_background :: [Sentence]
_background = [],
_quants :: [QuantityDict]
_quants = [QuantityDict]
symbolsAll,
_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 :: [UncertQ]
_constraints = [UncertQ]
inConstraints,
_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 the", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
motion Sentence -> Sentence -> Sentence
`S.ofA` String -> Sentence
S String
"double", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
pendulum]
symbolsAll :: [QuantityDict]
symbolsAll :: [QuantityDict]
symbolsAll = [QuantityDict]
symbols forall a. [a] -> [a] -> [a]
++ [QuantityDict]
scipyODESymbols forall a. [a] -> [a] -> [a]
++ [QuantityDict]
osloSymbols forall a. [a] -> [a] -> [a]
++ [QuantityDict]
apacheODESymbols forall a. [a] -> [a] -> [a]
++ [QuantityDict]
odeintSymbols
forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [CodeVarChunk -> CodeVarChunk
listToArray forall a b. (a -> b) -> a -> b
$ forall c. (Quantity c, MayHaveUnit c) => c -> CodeVarChunk
quantvar ConstrConcept
pendDisAngle, ODEInfo -> CodeVarChunk
arrayVecDepVar ODEInfo
dblPenODEInfo]
symbMap :: ChunkDB
symbMap :: ChunkDB
symbMap = 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 (forall a b. (a -> b) -> [a] -> [b]
map (forall s a. s -> Getting a s a -> a
^. forall c. HasOutput c => Getter c QuantityDict
output) [InstanceModel]
iMods forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [QuantityDict]
symbolsAll)
(forall c. Idea c => c -> IdeaDict
nw TheoryModel
newtonSLR forall a. a -> [a] -> [a]
: forall c. Idea c => c -> IdeaDict
nw CI
progName forall a. a -> [a] -> [a]
: forall c. Idea c => c -> IdeaDict
nw ConceptChunk
mass forall a. a -> [a] -> [a]
: forall c. Idea c => c -> IdeaDict
nw ConceptChunk
len forall a. a -> [a] -> [a]
: forall c. Idea c => c -> IdeaDict
nw UnitDefn
kilogram forall a. a -> [a] -> [a]
: forall c. Idea c => c -> IdeaDict
nw IdeaDict
inValue forall a. a -> [a] -> [a]
: forall c. Idea c => c -> IdeaDict
nw UnitDefn
newton forall a. a -> [a] -> [a]
: forall c. Idea c => c -> IdeaDict
nw UnitDefn
degree forall a. a -> [a] -> [a]
: forall c. Idea c => c -> IdeaDict
nw UnitDefn
radian
forall a. a -> [a] -> [a]
: forall c. Idea c => c -> IdeaDict
nw DefinedQuantityDict
unitVect forall a. a -> [a] -> [a]
: forall c. Idea c => c -> IdeaDict
nw DefinedQuantityDict
unitVectj forall a. a -> [a] -> [a]
: [forall c. Idea c => c -> IdeaDict
nw ConceptChunk
errMsg, forall c. Idea c => c -> IdeaDict
nw ConceptChunk
program] forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [QuantityDict]
symbols forall a. [a] -> [a] -> [a]
++
forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
doccon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [CI]
doccon' forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
physicCon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
mathcon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [CI]
mathcon' forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [CI]
physicCon' forall a. [a] -> [a] -> [a]
++
forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [UnitalChunk]
physicscon forall a. [a] -> [a] -> [a]
++ [IdeaDict]
concepts forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
physicalcon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [CI]
acronyms forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [QuantityDict]
symbols forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [UnitDefn
metre, UnitDefn
hertz] forall a. [a] -> [a] -> [a]
++
[forall c. Idea c => c -> IdeaDict
nw ConceptChunk
algorithm] forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
compcon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
educon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
prodtcon)
(forall a b. (a -> b) -> [a] -> [b]
map forall c. Concept c => c -> ConceptChunk
cw [InstanceModel]
iMods forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
srsDomains) (forall a b. (a -> b) -> [a] -> [b]
map forall u. IsUnit u => u -> UnitDefn
unitWrapper [UnitDefn
metre, UnitDefn
second, UnitDefn
newton, UnitDefn
kilogram, UnitDefn
degree, UnitDefn
radian, UnitDefn
hertz])
[DataDefinition]
dataDefs [InstanceModel]
iMods [GenDefn]
genDefns [TheoryModel]
tMods [ConceptInstance]
concIns [] [] ([] :: [Reference])
usedDB :: ChunkDB
usedDB :: ChunkDB
usedDB = 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]) (forall c. Idea c => c -> IdeaDict
nw CI
progName forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [CI]
acronyms forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [QuantityDict]
symbols) ([] :: [ConceptChunk])
([] :: [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]
assumpDouble forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
goals forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
funcReqs forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
nonFuncReqs
justification :: CI -> Sentence
justification :: CI -> Sentence
justification CI
prog = [Sentence] -> Sentence
foldlSent [ forall n. NounPhrase n => n -> Sentence
atStartNP (forall c. NamedIdea c => c -> NP
a_ ConceptChunk
pendulum), String -> Sentence
S String
"consists" Sentence -> Sentence -> Sentence
`S.of_` forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
mass,
String -> Sentence
S String
"attached to the end" Sentence -> Sentence -> Sentence
`S.ofA` forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
rod Sentence -> Sentence -> Sentence
`S.andIts` String -> Sentence
S String
"moving curve" Sentence -> Sentence -> Sentence
`S.is`
(String -> Sentence
S String
"highly sensitive to initial conditions" !.), String -> Sentence
S String
"Therefore" Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"it is useful to have a", forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
program, String -> Sentence
S String
"to simulate", forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
motion
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
pendulum), (String -> Sentence
S String
"to exhibit its chaotic characteristics" !.),
forall n. NounPhrase n => n -> Sentence
atStartNP (forall c. NamedIdea c => c -> NP
the ConceptChunk
program), String -> Sentence
S String
"documented here is called", forall n. NamedIdea n => n -> Sentence
phrase CI
prog]
scope :: Sentence
scope :: Sentence
scope = [Sentence] -> Sentence
foldlSent_ [forall n. NounPhrase n => n -> Sentence
phraseNP (NP -> NP
NP.the (IdeaDict
analysis forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofA` CI
twoD)),
Sentence -> Sentence
sParen (CI -> Sentence
getAcc CI
twoD), forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
pendMotion, forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem,
String -> Sentence
S String
"with various initial conditions"]
charsOfReader :: [Sentence]
charsOfReader :: [Sentence]
charsOfReader = [forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
undergraduate Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"level 2" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
Doc.physics,
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
undergraduate Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"level 1" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
calculus,
forall n. NamedIdea n => n -> Sentence
plural CI
ode]
sysCtxIntro :: CI -> Contents
sysCtxIntro :: CI -> Contents
sysCtxIntro CI
prog = [Sentence] -> Contents
foldlSP
[forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
sysCtxFig1, String -> Sentence
S String
"shows the" Sentence -> Sentence -> Sentence
+:+. forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
sysCont,
String -> Sentence
S String
"A circle represents an entity external to the", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
software
Sentence -> Sentence -> Sentence
`sC` forall n. NounPhrase n => n -> Sentence
phraseNP (forall c. NamedIdea c => c -> NP
the IdeaDict
user), String -> Sentence
S String
"in this case. A rectangle represents the",
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
softwareSys, String -> Sentence
S String
"itself", Sentence -> Sentence
sParen (forall c. Idea c => c -> Sentence
short CI
prog) Sentence -> Sentence -> Sentence
+:+. Sentence
EmptyS,
String -> Sentence
S String
"Arrows are used to show the data flow between the", forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
system
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", forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
product_
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
+:+.
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
interface, String -> Sentence
S String
"The responsibilities of the", forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
user
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` IdeaDict
system), String -> Sentence
S String
"are as follows"]
sysCtxUsrResp :: CI -> [Sentence]
sysCtxUsrResp :: CI -> [Sentence]
sysCtxUsrResp CI
prog = [String -> Sentence
S String
"Provide initial" Sentence -> Sentence -> Sentence
+:+ forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict
condition forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofThePS`
IdeaDict
physical) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"state of the" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
motion Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"and the" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural IdeaDict
inDatum Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"related to the" Sentence -> Sentence -> Sentence
+:+
forall n. NamedIdea n => n -> Sentence
phrase CI
prog Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"ensuring no errors in the" Sentence -> Sentence -> Sentence
+:+
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
datum Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"entry",
String -> Sentence
S String
"Ensure that consistent units are used for" Sentence -> Sentence -> Sentence
+:+. forall n. NounPhrase n => n -> Sentence
pluralNP (forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI IdeaDict
input_ IdeaDict
Doc.variable),
String -> Sentence
S String
"Ensure required" Sentence -> Sentence -> Sentence
+:+
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
SRS.assumpt ([]::[Contents]) ([]::[Section])) (forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
software Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural CI
assumption) Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"are appropriate for any particular" Sentence -> Sentence -> Sentence
+:+
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"input to the" Sentence -> Sentence -> Sentence
+:+. forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
software]
sysCtxSysResp :: [Sentence]
sysCtxSysResp :: [Sentence]
sysCtxSysResp = [String -> Sentence
S String
"Detect data type mismatch, such as a string of characters" Sentence -> Sentence -> Sentence
+:+
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
input_ Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"instead of a floating point number",
String -> Sentence
S String
"Determine if the" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural IdeaDict
input_ Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"satisfy the required" Sentence -> Sentence -> Sentence
+:+.
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict
physical forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` IdeaDict
softwareConstraint),
String -> Sentence
S String
"Calculate the required" Sentence -> Sentence -> Sentence
+:+. forall n. NamedIdea n => n -> Sentence
plural IdeaDict
output_,
String -> Sentence
S String
"Generate the required" Sentence -> Sentence -> Sentence
+:+. forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
graph]
sysCtxResp :: CI -> [Sentence]
sysCtxResp :: CI -> [Sentence]
sysCtxResp CI
prog = [forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
user Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"Responsibilities",
forall c. Idea c => c -> Sentence
short CI
prog Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"Responsibilities"]
sysCtxList :: CI -> Contents
sysCtxList :: CI -> Contents
sysCtxList CI
prog = UnlabelledContent -> Contents
UlC forall a b. (a -> b) -> a -> b
$ RawContent -> UnlabelledContent
ulcc forall a b. (a -> b) -> a -> b
$ ListType -> RawContent
Enumeration forall a b. (a -> b) -> a -> b
$ [Sentence] -> [ListType] -> ListType
bulletNested (CI -> [Sentence]
sysCtxResp CI
prog) forall a b. (a -> b) -> a -> b
$
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> ListType
bulletFlat [CI -> [Sentence]
sysCtxUsrResp CI
prog, [Sentence]
sysCtxSysResp]
userCharacteristicsIntro :: CI -> Contents
userCharacteristicsIntro :: CI -> Contents
userCharacteristicsIntro CI
prog = [Sentence] -> Contents
foldlSP
[String -> Sentence
S String
"The", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
endUser Sentence -> Sentence -> Sentence
`S.of_` forall c. Idea c => c -> Sentence
short CI
prog,
String -> Sentence
S String
"should have an understanding of",
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
highSchoolPhysics Sentence -> Sentence -> Sentence
`sC` forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
highSchoolCalculus Sentence -> Sentence -> Sentence
`S.and_` forall n. NamedIdea n => n -> Sentence
plural CI
ode]
terms :: [ConceptChunk]
terms :: [ConceptChunk]
terms = [ConceptChunk
gravity, ConceptChunk
cartesian]
physSystParts :: [Sentence]
physSystParts :: [Sentence]
physSystParts = forall a b. (a -> b) -> [a] -> [b]
map Sentence -> Sentence
(!.)
[forall n. NounPhrase n => n -> Sentence
atStartNP (forall c. NamedIdea c => c -> NP
the IdeaDict
firstRod) Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (String -> Sentence
S String
"with" Sentence -> Sentence -> Sentence
+:+ forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
lenRod_1),
forall n. NounPhrase n => n -> Sentence
atStartNP (forall c. NamedIdea c => c -> NP
the IdeaDict
secondRod) Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (String -> Sentence
S String
"with" Sentence -> Sentence -> Sentence
+:+ forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
lenRod_2),
forall n. NounPhrase n => n -> Sentence
atStartNP (forall c. NamedIdea c => c -> NP
the IdeaDict
firstObject),
forall n. NounPhrase n => n -> Sentence
atStartNP (forall c. NamedIdea c => c -> NP
the IdeaDict
secondObject)]
tMods :: [TheoryModel]
tMods :: [TheoryModel]
tMods = [TheoryModel
accelerationTM, TheoryModel
velocityTM, TheoryModel
newtonSL]