module Drasil.Sections.SpecificSystemDescription (
specSysDescr,
probDescF,
termDefnF, termDefnF',
physSystDesc,
goalStmtF,
solutionCharSpecIntro,
assumpF,
thModF,
genDefnF,
dataDefnF,
inModelF,
datConF,
inDataConstTbl, outDataConstTbl, propCorSolF, auxSpecSent,
tInDataCstRef, tOutDataCstRef,
helperCI,
tmStub, ddStub, gdStub, imStub, pdStub
) where
import Language.Drasil hiding (variable)
import Language.Drasil.Development (showUID)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.NounPhrase.Combinators as NP
import qualified Language.Drasil.Sentence.Combinators as S
import Drasil.Sections.ReferenceMaterial(emptySectSentPlu)
import Data.Drasil.Concepts.Documentation (assumption, column, constraint,
datum, datumConstraint, inDatumConstraint, outDatumConstraint, definition,
element, general, goalStmt, information, input_, limitation, model, output_,
physical, physicalConstraint, physicalSystem, physSyst, problem,
problemDescription, propOfCorSol, purpose, quantity, requirement, scope,
section_, softwareConstraint, solutionCharacteristic, specification, symbol_,
system, table_, term_, theory, typUnc, uncertainty, user, value, variable)
import qualified Data.Drasil.Concepts.Documentation as DCD (sec)
import Data.Drasil.Concepts.Math (equation, parameter)
import Data.Drasil.TheoryConcepts (inModel, thModel, dataDefn, genDefn)
import SysInfo.Drasil (SystemInformation)
import Drasil.DocumentLanguage.Definitions (helperRefs)
import qualified Drasil.DocLang.SRS as SRS
import Control.Lens ((^.), over)
import Data.Maybe
specSysDescr :: [Section] -> Section
specSysDescr :: [Section] -> Section
specSysDescr = [Contents] -> [Section] -> Section
SRS.specSysDes [Contents
intro_]
intro_ :: Contents
intro_ :: Contents
intro_ = Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"This", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
section_, String -> Sentence
S String
"first presents the",
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problemDescription Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"which gives a high-level view of the",
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem, String -> Sentence
S String
"to be solved. This is followed by the", forall n. NamedIdea n => n -> Sentence
plural IdeaDict
solutionCharacteristic,
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
specification Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"which presents the",
SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List [forall n. NamedIdea n => n -> Sentence
plural CI
assumption, forall n. NamedIdea n => n -> Sentence
plural IdeaDict
theory, forall n. NamedIdea n => n -> Sentence
plural IdeaDict
definition], String -> Sentence
S String
"that are used"]
probDescF :: Sentence -> [Section] -> Section
probDescF :: Sentence -> [Section] -> Section
probDescF Sentence
EmptyS = [Contents] -> [Section] -> Section
SRS.probDesc [Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"There is no", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problemDescription]]
probDescF Sentence
prob = [Contents] -> [Section] -> Section
SRS.probDesc [Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSent [forall n. NounPhrase n => n -> Sentence
atStartNP (forall c. NamedIdea c => c -> NP
a_ IdeaDict
system) Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"needed to", Sentence
prob]]
termDefnF :: Concept c => Maybe Sentence -> [c] -> Section
termDefnF :: forall c. Concept c => Maybe Sentence -> [c] -> Section
termDefnF Maybe Sentence
_ [] = [Contents] -> [Section] -> Section
SRS.termAndDefn [Contents
introNoTermDefn] []
termDefnF Maybe Sentence
end [c]
lst = [Contents] -> [Section] -> Section
SRS.termAndDefn [Contents
intro, [Sentence] -> Contents
enumBulletU forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall {s}. (NamedIdea s, Definition s) => s -> Sentence
termDef [c]
lst] []
where intro :: Contents
intro = [Sentence] -> Contents
foldlSP_ [
String -> Sentence
S String
"This subsection provides a list of terms that are used in the subsequent",
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
section_ Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"their meaning, with the", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
purpose Sentence -> Sentence -> Sentence
`S.of_`
String -> Sentence
S String
"reducing ambiguity and making it easier to correctly understand the" Sentence -> Sentence -> Sentence
+:+.
forall n. NamedIdea n => n -> Sentence
plural CI
requirement, forall a. a -> Maybe a -> a
fromMaybe Sentence
EmptyS Maybe Sentence
end]
termDef :: s -> Sentence
termDef s
x = forall n. NamedIdea n => n -> Sentence
atStart s
x Sentence -> Sentence -> Sentence
+: Sentence
EmptyS Sentence -> Sentence -> Sentence
+:+. Sentence -> Sentence
capSent (s
x forall s a. s -> Getting a s a -> a
^. forall c. Definition c => Lens' c Sentence
defn)
termDefnF' :: Maybe Sentence -> [Contents] -> Section
termDefnF' :: Maybe Sentence -> [Contents] -> Section
termDefnF' Maybe Sentence
_ [] = [Contents] -> [Section] -> Section
SRS.termAndDefn [Contents
introNoTermDefn] []
termDefnF' Maybe Sentence
end [Contents]
otherContents = [Contents] -> [Section] -> Section
SRS.termAndDefn (Contents
intro forall a. a -> [a] -> [a]
: [Contents]
otherContents) []
where intro :: Contents
intro = [Sentence] -> Contents
foldlSP [String -> Sentence
S String
"This subsection provides a list of terms",
String -> Sentence
S String
"that are used in the subsequent", forall n. NamedIdea n => n -> Sentence
plural IdeaDict
section_,
String -> Sentence
S String
"and their meaning, with the", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
purpose,
String -> Sentence
S String
"of reducing ambiguity and making it easier to correctly",
String -> Sentence
S String
"understand the", forall n. NamedIdea n => n -> Sentence
plural CI
requirement Sentence -> Sentence -> Sentence
:+: forall b a. b -> (a -> b) -> Maybe a -> b
maybe Sentence
EmptyS (String -> Sentence
S String
"." Sentence -> Sentence -> Sentence
+:+) Maybe Sentence
end]
introNoTermDefn :: Contents
introNoTermDefn :: Contents
introNoTermDefn = Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [IdeaDict
term_, IdeaDict
definition]
physSystDesc :: Idea a => a -> [Sentence] -> LabelledContent -> [Contents] -> Section
physSystDesc :: forall a.
Idea a =>
a -> [Sentence] -> LabelledContent -> [Contents] -> Section
physSystDesc a
_ [] LabelledContent
_ [Contents]
_ = [Contents] -> [Section] -> Section
SRS.physSyst [Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [CI
physSyst]] []
physSystDesc a
progName [Sentence]
parts LabelledContent
fg [Contents]
other = [Contents] -> [Section] -> Section
SRS.physSyst (Contents
intro forall a. a -> [a] -> [a]
: Contents
bullets forall a. a -> [a] -> [a]
: LabelledContent -> Contents
LlC LabelledContent
fg forall a. a -> [a] -> [a]
: [Contents]
other) []
where intro :: Contents
intro = Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSentCol [forall n. NounPhrase n => n -> Sentence
atStartNP (forall c. NamedIdea c => c -> NP
the IdeaDict
physicalSystem) Sentence -> Sentence -> Sentence
`S.of_` forall c. Idea c => c -> Sentence
short a
progName Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"as shown in", forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
fg Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"includes the following", forall n. NamedIdea n => n -> Sentence
plural IdeaDict
element]
bullets :: Contents
bullets = Integer -> Sentence -> [Sentence] -> Contents
enumSimpleU Integer
1 (forall c. Idea c => c -> Sentence
short CI
physSyst) [Sentence]
parts
goalStmtF :: [Sentence] -> [Contents] -> Int -> Section
goalStmtF :: [Sentence] -> [Contents] -> Int -> Section
goalStmtF [Sentence]
_ [] Int
_ = [Contents] -> [Section] -> Section
SRS.goalStmt [Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [CI
goalStmt]] []
goalStmtF [] [Contents]
_ Int
_ = [Contents] -> [Section] -> Section
SRS.goalStmt [Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [CI
goalStmt]] []
goalStmtF [Sentence]
givenInputs [Contents]
otherContents Int
amt = [Contents] -> [Section] -> Section
SRS.goalStmt (Contents
introforall a. a -> [a] -> [a]
:[Contents]
otherContents) []
where intro :: Contents
intro = Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"Given" Sentence -> Sentence -> Sentence
+:+ SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List
[Sentence]
givenInputs Sentence -> Sentence -> Sentence
`sC` if Int
amt forall a. Eq a => a -> a -> Bool
== Int
1
then forall n. NounPhrase n => n -> Sentence
phraseNP (forall c. NamedIdea c => c -> NP
the CI
goalStmt) Sentence -> Sentence -> Sentence
+: String -> Sentence
S String
"is"
else forall n. NounPhrase n => n -> Sentence
pluralNP (forall c. NamedIdea c => c -> NP
the CI
goalStmt) Sentence -> Sentence -> Sentence
+: String -> Sentence
S String
"are"
solutionCharSpecIntro :: (Idea a) => a -> Section -> Contents
solutionCharSpecIntro :: forall a. Idea a => a -> Section -> Contents
solutionCharSpecIntro a
progName Section
instModelSection = [Sentence] -> Contents
foldlSP [forall n. NounPhrase n => n -> Sentence
atStartNP' (forall c. NamedIdea c => c -> NP
the CI
inModel),
String -> Sentence
S String
"that govern", forall c. Idea c => c -> Sentence
short a
progName, String -> Sentence
S String
"are presented in the" Sentence -> Sentence -> Sentence
+:+.
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Section
instModelSection (forall n. NamedIdea n => n -> Sentence
titleize CI
inModel Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
titleize CI
DCD.sec),
forall n. NounPhrase n => n -> Sentence
atStartNP (forall c. NamedIdea c => c -> NP
the IdeaDict
information), String -> Sentence
S String
"to understand",
String -> Sentence
S String
"meaning" Sentence -> Sentence -> Sentence
`S.the_ofThe` forall n. NamedIdea n => n -> Sentence
plural CI
inModel,
String -> Sentence
S String
"and their derivation is also presented, so that the", forall n. NamedIdea n => n -> Sentence
plural CI
inModel,
String -> Sentence
S String
"can be verified"]
assumpF :: [Contents] -> Section
assumpF :: [Contents] -> Section
assumpF [Contents]
otherContents = [Contents] -> [Section] -> Section
SRS.assumpt (forall a. [a] -> Contents
assumpIntro [Contents]
otherContents forall a. a -> [a] -> [a]
: [Contents]
otherContents) []
assumpIntro :: [a] -> Contents
assumpIntro :: forall a. [a] -> Contents
assumpIntro [] = Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [CI
assumption]
assumpIntro [a]
_ = Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSent
[String -> Sentence
S String
"This", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
section_, String -> Sentence
S String
"simplifies the original", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem,
String -> Sentence
S String
"and helps in developing the", forall n. NamedIdea n => n -> Sentence
plural CI
thModel, String -> Sentence
S String
"by filling in the",
String -> Sentence
S String
"missing", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
information, String -> Sentence
S String
"for the" Sentence -> Sentence -> Sentence
+:+. forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
physicalSystem,
forall n. NounPhrase n => n -> Sentence
atStartNP' (forall c. NamedIdea c => c -> NP
the CI
assumption), String -> Sentence
S String
"refine the", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
scope,
String -> Sentence
S String
"by providing more detail"]
thModF :: (Idea a) => a -> [Contents] -> Section
thModF :: forall a. Idea a => a -> [Contents] -> Section
thModF a
_ [] = [Contents] -> [Section] -> Section
SRS.thModel [Contents
thModIntroNoContent] []
thModF a
progName [Contents]
otherContents = [Contents] -> [Section] -> Section
SRS.thModel (forall a. Idea a => a -> Contents
thModIntro a
progName forall a. a -> [a] -> [a]
:
[Contents]
otherContents) []
thModIntro :: (Idea a) => a -> Contents
thModIntro :: forall a. Idea a => a -> Contents
thModIntro a
progName = [Sentence] -> Contents
foldlSP [String -> Sentence
S String
"This", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
section_, String -> Sentence
S String
"focuses on the",
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
general, forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
equation Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"laws that", forall c. Idea c => c -> Sentence
short a
progName, String -> Sentence
S String
"is based on"]
thModIntroNoContent :: Contents
thModIntroNoContent :: Contents
thModIntroNoContent = Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [CI
thModel]
genDefnF :: [Contents] -> Section
genDefnF :: [Contents] -> Section
genDefnF [Contents]
otherContents = [Contents] -> [Section] -> Section
SRS.genDefn (forall a. [a] -> Contents
generalDefinitionIntro [Contents]
otherContents forall a. a -> [a] -> [a]
: [Contents]
otherContents) []
generalDefinitionIntro :: [t] -> Contents
generalDefinitionIntro :: forall a. [a] -> Contents
generalDefinitionIntro [] = Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [CI
genDefn]
generalDefinitionIntro [t]
_ = [Sentence] -> Contents
foldlSP [String -> Sentence
S String
"This", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
section_,
String -> Sentence
S String
"collects the laws and", forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
equation,
String -> Sentence
S String
"that will be used to build the", forall n. NamedIdea n => n -> Sentence
plural CI
inModel]
dataDefnF :: Sentence -> [Contents] -> Section
dataDefnF :: Sentence -> [Contents] -> Section
dataDefnF Sentence
_ [] = [Contents] -> [Section] -> Section
SRS.dataDefn [Contents
dataDefnIntroNoContent] []
dataDefnF Sentence
endingSent [Contents]
otherContents = [Contents] -> [Section] -> Section
SRS.dataDefn (Sentence -> Contents
dataDefinitionIntro
Sentence
endingSent forall a. a -> [a] -> [a]
: [Contents]
otherContents) []
dataDefinitionIntro :: Sentence -> Contents
dataDefinitionIntro :: Sentence -> Contents
dataDefinitionIntro Sentence
closingSent = Sentence -> Contents
mkParagraph ([Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"This", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
section_,
String -> Sentence
S String
"collects and defines all the", forall n. NamedIdea n => n -> Sentence
plural IdeaDict
datum,
String -> Sentence
S String
"needed to build the", forall n. NamedIdea n => n -> Sentence
plural CI
inModel] Sentence -> Sentence -> Sentence
+:+ Sentence
closingSent)
dataDefnIntroNoContent :: Contents
dataDefnIntroNoContent :: Contents
dataDefnIntroNoContent = Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [CI
dataDefn]
inModelF :: Section -> Section -> Section -> Section -> [Contents] -> Section
inModelF :: Section -> Section -> Section -> Section -> [Contents] -> Section
inModelF Section
_ Section
_ Section
_ Section
_ [] = [Contents] -> [Section] -> Section
SRS.inModel
[Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [CI
inModel]] []
inModelF Section
probDes Section
datDef Section
theMod Section
genDef [Contents]
otherContents = [Contents] -> [Section] -> Section
SRS.inModel (Section -> Section -> Section -> Section -> Contents
inModelIntro
Section
probDes Section
datDef Section
theMod
Section
genDef forall a. a -> [a] -> [a]
: [Contents]
otherContents)
[]
inModelIntro :: Section -> Section -> Section -> Section -> Contents
inModelIntro :: Section -> Section -> Section -> Section -> Contents
inModelIntro Section
r1 Section
r2 Section
r3 Section
r4 = [Sentence] -> Contents
foldlSP [String -> Sentence
S String
"This", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
section_,
String -> Sentence
S String
"transforms the", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem, String -> Sentence
S String
"defined in the", forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Section
r1 forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problemDescription,
String -> Sentence
S String
"into one which is expressed in mathematical terms. It uses concrete",
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
symbol_, String -> Sentence
S String
"defined in the", forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Section
r2 forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => n -> Sentence
plural CI
dataDefn, String -> Sentence
S String
"to replace the abstract",
forall n. NounPhrase n => n -> Sentence
pluralNP forall a b. (a -> b) -> a -> b
$ IdeaDict
symbol_ forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`inThePP` IdeaDict
model, String -> Sentence
S String
"identified in", forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Section
r3 (forall n. NamedIdea n => n -> Sentence
plural CI
thModel) Sentence -> Sentence -> Sentence
`S.and_`
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Section
r4 (forall n. NamedIdea n => n -> Sentence
plural CI
genDefn)]
datConF :: (HasUncertainty c, Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) =>
Sentence -> [c] -> Section
datConF :: forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
Sentence -> [c] -> Section
datConF Sentence
_ [] = [Contents] -> [Section] -> Section
SRS.datCon [Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [IdeaDict
datumConstraint]] []
datConF Sentence
t [c]
c = [Contents] -> [Section] -> Section
SRS.datCon [Sentence -> Contents
dataConstraintParagraph Sentence
t, LabelledContent -> Contents
LlC forall a b. (a -> b) -> a -> b
$ forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
[c] -> LabelledContent
inDataConstTbl [c]
c] []
dataConstraintParagraph :: Sentence -> Contents
dataConstraintParagraph :: Sentence -> Contents
dataConstraintParagraph Sentence
trailingSent = [Sentence] -> Contents
foldlSP_ [Sentence
inputTableSent, Sentence
physConsSent,
Sentence
uncertSent, Sentence
conservConsSent, Sentence
typValSent, Sentence
trailingSent]
inputTableSent :: Sentence
inputTableSent :: Sentence
inputTableSent = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"The", forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef (forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
[c] -> LabelledContent
inDataConstTbl ([] :: [UncertQ])) forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
datumConstraint Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
table_, String -> Sentence
S String
"shows the",
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict
datumConstraint forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`onThePS` IdeaDict
input_), forall n. NamedIdea n => n -> Sentence
plural IdeaDict
variable]
physConsSent :: Sentence
physConsSent :: Sentence
physConsSent = [Sentence] -> Sentence
foldlSent [forall n. NounPhrase n => n -> Sentence
atStartNP forall a b. (a -> b) -> a -> b
$ NP -> NP
NP.the forall a b. (a -> b) -> a -> b
$ IdeaDict
column forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`for` IdeaDict
physical,
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
constraint, String -> Sentence
S String
"gives the", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
physical, forall n. NamedIdea n => n -> Sentence
plural IdeaDict
limitation,
String -> Sentence
S String
"on the range" Sentence -> Sentence -> Sentence
`S.of_` forall n. NamedIdea n => n -> Sentence
plural IdeaDict
value, String -> Sentence
S String
"that can be taken by the", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
variable]
uncertSent :: Sentence
uncertSent :: Sentence
uncertSent = [Sentence] -> Sentence
foldlSent [forall n. NounPhrase n => n -> Sentence
atStartNP (forall c. NamedIdea c => c -> NP
the IdeaDict
uncertainty), forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
column,
String -> Sentence
S String
"provides an estimate of the confidence with which the", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
physical,
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
quantity Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"can be measured", String -> Sentence
S String
"This", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
information,
String -> Sentence
S String
"would be part of the", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
input_, String -> Sentence
S String
"if one were performing an",
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
uncertainty, String -> Sentence
S String
"quantification exercise"]
conservConsSent :: Sentence
conservConsSent :: Sentence
conservConsSent = [Sentence] -> Sentence
foldlSent [forall n. NounPhrase n => n -> Sentence
atStartNP' (forall c. NamedIdea c => c -> NP
the IdeaDict
constraint) Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"conservative" Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"to give", forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
user Sentence -> Sentence -> Sentence
`S.the_ofThe` forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
model,
String -> Sentence
S String
"the flexibility to experiment with unusual situations"]
typValSent :: Sentence
typValSent :: Sentence
typValSent = [Sentence] -> Sentence
foldlSent [forall n. NounPhrase n => n -> Sentence
atStartNP (forall c. NamedIdea c => c -> NP
the IdeaDict
column) Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"typical",
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
value Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"intended to provide a feel for a common scenario"]
auxSpecSent :: Sentence
auxSpecSent :: Sentence
auxSpecSent = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"The", forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
SRS.valsOfAuxCons [] []) forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"auxiliary constants", String -> Sentence
S String
"give",
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
value Sentence -> Sentence -> Sentence
`S.the_ofThe` forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
specification, forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
parameter, String -> Sentence
S String
"used in the",
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef (forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
[c] -> LabelledContent
inDataConstTbl ([] :: [UncertQ])) forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
datumConstraint Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
table_]
mkDataConstraintTable :: [(Sentence, [Sentence])] -> UID -> Sentence -> LabelledContent
mkDataConstraintTable :: [(Sentence, [Sentence])] -> UID -> Sentence -> LabelledContent
mkDataConstraintTable [(Sentence, [Sentence])]
col UID
rf Sentence
lab = Reference -> RawContent -> LabelledContent
llcc (UID -> Reference
makeTabRef' UID
rf) forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry [Sentence] -> [[Sentence]] -> Sentence -> Bool -> RawContent
Table
([(Sentence, [Sentence])] -> ([Sentence], [[Sentence]])
mkTableFromColumns [(Sentence, [Sentence])]
col) Sentence
lab Bool
True
inDataConstTbl :: (HasUncertainty c, Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) =>
[c] -> LabelledContent
inDataConstTbl :: forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
[c] -> LabelledContent
inDataConstTbl [c]
qlst = [(Sentence, [Sentence])] -> UID -> Sentence -> LabelledContent
mkDataConstraintTable [(String -> Sentence
S String
"Var", forall a b. (a -> b) -> [a] -> [b]
map forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch forall a b. (a -> b) -> a -> b
$ forall a. HasSymbol a => [a] -> [a]
sortBySymbol [c]
qlst),
(forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
physicalConstraint, forall a b. (a -> b) -> [a] -> [b]
map forall c. (Constrained c, Quantity c) => c -> Sentence
fmtPhys forall a b. (a -> b) -> a -> b
$ forall a. HasSymbol a => [a] -> [a]
sortBySymbol [c]
qlst),
(forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
softwareConstraint, forall a b. (a -> b) -> [a] -> [b]
map forall c. (Constrained c, Quantity c) => c -> Sentence
fmtSfwr forall a b. (a -> b) -> a -> b
$ forall a. HasSymbol a => [a] -> [a]
sortBySymbol [c]
qlst),
(String -> Sentence
S String
"Typical Value", forall a b. (a -> b) -> [a] -> [b]
map (\c
q -> forall a. MayHaveUnit a => Sentence -> a -> Sentence
fmtU (ModelExpr -> Sentence
eS forall a b. (a -> b) -> a -> b
$ forall c. Express c => c -> ModelExpr
express forall a b. (a -> b) -> a -> b
$ forall {s}. (HasUID s, HasReasVal s) => s -> Expr
getRVal c
q) c
q) forall a b. (a -> b) -> a -> b
$ forall a. HasSymbol a => [a] -> [a]
sortBySymbol [c]
qlst),
(forall c. Idea c => c -> Sentence
short CI
typUnc, forall a b. (a -> b) -> [a] -> [b]
map forall c. HasUncertainty c => c -> Sentence
typUncr forall a b. (a -> b) -> a -> b
$ forall a. HasSymbol a => [a] -> [a]
sortBySymbol [c]
qlst)] (IdeaDict
inDatumConstraint forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid) forall a b. (a -> b) -> a -> b
$
forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
inDatumConstraint
where
getRVal :: s -> Expr
getRVal s
c = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"getRVal found no Expr for " forall a. [a] -> [a] -> [a]
++ forall a. HasUID a => a -> String
showUID s
c) (s
c forall s a. s -> Getting a s a -> a
^. forall c. HasReasVal c => Lens' c (Maybe Expr)
reasVal)
outDataConstTbl :: (Quantity c, Constrained c) => [c] -> LabelledContent
outDataConstTbl :: forall c. (Quantity c, Constrained c) => [c] -> LabelledContent
outDataConstTbl [c]
qlst = [(Sentence, [Sentence])] -> UID -> Sentence -> LabelledContent
mkDataConstraintTable [(String -> Sentence
S String
"Var", forall a b. (a -> b) -> [a] -> [b]
map forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch [c]
qlst),
(forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
physicalConstraint, forall a b. (a -> b) -> [a] -> [b]
map forall c. (Constrained c, Quantity c) => c -> Sentence
fmtPhys [c]
qlst),
(forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
softwareConstraint, forall a b. (a -> b) -> [a] -> [b]
map forall c. (Constrained c, Quantity c) => c -> Sentence
fmtSfwr [c]
qlst)] (IdeaDict
outDatumConstraint forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid) forall a b. (a -> b) -> a -> b
$
forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
outDatumConstraint
tInDataCstRef, tOutDataCstRef :: Reference
tInDataCstRef :: Reference
tInDataCstRef = UID -> Reference
makeTabRef' (IdeaDict
inDatumConstraint forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid)
tOutDataCstRef :: Reference
tOutDataCstRef = UID -> Reference
makeTabRef' (IdeaDict
outDatumConstraint forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid)
fmtPhys :: (Constrained c, Quantity c) => c -> Sentence
fmtPhys :: forall c. (Constrained c, Quantity c) => c -> Sentence
fmtPhys c
c = forall c. Quantity c => c -> [ConstraintE] -> Sentence
foldConstraints c
c forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter forall e. Constraint e -> Bool
isPhysC (c
c forall s a. s -> Getting a s a -> a
^. forall c. Constrained c => Lens' c [ConstraintE]
constraints)
fmtSfwr :: (Constrained c, Quantity c) => c -> Sentence
fmtSfwr :: forall c. (Constrained c, Quantity c) => c -> Sentence
fmtSfwr c
c = forall c. Quantity c => c -> [ConstraintE] -> Sentence
foldConstraints c
c forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter forall e. Constraint e -> Bool
isSfwrC (c
c forall s a. s -> Getting a s a -> a
^. forall c. Constrained c => Lens' c [ConstraintE]
constraints)
propCorSolF :: (Quantity c, Constrained c) => [c] -> [Contents] -> Section
propCorSolF :: forall c.
(Quantity c, Constrained c) =>
[c] -> [Contents] -> Section
propCorSolF [] [] = [Contents] -> [Section] -> Section
SRS.propCorSol [Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [IdeaDict
propOfCorSol]] []
propCorSolF [] [Contents]
con = [Contents] -> [Section] -> Section
SRS.propCorSol [Contents]
con []
propCorSolF [c]
c [Contents]
con = [Contents] -> [Section] -> Section
SRS.propCorSol ([Contents
propsIntro, LabelledContent -> Contents
LlC forall a b. (a -> b) -> a -> b
$ forall c. (Quantity c, Constrained c) => [c] -> LabelledContent
outDataConstTbl [c]
c] forall a. [a] -> [a] -> [a]
++ [Contents]
con) []
propsIntro :: Contents
propsIntro :: Contents
propsIntro = [Sentence] -> Contents
foldlSP_ [Sentence
outputTableSent, Sentence
physConsSent]
outputTableSent :: Sentence
outputTableSent :: Sentence
outputTableSent = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"The", forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef (forall c. (Quantity c, Constrained c) => [c] -> LabelledContent
outDataConstTbl ([] :: [UncertQ])) forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
datumConstraint Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
table_, String -> Sentence
S String
"shows the",
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict
datumConstraint forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`onThePS` IdeaDict
output_), forall n. NamedIdea n => n -> Sentence
plural IdeaDict
variable]
helperCI :: ConceptInstance -> SystemInformation -> ConceptInstance
helperCI :: ConceptInstance -> SystemInformation -> ConceptInstance
helperCI ConceptInstance
a SystemInformation
c = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over forall c. Definition c => Lens' c Sentence
defn (\Sentence
x -> [Sentence] -> Sentence
foldlSent_ [Sentence
x, Sentence -> Sentence
refby forall a b. (a -> b) -> a -> b
$ forall t. HasUID t => t -> SystemInformation -> Sentence
helperRefs ConceptInstance
a SystemInformation
c]) ConceptInstance
a
where
refby :: Sentence -> Sentence
refby Sentence
EmptyS = Sentence
EmptyS
refby Sentence
sent = Sentence -> Sentence
sParen forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"RefBy:" Sentence -> Sentence -> Sentence
+:+. Sentence
sent
tmStub, ddStub, gdStub, imStub, pdStub :: Section
tmStub :: Section
tmStub = [Contents] -> [Section] -> Section
SRS.thModel [] []
ddStub :: Section
ddStub = [Contents] -> [Section] -> Section
SRS.dataDefn [] []
gdStub :: Section
gdStub = [Contents] -> [Section] -> Section
SRS.genDefn [] []
imStub :: Section
imStub = [Contents] -> [Section] -> Section
SRS.inModel [] []
pdStub :: Section
pdStub = [Contents] -> [Section] -> Section
SRS.probDesc [] []