{-# LANGUAGE PostfixOperators #-}
module Drasil.GlassBR.Body where
import Control.Lens ((^.))
import Language.Drasil hiding (organization, section, variable)
import Drasil.SRSDocument
import Drasil.DocLang (auxSpecSent, termDefnF')
import qualified Drasil.DocLang.SRS as SRS (reference, assumpt, inModel)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.Concepts.Computation (computerApp, inDatum, compcon, algorithm)
import Data.Drasil.Concepts.Documentation as Doc (appendix, assumption,
characteristic, company, condition, dataConst, datum, doccon, doccon',
environment, input_, interface, model, physical, problem, product_,
software, softwareConstraint, softwareSys, srsDomains, standard, sysCont,
system, term_, user, value, variable, reference, definition)
import qualified Data.Drasil.Concepts.Documentation as Doc (srs)
import Data.Drasil.TheoryConcepts as Doc (dataDefn, inModel, thModel)
import Data.Drasil.Concepts.Education as Edu (civilEng, scndYrCalculus, structuralMechanics,
educon)
import Data.Drasil.Concepts.Math (graph, mathcon, mathcon')
import Data.Drasil.Concepts.PhysicalProperties (dimension, physicalcon, materialProprty)
import Data.Drasil.Concepts.Physics (distance)
import Data.Drasil.Concepts.Software (correctness, verifiability,
understandability, reusability, maintainability, portability, softwarecon)
import Data.Drasil.Software.Products (sciCompS)
import Data.Drasil.People (mCampidelli, nikitha, spencerSmith)
import Data.Drasil.SI_Units (kilogram, metre, newton, pascal, second, fundamentals,
derived)
import Drasil.GlassBR.Assumptions (assumptionConstants, assumptions)
import Drasil.GlassBR.Changes (likelyChgs, unlikelyChgs)
import Drasil.GlassBR.Concepts (acronyms, blastRisk, glaPlane, glaSlab, glassBR,
ptOfExplsn, con, con', glass)
import Drasil.GlassBR.DataDefs (configFp)
import qualified Drasil.GlassBR.DataDefs as GB (dataDefs)
import Drasil.GlassBR.Figures
import Drasil.GlassBR.Goals (goals)
import Drasil.GlassBR.IMods (symb, iMods, instModIntro, qDefns)
import Drasil.GlassBR.References (astm2009, astm2012, astm2016, citations)
import Drasil.GlassBR.Requirements (funcReqs, inReqDesc, funcReqsTables, nonfuncReqs)
import Drasil.GlassBR.Symbols (symbolsForTable, thisSymbols)
import Drasil.GlassBR.TMods (tMods)
import Drasil.GlassBR.Unitals (blast, blastTy, bomb, explosion, constants,
constrained, inputDataConstraints, inputs, outputs, specParamVals, glassTy,
glassTypes, glBreakage, lateralLoad, load, loadTypes, pbTol, probBr, stressDistFac, probBreak,
sD, termsWithAccDefn, termsWithDefsOnly, terms)
srs :: Document
srs :: Document
srs = SRSDecl
-> (IdeaDict -> IdeaDict -> Sentence)
-> SystemInformation
-> 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) SystemInformation
si
fullSI :: SystemInformation
fullSI :: SystemInformation
fullSI = SRSDecl -> SystemInformation -> SystemInformation
fillcdbSRS SRSDecl
mkSRS SystemInformation
si
printSetting :: PrintingInformation
printSetting :: PrintingInformation
printSetting = SystemInformation
-> Stage -> PrintingConfiguration -> PrintingInformation
piSys SystemInformation
fullSI Stage
Equational PrintingConfiguration
defaultConfiguration
si :: SystemInformation
si :: SystemInformation
si = SI {
_sys :: CI
_sys = CI
glassBR,
_kind :: CI
_kind = CI
Doc.srs,
_authors :: People
_authors = [Person
nikitha, Person
spencerSmith],
_purpose :: Purpose
_purpose = [Sentence
purp],
_background :: Purpose
_background = [Sentence
background],
_motivation :: Purpose
_motivation = [],
_scope :: Purpose
_scope = [Sentence
scope],
_quants :: [QuantityDict]
_quants = [QuantityDict]
symbolsForTable,
_concepts :: [DefinedQuantityDict]
_concepts = [] :: [DefinedQuantityDict],
_instModels :: [InstanceModel]
_instModels = [InstanceModel]
iMods,
_datadefs :: [DataDefinition]
_datadefs = [DataDefinition]
GB.dataDefs,
_configFiles :: [String]
_configFiles = [String]
configFp,
_inputs :: [QuantityDict]
_inputs = [QuantityDict]
inputs,
_outputs :: [QuantityDict]
_outputs = [QuantityDict]
outputs,
_defSequence :: [Block SimpleQDef]
_defSequence = [Block SimpleQDef]
qDefns,
_constraints :: [ConstrainedChunk]
_constraints = [ConstrainedChunk]
constrained,
_constants :: [ConstQDef]
_constants = [ConstQDef]
constants,
_sysinfodb :: ChunkDB
_sysinfodb = ChunkDB
symbMap,
_usedinfodb :: ChunkDB
_usedinfodb = ChunkDB
usedDB,
refdb :: ReferenceDB
refdb = ReferenceDB
refDB
}
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 [RefTab
TUnits, [TSIntro] -> RefTab
tsymb [TSIntro
TSPurpose, TSIntro
SymbOrder], RefTab
TAandA],
IntroSec -> DocSection
IntroSec (IntroSec -> DocSection) -> IntroSec -> DocSection
forall a b. (a -> b) -> a -> b
$
Sentence -> Sentence -> [IntroSub] -> IntroSec
IntroProg (IdeaDict -> Sentence -> CI -> Sentence
forall n. NamedIdea n => n -> Sentence -> CI -> Sentence
startIntro IdeaDict
software Sentence
blstRskInvWGlassSlab CI
glassBR)
(CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
glassBR)
[Purpose -> IntroSub
IPurpose (Purpose -> IntroSub) -> Purpose -> IntroSub
forall a b. (a -> b) -> a -> b
$ CI -> Verbosity -> Purpose
purpDoc CI
glassBR Verbosity
Verbose,
Sentence -> IntroSub
IScope Sentence
scope,
Purpose -> Purpose -> Purpose -> IntroSub
IChar [] (Purpose
undIR Purpose -> Purpose -> Purpose
forall a. [a] -> [a] -> [a]
++ Purpose
appStanddIR) [],
CI -> Section -> Sentence -> IntroSub
IOrgSec CI
Doc.dataDefn ([Contents] -> [Section] -> Section
SRS.inModel [] []) Sentence
orgOfDocIntroEnd],
StkhldrSec -> DocSection
StkhldrSec (StkhldrSec -> DocSection) -> StkhldrSec -> DocSection
forall a b. (a -> b) -> a -> b
$
[StkhldrSub] -> StkhldrSec
StkhldrProg
[CI -> Sentence -> StkhldrSub
Client CI
glassBR (Sentence -> StkhldrSub) -> Sentence -> StkhldrSub
forall a b. (a -> b) -> a -> b
$ NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
a_ IdeaDict
company)
Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"named Entuitive" Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"It is developed by Dr." Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S (Person -> String
forall n. HasName n => n -> String
name Person
mCampidelli),
CI -> StkhldrSub
Cstmr CI
glassBR],
GSDSec -> DocSection
GSDSec (GSDSec -> DocSection) -> GSDSec -> DocSection
forall a b. (a -> b) -> a -> b
$ [GSDSub] -> GSDSec
GSDProg [[Contents] -> GSDSub
SysCntxt [Contents
sysCtxIntro, LabelledContent -> Contents
LlC LabelledContent
sysCtxFig, Contents
sysCtxDesc, Contents
sysCtxList],
[Contents] -> GSDSub
UsrChars [Contents
userCharacteristicsIntro], [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
purp [Section
termsAndDesc]
[ CI -> Purpose -> LabelledContent -> [Contents] -> PDSub
forall a.
Idea a =>
a -> Purpose -> LabelledContent -> [Contents] -> PDSub
PhySysDesc CI
glassBR Purpose
physSystParts LabelledContent
physSystFig []
, Purpose -> PDSub
Goals Purpose
goalInputs],
SolChSpec -> SSDSub
SSDSolChSpec (SolChSpec -> SSDSub) -> SolChSpec -> SSDSub
forall a b. (a -> b) -> a -> b
$ [SCSSub] -> SolChSpec
SCSProg
[ SCSSub
Assumptions
, Purpose -> Fields -> SCSSub
TMs [] (Field
Label Field -> Fields -> Fields
forall a. a -> [a] -> [a]
: Fields
stdFields)
, Purpose -> Fields -> DerivationDisplay -> SCSSub
GDs [] [] DerivationDisplay
HideDerivation
, Purpose -> Fields -> DerivationDisplay -> SCSSub
DDs [] ([Field
Label, Field
Symbol, Field
Units] Fields -> Fields -> Fields
forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation
, Purpose -> Fields -> DerivationDisplay -> SCSSub
IMs [Sentence
instModIntro] ([Field
Label, Field
Input, Field
Output, Field
InConstraints, Field
OutConstraints] Fields -> Fields -> Fields
forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
HideDerivation
, Sentence -> [UncertainChunk] -> SCSSub
forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
Sentence -> [c] -> SCSSub
Constraints Sentence
auxSpecSent [UncertainChunk]
inputDataConstraints
, [ConstrainedChunk] -> [Contents] -> SCSSub
forall c.
(Quantity c, Constrained c) =>
[c] -> [Contents] -> SCSSub
CorrSolnPpties [ConstrainedChunk
probBr, ConstrainedChunk
stressDistFac] []
]
],
ReqrmntSec -> DocSection
ReqrmntSec (ReqrmntSec -> DocSection) -> ReqrmntSec -> DocSection
forall a b. (a -> b) -> a -> b
$ [ReqsSub] -> ReqrmntSec
ReqsProg [
Sentence -> [LabelledContent] -> ReqsSub
FReqsSub Sentence
inReqDesc [LabelledContent]
funcReqsTables,
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
$ SystemInformation -> [TraceConfig]
traceMatStandard SystemInformation
si,
AuxConstntSec -> DocSection
AuxConstntSec (AuxConstntSec -> DocSection) -> AuxConstntSec -> DocSection
forall a b. (a -> b) -> a -> b
$ CI -> [ConstQDef] -> AuxConstntSec
AuxConsProg CI
glassBR [ConstQDef]
auxiliaryConstants,
DocSection
Bibliography,
AppndxSec -> DocSection
AppndxSec (AppndxSec -> DocSection) -> AppndxSec -> DocSection
forall a b. (a -> b) -> a -> b
$ [Contents] -> AppndxSec
AppndxProg [Contents
appdxIntro, LabelledContent -> Contents
LlC LabelledContent
demandVsSDFig, LabelledContent -> Contents
LlC LabelledContent
dimlessloadVsARFig]]
purp :: Sentence
purp :: Sentence
purp = Purpose -> Sentence
foldlSent_ [String -> Sentence
S String
"predict whether a", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
glaSlab, String -> Sentence
S String
"can withstand a",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
blast, String -> Sentence
S String
"under given", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
condition]
background :: Sentence
background :: Sentence
background = Purpose -> Sentence
foldlSent_ [ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
explosion, String -> Sentence
S String
"in downtown areas are dangerous from the",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
blast Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"itself" Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"also potentially from the secondary"
Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"effect of falling glass"]
symbMap :: ChunkDB
symbMap :: ChunkDB
symbMap = [QuantityDict]
-> [IdeaDict]
-> [ConceptChunk]
-> [UnitDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Section]
-> [LabelledContent]
-> [Reference]
-> ChunkDB
forall q t c u.
(Quantity q, MayHaveUnit q, Idea t, Concept c, IsUnit u) =>
[q]
-> [t]
-> [c]
-> [u]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Section]
-> [LabelledContent]
-> [Reference]
-> ChunkDB
cdb [QuantityDict]
thisSymbols ((CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
acronyms [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (QuantityDict -> IdeaDict) -> [QuantityDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map QuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [QuantityDict]
thisSymbols [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
con
[IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (IdeaDict -> IdeaDict) -> [IdeaDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
con' [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
terms [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (IdeaDict -> IdeaDict) -> [IdeaDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
doccon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
doccon' [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (IdeaDict -> IdeaDict) -> [IdeaDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
educon
[IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ [IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw IdeaDict
sciCompS] [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (IdeaDict -> IdeaDict) -> [IdeaDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [IdeaDict]
compcon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
mathcon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
mathcon'
[IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
softwarecon [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
terms [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ [IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw IdeaDict
lateralLoad, IdeaDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw IdeaDict
materialProprty]
[IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
distance, ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw ConceptChunk
algorithm] [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++
(UnitDefn -> IdeaDict) -> [UnitDefn] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [UnitDefn]
fundamentals [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (UnitDefn -> IdeaDict) -> [UnitDefn] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [UnitDefn]
derived [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> IdeaDict) -> [ConceptChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [ConceptChunk]
physicalcon)
((UnitalChunk -> ConceptChunk) -> [UnitalChunk] -> [ConceptChunk]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw [UnitalChunk]
symb [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
terms [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
Doc.srsDomains) ((UnitDefn -> UnitDefn) -> [UnitDefn] -> [UnitDefn]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> UnitDefn
forall u. IsUnit u => u -> UnitDefn
unitWrapper [UnitDefn
metre, UnitDefn
second, UnitDefn
kilogram]
[UnitDefn] -> [UnitDefn] -> [UnitDefn]
forall a. [a] -> [a] -> [a]
++ (UnitDefn -> UnitDefn) -> [UnitDefn] -> [UnitDefn]
forall a b. (a -> b) -> [a] -> [b]
map UnitDefn -> UnitDefn
forall u. IsUnit u => u -> UnitDefn
unitWrapper [UnitDefn
pascal, UnitDefn
newton]) [DataDefinition]
GB.dataDefs [InstanceModel]
iMods [] [TheoryModel]
tMods [ConceptInstance]
concIns [Section]
section
[LabelledContent]
labCon [Reference]
allRefs
allRefs :: [Reference]
allRefs :: [Reference]
allRefs = [Reference
externalLinkRef]
concIns :: [ConceptInstance]
concIns :: [ConceptInstance]
concIns = [ConceptInstance]
assumptions [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
goals [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
likelyChgs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
unlikelyChgs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
funcReqs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
nonfuncReqs
labCon :: [LabelledContent]
labCon :: [LabelledContent]
labCon = [LabelledContent]
funcReqsTables [LabelledContent] -> [LabelledContent] -> [LabelledContent]
forall a. [a] -> [a] -> [a]
++ [LabelledContent
demandVsSDFig, LabelledContent
dimlessloadVsARFig]
usedDB :: ChunkDB
usedDB :: ChunkDB
usedDB = [QuantityDict]
-> [IdeaDict]
-> [ConceptChunk]
-> [UnitDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Section]
-> [LabelledContent]
-> [Reference]
-> ChunkDB
forall q t c u.
(Quantity q, MayHaveUnit q, Idea t, Concept c, IsUnit u) =>
[q]
-> [t]
-> [c]
-> [u]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [Section]
-> [LabelledContent]
-> [Reference]
-> ChunkDB
cdb ([] :: [QuantityDict]) ((CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
acronyms [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (QuantityDict -> IdeaDict) -> [QuantityDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map QuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [QuantityDict]
thisSymbols)
([] :: [ConceptChunk]) ([] :: [UnitDefn]) [] [] [] [] [] [] [] ([] :: [Reference])
refDB :: ReferenceDB
refDB :: ReferenceDB
refDB = BibRef -> [ConceptInstance] -> ReferenceDB
rdb BibRef
citations [ConceptInstance]
concIns
section :: [Section]
section :: [Section]
section = Document -> [Section]
extractSection Document
srs
stdFields :: Fields
stdFields :: Fields
stdFields = [Field
DefiningEquation, Verbosity -> InclUnits -> Field
Description Verbosity
Verbose InclUnits
IncludeUnits, Field
Notes, Field
Source, Field
RefBy]
termsAndDescBullets :: Contents
termsAndDescBullets :: Contents
termsAndDescBullets = UnlabelledContent -> Contents
UlC (UnlabelledContent -> Contents) -> UnlabelledContent -> Contents
forall a b. (a -> b) -> a -> b
$ RawContent -> UnlabelledContent
ulcc (RawContent -> UnlabelledContent)
-> RawContent -> UnlabelledContent
forall a b. (a -> b) -> a -> b
$ ListType -> RawContent
Enumeration(ListType -> RawContent) -> ListType -> RawContent
forall a b. (a -> b) -> a -> b
$
[(ItemType, Maybe String)] -> ListType
Numeric ([(ItemType, Maybe String)] -> ListType)
-> [(ItemType, Maybe String)] -> ListType
forall a b. (a -> b) -> a -> b
$
[ItemType] -> [(ItemType, Maybe String)]
noRefs ([ItemType] -> [(ItemType, Maybe String)])
-> [ItemType] -> [(ItemType, Maybe String)]
forall a b. (a -> b) -> a -> b
$
(ConceptChunk -> ItemType) -> [ConceptChunk] -> [ItemType]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> ItemType
forall s. Concept s => s -> ItemType
tAndDOnly [ConceptChunk]
termsWithDefsOnly
[ItemType] -> [ItemType] -> [ItemType]
forall a. [a] -> [a] -> [a]
++ [ItemType]
termsAndDescBulletsGlTySubSec
[ItemType] -> [ItemType] -> [ItemType]
forall a. [a] -> [a] -> [a]
++ [ItemType]
termsAndDescBulletsLoadSubSec
[ItemType] -> [ItemType] -> [ItemType]
forall a. [a] -> [a] -> [a]
++ (ConceptChunk -> ItemType) -> [ConceptChunk] -> [ItemType]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> ItemType
forall s. Concept s => s -> ItemType
tAndDWAcc [ConceptChunk]
termsWithAccDefn
[ItemType] -> [ItemType] -> [ItemType]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk -> ConstrainedChunk -> ItemType
forall s a. (Concept s, Quantity a) => s -> a -> ItemType
tAndDWSym ConceptChunk
probBreak ConstrainedChunk
probBr]
termsAndDescBulletsGlTySubSec, termsAndDescBulletsLoadSubSec :: [ItemType]
termsAndDescBulletsGlTySubSec :: [ItemType]
termsAndDescBulletsGlTySubSec = [Sentence -> ListType -> ItemType
Nested (Sentence
EmptyS Sentence -> Sentence -> Sentence
+: ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize ConceptChunk
glassTy) (ListType -> ItemType) -> ListType -> ItemType
forall a b. (a -> b) -> a -> b
$
[(ItemType, Maybe String)] -> ListType
Bullet ([(ItemType, Maybe String)] -> ListType)
-> [(ItemType, Maybe String)] -> ListType
forall a b. (a -> b) -> a -> b
$ [ItemType] -> [(ItemType, Maybe String)]
noRefs ([ItemType] -> [(ItemType, Maybe String)])
-> [ItemType] -> [(ItemType, Maybe String)]
forall a b. (a -> b) -> a -> b
$ (ConceptChunk -> ItemType) -> [ConceptChunk] -> [ItemType]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> ItemType
forall s. Concept s => s -> ItemType
tAndDWAcc [ConceptChunk]
glassTypes]
termsAndDescBulletsLoadSubSec :: [ItemType]
termsAndDescBulletsLoadSubSec = [Sentence -> ListType -> ItemType
Nested (ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart ConceptChunk
load Sentence -> Sentence -> Sentence
`sDash` Sentence -> Sentence
capSent (ConceptChunk
load ConceptChunk -> Getting Sentence ConceptChunk Sentence -> Sentence
forall s a. s -> Getting a s a -> a
^. Getting Sentence ConceptChunk Sentence
forall c. Definition c => Lens' c Sentence
Lens' ConceptChunk Sentence
defn) !.) (ListType -> ItemType) -> ListType -> ItemType
forall a b. (a -> b) -> a -> b
$
[(ItemType, Maybe String)] -> ListType
Bullet ([(ItemType, Maybe String)] -> ListType)
-> [(ItemType, Maybe String)] -> ListType
forall a b. (a -> b) -> a -> b
$ [ItemType] -> [(ItemType, Maybe String)]
noRefs ([ItemType] -> [(ItemType, Maybe String)])
-> [ItemType] -> [(ItemType, Maybe String)]
forall a b. (a -> b) -> a -> b
$ (ConceptChunk -> ItemType) -> [ConceptChunk] -> [ItemType]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> ItemType
forall s. Concept s => s -> ItemType
tAndDWAcc (Int -> [ConceptChunk] -> [ConceptChunk]
forall a. Int -> [a] -> [a]
take Int
2 [ConceptChunk]
loadTypes)
[ItemType] -> [ItemType] -> [ItemType]
forall a. [a] -> [a] -> [a]
++
(ConceptChunk -> ItemType) -> [ConceptChunk] -> [ItemType]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> ItemType
forall s. Concept s => s -> ItemType
tAndDOnly (Int -> [ConceptChunk] -> [ConceptChunk]
forall a. Int -> [a] -> [a]
drop Int
2 [ConceptChunk]
loadTypes)]
solChSpecSubsections :: [CI]
solChSpecSubsections :: [CI]
solChSpecSubsections = [CI
thModel, CI
inModel, CI
Doc.dataDefn, CI
dataConst]
auxiliaryConstants :: [ConstQDef]
auxiliaryConstants :: [ConstQDef]
auxiliaryConstants = [ConstQDef]
assumptionConstants [ConstQDef] -> [ConstQDef] -> [ConstQDef]
forall a. [a] -> [a] -> [a]
++ [ConstQDef]
specParamVals
priorityNFReqs :: [ConceptChunk]
priorityNFReqs :: [ConceptChunk]
priorityNFReqs = [ConceptChunk
correctness, ConceptChunk
verifiability, ConceptChunk
understandability,
ConceptChunk
reusability, ConceptChunk
maintainability, ConceptChunk
portability]
startIntro :: (NamedIdea n) => n -> Sentence -> CI -> Sentence
startIntro :: forall n. NamedIdea n => n -> Sentence -> CI -> Sentence
startIntro n
prgm Sentence
_ CI
progName = Purpose -> Sentence
foldlSent [
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart' ConceptChunk
explosion, String -> Sentence
S String
"in downtown areas are dangerous" Sentence -> Sentence -> Sentence
`S.fromThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
blast Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"itself" Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"also potentially from the secondary" Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"effect of falling glass. Therefore" Sentence -> Sentence -> Sentence
`sC` n -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase n
prgm Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"needed to" Sentence -> Sentence -> Sentence
+:+.
Sentence
purp, String -> Sentence
S String
"For example" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"we might wish to know whether a pane of",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
glass, String -> Sentence
S String
"fails from a gas main", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
explosion Sentence -> Sentence -> Sentence
`S.or_`
String -> Sentence
S String
"from a small fertilizer truck bomb." Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"The document describes the program called", CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
progName,
String -> Sentence
S String
", which is based" Sentence -> Sentence -> Sentence
`S.onThe` String -> Sentence
S String
"original" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"manually created version of" Sentence -> Sentence -> Sentence
+:+
Reference -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Reference
externalLinkRef (String -> Sentence
S String
"GlassBR")]
externalLinkRef :: Reference
externalLinkRef :: Reference
externalLinkRef = String -> String -> ShortName -> Reference
makeURI String
"glassBRSRSLink"
String
"https://github.com/smiths/caseStudies/tree/master/CaseStudies/glass"
(Sentence -> ShortName
shortname' (Sentence -> ShortName) -> Sentence -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"glassBRSRSLink")
undIR, appStanddIR :: [Sentence]
undIR :: Purpose
undIR = [IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
scndYrCalculus, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
structuralMechanics, ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
glBreakage,
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
blastRisk, NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict
computerApp IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`in_PS` IdeaDict
Edu.civilEng)]
appStanddIR :: Purpose
appStanddIR = [String -> Sentence
S String
"applicable" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
standard Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"for constructions using glass from" Sentence -> Sentence -> Sentence
+:+ SepType -> FoldType -> Purpose -> Sentence
foldlList SepType
Comma FoldType
List
((Citation -> Sentence) -> BibRef -> Purpose
forall a b. (a -> b) -> [a] -> [b]
map Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS [Citation
astm2009, Citation
astm2012, Citation
astm2016]) Sentence -> Sentence -> Sentence
`S.in_`
Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
SRS.reference ([]::[Contents]) ([]::[Section])) (IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
reference)]
scope :: Sentence
scope :: Sentence
scope = Purpose -> Sentence
foldlSent_ [String -> Sentence
S String
"determining the safety" Sentence -> Sentence -> Sentence
`S.ofA` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
glaSlab,
String -> Sentence
S String
"under a", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
blast, String -> Sentence
S String
"loading following the ASTM", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
standard,
Sentence -> Sentence
sParen (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
astm2009]
orgOfDocIntroEnd :: Sentence
orgOfDocIntroEnd :: Sentence
orgOfDocIntroEnd = Purpose -> Sentence
foldlSent_ [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (CI -> NP
forall c. NamedIdea c => c -> NP
the CI
dataDefn) Sentence -> Sentence -> Sentence
`S.are`
String -> Sentence
S String
"used to support", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
definition Sentence -> Sentence -> Sentence
`S.the_ofThe` String -> Sentence
S String
"different", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
model]
sysCtxIntro :: Contents
sysCtxIntro :: Contents
sysCtxIntro = Purpose -> Contents
foldlSP
[LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
sysCtxFig Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"shows the" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
sysCont,
String -> Sentence
S String
"A circle represents an external entity outside the" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
software
Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
user), String -> Sentence
S String
"in this case. A rectangle represents the",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
softwareSys, String -> Sentence
S String
"itself", (Sentence -> Sentence
sParen (CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
glassBR) !.),
String -> Sentence
S String
"Arrows are used to show the data flow between the" Sentence -> Sentence -> Sentence
+:+ NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
system
IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andIts` IdeaDict
environment)]
sysCtxDesc :: Contents
sysCtxDesc :: Contents
sysCtxDesc = Purpose -> Contents
foldlSPCol
[String -> Sentence
S String
"The interaction between the", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
product_ IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` IdeaDict
user),
String -> Sentence
S String
"is through a user" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
interface,
String -> Sentence
S String
"The responsibilities" Sentence -> Sentence -> Sentence
`S.ofThe` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
user IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` IdeaDict
system),
String -> Sentence
S String
"are as follows"]
sysCtxUsrResp :: [Sentence]
sysCtxUsrResp :: Purpose
sysCtxUsrResp = [String -> Sentence
S String
"Provide the" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
inDatum Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"related to the" Sentence -> Sentence -> Sentence
+:+
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
glaSlab IdeaDict -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` ConceptChunk
blastTy) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"ensuring no errors" Sentence -> Sentence -> Sentence
`S.inThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
datum Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"entry",
String -> Sentence
S String
"Ensure that consistent units are used for" Sentence -> Sentence -> Sentence
+:+. NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI IdeaDict
input_ IdeaDict
variable),
String -> Sentence
S String
"Ensure required" Sentence -> Sentence -> Sentence
+:+
Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
SRS.assumpt [] []) (NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict -> CI -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI IdeaDict
software CI
assumption))
Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"are appropriate for any particular" Sentence -> Sentence -> Sentence
+:+
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"input to the" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
software]
sysCtxSysResp :: [Sentence]
sysCtxSysResp :: Purpose
sysCtxSysResp = [String -> Sentence
S String
"Detect data type mismatch, such as a string of characters" Sentence -> Sentence -> Sentence
+:+
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
input_ Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"instead of a floating point number",
String -> Sentence
S String
"Determine if the" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
input_ Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"satisfy the required" Sentence -> Sentence -> Sentence
+:+.
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict
physical IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` IdeaDict
softwareConstraint),
String -> Sentence
S String
"Predict whether the" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
glaSlab Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"is safe or not"]
sysCtxResp :: [Sentence]
sysCtxResp :: Purpose
sysCtxResp = [IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
user Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"Responsibilities",
CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
glassBR Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"Responsibilities"]
sysCtxList :: Contents
sysCtxList :: Contents
sysCtxList = UnlabelledContent -> Contents
UlC (UnlabelledContent -> Contents) -> UnlabelledContent -> Contents
forall a b. (a -> b) -> a -> b
$ RawContent -> UnlabelledContent
ulcc (RawContent -> UnlabelledContent)
-> RawContent -> UnlabelledContent
forall a b. (a -> b) -> a -> b
$ ListType -> RawContent
Enumeration (ListType -> RawContent) -> ListType -> RawContent
forall a b. (a -> b) -> a -> b
$ Purpose -> [ListType] -> ListType
bulletNested Purpose
sysCtxResp ([ListType] -> ListType) -> [ListType] -> ListType
forall a b. (a -> b) -> a -> b
$
(Purpose -> ListType) -> [Purpose] -> [ListType]
forall a b. (a -> b) -> [a] -> [b]
map Purpose -> ListType
bulletFlat [Purpose
sysCtxUsrResp, Purpose
sysCtxSysResp]
userCharacteristicsIntro :: Contents
userCharacteristicsIntro :: Contents
userCharacteristicsIntro = Purpose -> Contents
enumBulletU (Purpose -> Contents) -> Purpose -> Contents
forall a b. (a -> b) -> a -> b
$ (Purpose -> Sentence) -> [Purpose] -> Purpose
forall a b. (a -> b) -> [a] -> [b]
map Purpose -> Sentence
foldlSent
[[String -> Sentence
S String
"The end user of GlassBR is expected to have completed at least the",
String -> Sentence
S String
"equivalent of the second year of an undergraduate degree in civil engineering or structural engineering"],
[String -> Sentence
S String
"The end user is expected to have an understanding of theory behind glass",
String -> Sentence
S String
"breakage and blast risk"],
[String -> Sentence
S String
"The end user is expected to have basic computer literacy to handle the software"]]
termsAndDesc :: Section
termsAndDesc :: Section
termsAndDesc = Maybe Sentence -> [Contents] -> Section
termDefnF' (Sentence -> Maybe Sentence
forall a. a -> Maybe a
Just (String -> Sentence
S String
"All of the" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
term_ Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"are extracted from" Sentence -> Sentence -> Sentence
+:+ Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
astm2009)) [Contents
termsAndDescBullets]
physSystParts :: [Sentence]
physSystParts :: Purpose
physSystParts = [(NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
glaSlab)!.),
Purpose -> Sentence
foldlSent [(NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
ptOfExplsn) !.), String -> Sentence
S String
"Where the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
bomb Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"or", (ConceptChunk
blast ConceptChunk -> Getting Sentence ConceptChunk Sentence -> Sentence
forall s a. s -> Getting a s a -> a
^. Getting Sentence ConceptChunk Sentence
forall c. Definition c => Lens' c Sentence
Lens' ConceptChunk Sentence
defn) Sentence -> Sentence -> Sentence
`sC` (String -> Sentence
S String
"is located" !.), NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall c. NamedIdea c => c -> NP
the ConceptChunk
sD) Sentence -> Sentence -> Sentence
`S.isThe`
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
distance, String -> Sentence
S String
"between the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
ptOfExplsn Sentence -> Sentence -> Sentence
`S.and_` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
glass)]]
goalInputs :: [Sentence]
goalInputs :: Purpose
goalInputs = [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (ConceptChunk
dimension ConceptChunk -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThePS` IdeaDict
glaPlane), NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall c. NamedIdea c => c -> NP
the ConceptChunk
glassTy),
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict
characteristic IdeaDict -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThePS` ConceptChunk
explosion), NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UncertainChunk -> NP
forall c. NamedIdea c => c -> NP
the UncertainChunk
pbTol)]
appdxIntro :: Contents
appdxIntro :: Contents
appdxIntro = Purpose -> Contents
foldlSP [
String -> Sentence
S String
"This", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
appendix, String -> Sentence
S String
"holds the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
graph,
Sentence -> Sentence
sParen (LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
demandVsSDFig Sentence -> Sentence -> Sentence
`S.and_` LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
dimlessloadVsARFig),
String -> Sentence
S String
"used for interpolating", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
value, String -> Sentence
S String
"needed in the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
model]
blstRskInvWGlassSlab :: Sentence
blstRskInvWGlassSlab :: Sentence
blstRskInvWGlassSlab = IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
blastRisk Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"involved with the" Sentence -> Sentence -> Sentence
+:+
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
glaSlab