{-# 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 ((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 (CI -> Sentence
justification CI
progName) (CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
progName)
[[Sentence] -> IntroSub
IPurpose ([Sentence] -> IntroSub) -> [Sentence] -> IntroSub
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 (GSDSec -> DocSection) -> GSDSec -> DocSection
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 (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
progName [Sentence]
physSystParts LabelledContent
figMotion []
, [Sentence] -> PDSub
Goals [Sentence]
goalsInputs]
, 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
progName [],
DocSection
Bibliography
]
si :: SystemInformation
si :: SystemInformation
si = SI {
_sys :: CI
_sys = CI
progName,
_kind :: CI
_kind = CI
Doc.srs,
_authors :: People
_authors = [Person
dong],
_purpose :: [Sentence]
_purpose = [Sentence
purp],
_background :: [Sentence]
_background = [Sentence
background],
_motivation :: [Sentence]
_motivation = [Sentence
motivation],
_scope :: [Sentence]
_scope = [Sentence
scope],
_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", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
motion Sentence -> Sentence -> Sentence
`S.ofA` String -> Sentence
S String
"double", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
pendulum]
motivation :: Sentence
motivation :: Sentence
motivation = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"To simulate", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
motion ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
pendulum),
String -> Sentence
S String
"and exhibit its chaotic characteristics"]
background :: Sentence
background :: Sentence
background = [Sentence] -> Sentence
foldlSent_ [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall c. NamedIdea c => c -> NP
a_ ConceptChunk
pendulum), String -> Sentence
S String
"consists" Sentence -> Sentence -> Sentence
`S.of_` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
mass,
String -> Sentence
S String
"attached to the end" Sentence -> Sentence -> Sentence
`S.ofA` IdeaDict -> Sentence
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"]
symbolsAll :: [QuantityDict]
symbolsAll :: [QuantityDict]
symbolsAll = [QuantityDict]
symbols [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ [QuantityDict]
scipyODESymbols [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ [QuantityDict]
osloSymbols [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ [QuantityDict]
apacheODESymbols [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ [QuantityDict]
odeintSymbols
[QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ (CodeVarChunk -> QuantityDict) -> [CodeVarChunk] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map CodeVarChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [CodeVarChunk -> CodeVarChunk
listToArray (CodeVarChunk -> CodeVarChunk) -> CodeVarChunk -> CodeVarChunk
forall a b. (a -> b) -> a -> b
$ ConstrConcept -> CodeVarChunk
forall c. (Quantity c, MayHaveUnit c) => c -> CodeVarChunk
quantvar ConstrConcept
pendDisAngle, ODEInfo -> CodeVarChunk
arrayVecDepVar ODEInfo
dblPenODEInfo]
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 ((InstanceModel -> QuantityDict)
-> [InstanceModel] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map (InstanceModel
-> Getting QuantityDict InstanceModel QuantityDict -> QuantityDict
forall s a. s -> Getting a s a -> a
^. Getting QuantityDict InstanceModel QuantityDict
forall c. HasOutput c => Getter c QuantityDict
Getter InstanceModel QuantityDict
output) [InstanceModel]
iMods [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ (QuantityDict -> QuantityDict) -> [QuantityDict] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map QuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [QuantityDict]
symbolsAll)
(TheoryModel -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw TheoryModel
newtonSLR IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
progName 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]
: ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
len IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw UnitDefn
kilogram 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]
: UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw UnitDefn
newton IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw UnitDefn
degree IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw UnitDefn
radian
IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: DefinedQuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw DefinedQuantityDict
unitVect IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: DefinedQuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw DefinedQuantityDict
unitVectj 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]
++ (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]
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]
++ (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]
++ (CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
mathcon' [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]
++ [IdeaDict]
concepts [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]
physicalcon [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
hertz] [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 -> IdeaDict) -> [IdeaDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
compcon [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]
++ (IdeaDict -> IdeaDict) -> [IdeaDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
prodtcon)
((InstanceModel -> ConceptChunk)
-> [InstanceModel] -> [ConceptChunk]
forall a b. (a -> b) -> [a] -> [b]
map InstanceModel -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw [InstanceModel]
iMods [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
second, UnitDefn
newton, UnitDefn
kilogram, UnitDefn
degree, UnitDefn
radian, UnitDefn
hertz])
[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]) (CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
progName 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) ([] :: [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 [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
goals [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
funcReqs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
nonFuncReqs
justification :: CI -> Sentence
justification :: CI -> Sentence
justification CI
prog = [Sentence] -> Sentence
foldlSent [ NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall c. NamedIdea c => c -> NP
a_ ConceptChunk
pendulum), String -> Sentence
S String
"consists" Sentence -> Sentence -> Sentence
`S.of_` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
mass,
String -> Sentence
S String
"attached to the end" Sentence -> Sentence -> Sentence
`S.ofA` IdeaDict -> Sentence
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", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
program, String -> Sentence
S String
"to simulate", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
motion
ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
pendulum), (String -> Sentence
S String
"to exhibit its chaotic characteristics" !.),
String -> Sentence
S String
"The document describes the program called", CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
prog,
String -> Sentence
S String
", which is based on the 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
"Double Pendulum")]
externalLinkRef :: Reference
externalLinkRef :: Reference
externalLinkRef = String -> String -> ShortName -> Reference
makeURI String
"DblPendSRSLink"
String
"https://github.com/Zhang-Zhi-ZZ/CAS741Project/tree/master/Double%20Pendulum"
(Sentence -> ShortName
shortname' (Sentence -> ShortName) -> Sentence -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"DblPendSRSLink")
scope :: Sentence
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), IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
pendMotion, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem,
String -> Sentence
S String
"with various initial conditions"]
charsOfReader :: [Sentence]
charsOfReader :: [Sentence]
charsOfReader = [IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
undergraduate Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"level 2" 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,
CI -> Sentence
forall n. NamedIdea n => n -> Sentence
plural CI
ode]
sysCtxIntro :: CI -> Contents
sysCtxIntro :: CI -> Contents
sysCtxIntro CI
prog = [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 c. NamedIdea c => c -> 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
sParen (CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
prog) Sentence -> Sentence -> Sentence
+:+. Sentence
EmptyS,
String -> Sentence
S String
"Arrows" Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"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
"The responsibilities" Sentence -> Sentence -> Sentence
`S.ofThe` 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 :: CI -> [Sentence]
sysCtxUsrResp :: CI -> [Sentence]
sysCtxUsrResp CI
prog = [String -> Sentence
S String
"Provide initial" Sentence -> Sentence -> Sentence
+:+ 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) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"state" Sentence -> Sentence -> Sentence
`S.ofThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
motion Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"and the" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
inDatum Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"related to the" Sentence -> Sentence -> Sentence
+:+
CI -> 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
+:+
IdeaDict -> 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" Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"used for" Sentence -> Sentence -> Sentence
+:+. 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" Sentence -> Sentence -> Sentence
+:+
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) Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"are appropriate for any particular" Sentence -> Sentence -> Sentence
+:+
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"input to the" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> 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
+:+
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
input_ Sentence -> Sentence -> Sentence
+:+. (String -> Sentence
S String
"instead" Sentence -> Sentence -> Sentence
`S.ofA` String -> Sentence
S String
"floating point number"),
String -> Sentence
S String
"Determine if the" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
input_ Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"satisfy the required" Sentence -> Sentence -> Sentence
+:+.
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" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
output_,
String -> Sentence
S String
"Generate the required" Sentence -> Sentence -> Sentence
+:+. ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
graph]
sysCtxResp :: CI -> [Sentence]
sysCtxResp :: CI -> [Sentence]
sysCtxResp CI
prog = [IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
user Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"Responsibilities",
CI -> Sentence
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 (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 (CI -> [Sentence]
sysCtxResp CI
prog) ([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 [CI -> [Sentence]
sysCtxUsrResp CI
prog, [Sentence]
sysCtxSysResp]
userCharacteristicsIntro :: CI -> Contents
userCharacteristicsIntro :: CI -> Contents
userCharacteristicsIntro CI
prog = [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
prog,
String -> Sentence
S String
"should have an understanding of",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
highSchoolPhysics Sentence -> Sentence -> Sentence
`sC` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
highSchoolCalculus Sentence -> Sentence -> Sentence
`S.and_` CI -> Sentence
forall n. NamedIdea n => n -> Sentence
plural CI
ode]
terms :: [ConceptChunk]
terms :: [ConceptChunk]
terms = [ConceptChunk
gravity, ConceptChunk
cartesian]
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 (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
firstRod) Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (String -> Sentence
S String
"with" Sentence -> Sentence -> Sentence
+:+ UnitalChunk -> Sentence
forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
lenRod_1),
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
secondRod) Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (String -> Sentence
S String
"with" Sentence -> Sentence -> Sentence
+:+ UnitalChunk -> Sentence
forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
lenRod_2),
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
firstObject),
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
secondObject)]
tMods :: [TheoryModel]
tMods :: [TheoryModel]
tMods = [TheoryModel
accelerationTM, TheoryModel
velocityTM, TheoryModel
newtonSL]