{-# LANGUAGE PostfixOperators #-}
module Drasil.SglPend.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 (the)
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.People (olu)
import Data.Drasil.SI_Units (metre, second, newton, kilogram, degree, radian, hertz)
import Data.Drasil.Concepts.Computation (compcon, inValue, algorithm)
import Data.Drasil.Concepts.Documentation (srsDomains, doccon, doccon')
import qualified Data.Drasil.Concepts.Documentation as Doc (srs)
import Data.Drasil.Concepts.Education (educon)
import Data.Drasil.Concepts.Math (mathcon, mathcon')
import Data.Drasil.Concepts.Physics (physicCon, physicCon', motion, pendulum)
import Data.Drasil.Concepts.PhysicalProperties (mass, len, physicalcon)
import Data.Drasil.Concepts.Software (program, errMsg)
import Data.Drasil.Domains (physics)
import Data.Drasil.Software.Products (prodtcon)
import Data.Drasil.Theories.Physics (newtonSLR)
import Data.Drasil.TheoryConcepts (inModel)
import Data.Drasil.Quantities.Math (unitVect, unitVectj)
import Data.Drasil.Quantities.Physics (physicscon)
import Drasil.DblPend.Assumptions (assumpSingle)
import Drasil.DblPend.Body (justification, externalLinkRef, charsOfReader,
sysCtxIntro, sysCtxDesc, sysCtxList, stdFields, scope, terms,
userCharacteristicsIntro)
import qualified Drasil.DblPend.Body as DPD (tMods)
import Drasil.DblPend.Concepts (concepts, rod)
import Drasil.DblPend.Requirements (nonFuncReqs)
import Drasil.DblPend.Unitals (acronyms)
import Drasil.DblPend.References (citations)
import Drasil.SglPend.Figures (figMotion, sysCtxFig1)
import Drasil.SglPend.Goals (goals, goalsInputs)
import Drasil.SglPend.DataDefs (dataDefs)
import Drasil.SglPend.IMods (iMods)
import Drasil.SglPend.GenDefs (genDefns)
import Drasil.SglPend.Unitals (inputs, outputs, inConstraints, outConstraints, symbols)
import Drasil.SglPend.Requirements (funcReqs)
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
]
progName :: CI
progName :: CI
progName = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict String
"sglPendulum" (String -> NP
pn String
"Single Pendulum") String
"SglPend" [IdeaDict
physics]
si :: SystemInformation
si :: SystemInformation
si = SI {
_sys :: CI
_sys = CI
progName,
_kind :: CI
_kind = CI
Doc.srs,
_authors :: People
_authors = [Person
olu],
_purpose :: [Sentence]
_purpose = [Sentence
purp],
_background :: [Sentence]
_background = [],
_scope :: [Sentence]
_scope = [],
_motivation :: [Sentence]
_motivation = [],
_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 :: [UncertQ]
_constraints = [UncertQ]
inConstraints,
_constants :: [ConstQDef]
_constants = [] :: [ConstQDef],
_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
"single", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
pendulum]
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]
symbols)
(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])
refDB :: ReferenceDB
refDB :: ReferenceDB
refDB = BibRef -> [ConceptInstance] -> ReferenceDB
rdb BibRef
citations [ConceptInstance]
concIns
concIns :: [ConceptInstance]
concIns :: [ConceptInstance]
concIns = [ConceptInstance]
assumpSingle [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
physSystParts :: [Sentence]
physSystParts :: [Sentence]
physSystParts = (NP -> Sentence) -> [NP] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map (Sentence -> Sentence
(!.) (Sentence -> Sentence) -> (NP -> Sentence) -> NP -> Sentence
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP) [IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
rod, ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
mass]
tMods :: [TheoryModel]
tMods :: [TheoryModel]
tMods = [TheoryModel]
DPD.tMods [TheoryModel] -> [TheoryModel] -> [TheoryModel]
forall a. [a] -> [a] -> [a]
++ [TheoryModel
newtonSLR]