{-# LANGUAGE PostfixOperators #-}
module Drasil.SSP.Body (srs, si, symbMap, printSetting, fullSI) where
import Prelude hiding (sin, cos, tan)
import Control.Lens ((^.))
import Drasil.System (SystemKind(Specification), mkSystem)
import Language.Drasil hiding (Verb, number, organization, section, variable)
import Drasil.SRSDocument
import Database.Drasil.ChunkDB (cdb)
import qualified Drasil.DocLang.SRS as SRS (inModel, assumpt,
  genDefn, dataDefn, datCon)
import Theory.Drasil (output)
import Drasil.Metadata (inModel)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.NounPhrase.Combinators as NP
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.Concepts.Documentation as Doc (analysis, assumption,
  constant, effect, endUser, environment, input_, interest, loss, method_,
  physical, physics, problem, software, softwareSys, symbol_,
  sysCont, system, type_, user, value, variable, datumConstraint)
import Data.Drasil.Concepts.Education (solidMechanics, undergraduate)
import Data.Drasil.Concepts.Math (equation, shape, surface, mathcon',
  number)
import Data.Drasil.Concepts.PhysicalProperties (dimension, mass, physicalcon)
import Data.Drasil.Quantities.PhysicalProperties (len)
import Data.Drasil.Concepts.Physics (cohesion, fbd, force, gravity, isotropy,
  strain, stress, time, twoD, physicCon', distance, friction, linear, velocity, position)
import Data.Drasil.Concepts.Software (program, softwarecon)
import Data.Drasil.Concepts.SolidMechanics (mobShear, normForce, shearForce, 
  shearRes, solidcon)
import Data.Drasil.Theories.Physics (weightSrc, hsPressureSrc)
import Data.Drasil.People (brooks, henryFrankis)
import Data.Drasil.SI_Units (degree)
import Drasil.SSP.Assumptions (assumptions)
import Drasil.SSP.Changes (likelyChgs, unlikelyChgs)
import Drasil.SSP.DataDefs (dataDefs)
import Drasil.SSP.Defs (acronyms, crtSlpSrf, defs, defs', effFandS, factor, fsConcept,
  intrslce, layer, morPrice, mtrlPrpty, plnStrn, slice, slip, slope, slpSrf, soil,
  soilLyr, soilMechanics, soilPrpty, ssa, stabAnalysis, waterTable)
import Drasil.SSP.GenDefs (generalDefinitions)
import Drasil.SSP.Goals (goals)
import Drasil.SSP.MetaConcepts (progName)
import Drasil.SSP.IMods (instModIntro, iMods)
import Drasil.SSP.References (citations, morgenstern1965)
import Drasil.SSP.Requirements (funcReqs, funcReqTables, nonFuncReqs)
import Drasil.SSP.TMods (tMods)
import Drasil.SSP.Unitals (constrained, effCohesion, fricAngle, fs, index,
  inputs, inputsWUncrtn, outputs, symbols)
srs :: Document
srs :: Document
srs = SRSDecl -> (IdeaDict -> IdeaDict -> Sentence) -> System -> Document
mkDoc SRSDecl
mkSRS IdeaDict -> IdeaDict -> Sentence
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> Sentence
S.forT System
si
printSetting :: PrintingInformation
printSetting :: PrintingInformation
printSetting = System -> Stage -> PrintingConfiguration -> PrintingInformation
piSys System
fullSI Stage
Equational PrintingConfiguration
defaultConfiguration
fullSI :: System
fullSI :: System
fullSI = SRSDecl -> System -> System
fillcdbSRS SRSDecl
mkSRS System
si
resourcePath :: String
resourcePath :: String
resourcePath = String
"../../../../datafiles/ssp/"
si :: System
si :: System
si = CI
-> SystemKind
-> People
-> Purpose
-> Purpose
-> Purpose
-> Purpose
-> [DefinedQuantityDict]
-> [TheoryModel]
-> [GenDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [String]
-> [DefinedQuantityDict]
-> [ConstrConcept]
-> [ConstrConcept]
-> [ConstQDef]
-> ChunkDB
-> System
forall a e h i j.
(CommonIdea a, Idea a, Quantity e, Eq e, MayHaveUnit e, Concept e,
 Quantity h, MayHaveUnit h, Concept h, Quantity i, MayHaveUnit i,
 Concept i, HasUID j, Constrained j) =>
a
-> SystemKind
-> People
-> Purpose
-> Purpose
-> Purpose
-> Purpose
-> [e]
-> [TheoryModel]
-> [GenDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [String]
-> [h]
-> [i]
-> [j]
-> [ConstQDef]
-> ChunkDB
-> System
mkSystem
  CI
progName SystemKind
Specification [Person
henryFrankis, Person
brooks]
  [Sentence
purp] [] [] []
  [DefinedQuantityDict]
symbols
  [TheoryModel]
tMods [GenDefn]
generalDefinitions [DataDefinition]
dataDefs [InstanceModel]
iMods
  []
  [DefinedQuantityDict]
inputs [ConstrConcept]
outputs [ConstrConcept]
constrained []
  ChunkDB
symbMap
  
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] -> LFunc -> RefTab
tsymb'' [TSIntro]
tableOfSymbIntro LFunc
TAD, [IdeaDict] -> RefTab
TAandA [IdeaDict]
abbreviationsList],
  IntroSec -> DocSection
IntroSec (IntroSec -> DocSection) -> IntroSec -> DocSection
forall a b. (a -> b) -> a -> b
$ Sentence -> Sentence -> [IntroSub] -> IntroSec
IntroProg Sentence
startIntro Sentence
kSent
    [ Purpose -> IntroSub
IPurpose (Purpose -> IntroSub) -> Purpose -> IntroSub
forall a b. (a -> b) -> a -> b
$ CI -> Verbosity -> Purpose
purpDoc CI
progName Verbosity
Verbose
    , Sentence -> IntroSub
IScope Sentence
scope
    , Purpose -> Purpose -> Purpose -> IntroSub
IChar []
        [IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
undergraduate Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"level 4" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
Doc.physics,
        IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
undergraduate Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"level 2 or higher" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
solidMechanics]
        [IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soilMechanics]
    , CI -> Section -> Sentence -> IntroSub
IOrgSec CI
inModel ([Contents] -> [Section] -> Section
SRS.inModel [] []) Sentence
orgSecEnd
    ],
    
  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
sysCtxFig1, Contents
sysCtxDesc, Contents
sysCtxList]
    , [Contents] -> GSDSub
UsrChars [Contents
userCharIntro], [Contents] -> [Section] -> GSDSub
SystCons [Contents
sysConstraints] []
    ],
  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 []
        [ Maybe Sentence -> [ConceptChunk] -> PDSub
forall c. Concept c => Maybe Sentence -> [c] -> PDSub
TermsAndDefs Maybe Sentence
forall a. Maybe a
Nothing [ConceptChunk]
terms
        , CI -> Purpose -> LabelledContent -> [Contents] -> PDSub
forall a.
Idea a =>
a -> Purpose -> LabelledContent -> [Contents] -> PDSub
PhySysDesc CI
progName Purpose
physSystParts LabelledContent
figPhysSyst [Contents]
physSystContents 
        , Purpose -> PDSub
Goals Purpose
goalsInputs]
      , 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 [] ([Field
Label, Field
Units] Fields -> Fields -> Fields
forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation
        , 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 Purpose
instModIntro ([Field
Label, Field
Input, Field
Output, Field
InConstraints, Field
OutConstraints] Fields -> Fields -> Fields
forall a. [a] -> [a] -> [a]
++ Fields
stdFields) DerivationDisplay
ShowDerivation
        , Sentence -> [UncertQ] -> SCSSub
forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
 MayHaveUnit c) =>
Sentence -> [c] -> SCSSub
Constraints Sentence
EmptyS [UncertQ]
inputsWUncrtn 
        , [ConstrConcept] -> [Contents] -> SCSSub
forall c.
(Quantity c, Constrained c) =>
[c] -> [Contents] -> SCSSub
CorrSolnPpties [ConstrConcept]
outputs []
        ]
      ],
  ReqrmntSec -> DocSection
ReqrmntSec (ReqrmntSec -> DocSection) -> ReqrmntSec -> DocSection
forall a b. (a -> b) -> a -> b
$ [ReqsSub] -> ReqrmntSec
ReqsProg
    [ [LabelledContent] -> ReqsSub
FReqsSub' [LabelledContent]
funcReqTables
    , 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
$ System -> [TraceConfig]
traceMatStandard System
si,
  AuxConstntSec -> DocSection
AuxConstntSec (AuxConstntSec -> DocSection) -> AuxConstntSec -> DocSection
forall a b. (a -> b) -> a -> b
$ CI -> [ConstQDef] -> AuxConstntSec
AuxConsProg CI
progName [],
  DocSection
Bibliography]
purp :: Sentence
purp :: Sentence
purp = Purpose -> Sentence
foldlSent_ [String -> Sentence
S String
"evaluate the", ConstrConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConstrConcept
fs Sentence -> Sentence -> Sentence
`S.ofA` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrasePoss IdeaDict
slope,
  ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
slpSrf Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"identify", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
crtSlpSrf ConceptChunk -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` IdeaDict
slope) Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"as well as the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
intrslce, NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
normForce ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` ConceptChunk
shearForce),
  String -> Sentence
S String
"along the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
crtSlpSrf]
concIns :: [ConceptInstance]
concIns :: [ConceptInstance]
concIns = [ConceptInstance]
goals [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
assumptions [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
funcReqs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
nonFuncReqs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
likelyChgs [ConceptInstance] -> [ConceptInstance] -> [ConceptInstance]
forall a. [a] -> [a] -> [a]
++ [ConceptInstance]
unlikelyChgs
labCon :: [LabelledContent]
labCon :: [LabelledContent]
labCon = [LabelledContent
figPhysSyst, LabelledContent
figIndexConv, LabelledContent
figForceActing] [LabelledContent] -> [LabelledContent] -> [LabelledContent]
forall a. [a] -> [a] -> [a]
++ [LabelledContent]
funcReqTables
stdFields :: Fields
stdFields :: Fields
stdFields = [Field
DefiningEquation, Verbosity -> InclUnits -> Field
Description Verbosity
Verbose InclUnits
IncludeUnits, Field
Notes, Field
Source, Field
RefBy]
ideaDicts :: [IdeaDict]
ideaDicts :: [IdeaDict]
ideaDicts = 
  
  [IdeaDict]
defs [IdeaDict] -> [IdeaDict] -> [IdeaDict]
forall a. [a] -> [a] -> [a]
++
  
  CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
progName 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]
++ (CI -> IdeaDict) -> [CI] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [CI]
physicCon'
conceptChunks :: [ConceptChunk]
conceptChunks :: [ConceptChunk]
conceptChunks =
  
  [ConceptChunk]
defs' [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
softwarecon [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
solidcon [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++ [ConceptChunk]
physicalcon [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++
  [ConceptChunk
distance, ConceptChunk
friction, ConceptChunk
linear, ConceptChunk
velocity, ConceptChunk
gravity, ConceptChunk
stress, ConceptChunk
fbd, ConceptChunk
position] [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++
  
  [UnitalChunk -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw UnitalChunk
len] [ConceptChunk] -> [ConceptChunk] -> [ConceptChunk]
forall a. [a] -> [a] -> [a]
++
  
  (ConceptChunk -> ConceptChunk) -> [ConceptChunk] -> [ConceptChunk]
forall a b. (a -> b) -> [a] -> [b]
map ConceptChunk -> ConceptChunk
forall c. Concept c => c -> ConceptChunk
cw [ConceptChunk
time, ConceptChunk
surface]
symbMap :: ChunkDB
symbMap :: ChunkDB
symbMap = [DefinedQuantityDict]
-> [IdeaDict]
-> [ConceptChunk]
-> [UnitDefn]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [LabelledContent]
-> [Reference]
-> [Citation]
-> ChunkDB
forall q c u.
(Quantity q, MayHaveUnit q, Concept q, Concept c, IsUnit u) =>
[q]
-> [IdeaDict]
-> [c]
-> [u]
-> [DataDefinition]
-> [InstanceModel]
-> [GenDefn]
-> [TheoryModel]
-> [ConceptInstance]
-> [LabelledContent]
-> [Reference]
-> [Citation]
-> ChunkDB
cdb ((InstanceModel -> DefinedQuantityDict)
-> [InstanceModel] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map (InstanceModel
-> Getting DefinedQuantityDict InstanceModel DefinedQuantityDict
-> DefinedQuantityDict
forall s a. s -> Getting a s a -> a
^. Getting DefinedQuantityDict InstanceModel DefinedQuantityDict
forall c. HasOutput c => Getter c DefinedQuantityDict
Getter InstanceModel DefinedQuantityDict
output) [InstanceModel]
iMods [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ [DefinedQuantityDict]
symbols) [IdeaDict]
ideaDicts [ConceptChunk]
conceptChunks
  [UnitDefn
degree] [DataDefinition]
dataDefs [InstanceModel]
iMods [GenDefn]
generalDefinitions [TheoryModel]
tMods [ConceptInstance]
concIns [LabelledContent]
labCon [Reference]
allRefs [Citation]
citations
abbreviationsList :: [IdeaDict]
abbreviationsList :: [IdeaDict]
abbreviationsList =
  
  (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]
++
  
  CI -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw CI
progName IdeaDict -> [IdeaDict] -> [IdeaDict]
forall a. a -> [a] -> [a]
:
  
  (DefinedQuantityDict -> IdeaDict)
-> [DefinedQuantityDict] -> [IdeaDict]
forall a b. (a -> b) -> [a] -> [b]
map DefinedQuantityDict -> IdeaDict
forall c. Idea c => c -> IdeaDict
nw [DefinedQuantityDict]
symbols
allRefs :: [Reference]
allRefs :: [Reference]
allRefs = [Reference
externalLinkRef, Reference
weightSrc, Reference
hsPressureSrc]
tableOfSymbIntro :: [TSIntro]
tableOfSymbIntro :: [TSIntro]
tableOfSymbIntro = [TSIntro
TSPurpose, [TConvention] -> TSIntro
TypogConvention [Sentence -> TConvention
Verb (Sentence -> TConvention) -> Sentence -> TConvention
forall a b. (a -> b) -> a -> b
$ Purpose -> Sentence
foldlSent_
  [String -> Sentence
S String
"a subscript", DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index, String -> Sentence
S String
"indicates that the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
value, 
  String -> Sentence
S String
"will be taken at" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"and analyzed at, a", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice Sentence -> Sentence -> Sentence
`S.or_` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, 
  String -> Sentence
S String
"interface composing the total slip", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
mass]], TSIntro
VectorUnits]
startIntro, kSent :: Sentence
startIntro :: Sentence
startIntro = Purpose -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
a_ IdeaDict
slope), String -> Sentence
S String
"of geological",
  ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
mass Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"composed of", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil, String -> Sentence
S String
"and rock and sometimes",
  String -> Sentence
S String
"water" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"is subject" Sentence -> Sentence -> Sentence
`S.toThe` String -> Sentence
S String
"influence" Sentence -> Sentence -> Sentence
`S.of_` (NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
gravity ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`onThe` ConceptChunk
mass) !.),
  String -> Sentence
S String
"This can cause instability" Sentence -> Sentence -> Sentence
`S.inThe` String -> Sentence
S String
"form" Sentence -> Sentence -> Sentence
`S.of_` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil Sentence -> Sentence -> Sentence
+:+.
  String -> Sentence
S String
"or rock movement", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (NP -> NP
NP.the (IdeaDict
effect IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`of_PS` IdeaDict
soil)),
  String -> Sentence
S String
"or rock movement can range from inconvenient to",
  String -> Sentence
S String
"seriously hazardous" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"resulting in significant life and economic" Sentence -> Sentence -> Sentence
+:+.
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
loss, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart IdeaDict
slope, String -> Sentence
S String
"stability is of", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
interest,
  String -> Sentence
S String
"both when analysing natural", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
slope Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"and when designing an excavated" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slope, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart IdeaDict
ssa Sentence -> Sentence -> Sentence
`S.isThe`
  String -> Sentence
S String
"assessment" Sentence -> Sentence -> Sentence
`S.ofThe` String -> Sentence
S String
"safety" Sentence -> Sentence -> Sentence
`S.ofA` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slope Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"identifying the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
surface,
  String -> Sentence
S String
"most likely to experience", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slip Sentence -> Sentence -> Sentence
`S.and_`
  String -> Sentence
S String
"an index" Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"its relative stability known as the" Sentence -> Sentence -> Sentence
+:+. ConstrConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConstrConcept
fs]
kSent :: Sentence
kSent = IdeaDict -> CI -> Sentence
forall a b. (Idea a, Idea b) => a -> b -> Sentence
keySent IdeaDict
ssa CI
progName
keySent :: (Idea a, Idea b) => a -> b -> Sentence
keySent :: forall a b. (Idea a, Idea b) => a -> b -> Sentence
keySent a
probType b
pname = Purpose -> Sentence
foldlSent_ [(NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NP -> NP
NP.a_ (a -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI a
probType IdeaDict
problem)) !.),
  String -> Sentence
S String
"The developed", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
program, String -> Sentence
S String
"will be referred to as the",
  b -> Sentence
forall n. Idea n => n -> Sentence
introduceAbb b
pname,
  String -> Sentence
S String
"based on the original, 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
"SSP")]
externalLinkRef :: Reference
externalLinkRef :: Reference
externalLinkRef = String -> String -> ShortName -> Reference
makeURI String
"SSP" 
  String
"https://github.com/smiths/caseStudies/blob/master/CaseStudies/ssp" 
  (Sentence -> ShortName
shortname' (Sentence -> ShortName) -> Sentence -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"SSP")
  
scope :: Sentence
scope :: Sentence
scope = Purpose -> Sentence
foldlSent_ [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
stabAnalysis IdeaDict -> CI -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofA` CI
twoD), Sentence -> Sentence
sParen (CI -> Sentence
forall n. Idea n => n -> Sentence
short CI
twoD),
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI IdeaDict
soil ConceptChunk
mass) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"composed of a single homogeneous", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
layer,
  String -> Sentence
S String
"with" 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
constant IdeaDict
mtrlPrpty), NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NP -> NP
NP.the (IdeaDict -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI IdeaDict
soil ConceptChunk
mass))
  Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"assumed to extend infinitely in the third" Sentence -> Sentence -> Sentence
+:+.
  ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
dimension, NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
analysis), String -> Sentence
S String
"will be at an instant" Sentence -> Sentence -> Sentence
`S.in_`
  ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
time Sentence -> Sentence -> Sentence
:+: String -> Sentence
S String
";", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
factor, String -> Sentence
S String
"that may change the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
soilPrpty,
  String -> Sentence
S String
"over", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
time, String -> Sentence
S String
"will not be considered"]
orgSecEnd :: Sentence
orgSecEnd :: Sentence
orgSecEnd = Purpose -> Sentence
foldlSent_ [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (CI -> NP
forall c. NamedIdea c => c -> NP
the CI
inModel), String -> Sentence
S String
"provide the set of",
  String -> Sentence
S String
"algebraic", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
equation, String -> Sentence
S String
"that must be solved"]
sysCtxIntro :: Contents
sysCtxIntro :: Contents
sysCtxIntro = Purpose -> Contents
foldlSP
  [LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
sysCtxFig1 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, String -> Sentence
S String
"A rectangle represents the",
   IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
softwareSys, String -> Sentence
S String
"itself" Sentence -> Sentence -> Sentence
+:+. Sentence -> Sentence
sParen (CI -> Sentence
forall n. Idea n => n -> Sentence
short CI
progName),
   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)]
   
sysCtxFig1 :: LabelledContent
sysCtxFig1 :: LabelledContent
sysCtxFig1 = Reference -> RawContent -> LabelledContent
llcc (String -> Reference
makeFigRef String
"sysCtxDiag") (RawContent -> LabelledContent) -> RawContent -> LabelledContent
forall a b. (a -> b) -> a -> b
$ Sentence -> String -> RawContent
fig (IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
sysCont) (String
resourcePath String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"SystemContextFigure.png")
sysCtxDesc :: Contents
sysCtxDesc :: Contents
sysCtxDesc = Purpose -> Contents
foldlSPCol
  [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" Sentence -> Sentence -> Sentence
+:+ NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
input_) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"data related to" Sentence -> Sentence -> Sentence
+:+
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
soilLyr) Sentence -> Sentence -> Sentence
:+: String -> Sentence
S String
"(s) and water table (if applicable)" Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"ensuring conformation to" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
input_ Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"data format" Sentence -> Sentence -> Sentence
+:+
  String -> Sentence
S String
"required by" Sentence -> Sentence -> Sentence
+:+ CI -> Sentence
forall n. Idea n => n -> Sentence
short CI
progName,
  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" Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"appropriate for the" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
problem Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"to which the" Sentence -> Sentence -> Sentence
+:+ 
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
user Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"is applying 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" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
type_ Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"mismatch, such as" Sentence -> Sentence -> Sentence
+:+
  String -> Sentence
S String
"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" Sentence -> Sentence -> Sentence
+:+
  String -> Sentence
S String
"point" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
number,
  String -> Sentence
S String
"Verify that 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
+:+
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
physical Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"other" Sentence -> Sentence -> Sentence
+:+ Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
SRS.datCon [] []) (IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
datumConstraint),
  String -> Sentence
S String
"Identify the" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
crtSlpSrf Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"within the possible" Sentence -> Sentence -> Sentence
+:+
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
input_ Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"range",
  String -> Sentence
S String
"Find the" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
fsConcept Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"for the" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slope,
  String -> Sentence
S String
"Find the" Sentence -> Sentence -> Sentence
+:+ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
intrslce Sentence -> Sentence -> Sentence
+:+ NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
normForce ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` ConceptChunk
shearForce) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"along the" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
crtSlpSrf]
  
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 n. Idea n => n -> Sentence
short CI
progName 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]
userCharIntro :: Contents
userCharIntro :: Contents
userCharIntro = CI -> Purpose -> Purpose -> Purpose -> Contents
forall a. Idea a => a -> Purpose -> Purpose -> Purpose -> Contents
userChar CI
progName [String -> Sentence
S String
"Calculus", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize IdeaDict
Doc.physics]
  [IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
mtrlPrpty] [UncertQ -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UncertQ
effCohesion, UncertQ -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UncertQ
fricAngle, 
  String -> Sentence
S String
"unit weight"]
userChar :: (Idea a) => a -> [Sentence] -> [Sentence] -> [Sentence] -> Contents
userChar :: forall a. Idea a => a -> Purpose -> Purpose -> Purpose -> Contents
userChar a
pname Purpose
understandings Purpose
familiarities Purpose
specifics = Purpose -> Contents
foldlSP [
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
the IdeaDict
endUser) Sentence -> Sentence -> Sentence
`S.of_` a -> Sentence
forall n. Idea n => n -> Sentence
short a
pname,
  String -> Sentence
S String
"should have an understanding" Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"undergraduate Level 1",
  SepType -> FoldType -> Purpose -> Sentence
foldlList SepType
Comma FoldType
List Purpose
understandings Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"and be familiar with", SepType -> FoldType -> Purpose -> Sentence
foldlList SepType
Comma FoldType
List Purpose
familiarities Sentence -> Sentence -> Sentence
`sC` 
  String -> Sentence
S String
"specifically", SepType -> FoldType -> Purpose -> Sentence
foldlList SepType
Comma FoldType
List Purpose
specifics]
sysConstraints :: Contents
sysConstraints :: Contents
sysConstraints = Purpose -> Contents
foldlSP [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NP -> NP
NP.the (IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI IdeaDict
morPrice IdeaDict
method_)), 
  Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
morgenstern1965 Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"which involves dividing the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slope,
  String -> Sentence
S String
"into vertical", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
slice Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"will be used to derive the",
  ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
equation, String -> Sentence
S String
"for analysing the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slope]
terms :: [ConceptChunk]
terms :: [ConceptChunk]
terms = [ConceptChunk
fsConcept, ConceptChunk
slpSrf, ConceptChunk
crtSlpSrf, ConceptChunk
waterTable, ConceptChunk
stress, ConceptChunk
strain, ConceptChunk
normForce,
  ConceptChunk
shearForce, ConceptChunk
mobShear, ConceptChunk
shearRes, ConceptChunk
effFandS, ConceptChunk
cohesion, ConceptChunk
isotropy, ConceptChunk
plnStrn]
  
  
physSystParts :: [Sentence]
physSystParts :: Purpose
physSystParts = (Purpose -> Sentence) -> [Purpose] -> Purpose
forall a b. (a -> b) -> [a] -> [b]
map Purpose -> Sentence
foldlSent [
  [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall c. NamedIdea c => c -> NP
a_ IdeaDict
slope), String -> Sentence
S String
"comprised of one", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soilLyr],
  [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall c. NamedIdea c => c -> NP
a_ ConceptChunk
waterTable) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"which may or may not exist"]]
figPhysSyst :: LabelledContent
figPhysSyst :: LabelledContent
figPhysSyst = Reference -> RawContent -> LabelledContent
llcc (String -> Reference
makeFigRef String
"PhysicalSystem") (RawContent -> LabelledContent) -> RawContent -> LabelledContent
forall a b. (a -> b) -> a -> b
$
  Sentence -> String -> RawContent
fig (Purpose -> Sentence
foldlSent_ [String -> Sentence
S String
"An example", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
slope IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`for` IdeaDict
analysis),
  String -> Sentence
S String
"by", CI -> Sentence
forall n. Idea n => n -> Sentence
short CI
progName Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"where the dashed line represents the",
  ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
waterTable]) (String
resourcePath String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"PhysSyst.png")
physSystContents :: [Contents]
physSystContents :: [Contents]
physSystContents = [Contents
physSysConv, LabelledContent -> Contents
LlC LabelledContent
figIndexConv, Contents
physSysFbd, LabelledContent -> Contents
LlC LabelledContent
figForceActing]
physSysConv :: Contents
physSysConv :: Contents
physSysConv = Purpose -> Contents
foldlSP [IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart IdeaDict
morPrice, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
analysis, Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
morgenstern1965
  Sentence -> Sentence -> Sentence
`S.ofThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slope, String -> Sentence
S String
"involves representing the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slope,
  String -> Sentence
S String
"as a series of vertical" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
slice, String -> Sentence
S String
"As shown in",
  LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
figIndexConv Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (DefinedQuantityDict -> NP
forall c. NamedIdea c => c -> NP
the DefinedQuantityDict
index), DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index, String -> Sentence
S String
"is used to denote a",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
value Sentence -> Sentence -> Sentence
`S.for` String -> Sentence
S String
"a single", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"and an", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
intrslce, 
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
value, String -> Sentence
S String
"at a given", DefinedQuantityDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase DefinedQuantityDict
index, DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index, String -> Sentence
S String
"refers to the",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
value, String -> Sentence
S String
"between", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"adjacent", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice,
  ModelExpr -> Sentence
eS (ModelExpr -> Sentence) -> ModelExpr -> Sentence
forall a b. (a -> b) -> a -> b
$ DefinedQuantityDict -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
index ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$+ Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
int Integer
1]
figIndexConv :: LabelledContent
figIndexConv :: LabelledContent
figIndexConv = Reference -> RawContent -> LabelledContent
llcc (String -> Reference
makeFigRef String
"IndexConvention") (RawContent -> LabelledContent) -> RawContent -> LabelledContent
forall a b. (a -> b) -> a -> b
$ 
  Sentence -> String -> RawContent
fig (Purpose -> Sentence
foldlSent_ [String -> Sentence
S String
"Index convention for", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
slice IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` 
  IdeaDict
intrslce), IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
value]) (String
resourcePath String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"IndexConvention.png")
physSysFbd :: Contents
physSysFbd :: Contents
physSysFbd = Purpose -> Contents
foldlSP [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (NP -> NP
NP.a_ (ConceptChunk
fbd ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofThe` ConceptChunk
force)), String -> Sentence
S String
"acting on a",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"displayed in" Sentence -> Sentence -> Sentence
+:+. LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
figForceActing, String -> Sentence
S String
"The specific",
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (ConceptChunk
force ConceptChunk -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_PP` IdeaDict
symbol_), String -> Sentence
S String
"will be discussed in detail in",
  Section -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ([Contents] -> [Section] -> Section
SRS.genDefn [] []) Sentence -> Sentence -> Sentence
`S.and_` Section -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ([Contents] -> [Section] -> Section
SRS.dataDefn [] [])]
figForceActing :: LabelledContent
figForceActing :: LabelledContent
figForceActing = Reference -> RawContent -> LabelledContent
llcc (String -> Reference
makeFigRef String
"ForceDiagram") (RawContent -> LabelledContent) -> RawContent -> LabelledContent
forall a b. (a -> b) -> a -> b
$
  Sentence -> String -> RawContent
fig (NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (ConceptChunk
fbd ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`of_` ConceptChunk
force) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"acting on a" Sentence -> Sentence -> Sentence
+:+
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice) (String
resourcePath String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"ForceDiagram.png")
goalsInputs :: [Sentence]
goalsInputs :: Purpose
goalsInputs = [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall c. NamedIdea c => c -> NP
the ConceptChunk
shape NP -> NP -> NP
`NP.ofThe` IdeaDict -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI IdeaDict
soil ConceptChunk
mass),
  String -> Sentence
S String
"location" Sentence -> Sentence -> Sentence
`S.the_ofThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
waterTable, NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict
mtrlPrpty IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThePS` IdeaDict
soil)]