module Drasil.Template.Body where
import Language.Drasil
import Drasil.SRSDocument
import Theory.Drasil (DataDefinition, GenDefn, InstanceModel, TheoryModel)
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.Concepts.Documentation (doccon, doccon', srsDomains)
import Data.Drasil.Concepts.Computation (inValue, algorithm)
import Data.Drasil.Concepts.Software (errMsg, program)
import Data.Drasil.Concepts.Math (mathcon)
import qualified Data.Drasil.Concepts.Documentation as Doc (srs)
import qualified Drasil.DocLang.SRS as SRS
import Data.Drasil.Software.Products
import Data.Drasil.TheoryConcepts
import Data.Drasil.Citations
import Drasil.DocumentLanguage.TraceabilityGraph
import Drasil.DocLang (tunitNone)
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
[ [TUIntro] -> RefTab
tunitNone []
, [TSIntro] -> RefTab
tsymb []
, RefTab
TAandA
],
IntroSec -> DocSection
IntroSec forall a b. (a -> b) -> a -> b
$
Sentence -> Sentence -> [IntroSub] -> IntroSec
IntroProg Sentence
EmptyS (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
EmptyS,
[Sentence] -> [Sentence] -> [Sentence] -> IntroSub
IChar [] [] [],
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 [],
[Contents] -> GSDSub
UsrChars [],
[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
EmptyS []
[ forall c. Concept c => Maybe Sentence -> [c] -> PDSub
TermsAndDefs forall a. Maybe a
Nothing ([] :: [ConceptChunk])
, forall a.
Idea a =>
a -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
PhySysDesc CI
progName [] LabelledContent
figTemp []
, [Sentence] -> PDSub
Goals []
]
, SolChSpec -> SSDSub
SSDSolChSpec forall a b. (a -> b) -> a -> b
$ [SCSSub] -> SolChSpec
SCSProg
[ SCSSub
Assumptions
, [Sentence] -> Fields -> SCSSub
TMs [] []
, [Sentence] -> Fields -> DerivationDisplay -> SCSSub
GDs [] [] DerivationDisplay
HideDerivation
, [Sentence] -> Fields -> DerivationDisplay -> SCSSub
DDs [] [] DerivationDisplay
HideDerivation
, [Sentence] -> Fields -> DerivationDisplay -> SCSSub
IMs [] [] DerivationDisplay
HideDerivation
, forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
Sentence -> [c] -> SCSSub
Constraints Sentence
EmptyS ([] :: [UncertQ])
, forall c.
(Quantity c, Constrained c) =>
[c] -> [Contents] -> SCSSub
CorrSolnPpties ([] :: [UncertQ]) []
]
],
ReqrmntSec -> DocSection
ReqrmntSec forall a b. (a -> b) -> a -> b
$ [ReqsSub] -> ReqrmntSec
ReqsProg
[
Sentence -> [LabelledContent] -> ReqsSub
FReqsSub Sentence
EmptyS []
, ReqsSub
NonFReqsSub
],
DocSection
LCsSec,
DocSection
UCsSec,
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
authorName],
_background :: [Sentence]
_background = [],
_purpose :: [Sentence]
_purpose = [],
_quants :: [QuantityDict]
_quants = [] :: [QuantityDict],
_concepts :: [DefinedQuantityDict]
_concepts = [] :: [DefinedQuantityDict],
_instModels :: [InstanceModel]
_instModels = [] :: [InstanceModel],
_datadefs :: [DataDefinition]
_datadefs = [] :: [DataDefinition],
_configFiles :: [String]
_configFiles = [],
_inputs :: [QuantityDict]
_inputs = [] :: [QuantityDict],
_outputs :: [QuantityDict]
_outputs = [] :: [QuantityDict],
_defSequence :: [Block SimpleQDef]
_defSequence = [] :: [Block SimpleQDef],
_constraints :: [ConstrainedChunk]
_constraints = [] :: [ConstrainedChunk],
_constants :: [ConstQDef]
_constants = [] :: [ConstQDef],
_sysinfodb :: ChunkDB
_sysinfodb = ChunkDB
symbMap,
_usedinfodb :: ChunkDB
_usedinfodb = ChunkDB
usedDB,
refdb :: ReferenceDB
refdb = ReferenceDB
refDB
}
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 ([] :: [QuantityDict]) (forall c. Idea c => c -> IdeaDict
nw CI
progName 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 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 [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 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]
prodtcon forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
mathcon) [ConceptChunk]
srsDomains
([] :: [UnitDefn]) ([] :: [DataDefinition]) ([] :: [InstanceModel])
([] :: [GenDefn]) ([] :: [TheoryModel]) ([] :: [ConceptInstance])
([] :: [Section]) ([] :: [LabelledContent]) ([] :: [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]) ([] :: [IdeaDict]) ([] :: [ConceptChunk])
([] :: [UnitDefn]) ([] :: [DataDefinition]) ([] :: [InstanceModel])
([] :: [GenDefn]) ([] :: [TheoryModel]) ([] :: [ConceptInstance])
([] :: [Section]) ([] :: [LabelledContent]) ([] :: [Reference])
refDB :: ReferenceDB
refDB :: ReferenceDB
refDB = BibRef -> [ConceptInstance] -> ReferenceDB
rdb BibRef
citations []
citations :: BibRef
citations :: BibRef
citations = [Citation
parnasClements1986, Citation
koothoor2013, Citation
smithEtAl2007, Citation
smithLai2005,
Citation
smithKoothoor2016]
inConstraints :: [UncertQ]
inConstraints :: [UncertQ]
inConstraints = []
outConstraints :: [UncertQ]
outConstraints :: [UncertQ]
outConstraints = []
figTemp :: LabelledContent
figTemp :: LabelledContent
figTemp = Reference -> RawContent -> LabelledContent
llcc (String -> Reference
makeFigRef String
"dblpend") forall a b. (a -> b) -> a -> b
$ Sentence -> String -> MaxWidthPercent -> RawContent
figWithWidth Sentence
EmptyS
(String
resourcePath forall a. [a] -> [a] -> [a]
++ String
"dblpend.png") MaxWidthPercent
60
progName :: CI
progName :: CI
progName = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict String
"progName" (String -> NP
pn String
"ProgName") String
"ProgName" []
authorName :: Person
authorName :: Person
authorName = String -> String -> Person
person String
"Author" String
"Name"