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 Control.Lens ((^.), over)
import Data.Maybe
import Drasil.Database (UID, HasUID(..), showUID)
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, scope,
section_, softwareConstraint, solutionCharacteristic, 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 Drasil.Metadata (inModel, thModel, dataDefn, genDefn, requirement, specification)
import Drasil.System (System)
import Language.Drasil hiding (variable)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.NounPhrase.Combinators as NP
import qualified Language.Drasil.Sentence.Combinators as S
import qualified Language.Drasil.Development as D
import Drasil.Document.Contents (enumBulletU, enumSimpleU, foldlSP, foldlSP_)
import Drasil.DocumentLanguage.Definitions (helperRefs)
import qualified Drasil.DocLang.SRS as SRS
import Drasil.Sections.ReferenceMaterial(emptySectSentPlu)
import Drasil.Sentence.Combinators (mkTableFromColumns, fmtU, typUncr)
specSysDescr :: [Section] -> Section
specSysDescr :: [Section] -> Section
specSysDescr = [Contents] -> [Section] -> Section
SRS.specSysDes [Contents
intro_]
intro_ :: Contents
intro_ :: Contents
intro_ = Sentence -> Contents
mkParagraph (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"This", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
section_, String -> Sentence
S String
"first presents the",
IdeaDict -> Sentence
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",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem, String -> Sentence
S String
"to be solved. This is followed by the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
solutionCharacteristic,
IdeaDict -> Sentence
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 [CI -> Sentence
forall n. NamedIdea n => n -> Sentence
plural CI
assumption, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
theory, IdeaDict -> Sentence
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 (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"There is no", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problemDescription]]
probDescF Sentence
prob = [Contents] -> [Section] -> Section
SRS.probDesc [Sentence -> Contents
mkParagraph (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSent [NPStruct -> Sentence
D.toSent (NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
atStartNP (IdeaDict -> NP
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 ([Sentence] -> Contents) -> [Sentence] -> Contents
forall a b. (a -> b) -> a -> b
$ (c -> Sentence) -> [c] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map c -> Sentence
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",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
section_ Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"their meaning, with the", IdeaDict -> Sentence
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
+:+.
CI -> Sentence
forall n. NamedIdea n => n -> Sentence
plural CI
requirement, Sentence -> Maybe Sentence -> Sentence
forall a. a -> Maybe a -> a
fromMaybe Sentence
EmptyS Maybe Sentence
end]
termDef :: s -> Sentence
termDef s
x = s -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart s
x Sentence -> Sentence -> Sentence
+: Sentence
EmptyS Sentence -> Sentence -> Sentence
+:+. Sentence -> Sentence
capSent (s
x s -> Getting Sentence s Sentence -> Sentence
forall s a. s -> Getting a s a -> a
^. Getting Sentence s Sentence
forall c. Definition c => Lens' c Sentence
Lens' s 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 Contents -> [Contents] -> [Contents]
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", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
section_,
String -> Sentence
S String
"and their meaning, with the", IdeaDict -> Sentence
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", CI -> Sentence
forall n. NamedIdea n => n -> Sentence
plural CI
requirement Sentence -> Sentence -> Sentence
:+: Sentence -> (Sentence -> Sentence) -> Maybe 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 (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [IdeaDict] -> Sentence
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 (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [CI] -> Sentence
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 Contents -> [Contents] -> [Contents]
forall a. a -> [a] -> [a]
: Contents
bullets Contents -> [Contents] -> [Contents]
forall a. a -> [a] -> [a]
: LabelledContent -> Contents
LlC LabelledContent
fg Contents -> [Contents] -> [Contents]
forall a. a -> [a] -> [a]
: [Contents]
other) []
where intro :: Contents
intro = Sentence -> Contents
mkParagraph (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSentCol [NPStruct -> Sentence
D.toSent (NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
atStartNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
physicalSystem)) Sentence -> Sentence -> Sentence
`S.of_` a -> Sentence
forall c. Idea c => c -> Sentence
short a
progName Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"as shown in", LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
fg Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"includes the following", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
element]
bullets :: Contents
bullets = Integer -> Sentence -> [Sentence] -> Contents
enumSimpleU Integer
1 (CI -> Sentence
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 (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [CI] -> Sentence
forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [CI
goalStmt]] []
goalStmtF [] [Contents]
_ Int
_ = [Contents] -> [Section] -> Section
SRS.goalStmt [Sentence -> Contents
mkParagraph (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [CI] -> Sentence
forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [CI
goalStmt]] []
goalStmtF [Sentence]
givenInputs [Contents]
otherContents Int
amt = [Contents] -> [Section] -> Section
SRS.goalStmt (Contents
introContents -> [Contents] -> [Contents]
forall a. a -> [a] -> [a]
:[Contents]
otherContents) []
where intro :: Contents
intro = Sentence -> Contents
mkParagraph (Sentence -> Contents) -> Sentence -> Contents
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 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
then NPStruct -> Sentence
D.toSent (NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
phraseNP (CI -> NP
forall c. NamedIdea c => c -> NP
the CI
goalStmt)) Sentence -> Sentence -> Sentence
+: String -> Sentence
S String
"is"
else NPStruct -> Sentence
D.toSent (NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
pluralNP (CI -> NP
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 [NPStruct -> Sentence
D.toSent (NPStruct -> Sentence) -> NPStruct -> Sentence
forall a b. (a -> b) -> a -> b
$ NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
atStartNP' (CI -> NP
forall c. NamedIdea c => c -> NP
the CI
inModel),
String -> Sentence
S String
"that govern", a -> Sentence
forall c. Idea c => c -> Sentence
short a
progName, String -> Sentence
S String
"are presented in the" Sentence -> Sentence -> Sentence
+:+.
Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Section
instModelSection (CI -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize CI
inModel Sentence -> Sentence -> Sentence
+:+ CI -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize CI
DCD.sec),
NPStruct -> Sentence
D.toSent (NPStruct -> Sentence) -> NPStruct -> Sentence
forall a b. (a -> b) -> a -> b
$ NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
atStartNP (IdeaDict -> NP
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` CI -> Sentence
forall n. NamedIdea n => n -> Sentence
plural CI
inModel,
String -> Sentence
S String
"and their derivation is also presented, so that the", CI -> Sentence
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 ([Contents] -> Contents
forall a. [a] -> Contents
assumpIntro [Contents]
otherContents Contents -> [Contents] -> [Contents]
forall a. a -> [a] -> [a]
: [Contents]
otherContents) []
assumpIntro :: [a] -> Contents
assumpIntro :: forall a. [a] -> Contents
assumpIntro [] = Sentence -> Contents
mkParagraph (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [CI] -> Sentence
forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [CI
assumption]
assumpIntro [a]
_ = Sentence -> Contents
mkParagraph (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSent
[String -> Sentence
S String
"This", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
section_, String -> Sentence
S String
"simplifies the original", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem,
String -> Sentence
S String
"and helps in developing the", CI -> Sentence
forall n. NamedIdea n => n -> Sentence
plural CI
thModel, String -> Sentence
S String
"by filling in the",
String -> Sentence
S String
"missing", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
information, String -> Sentence
S String
"for the" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
physicalSystem,
NPStruct -> Sentence
D.toSent (NPStruct -> Sentence) -> NPStruct -> Sentence
forall a b. (a -> b) -> a -> b
$ NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
atStartNP' (CI -> NP
forall c. NamedIdea c => c -> NP
the CI
assumption), String -> Sentence
S String
"refine the", IdeaDict -> Sentence
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 (a -> Contents
forall a. Idea a => a -> Contents
thModIntro a
progName Contents -> [Contents] -> [Contents]
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", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
section_, String -> Sentence
S String
"focuses on the",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
general, ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
equation Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"laws that", a -> Sentence
forall c. Idea c => c -> Sentence
short a
progName, String -> Sentence
S String
"is based on"]
thModIntroNoContent :: Contents
thModIntroNoContent :: Contents
thModIntroNoContent = Sentence -> Contents
mkParagraph (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [CI] -> Sentence
forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [CI
thModel]
genDefnF :: [Contents] -> Section
genDefnF :: [Contents] -> Section
genDefnF [Contents]
otherContents = [Contents] -> [Section] -> Section
SRS.genDefn ([Contents] -> Contents
forall a. [a] -> Contents
generalDefinitionIntro [Contents]
otherContents Contents -> [Contents] -> [Contents]
forall a. a -> [a] -> [a]
: [Contents]
otherContents) []
generalDefinitionIntro :: [t] -> Contents
generalDefinitionIntro :: forall a. [a] -> Contents
generalDefinitionIntro [] = Sentence -> Contents
mkParagraph (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [CI] -> Sentence
forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [CI
genDefn]
generalDefinitionIntro [t]
_ = [Sentence] -> Contents
foldlSP [String -> Sentence
S String
"This", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
section_,
String -> Sentence
S String
"collects the laws and", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
equation,
String -> Sentence
S String
"that will be used to build the", CI -> Sentence
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 Contents -> [Contents] -> [Contents]
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", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
section_,
String -> Sentence
S String
"collects and defines all the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
datum,
String -> Sentence
S String
"needed to build the", CI -> Sentence
forall n. NamedIdea n => n -> Sentence
plural CI
inModel] Sentence -> Sentence -> Sentence
+:+ Sentence
closingSent)
dataDefnIntroNoContent :: Contents
dataDefnIntroNoContent :: Contents
dataDefnIntroNoContent = Sentence -> Contents
mkParagraph (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [CI] -> Sentence
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 (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [CI] -> Sentence
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 Contents -> [Contents] -> [Contents]
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", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
section_,
String -> Sentence
S String
"transforms the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem, String -> Sentence
S String
"defined in the", Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Section
r1 (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problemDescription,
String -> Sentence
S String
"into one which is expressed in mathematical terms. It uses concrete",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
symbol_, String -> Sentence
S String
"defined in the", Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Section
r2 (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ CI -> Sentence
forall n. NamedIdea n => n -> Sentence
plural CI
dataDefn, String -> Sentence
S String
"to replace the abstract",
NPStruct -> Sentence
D.toSent (NPStruct -> Sentence) -> NPStruct -> Sentence
forall a b. (a -> b) -> a -> b
$ NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
pluralNP (NP -> NPStruct) -> NP -> NPStruct
forall a b. (a -> b) -> a -> b
$ IdeaDict
symbol_ IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`inThePP` IdeaDict
model, String -> Sentence
S String
"identified in", Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Section
r3 (CI -> Sentence
forall n. NamedIdea n => n -> Sentence
plural CI
thModel) Sentence -> Sentence -> Sentence
`S.and_`
Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Section
r4 (CI -> Sentence
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 (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [IdeaDict] -> Sentence
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 (LabelledContent -> Contents) -> LabelledContent -> Contents
forall a b. (a -> b) -> a -> b
$ [c] -> LabelledContent
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", LabelledContent -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([UncertQ] -> LabelledContent
forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
[c] -> LabelledContent
inDataConstTbl ([] :: [UncertQ])) (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
inDatumConstraint Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
table_, String -> Sentence
S String
"shows the",
NPStruct -> Sentence
D.toSent (NPStruct -> Sentence) -> NPStruct -> Sentence
forall a b. (a -> b) -> a -> b
$ NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
pluralNP (IdeaDict
datumConstraint IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`onThePS` IdeaDict
input_), IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
variable]
physConsSent :: Sentence
physConsSent :: Sentence
physConsSent = [Sentence] -> Sentence
foldlSent [NPStruct -> Sentence
D.toSent (NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
atStartNP (NP -> NPStruct) -> NP -> NPStruct
forall a b. (a -> b) -> a -> b
$ NP -> NP
NP.the (NP -> NP) -> NP -> NP
forall a b. (a -> b) -> a -> b
$ IdeaDict
column IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`for` IdeaDict
physical),
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
constraint, String -> Sentence
S String
"gives the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
physical, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
limitation,
String -> Sentence
S String
"on the range" Sentence -> Sentence -> Sentence
`S.of_` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
value, String -> Sentence
S String
"that can be taken by the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
variable]
uncertSent :: Sentence
uncertSent :: Sentence
uncertSent = [Sentence] -> Sentence
foldlSent [NPStruct -> Sentence
D.toSent (NPStruct -> Sentence) -> NPStruct -> Sentence
forall a b. (a -> b) -> a -> b
$ NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
atStartNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
uncertainty), IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
column,
String -> Sentence
S String
"provides an estimate of the confidence with which the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
physical,
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
quantity Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"can be measured", String -> Sentence
S String
"This", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
information,
String -> Sentence
S String
"would be part of the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
input_, String -> Sentence
S String
"if one were performing an",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
uncertainty, String -> Sentence
S String
"quantification exercise"]
conservConsSent :: Sentence
conservConsSent :: Sentence
conservConsSent = [Sentence] -> Sentence
foldlSent [NPStruct -> Sentence
D.toSent (NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
atStartNP' (IdeaDict -> NP
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", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
user Sentence -> Sentence -> Sentence
`S.the_ofThe` IdeaDict -> Sentence
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 [NPStruct -> Sentence
D.toSent (NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
atStartNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
column)) Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"typical",
IdeaDict -> Sentence
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", Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
SRS.valsOfAuxCons [] []) (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"auxiliary constants", String -> Sentence
S String
"give",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
value Sentence -> Sentence -> Sentence
`S.the_ofThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
specification, ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
parameter, String -> Sentence
S String
"used in the",
LabelledContent -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([UncertQ] -> LabelledContent
forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
[c] -> LabelledContent
inDataConstTbl ([] :: [UncertQ])) (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
inDatumConstraint Sentence -> Sentence -> Sentence
+:+ IdeaDict -> 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 = UID -> RawContent -> LabelledContent
llccTab' UID
rf (RawContent -> LabelledContent) -> RawContent -> LabelledContent
forall a b. (a -> b) -> a -> b
$ ([Sentence] -> [[Sentence]] -> Sentence -> Bool -> RawContent)
-> ([Sentence], [[Sentence]]) -> Sentence -> Bool -> RawContent
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", (c -> Sentence) -> [c] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map c -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ([c] -> [Sentence]) -> [c] -> [Sentence]
forall a b. (a -> b) -> a -> b
$ [c] -> [c]
forall a. HasSymbol a => [a] -> [a]
sortBySymbol [c]
qlst),
(IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
physicalConstraint, (c -> Sentence) -> [c] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map c -> Sentence
forall c. (Constrained c, Quantity c) => c -> Sentence
fmtPhys ([c] -> [Sentence]) -> [c] -> [Sentence]
forall a b. (a -> b) -> a -> b
$ [c] -> [c]
forall a. HasSymbol a => [a] -> [a]
sortBySymbol [c]
qlst),
(IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
softwareConstraint, (c -> Sentence) -> [c] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map c -> Sentence
forall c. (Constrained c, Quantity c) => c -> Sentence
fmtSfwr ([c] -> [Sentence]) -> [c] -> [Sentence]
forall a b. (a -> b) -> a -> b
$ [c] -> [c]
forall a. HasSymbol a => [a] -> [a]
sortBySymbol [c]
qlst),
(String -> Sentence
S String
"Typical Value", (c -> Sentence) -> [c] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map (\c
q -> Sentence -> c -> Sentence
forall a. MayHaveUnit a => Sentence -> a -> Sentence
fmtU (ModelExpr -> Sentence
eS (ModelExpr -> Sentence) -> ModelExpr -> Sentence
forall a b. (a -> b) -> a -> b
$ Expr -> ModelExpr
forall c. Express c => c -> ModelExpr
express (Expr -> ModelExpr) -> Expr -> ModelExpr
forall a b. (a -> b) -> a -> b
$ c -> Expr
forall {s}. (HasUID s, HasReasVal s) => s -> Expr
getRVal c
q) c
q) ([c] -> [Sentence]) -> [c] -> [Sentence]
forall a b. (a -> b) -> a -> b
$ [c] -> [c]
forall a. HasSymbol a => [a] -> [a]
sortBySymbol [c]
qlst),
(CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
typUnc, (c -> Sentence) -> [c] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map (\c
q -> (Double, Maybe Int) -> Sentence
typUncr (c -> Double
forall x. HasUncertainty x => x -> Double
uncVal c
q, c -> Maybe Int
forall x. HasUncertainty x => x -> Maybe Int
uncPrec c
q)) ([c] -> [Sentence]) -> [c] -> [Sentence]
forall a b. (a -> b) -> a -> b
$ [c] -> [c]
forall a. HasSymbol a => [a] -> [a]
sortBySymbol [c]
qlst)]
(IdeaDict
inDatumConstraint IdeaDict -> Getting UID IdeaDict UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID IdeaDict UID
forall c. HasUID c => Getter c UID
Getter IdeaDict UID
uid) (Sentence -> LabelledContent) -> Sentence -> LabelledContent
forall a b. (a -> b) -> a -> b
$ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
inDatumConstraint
where
getRVal :: s -> Expr
getRVal s
c = Expr -> Maybe Expr -> Expr
forall a. a -> Maybe a -> a
fromMaybe (String -> Expr
forall a. HasCallStack => String -> a
error (String -> Expr) -> String -> Expr
forall a b. (a -> b) -> a -> b
$ String
"getRVal found no Expr for " String -> String -> String
forall a. [a] -> [a] -> [a]
++ s -> String
forall a. HasUID a => a -> String
showUID s
c) (s
c s -> Getting (Maybe Expr) s (Maybe Expr) -> Maybe Expr
forall s a. s -> Getting a s a -> a
^. Getting (Maybe Expr) s (Maybe Expr)
forall c. HasReasVal c => Lens' c (Maybe Expr)
Lens' s (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", (c -> Sentence) -> [c] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map c -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch [c]
qlst),
(IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
physicalConstraint, (c -> Sentence) -> [c] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map c -> Sentence
forall c. (Constrained c, Quantity c) => c -> Sentence
fmtPhys [c]
qlst),
(IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
softwareConstraint, (c -> Sentence) -> [c] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map c -> Sentence
forall c. (Constrained c, Quantity c) => c -> Sentence
fmtSfwr [c]
qlst)] (IdeaDict
outDatumConstraint IdeaDict -> Getting UID IdeaDict UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID IdeaDict UID
forall c. HasUID c => Getter c UID
Getter IdeaDict UID
uid) (Sentence -> LabelledContent) -> Sentence -> LabelledContent
forall a b. (a -> b) -> a -> b
$
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
outDatumConstraint
tInDataCstRef, tOutDataCstRef :: Reference
tInDataCstRef :: Reference
tInDataCstRef = UID -> Reference
makeTabRef' (IdeaDict
inDatumConstraint IdeaDict -> Getting UID IdeaDict UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID IdeaDict UID
forall c. HasUID c => Getter c UID
Getter IdeaDict UID
uid)
tOutDataCstRef :: Reference
tOutDataCstRef = UID -> Reference
makeTabRef' (IdeaDict
outDatumConstraint IdeaDict -> Getting UID IdeaDict UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID IdeaDict UID
forall c. HasUID c => Getter c UID
Getter IdeaDict UID
uid)
fmtPhys :: (Constrained c, Quantity c) => c -> Sentence
fmtPhys :: forall c. (Constrained c, Quantity c) => c -> Sentence
fmtPhys c
c = c -> [ConstraintE] -> Sentence
forall c. Quantity c => c -> [ConstraintE] -> Sentence
foldConstraints c
c ([ConstraintE] -> Sentence) -> [ConstraintE] -> Sentence
forall a b. (a -> b) -> a -> b
$ (ConstraintE -> Bool) -> [ConstraintE] -> [ConstraintE]
forall a. (a -> Bool) -> [a] -> [a]
filter ConstraintE -> Bool
forall e. Constraint e -> Bool
isPhysC (c
c c -> Getting [ConstraintE] c [ConstraintE] -> [ConstraintE]
forall s a. s -> Getting a s a -> a
^. Getting [ConstraintE] c [ConstraintE]
forall c. Constrained c => Lens' c [ConstraintE]
Lens' c [ConstraintE]
constraints)
fmtSfwr :: (Constrained c, Quantity c) => c -> Sentence
fmtSfwr :: forall c. (Constrained c, Quantity c) => c -> Sentence
fmtSfwr c
c = c -> [ConstraintE] -> Sentence
forall c. Quantity c => c -> [ConstraintE] -> Sentence
foldConstraints c
c ([ConstraintE] -> Sentence) -> [ConstraintE] -> Sentence
forall a b. (a -> b) -> a -> b
$ (ConstraintE -> Bool) -> [ConstraintE] -> [ConstraintE]
forall a. (a -> Bool) -> [a] -> [a]
filter ConstraintE -> Bool
forall e. Constraint e -> Bool
isSfwrC (c
c c -> Getting [ConstraintE] c [ConstraintE] -> [ConstraintE]
forall s a. s -> Getting a s a -> a
^. Getting [ConstraintE] c [ConstraintE]
forall c. Constrained c => Lens' c [ConstraintE]
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 (Sentence -> Contents) -> Sentence -> Contents
forall a b. (a -> b) -> a -> b
$ [IdeaDict] -> Sentence
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 (LabelledContent -> Contents) -> LabelledContent -> Contents
forall a b. (a -> b) -> a -> b
$ [c] -> LabelledContent
forall c. (Quantity c, Constrained c) => [c] -> LabelledContent
outDataConstTbl [c]
c] [Contents] -> [Contents] -> [Contents]
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", LabelledContent -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([UncertQ] -> LabelledContent
forall c. (Quantity c, Constrained c) => [c] -> LabelledContent
outDataConstTbl ([] :: [UncertQ])) (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
outDatumConstraint Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
table_, String -> Sentence
S String
"shows the",
NPStruct -> Sentence
D.toSent (NPStruct -> Sentence) -> NPStruct -> Sentence
forall a b. (a -> b) -> a -> b
$ NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
pluralNP (IdeaDict
datumConstraint IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`onThePS` IdeaDict
output_), IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
variable]
helperCI :: ConceptInstance -> System -> ConceptInstance
helperCI :: ConceptInstance -> System -> ConceptInstance
helperCI ConceptInstance
a System
c = ASetter ConceptInstance ConceptInstance Sentence Sentence
-> (Sentence -> Sentence) -> ConceptInstance -> ConceptInstance
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ConceptInstance ConceptInstance Sentence Sentence
forall c. Definition c => Lens' c Sentence
Lens' ConceptInstance Sentence
defn (\Sentence
x -> [Sentence] -> Sentence
foldlSent_ [Sentence
x, Sentence -> Sentence
refby (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ ConceptInstance -> System -> Sentence
forall t. HasUID t => t -> System -> Sentence
helperRefs ConceptInstance
a System
c]) ConceptInstance
a
where
refby :: Sentence -> Sentence
refby Sentence
EmptyS = Sentence
EmptyS
refby Sentence
sent = Sentence -> Sentence
sParen (Sentence -> Sentence) -> Sentence -> Sentence
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 [] []