{-# 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, aspect,
assumption, characteristic, company, condition, dataConst, datum,
definition, doccon, doccon', document, environment,
input_, interface, model, organization, physical, problem,
product_, software, softwareConstraint, softwareSys,
srsDomains, standard, sysCont, system, template, term_,
user, value, variable, reference)
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.Citations (koothoor2013, smithLai2005)
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 (qDefns, 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)
import Drasil.GlassBR.References (astm2009, astm2012, astm2016, citations, rbrtsn2012)
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. (HasUID 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 :: forall a b c e f h i j d.
(CommonIdea a, Idea a, Idea b, HasName c, Quantity e, Eq e,
MayHaveUnit e, Quantity f, MayHaveUnit f, Concept f, Eq f,
Quantity h, MayHaveUnit h, Quantity i, MayHaveUnit i, HasUID j,
Constrained j) =>
a
-> b
-> [c]
-> d
-> [e]
-> [f]
-> [InstanceModel]
-> [DataDefinition]
-> [String]
-> [h]
-> [i]
-> [Block SimpleQDef]
-> [j]
-> [ConstQDef]
-> ChunkDB
-> ChunkDB
-> ReferenceDB
-> SystemInformation
SI {
_sys :: CI
_sys = CI
glassBR,
_kind :: CI
_kind = CI
Doc.srs,
_authors :: [Person]
_authors = [Person
nikitha, Person
spencerSmith],
_purpose :: [Sentence]
_purpose = CI -> Verbosity -> [Sentence]
purpDoc CI
glassBR Verbosity
Verbose,
_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 (NamedChunk -> Sentence -> CI -> Sentence
startIntro NamedChunk
software Sentence
blstRskInvWGlassSlab CI
glassBR)
(CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
glassBR)
[[Sentence] -> IntroSub
IPurpose ([Sentence] -> IntroSub) -> [Sentence] -> IntroSub
forall a b. (a -> b) -> a -> b
$ CI -> Verbosity -> [Sentence]
purpDoc CI
glassBR Verbosity
Verbose,
Sentence -> IntroSub
IScope Sentence
scope,
[Sentence] -> [Sentence] -> [Sentence] -> IntroSub
IChar [] ([Sentence]
undIR [Sentence] -> [Sentence] -> [Sentence]
forall a. [a] -> [a] -> [a]
++ [Sentence]
appStanddIR) [],
Sentence -> CI -> Section -> Sentence -> IntroSub
IOrgSec Sentence
orgOfDocIntro 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 (NamedChunk -> NP
forall c. NamedIdea c => c -> NP
a_ NamedChunk
company)
Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S "named Entuitive" Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "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
prob [Section
termsAndDesc]
[ CI -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
forall a.
Idea a =>
a -> [Sentence] -> LabelledContent -> [Contents] -> PDSub
PhySysDesc CI
glassBR [Sentence]
physSystParts LabelledContent
physSystFig []
, [Sentence] -> PDSub
Goals [Sentence]
goalInputs],
SolChSpec -> SSDSub
SSDSolChSpec (SolChSpec -> SSDSub) -> SolChSpec -> SSDSub
forall a b. (a -> b) -> a -> b
$ [SCSSub] -> SolChSpec
SCSProg
[ SCSSub
Assumptions
, [Sentence] -> Fields -> SCSSub
TMs [] (Field
Label Field -> Fields -> Fields
forall a. a -> [a] -> [a]
: Fields
stdFields)
, [Sentence] -> Fields -> DerivationDisplay -> SCSSub
GDs [] [] DerivationDisplay
HideDerivation
, [Sentence] -> Fields -> DerivationDisplay -> SCSSub
DDs [] ([Field
Label, Field
Symbol, Field
Units] Fields -> Fields -> Fields
forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation
, [Sentence] -> 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]]
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]
++ (NamedChunk -> IdeaDict) -> [NamedChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [NamedChunk]
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]
++ (NamedChunk -> IdeaDict) -> [NamedChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [NamedChunk]
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]
++ (NamedChunk -> IdeaDict) -> [NamedChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [NamedChunk]
educon
[IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ [NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw NamedChunk
sciCompS] [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++ (NamedChunk -> IdeaDict) -> [NamedChunk] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [NamedChunk]
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]
++ [NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw NamedChunk
lateralLoad, NamedChunk -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw NamedChunk
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 []
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
defn) Sentence -> Sentence
!.) (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 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 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 :: NamedChunk -> Sentence -> CI -> Sentence
startIntro :: NamedChunk -> Sentence -> CI -> Sentence
startIntro prgm :: NamedChunk
prgm sfwrPredicts :: Sentence
sfwrPredicts progName :: CI
progName = [Sentence] -> Sentence
foldlSent [
NamedChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart NamedChunk
prgm, String -> Sentence
S "is helpful to efficiently" Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S "correctly predict the"
Sentence -> Sentence -> Sentence
+:+. Sentence
sfwrPredicts, ConceptChunk -> Sentence
underConsidertn ConceptChunk
blast,
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall c. NamedIdea c => c -> NP
the NamedChunk
prgm) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "herein called", CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
progName Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S "aims to predict the", Sentence
sfwrPredicts, String -> Sentence
S "using an intuitive",
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
interface]
undIR, appStanddIR :: [Sentence]
undIR :: [Sentence]
undIR = [NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
scndYrCalculus, NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
structuralMechanics, ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
glBreakage,
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
blastRisk, NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (NamedChunk
computerApp NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`in_PS` NamedChunk
Edu.civilEng)]
appStanddIR :: [Sentence]
appStanddIR = [String -> Sentence
S "applicable" Sentence -> Sentence -> Sentence
+:+ NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
standard Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S "for constructions using glass from" Sentence -> Sentence -> Sentence
+:+ SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List
((Citation -> Sentence) -> BibRef -> [Sentence]
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])) (NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
reference)]
scope :: Sentence
scope :: Sentence
scope = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S "determining the safety of a", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
glaSlab,
String -> Sentence
S "under a", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
blast, String -> Sentence
S "loading following the ASTM", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
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]
orgOfDocIntro, orgOfDocIntroEnd :: Sentence
orgOfDocIntro :: Sentence
orgOfDocIntro = [Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall c. NamedIdea c => c -> NP
the NamedChunk
organization), String -> Sentence
S "of this",
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
document, String -> Sentence
S "follows the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
template, String -> Sentence
S "for an", CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
Doc.srs
Sentence -> Sentence -> Sentence
`S.for` NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
sciCompS, String -> Sentence
S "proposed by" Sentence -> Sentence -> Sentence
+:+ Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
koothoor2013
Sentence -> Sentence -> Sentence
`S.and_` Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
smithLai2005 Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "with some",
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
aspect, String -> Sentence
S "taken from Volere", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
template,
String -> Sentence
S "16", Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
rbrtsn2012]
orgOfDocIntroEnd :: Sentence
orgOfDocIntroEnd = [Sentence] -> Sentence
foldlSent_ [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (CI -> NP
forall c. NamedIdea c => c -> NP
the CI
Doc.dataDefn) Sentence -> Sentence -> Sentence
`S.are`
String -> Sentence
S "used to support", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
definition Sentence -> Sentence -> Sentence
`S.the_ofThe` String -> Sentence
S "different", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
model]
sysCtxIntro :: Contents
sysCtxIntro :: Contents
sysCtxIntro = [Sentence] -> Contents
foldlSP
[LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
sysCtxFig Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "shows the" Sentence -> Sentence -> Sentence
+:+. NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
sysCont,
String -> Sentence
S "A circle represents an external entity outside the" Sentence -> Sentence -> Sentence
+:+ NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
software
Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk -> NP
forall c. NamedIdea c => c -> NP
the NamedChunk
user), String -> Sentence
S "in this case. A rectangle represents the",
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
softwareSys, String -> Sentence
S "itself", (Sentence -> Sentence
sParen (CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
glassBR) Sentence -> Sentence
!.),
String -> Sentence
S "Arrows are used to show the data flow between the" Sentence -> Sentence -> Sentence
+:+ NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk
system
NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andIts` NamedChunk
environment)]
sysCtxDesc :: Contents
sysCtxDesc :: Contents
sysCtxDesc = [Sentence] -> Contents
foldlSPCol
[String -> Sentence
S "The interaction between the", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk
product_ NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` NamedChunk
user),
String -> Sentence
S "is through a user" Sentence -> Sentence -> Sentence
+:+. NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
interface,
String -> Sentence
S "The responsibilities of the", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk
user NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`andThe` NamedChunk
system),
String -> Sentence
S "are as follows"]
sysCtxUsrResp :: [Sentence]
sysCtxUsrResp :: [Sentence]
sysCtxUsrResp = [String -> Sentence
S "Provide the" Sentence -> Sentence -> Sentence
+:+ NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
inDatum Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "related to the" Sentence -> Sentence -> Sentence
+:+
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk
glaSlab NamedChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` ConceptChunk
blastTy) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "ensuring no errors in the" Sentence -> Sentence -> Sentence
+:+
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
datum Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S "entry",
String -> Sentence
S "Ensure that consistent units are used for" Sentence -> Sentence -> Sentence
+:+. NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI NamedChunk
input_ NamedChunk
variable),
String -> Sentence
S "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 (NamedChunk -> CI -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI NamedChunk
software CI
assumption))
Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "are appropriate for any particular" Sentence -> Sentence -> Sentence
+:+
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
problem Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "input to the" Sentence -> Sentence -> Sentence
+:+. NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
software]
sysCtxSysResp :: [Sentence]
sysCtxSysResp :: [Sentence]
sysCtxSysResp = [String -> Sentence
S "Detect data type mismatch, such as a string of characters" Sentence -> Sentence -> Sentence
+:+
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
input_ Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S "instead of a floating point number",
String -> Sentence
S "Determine if the" Sentence -> Sentence -> Sentence
+:+ NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
input_ Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "satisfy the required" Sentence -> Sentence -> Sentence
+:+.
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (NamedChunk
physical NamedChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` NamedChunk
softwareConstraint),
String -> Sentence
S "Predict whether the" Sentence -> Sentence -> Sentence
+:+ NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
glaSlab Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S "is safe or not"]
sysCtxResp :: [Sentence]
sysCtxResp :: [Sentence]
sysCtxResp = [NamedChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize NamedChunk
user Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "Responsibilities",
CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
glassBR Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "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
$ [Sentence] -> [ListType] -> ListType
bulletNested [Sentence]
sysCtxResp ([ListType] -> ListType) -> [ListType] -> ListType
forall a b. (a -> b) -> a -> b
$
([Sentence] -> ListType) -> [[Sentence]] -> [ListType]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> ListType
bulletFlat [[Sentence]
sysCtxUsrResp, [Sentence]
sysCtxSysResp]
userCharacteristicsIntro :: Contents
userCharacteristicsIntro :: Contents
userCharacteristicsIntro = [Sentence] -> Contents
enumBulletU ([Sentence] -> Contents) -> [Sentence] -> Contents
forall a b. (a -> b) -> a -> b
$ ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent
[[String -> Sentence
S "The end user of GlassBR is expected to have completed at least the",
String -> Sentence
S "equivalent of the second year of an undergraduate degree in civil engineering or structural engineering"],
[String -> Sentence
S "The end user is expected to have an understanding of theory behind glass",
String -> Sentence
S "breakage and blast risk"],
[String -> Sentence
S "The end user is expected to have basic computer literacy to handle the software"]]
prob :: Sentence
prob :: Sentence
prob = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S "efficiently" Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S "correctly predict whether a",
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
glaSlab, String -> Sentence
S "can withstand a", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
blast, String -> Sentence
S "under given",
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
condition]
termsAndDesc :: Section
termsAndDesc :: Section
termsAndDesc = Maybe Sentence -> [Contents] -> Section
termDefnF' (Sentence -> Maybe Sentence
forall a. a -> Maybe a
Just (String -> Sentence
S "All of the" Sentence -> Sentence -> Sentence
+:+ NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
term_ Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S "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 :: [Sentence]
physSystParts = [(NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall c. NamedIdea c => c -> NP
the NamedChunk
glaSlab)Sentence -> Sentence
!.),
[Sentence] -> Sentence
foldlSent [(NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall c. NamedIdea c => c -> NP
the NamedChunk
ptOfExplsn) Sentence -> Sentence
!.), String -> Sentence
S "Where the", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
bomb Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S "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
defn) Sentence -> Sentence -> Sentence
`sC` (String -> Sentence
S "is located" Sentence -> Sentence
!.), 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. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
distance, String -> Sentence
S "between the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
ptOfExplsn Sentence -> Sentence -> Sentence
`S.and_` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk -> NP
forall c. NamedIdea c => c -> NP
the NamedChunk
glass)]]
goalInputs :: [Sentence]
goalInputs :: [Sentence]
goalInputs = [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (ConceptChunk
dimension ConceptChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThePS` NamedChunk
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 (NamedChunk
characteristic NamedChunk -> 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 = [Sentence] -> Contents
foldlSP [
String -> Sentence
S "This", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
appendix, String -> Sentence
S "holds the", ConceptChunk -> Sentence
forall n. (HasUID 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 "used for interpolating", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
value, String -> Sentence
S "needed in the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
model]
blstRskInvWGlassSlab :: Sentence
blstRskInvWGlassSlab :: Sentence
blstRskInvWGlassSlab = NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
blastRisk Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "involved with the" Sentence -> Sentence -> Sentence
+:+
NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
glaSlab