module Drasil.PDController.Body (pidODEInfo, printSetting, si, srs, fullSI) where
import Language.Drasil
import Drasil.SRSDocument
import qualified Drasil.DocLang.SRS as SRS (inModel)
import Theory.Drasil (DataDefinition, GenDefn, InstanceModel, TheoryModel)
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.Concepts.Documentation (doccon, doccon', srsDomains)
import qualified Data.Drasil.Concepts.Documentation as Doc (srs)
import Data.Drasil.Concepts.Math (mathcon, mathcon', ode)
import Data.Drasil.Concepts.Software (program)
import Data.Drasil.Software.Products (sciCompS)
import Data.Drasil.ExternalLibraries.ODELibraries
(apacheODESymbols, arrayVecDepVar, odeintSymbols, osloSymbols,
scipyODESymbols)
import qualified Data.Drasil.TheoryConcepts as IDict (dataDefn)
import Data.Drasil.Quantities.Physics (physicscon)
import Data.Drasil.Concepts.PhysicalProperties (physicalcon)
import Data.Drasil.Concepts.Physics (angular, linear)
import Data.Drasil.Quantities.PhysicalProperties (mass)
import Data.Drasil.SI_Units (second, kilogram)
import Data.Drasil.Quantities.Math (posInf, negInf)
import Drasil.PDController.Assumptions (assumptions)
import Drasil.PDController.Changes (likelyChgs)
import Drasil.PDController.Concepts (acronyms, pdControllerApp,
pidC, concepts, defs)
import Drasil.PDController.DataDefs (dataDefinitions)
import Drasil.PDController.GenDefs (genDefns)
import Drasil.PDController.GenSysDesc
(gsdSysContextFig, gsdSysContextList, gsdSysContextP1, gsdSysContextP2,
gsduserCharacteristics)
import Drasil.PDController.IModel (instanceModels, imPD)
import Drasil.PDController.IntroSection (introPara, introPurposeOfDoc, externalLinkRef,
introUserChar1, introUserChar2, introscopeOfReq, scope)
import Drasil.PDController.References (citations)
import Drasil.PDController.Requirements (funcReqs, nonfuncReqs)
import Drasil.PDController.SpSysDesc (goals, sysFigure, sysGoalInput, sysParts)
import Drasil.PDController.TModel (theoreticalModels)
import Drasil.PDController.Unitals (symbols, inputs, outputs, inputsUC,
inpConstrained, pidConstants, pidDqdConstants, opProcessVariable)
import Drasil.PDController.ODEs (pidODEInfo)
import Language.Drasil.Code (quantvar)
naveen :: Person
naveen :: Person
naveen = String -> String -> Person
person String
"Naveen Ganesh" String
"Muralidharan"
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, TSIntro
SymbOrder], RefTab
TAandA],
IntroSec -> DocSection
IntroSec (IntroSec -> DocSection) -> IntroSec -> DocSection
forall a b. (a -> b) -> a -> b
$
Sentence -> Sentence -> [IntroSub] -> IntroSec
IntroProg Sentence
introPara (CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
pdControllerApp)
[[Sentence] -> IntroSub
IPurpose [Sentence
introPurposeOfDoc], Sentence -> IntroSub
IScope Sentence
introscopeOfReq,
[Sentence] -> [Sentence] -> [Sentence] -> IntroSub
IChar [Sentence]
introUserChar1 [Sentence]
introUserChar2 [],
CI -> Section -> Sentence -> IntroSub
IOrgSec CI
IDict.dataDefn ([Contents] -> [Section] -> Section
SRS.inModel [] [])
(String -> Sentence
S String
"The instance model referred as" Sentence -> Sentence -> Sentence
+:+ InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
imPD Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"provides an"
Sentence -> Sentence -> Sentence
+:+ CI -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize CI
ode Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
ode)
Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"that models the"
Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
pidC)],
GSDSec -> DocSection
GSDSec (GSDSec -> DocSection) -> GSDSec -> DocSection
forall a b. (a -> b) -> a -> b
$
[GSDSub] -> GSDSec
GSDProg
[[Contents] -> GSDSub
SysCntxt
[Contents
gsdSysContextP1, LabelledContent -> Contents
LlC LabelledContent
gsdSysContextFig, Contents
gsdSysContextP2,
Contents
gsdSysContextList],
[Contents] -> GSDSub
UsrChars [Contents
gsduserCharacteristics], [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]
defs,
CI -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
forall a.
Idea a =>
a -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
PhySysDesc CI
pdControllerApp [Sentence]
sysParts LabelledContent
sysFigure [],
[Sentence] -> PDSub
Goals [Sentence]
sysGoalInput],
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 -> Fields -> Fields
forall a. a -> [a] -> [a]
: Fields
stdFields) DerivationDisplay
HideDerivation,
[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]
inputsUC]],
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], DocSection
LCsSec,
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, DocSection
Bibliography]
si :: SystemInformation
si :: SystemInformation
si = SI {
_sys :: CI
_sys = CI
pdControllerApp,
_kind :: CI
_kind = CI
Doc.srs,
_authors :: People
_authors = [Person
naveen],
_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],
_datadefs :: [DataDefinition]
_datadefs = [DataDefinition]
dataDefinitions,
_instModels :: [InstanceModel]
_instModels = [InstanceModel]
instanceModels,
_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]
inpConstrained,
_constants :: [ConstQDef]
_constants = [ConstQDef]
pidConstants,
_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
"provide a model" Sentence -> Sentence -> Sentence
`S.ofA` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
pidC,
String -> Sentence
S String
"that can be used for the tuning" Sentence -> Sentence -> Sentence
`S.ofThe` String -> Sentence
S String
"gain constants before",
String -> Sentence
S String
"the deployment" Sentence -> Sentence -> Sentence
`S.ofThe` String -> Sentence
S String
"controller"]
motivation :: Sentence
motivation :: Sentence
motivation = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"The gains of a controller in an application" Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"must be tuned before the controller is ready for production"]
background :: Sentence
background :: Sentence
background = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"Automatic process control with a controller (P/PI/PD/PID) is used",
String -> Sentence
S String
"in a variety of applications such as thermostats, automobile",
String -> Sentence
S String
"cruise-control, etc"]
symbolsAll :: [QuantityDict]
symbolsAll :: [QuantityDict]
symbolsAll = [QuantityDict]
symbols [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ (DefinedQuantityDict -> QuantityDict)
-> [DefinedQuantityDict] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map DefinedQuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [DefinedQuantityDict]
pidDqdConstants [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]
pidConstants
[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
opProcessVariable, ODEInfo -> CodeVarChunk
arrayVecDepVar ODEInfo
pidODEInfo]
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 ((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]
symbolsAll [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ [UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
mass, DefinedQuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw DefinedQuantityDict
posInf, DefinedQuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw DefinedQuantityDict
negInf])
(CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
pdControllerApp IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
: [ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
program, ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
angular, ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
linear] [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 -> 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]
++ [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]
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]
++ (UnitDefn -> IdeaDict) -> [UnitDefn] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [UnitDefn
second, UnitDefn
kilogram] [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]
++ (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]
++ (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]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
physicalcon)
((ConstrConcept -> ConceptChunk)
-> [ConstrConcept] -> [ConceptChunk]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw [ConstrConcept]
inpConstrained [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
second, UnitDefn
kilogram])
[DataDefinition]
dataDefinitions
[InstanceModel]
instanceModels
[GenDefn]
genDefns
[TheoryModel]
theoreticalModels
[ConceptInstance]
conceptInstances
([] :: [Section])
([] :: [LabelledContent])
[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) -> [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]
symbolsAll)
([] :: [ConceptChunk])
([] :: [UnitDefn])
([] :: [DataDefinition])
([] :: [InstanceModel])
([] :: [GenDefn])
([] :: [TheoryModel])
([] :: [ConceptInstance])
([] :: [Section])
([] :: [LabelledContent])
([] :: [Reference])
refDB :: ReferenceDB
refDB :: ReferenceDB
refDB = BibRef -> [ConceptInstance] -> ReferenceDB
rdb BibRef
citations [ConceptInstance]
conceptInstances
conceptInstances :: [ConceptInstance]
conceptInstances :: [ConceptInstance]
conceptInstances = [ConceptInstance]
assumptions [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 [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
likelyChgs
stdFields :: Fields
stdFields :: Fields
stdFields
= [Field
DefiningEquation, Verbosity -> InclUnits -> Field
Description Verbosity
Verbose InclUnits
IncludeUnits, Field
Notes, Field
Source, Field
RefBy]