{-# LANGUAGE PostfixOperators #-}
module Drasil.Sections.Introduction (orgSec, introductionSection, purposeOfDoc, scopeOfRequirements,
charIntRdrF, purpDoc) where
import Language.Drasil
import qualified Drasil.DocLang.SRS as SRS (intro, prpsOfDoc, scpOfReq,
charOfIR, orgOfDoc, goalStmt, thModel, inModel, sysCon)
import Drasil.DocumentLanguage.Definitions(Verbosity(..))
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.Concepts.Computation (algorithm)
import Data.Drasil.Concepts.Documentation as Doc (assumption, characteristic,
decision, definition, desSpec, design, designDoc, document, documentation,
environment, goal, goalStmt, implementation, intReader, model, organization,
purpose, requirement, scope, section_, softwareDoc, softwareVAV, srs,
theory, user, vavPlan, problem, information, systemConstraint)
import Data.Drasil.TheoryConcepts as Doc (inModel, thModel)
import Data.Drasil.Citations (parnasClements1986)
developmentProcessParagraph :: Sentence
developmentProcessParagraph :: Sentence
developmentProcessParagraph = [Sentence] -> Sentence
foldlSent [String -> Sentence
S "This", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
document,
String -> Sentence
S "will be used as a starting point for subsequent development",
String -> Sentence
S "phases, including writing the", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (CI
desSpec CI -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` NamedChunk
softwareVAV) Sentence -> Sentence -> Sentence
+:+.
String -> Sentence
S "plan", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall t. NamedIdea t => t -> NP
the NamedChunk
designDoc), String -> Sentence
S "will show how the",
CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CI
requirement, String -> Sentence
S "are to be realized, including", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
decision,
String -> Sentence
S "on the numerical", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural ConceptChunk
algorithm, String -> Sentence
S "and programming" Sentence -> Sentence -> Sentence
+:+.
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
environment, String -> Sentence
S "The", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
vavPlan,
String -> Sentence
S "will show the steps that will be used to increase confidence in the",
(NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk
softwareDoc NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` NamedChunk
implementation) Sentence -> Sentence
!.), String -> Sentence
S "Although",
String -> Sentence
S "the", CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
srs, String -> Sentence
S "fits in a series of", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
document,
String -> Sentence
S "that follow the so-called waterfall", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
model Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S "the actual development process is not constrained",
String -> Sentence
S "in any way. Even when the waterfall model is not followed, as",
String -> Sentence
S "Parnas and Clements point out", Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
parnasClements1986 Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S "the most logical way to present the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
documentation,
String -> Sentence
S "is still to", Sentence -> Sentence
Quote (String -> Sentence
S "fake"), String -> Sentence
S "a rational", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
design,
String -> Sentence
S "process"]
introductionSubsections :: Sentence
introductionSubsections :: Sentence
introductionSubsections = SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List (((Sentence, Sentence) -> Sentence)
-> [(Sentence, Sentence)] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ((Sentence -> Sentence -> Sentence)
-> (Sentence, Sentence) -> Sentence
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Sentence -> Sentence -> Sentence
S.the_ofThe)
[(NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
scope, CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CI
requirement),
(NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
characteristic, NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
intReader),
(NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
Doc.organization, NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
document)])
introductionSection :: Sentence -> Sentence -> [Section] -> Section
introductionSection :: Sentence -> Sentence -> [Section] -> Section
introductionSection problemIntroduction :: Sentence
problemIntroduction programDefinition :: Sentence
programDefinition = [Contents] -> [Section] -> Section
SRS.intro
[Sentence -> Contents
mkParagraph Sentence
problemIntroduction, Sentence -> Contents
overviewParagraph Sentence
programDefinition]
overviewParagraph :: Sentence -> Contents
overviewParagraph :: Sentence -> Contents
overviewParagraph programDefinition :: Sentence
programDefinition = [Sentence] -> Contents
foldlSP [String -> Sentence
S "The following", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
section_,
String -> Sentence
S "provides an overview of the", CI -> Sentence
forall n. Idea n => n -> Sentence
introduceAbb CI
srs, String -> Sentence
S "for" Sentence -> Sentence -> Sentence
+:+.
Sentence
programDefinition, String -> Sentence
S "This", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
section_, String -> Sentence
S "explains the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
purpose,
String -> Sentence
S "of this", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
document Sentence -> Sentence -> Sentence
`sC` Sentence
introductionSubsections]
purpDocPara1 :: CI -> Sentence
purpDocPara1 :: CI -> Sentence
purpDocPara1 proName :: CI
proName = [Sentence] -> Sentence
foldlSent [String -> Sentence
S "The primary purpose of this", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
document, String -> Sentence
S "is to",
String -> Sentence
S "record the", CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CI
requirement, String -> Sentence
S "of the" Sentence -> Sentence -> Sentence
+:+. CI -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize CI
proName,
NamedChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart' NamedChunk
goal Sentence -> Sentence -> Sentence
`sC` CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CI
assumption Sentence -> Sentence -> Sentence
`sC` CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CI
thModel Sentence -> Sentence -> Sentence
`sC`
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
definition Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "and other", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
model, String -> Sentence
S "derivation",
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
information, String -> Sentence
S "are specified" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "allowing the reader to fully",
String -> Sentence
S "understand" Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S "verify the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
purpose Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S "scientific",
String -> Sentence
S "basis of" Sentence -> Sentence -> Sentence
+:+. CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
proName, String -> Sentence
S "With the exception of",
Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
SRS.sysCon [] []) (NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
systemConstraint) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "this",
CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
Doc.srs, String -> Sentence
S "will remain abstract, describing what", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
problem,
String -> Sentence
S "is being solved, but not how to solve it"]
purpDoc :: CI -> Verbosity -> [Sentence]
purpDoc :: CI -> Verbosity -> [Sentence]
purpDoc proName :: CI
proName Verbose = [CI -> Sentence
purpDocPara1 CI
proName, Sentence
developmentProcessParagraph]
purpDoc proName :: CI
proName Succinct = [CI -> Sentence
purpDocPara1 CI
proName]
purposeOfDoc :: [Sentence] -> Section
purposeOfDoc :: [Sentence] -> Section
purposeOfDoc [purposeOfProgram :: Sentence
purposeOfProgram] = [Contents] -> [Section] -> Section
SRS.prpsOfDoc [Sentence -> Contents
mkParagraph Sentence
purposeOfProgram] []
purposeOfDoc [purposeOfProgram :: Sentence
purposeOfProgram, developmentProcess :: Sentence
developmentProcess] = [Contents] -> [Section] -> Section
SRS.prpsOfDoc
[Sentence -> Contents
mkParagraph Sentence
purposeOfProgram, Sentence -> Contents
mkParagraph Sentence
developmentProcess] []
purposeOfDoc _ = [Contents] -> [Section] -> Section
SRS.prpsOfDoc [Sentence -> Contents
mkParagraph Sentence
developmentProcessParagraph] []
scopeOfRequirements :: Sentence -> Section
scopeOfRequirements :: Sentence -> Section
scopeOfRequirements req :: Sentence
req = [Contents] -> [Section] -> Section
SRS.scpOfReq [[Sentence] -> Contents
foldlSP
[NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
scope Sentence -> Sentence -> Sentence
`S.the_ofTheC` CI -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural CI
requirement, String -> Sentence
S "includes", Sentence
req]] []
charIntRdrF :: (Idea a) => a -> [Sentence] -> [Sentence] -> [Sentence] ->
Section -> Section
charIntRdrF :: a -> [Sentence] -> [Sentence] -> [Sentence] -> Section -> Section
charIntRdrF progName :: a
progName assumed :: [Sentence]
assumed topic :: [Sentence]
topic asset :: [Sentence]
asset r :: Section
r =
[Contents] -> [Section] -> Section
SRS.charOfIR (a
-> [Sentence] -> [Sentence] -> [Sentence] -> Section -> [Contents]
forall a.
Idea a =>
a
-> [Sentence] -> [Sentence] -> [Sentence] -> Section -> [Contents]
intReaderIntro a
progName [Sentence]
assumed [Sentence]
topic [Sentence]
asset Section
r) []
intReaderIntro :: (Idea a) => a -> [Sentence] -> [Sentence] -> [Sentence] ->
Section -> [Contents]
intReaderIntro :: a
-> [Sentence] -> [Sentence] -> [Sentence] -> Section -> [Contents]
intReaderIntro progName :: a
progName assumed :: [Sentence]
assumed topic :: [Sentence]
topic asset :: [Sentence]
asset sectionRef :: Section
sectionRef =
[[Sentence] -> Contents
foldlSP [String -> Sentence
S "Reviewers of this", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
documentation,
String -> Sentence
S "should have an understanding of" Sentence -> Sentence -> Sentence
+:+.
SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List ([Sentence]
assumed [Sentence] -> [Sentence] -> [Sentence]
forall a. [a] -> [a] -> [a]
++ [Sentence]
topic), Sentence
assetSent,
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (NamedChunk -> NP
forall t. NamedIdea t => t -> NP
the NamedChunk
user) Sentence -> Sentence -> Sentence
`S.of_` a -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short a
progName, String -> Sentence
S "can have a lower level" Sentence -> Sentence -> Sentence
`S.of_`
String -> Sentence
S "expertise, as explained" Sentence -> Sentence -> Sentence
`S.in_` Section -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Section
sectionRef]]
where
assetSent :: Sentence
assetSent = case [Sentence]
asset of
[] -> Sentence
EmptyS
_ -> String -> Sentence
S "It would be an asset to understand" Sentence -> Sentence -> Sentence
+:+. SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List [Sentence]
asset
orgSec :: NamedIdea c => Sentence -> c -> Section -> Sentence -> Section
orgSec :: Sentence -> c -> Section -> Sentence -> Section
orgSec i :: Sentence
i b :: c
b s :: Section
s t :: Sentence
t = [Contents] -> [Section] -> Section
SRS.orgOfDoc (Sentence -> c -> Section -> Sentence -> [Contents]
forall c.
NamedIdea c =>
Sentence -> c -> Section -> Sentence -> [Contents]
orgIntro Sentence
i c
b Section
s Sentence
t) []
orgIntro :: NamedIdea c => Sentence -> c -> Section -> Sentence -> [Contents]
orgIntro :: Sentence -> c -> Section -> Sentence -> [Contents]
orgIntro intro :: Sentence
intro bottom :: c
bottom bottomSec :: Section
bottomSec trailingSentence :: Sentence
trailingSentence = [[Sentence] -> Contents
foldlSP [
Sentence
intro, String -> Sentence
S "The presentation follows the standard pattern of presenting" Sentence -> Sentence -> Sentence
+:+.
SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List ((IdeaDict -> Sentence) -> [IdeaDict] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map IdeaDict -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural [NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw NamedChunk
Doc.goal, NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw NamedChunk
theory, NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw NamedChunk
definition, CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
assumption]),
String -> Sentence
S "For readers that would like a more bottom up approach" Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S "they can start reading the", Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Section
bottomSec (c -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural c
bottom)Sentence -> Sentence -> Sentence
`S.and_`
String -> Sentence
S "trace back to find any additional information they require"],
[Sentence] -> Contents
folder [[(CI, Section)] -> Sentence
forall c. NamedIdea c => [(c, Section)] -> Sentence
refineChain ([CI] -> [Section] -> [(CI, Section)]
forall a b. [a] -> [b] -> [(a, b)]
zip [CI
goalStmt, CI
thModel, CI
inModel]
[[Contents] -> [Section] -> Section
SRS.goalStmt [] [], [Contents] -> [Section] -> Section
SRS.thModel [] [], [Contents] -> [Section] -> Section
SRS.inModel [] []]), Sentence
trailingSentence]]
where
folder :: [Sentence] -> Contents
folder = case Sentence
trailingSentence of
EmptyS -> [Sentence] -> Contents
foldlSP_
_ -> [Sentence] -> Contents
foldlSP