module Drasil.Template.Body where
import Drasil.System (SystemKind(Specification), mkSystem)
import Drasil.Metadata
import Language.Drasil
import Drasil.SRSDocument
import Database.Drasil.ChunkDB (cdb)
import Theory.Drasil (DataDefinition, GenDefn, InstanceModel, TheoryModel)
import qualified Language.Drasil.Sentence.Combinators as S
import qualified Drasil.DocLang.SRS as SRS
import Data.Drasil.Citations
import Drasil.DocumentLanguage.TraceabilityGraph
import Drasil.DocLang (tunitNone)
srs :: Document
srs :: Document
srs = SRSDecl -> (IdeaDict -> IdeaDict -> Sentence) -> System -> 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) System
si
fullSI :: System
fullSI :: System
fullSI = SRSDecl -> System -> System
fillcdbSRS SRSDecl
mkSRS System
si
printSetting :: PrintingInformation
printSetting :: PrintingInformation
printSetting = System -> Stage -> PrintingConfiguration -> PrintingInformation
piSys System
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
[ [TUIntro] -> RefTab
tunitNone []
, [TSIntro] -> RefTab
tsymb []
],
IntroSec -> DocSection
IntroSec (IntroSec -> DocSection) -> IntroSec -> DocSection
forall a b. (a -> b) -> a -> b
$
Sentence -> Sentence -> [IntroSub] -> IntroSec
IntroProg Sentence
EmptyS (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
EmptyS,
[Sentence] -> [Sentence] -> [Sentence] -> IntroSub
IChar [] [] [],
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 [],
[Contents] -> GSDSub
UsrChars [],
[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
EmptyS []
[ Maybe Sentence -> [ConceptChunk] -> PDSub
forall c. Concept c => Maybe Sentence -> [c] -> PDSub
TermsAndDefs Maybe Sentence
forall a. Maybe a
Nothing ([] :: [ConceptChunk])
, CI -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
forall a.
Idea a =>
a -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
PhySysDesc CI
progName [] LabelledContent
figTemp []
, [Sentence] -> PDSub
Goals []
]
, SolChSpec -> SSDSub
SSDSolChSpec (SolChSpec -> SSDSub) -> SolChSpec -> SSDSub
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
, Sentence -> [UncertQ] -> SCSSub
forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
Sentence -> [c] -> SCSSub
Constraints Sentence
EmptyS ([] :: [UncertQ])
, [UncertQ] -> [Contents] -> SCSSub
forall c.
(Quantity c, Constrained c) =>
[c] -> [Contents] -> SCSSub
CorrSolnPpties ([] :: [UncertQ]) []
]
],
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,
DocSection
UCsSec,
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
$ System -> [TraceConfig]
traceMatStandard System
si,
AuxConstntSec -> DocSection
AuxConstntSec (AuxConstntSec -> DocSection) -> AuxConstntSec -> DocSection
forall a b. (a -> b) -> a -> b
$
CI -> [ConstQDef] -> AuxConstntSec
AuxConsProg CI
progName [],
DocSection
Bibliography]
si :: System
si :: System
si = CI
-> SystemKind
-> People
-> [Sentence]
-> [Sentence]
-> [Sentence]
-> [Sentence]
-> [DefinedQuantityDict]
-> [TheoryModel]
-> [GenDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [String]
-> [DefinedQuantityDict]
-> [DefinedQuantityDict]
-> [ConstrConcept]
-> [ConstQDef]
-> ChunkDB
-> System
forall a e h i j.
(CommonIdea a, Idea a, Quantity e, Eq e, MayHaveUnit e, Concept e,
Quantity h, MayHaveUnit h, Concept h, Quantity i, MayHaveUnit i,
Concept i, HasUID j, Constrained j) =>
a
-> SystemKind
-> People
-> [Sentence]
-> [Sentence]
-> [Sentence]
-> [Sentence]
-> [e]
-> [TheoryModel]
-> [GenDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [String]
-> [h]
-> [i]
-> [j]
-> [ConstQDef]
-> ChunkDB
-> System
mkSystem
CI
progName SystemKind
Specification [Person
authorName]
[] [] [] []
([] :: [DefinedQuantityDict])
([] :: [TheoryModel]) ([] :: [GenDefn]) ([] :: [DataDefinition]) ([] :: [InstanceModel])
[]
([] :: [DefinedQuantityDict]) ([] :: [DefinedQuantityDict]) ([] :: [ConstrConcept]) ([] :: [ConstQDef])
ChunkDB
symbMap
ideaDicts :: [IdeaDict]
ideaDicts :: [IdeaDict]
ideaDicts =
[CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
progName]
conceptChunks :: [ConceptChunk]
conceptChunks :: [ConceptChunk]
conceptChunks = [] :: [ConceptChunk]
symbMap :: ChunkDB
symbMap :: ChunkDB
symbMap = [DefinedQuantityDict]
-> [IdeaDict]
-> [ConceptChunk]
-> [UnitDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [LabelledContent]
-> [Reference]
-> [Citation]
-> ChunkDB
forall q c u.
(Quantity q, MayHaveUnit q, Concept q, Concept c, IsUnit u) =>
[q]
-> [IdeaDict]
-> [c]
-> [u]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [LabelledContent]
-> [Reference]
-> [Citation]
-> ChunkDB
cdb ([] :: [DefinedQuantityDict]) [IdeaDict]
ideaDicts [ConceptChunk]
conceptChunks
([] :: [UnitDefn]) ([] :: [DataDefinition]) ([] :: [InstanceModel])
([] :: [GenDefn]) ([] :: [TheoryModel]) ([] :: [ConceptInstance])
([] :: [LabelledContent]) ([] :: [Reference]) [Citation]
citations
citations :: BibRef
citations :: [Citation]
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") (RawContent -> LabelledContent) -> RawContent -> LabelledContent
forall a b. (a -> b) -> a -> b
$ Sentence -> String -> MaxWidthPercent -> RawContent
figWithWidth Sentence
EmptyS
(String
resourcePath String -> String -> String
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"