module Drasil.GlassBR.IMods (symb, iMods, pbIsSafe, lrIsSafe, instModIntro,
qDefns) where
import Control.Lens ((^.))
import Prelude hiding (exp)
import Language.Drasil
import Theory.Drasil (InstanceModel, imNoDeriv, qwC, qwUC, equationalModelN,
output)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S
import Drasil.SRSDocument (Block (Parallel))
import Data.Drasil.Citations (campidelli)
import Data.Drasil.Concepts.Documentation (goal, user, datum)
import Data.Drasil.SI_Units
import Drasil.GlassBR.DataDefs (aGrtrThanB, arRef, calofDemand, glaTyFac,
glaTyFacQD, gtfRef, hFromtQD, hRef, loadDF, stdVals)
import Drasil.GlassBR.Figures (dimlessloadVsARFig)
import Drasil.GlassBR.Goals (willBreakGS)
import Drasil.GlassBR.References (astm2009, beasonEtAl1998)
import Drasil.GlassBR.Unitals
iMods :: [InstanceModel]
iMods :: [InstanceModel]
iMods = [InstanceModel
risk, InstanceModel
strDisFac, InstanceModel
nonFL, InstanceModel
dimLL, InstanceModel
tolPre, InstanceModel
tolStrDisFac, InstanceModel
probOfBreak,
InstanceModel
calofCapacity, InstanceModel
pbIsSafe, InstanceModel
lrIsSafe]
symb :: [UnitalChunk]
symb :: [UnitalChunk]
symb = [UncertQ -> UnitDefn -> UnitalChunk
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> UnitDefn -> UnitalChunk
ucuc UncertQ
plateLen UnitDefn
metre, UncertQ -> UnitDefn -> UnitalChunk
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> UnitDefn -> UnitalChunk
ucuc UncertQ
plateWidth UnitDefn
metre, UncertQ -> UnitDefn -> UnitalChunk
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> UnitDefn -> UnitalChunk
ucuc UncertQ
charWeight UnitDefn
kilogram,
UncertQ -> UnitDefn -> UnitalChunk
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> UnitDefn -> UnitalChunk
ucuc UncertQ
standOffDist UnitDefn
metre, UnitalChunk
demand]
qDefns :: [Block SimpleQDef]
qDefns :: [Block SimpleQDef]
qDefns = SimpleQDef -> [SimpleQDef] -> Block SimpleQDef
forall a. a -> [a] -> Block a
Parallel SimpleQDef
hFromtQD [SimpleQDef
glaTyFacQD] Block SimpleQDef -> [Block SimpleQDef] -> [Block SimpleQDef]
forall a. a -> [a] -> [a]
:
(SimpleQDef -> Block SimpleQDef)
-> [SimpleQDef] -> [Block SimpleQDef]
forall a b. (a -> b) -> [a] -> [b]
map (SimpleQDef -> [SimpleQDef] -> Block SimpleQDef
forall a. a -> [a] -> Block a
`Parallel` []) [SimpleQDef
dimLLQD, SimpleQDef
strDisFacQD, SimpleQDef
riskQD, SimpleQDef
tolStrDisFacQD, SimpleQDef
tolPreQD,
SimpleQDef
nonFLQD]
abInputConstraints :: [(QuantityDict, Maybe (RealInterval Expr Expr))]
abInputConstraints :: [(QuantityDict, Maybe (RealInterval Expr Expr))]
abInputConstraints = [UncertQ
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
qwC UncertQ
plateLen (RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr)))
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0),
UncertQ
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
qwC UncertQ
plateWidth (RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr)))
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Inc, UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
plateLen)]
aspectRatioConstraint :: RealInterval Expr Expr
aspectRatioConstraint :: RealInterval Expr Expr
aspectRatioConstraint = (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Inc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1)
probConstraint :: RealInterval Expr Expr
probConstraint :: RealInterval Expr Expr
probConstraint = (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Inc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Inc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1)
risk :: InstanceModel
risk :: InstanceModel
risk = ModelKind Expr
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> QuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (QuantityDict
riskFun QuantityDict -> Getting NP QuantityDict NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP QuantityDict NP
forall c. NamedIdea c => Lens' c NP
Lens' QuantityDict NP
term) SimpleQDef
riskQD)
(UnitalChunk -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitalChunk
modElas (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: QuantityDict -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC QuantityDict
lDurFac (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: ConstrainedChunk -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC ConstrainedChunk
stressDistFac (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
:
(UnitaryChunk -> (QuantityDict, Maybe (RealInterval Expr Expr)))
-> [UnitaryChunk]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a b. (a -> b) -> [a] -> [b]
map UnitaryChunk -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC [UnitaryChunk
sflawParamK, UnitaryChunk
sflawParamM, UnitaryChunk
minThick] [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. [a] -> [a] -> [a]
++ [(QuantityDict, Maybe (RealInterval Expr Expr))]
abInputConstraints)
(QuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw QuantityDict
riskFun) [] [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
astm2009, Citation -> RefInfo -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> RefInfo -> DecRef
dRefInfo Citation
beasonEtAl1998 (RefInfo -> DecRef) -> RefInfo -> DecRef
forall a b. (a -> b) -> a -> b
$ [Int] -> RefInfo
Equation [Int
4, Int
5],
Citation -> RefInfo -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> RefInfo -> DecRef
dRefInfo Citation
campidelli (RefInfo -> DecRef) -> RefInfo -> DecRef
forall a b. (a -> b) -> a -> b
$ [Int] -> RefInfo
Equation [Int
14]] String
"riskFun" [Sentence
aGrtrThanB, Sentence
hRef, Sentence
ldfRef, Sentence
jRef]
riskQD :: SimpleQDef
riskQD :: SimpleQDef
riskQD = QuantityDict -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef QuantityDict
riskFun ((UnitaryChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitaryChunk
sflawParamK Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$/
(UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
plateLen Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
plateWidth Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$^ (UnitaryChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitaryChunk
sflawParamM Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$- Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1))) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$*
((UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
modElas Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* Expr -> Expr
forall r. (ExprC r, LiteralC r) => r -> r
square (UnitaryChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitaryChunk
minThick)) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$^ UnitaryChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitaryChunk
sflawParamM) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
lDurFac Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* Expr -> Expr
forall r. ExprC r => r -> r
exp (ConstrainedChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrainedChunk
stressDistFac))
strDisFac :: InstanceModel
strDisFac :: InstanceModel
strDisFac = ModelKind Expr
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> QuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (ConstrainedChunk
stressDistFac ConstrainedChunk -> Getting NP ConstrainedChunk NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP ConstrainedChunk NP
forall c. NamedIdea c => Lens' c NP
Lens' ConstrainedChunk NP
term) SimpleQDef
strDisFacQD)
(UncertQ
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
qwC UncertQ
aspectRatio RealInterval Expr Expr
aspectRatioConstraint (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: [QuantityDict -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC QuantityDict
dimlessLoad]) (ConstrainedChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrainedChunk
stressDistFac)
[(Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
stressDistFacMin) (Inclusive
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
stressDistFacMax)]
[Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
astm2009] String
"stressDistFac"
[ConstrainedChunk -> LabelledContent -> Sentence
forall s f.
(HasUID s, HasSymbol s, Referable f, HasShortName f) =>
s -> f -> Sentence
interpolating ConstrainedChunk
stressDistFac LabelledContent
dimlessloadVsARFig, Sentence
arRef, Sentence
qHtRef]
strDisFacQD :: SimpleQDef
strDisFacQD :: SimpleQDef
strDisFacQD = ConstrainedChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef ConstrainedChunk
stressDistFac Expr
strDisFacEq
strDisFacEq :: Expr
strDisFacEq :: Expr
strDisFacEq = QuantityDict -> [Expr] -> Expr
forall f. (HasUID f, HasSymbol f) => f -> [Expr] -> Expr
forall r f. (ExprC r, HasUID f, HasSymbol f) => f -> [r] -> r
apply QuantityDict
interpZ [String -> Expr
forall r. LiteralC r => String -> r
str String
"SDF.txt", UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
aspectRatio, QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
dimlessLoad]
nonFL :: InstanceModel
nonFL :: InstanceModel
nonFL = ModelKind Expr
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> QuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (UnitalChunk
nonFactorL UnitalChunk -> Getting NP UnitalChunk NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP UnitalChunk NP
forall c. NamedIdea c => Lens' c NP
Lens' UnitalChunk NP
term) SimpleQDef
nonFLQD)
(QuantityDict -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC QuantityDict
tolLoad (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: UnitalChunk -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitalChunk
modElas (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: UnitaryChunk -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitaryChunk
minThick (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: [(QuantityDict, Maybe (RealInterval Expr Expr))]
abInputConstraints)
(UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
nonFactorL) [] [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
astm2009] String
"nFL"
[Sentence
qHtTlTolRef, [UnitalChunk] -> Sentence
forall s. (HasSymbol s, HasUID s) => [s] -> Sentence
stdVals [UnitalChunk
modElas], Sentence
hRef, Sentence
aGrtrThanB]
nonFLEq :: Expr
nonFLEq :: Expr
nonFLEq = (QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
tolLoad Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
modElas) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* (UnitaryChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitaryChunk
minThick Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$^ Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
4) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$/
Expr -> Expr
forall r. (ExprC r, LiteralC r) => r -> r
square (UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
plateLen Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
plateWidth)
nonFLQD :: SimpleQDef
nonFLQD :: SimpleQDef
nonFLQD = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
nonFactorL Expr
nonFLEq
dimLL :: InstanceModel
dimLL :: InstanceModel
dimLL = ModelKind Expr
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> QuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (QuantityDict
dimlessLoad QuantityDict -> Getting NP QuantityDict NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP QuantityDict NP
forall c. NamedIdea c => Lens' c NP
Lens' QuantityDict NP
term) SimpleQDef
dimLLQD)
(UnitalChunk -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitalChunk
demand (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: UnitalChunk -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitalChunk
modElas (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: UnitaryChunk -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitaryChunk
minThick (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: DefinedQuantityDict
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC DefinedQuantityDict
gTF (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: [(QuantityDict, Maybe (RealInterval Expr Expr))]
abInputConstraints)
(QuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw QuantityDict
dimlessLoad) [] [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
astm2009, Citation -> RefInfo -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> RefInfo -> DecRef
dRefInfo Citation
campidelli (RefInfo -> DecRef) -> RefInfo -> DecRef
forall a b. (a -> b) -> a -> b
$ [Int] -> RefInfo
Equation [Int
7]]
String
"dimlessLoad" [Sentence
qRef, Sentence
aGrtrThanB, [UnitalChunk] -> Sentence
forall s. (HasSymbol s, HasUID s) => [s] -> Sentence
stdVals [UnitalChunk
modElas], Sentence
hRef, Sentence
gtfRef]
dimLLEq :: Expr
dimLLEq :: Expr
dimLLEq = UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
demand Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* Expr -> Expr
forall r. (ExprC r, LiteralC r) => r -> r
square (UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
plateLen Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
plateWidth)
Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$/ (UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
modElas Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* (UnitaryChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitaryChunk
minThick Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$^ Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
4)) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* DefinedQuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
gTF
dimLLQD :: SimpleQDef
dimLLQD :: SimpleQDef
dimLLQD = QuantityDict -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef QuantityDict
dimlessLoad Expr
dimLLEq
tolPre :: InstanceModel
tolPre :: InstanceModel
tolPre = ModelKind Expr
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> QuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (QuantityDict
tolLoad QuantityDict -> Getting NP QuantityDict NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP QuantityDict NP
forall c. NamedIdea c => Lens' c NP
Lens' QuantityDict NP
term) SimpleQDef
tolPreQD)
[UncertQ
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
qwC UncertQ
aspectRatio RealInterval Expr Expr
aspectRatioConstraint, QuantityDict -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC (QuantityDict -> (QuantityDict, Maybe (RealInterval Expr Expr)))
-> QuantityDict -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall a b. (a -> b) -> a -> b
$ InstanceModel
tolStrDisFac InstanceModel
-> Getting QuantityDict InstanceModel QuantityDict -> QuantityDict
forall s a. s -> Getting a s a -> a
^. Getting QuantityDict InstanceModel QuantityDict
forall c. HasOutput c => Getter c QuantityDict
Getter InstanceModel QuantityDict
output] (QuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw QuantityDict
tolLoad) []
[Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
astm2009] String
"tolLoad" [QuantityDict -> LabelledContent -> Sentence
forall s f.
(HasUID s, HasSymbol s, Referable f, HasShortName f) =>
s -> f -> Sentence
interpolating QuantityDict
tolLoad LabelledContent
dimlessloadVsARFig, Sentence
arRef,
Sentence
jtolRef]
tolPreEq :: Expr
tolPreEq :: Expr
tolPreEq = QuantityDict -> [Expr] -> Expr
forall f. (HasUID f, HasSymbol f) => f -> [Expr] -> Expr
forall r f. (ExprC r, HasUID f, HasSymbol f) => f -> [r] -> r
apply QuantityDict
interpY [String -> Expr
forall r. LiteralC r => String -> r
str String
"SDF.txt", UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
aspectRatio, QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
sdfTol]
tolPreQD :: SimpleQDef
tolPreQD :: SimpleQDef
tolPreQD = QuantityDict -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef QuantityDict
tolLoad Expr
tolPreEq
tolStrDisFac :: InstanceModel
tolStrDisFac :: InstanceModel
tolStrDisFac = ModelKind Expr
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> QuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (QuantityDict
sdfTol QuantityDict -> Getting NP QuantityDict NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP QuantityDict NP
forall c. NamedIdea c => Lens' c NP
Lens' QuantityDict NP
term) SimpleQDef
tolStrDisFacQD)
((QuantityDict
lDurFac, Maybe (RealInterval Expr Expr)
forall a. Maybe a
Nothing) (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: UncertainChunk
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
qwC UncertainChunk
pbTol RealInterval Expr Expr
probConstraint (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: UnitalChunk -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitalChunk
modElas (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: [(QuantityDict, Maybe (RealInterval Expr Expr))]
abInputConstraints [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. [a] -> [a] -> [a]
++
(UnitaryChunk -> (QuantityDict, Maybe (RealInterval Expr Expr)))
-> [UnitaryChunk]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a b. (a -> b) -> [a] -> [b]
map UnitaryChunk -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC [UnitaryChunk
sflawParamM, UnitaryChunk
sflawParamK, UnitaryChunk
minThick]) (QuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw QuantityDict
sdfTol) []
[Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
astm2009] String
"sdfTol" [Sentence
pbTolUsr, Sentence
aGrtrThanB, [UnitaryChunk] -> Sentence
forall s. (HasSymbol s, HasUID s) => [s] -> Sentence
stdVals [UnitaryChunk
sflawParamM,
UnitaryChunk
sflawParamK, UnitalChunk -> UnitaryChunk
forall u. (Unitary u, MayHaveUnit u) => u -> UnitaryChunk
mkUnitary UnitalChunk
modElas], Sentence
hRef, Sentence
ldfRef]
tolStrDisFacQD :: SimpleQDef
tolStrDisFacQD :: SimpleQDef
tolStrDisFacQD = QuantityDict -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef QuantityDict
sdfTol (Expr -> SimpleQDef) -> Expr -> SimpleQDef
forall a b. (a -> b) -> a -> b
$ Expr -> Expr
forall r. ExprC r => r -> r
ln (Expr -> Expr
forall r. ExprC r => r -> r
ln (Expr -> Expr
forall r. (ExprC r, LiteralC r) => r -> r
recip_ (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1 Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$- UncertainChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertainChunk
pbTol))
Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* ((UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
plateLen Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
plateWidth) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$^ (UnitaryChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitaryChunk
sflawParamM Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$- Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$/
(UnitaryChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitaryChunk
sflawParamK Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* ((UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
modElas Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$*
Expr -> Expr
forall r. (ExprC r, LiteralC r) => r -> r
square (UnitaryChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitaryChunk
minThick)) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$^ UnitaryChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitaryChunk
sflawParamM) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy QuantityDict
lDurFac)))
probOfBreak :: InstanceModel
probOfBreak :: InstanceModel
probOfBreak = ModelKind Expr
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> QuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (ConstrainedChunk
probBr ConstrainedChunk -> Getting NP ConstrainedChunk NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP ConstrainedChunk NP
forall c. NamedIdea c => Lens' c NP
Lens' ConstrainedChunk NP
term) SimpleQDef
probOfBreakQD)
[QuantityDict -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC (QuantityDict -> (QuantityDict, Maybe (RealInterval Expr Expr)))
-> QuantityDict -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall a b. (a -> b) -> a -> b
$ InstanceModel
risk InstanceModel
-> Getting QuantityDict InstanceModel QuantityDict -> QuantityDict
forall s a. s -> Getting a s a -> a
^. Getting QuantityDict InstanceModel QuantityDict
forall c. HasOutput c => Getter c QuantityDict
Getter InstanceModel QuantityDict
output] (ConstrainedChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrainedChunk
probBr) [RealInterval Expr Expr
probConstraint] ((Citation -> DecRef) -> [Citation] -> [DecRef]
forall a b. (a -> b) -> [a] -> [b]
map Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef [Citation
astm2009, Citation
beasonEtAl1998]) String
"probOfBreak"
[Sentence
riskRef]
probOfBreakQD :: SimpleQDef
probOfBreakQD :: SimpleQDef
probOfBreakQD = ConstrainedChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef ConstrainedChunk
probBr (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1 Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$- Expr -> Expr
forall r. ExprC r => r -> r
exp (Expr -> Expr
forall r. ExprC r => r -> r
neg (Expr -> Expr) -> Expr -> Expr
forall a b. (a -> b) -> a -> b
$ QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy (QuantityDict -> Expr) -> QuantityDict -> Expr
forall a b. (a -> b) -> a -> b
$ InstanceModel
risk InstanceModel
-> Getting QuantityDict InstanceModel QuantityDict -> QuantityDict
forall s a. s -> Getting a s a -> a
^. Getting QuantityDict InstanceModel QuantityDict
forall c. HasOutput c => Getter c QuantityDict
Getter InstanceModel QuantityDict
output))
calofCapacity :: InstanceModel
calofCapacity :: InstanceModel
calofCapacity = ModelKind Expr
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> QuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (UnitalChunk
lRe UnitalChunk -> Getting NP UnitalChunk NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP UnitalChunk NP
forall c. NamedIdea c => Lens' c NP
Lens' UnitalChunk NP
term) SimpleQDef
calofCapacityQD)
(QuantityDict -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC (InstanceModel
nonFL InstanceModel
-> Getting QuantityDict InstanceModel QuantityDict -> QuantityDict
forall s a. s -> Getting a s a -> a
^. Getting QuantityDict InstanceModel QuantityDict
forall c. HasOutput c => Getter c QuantityDict
Getter InstanceModel QuantityDict
output) (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: QuantityDict -> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC (DataDefinition
glaTyFac DataDefinition
-> Getting QuantityDict DataDefinition QuantityDict -> QuantityDict
forall s a. s -> Getting a s a -> a
^. Getting QuantityDict DataDefinition QuantityDict
forall c. HasOutput c => Getter c QuantityDict
Getter DataDefinition QuantityDict
output) (QuantityDict, Maybe (RealInterval Expr Expr))
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: [DefinedQuantityDict
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q -> (QuantityDict, Maybe (RealInterval Expr Expr))
qwUC DefinedQuantityDict
loadSF]) (UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
lRe) []
[Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
astm2009] String
"calofCapacity" [Sentence
lrCap, Sentence
nonFLRef, Sentence
gtfRef]
calofCapacityQD :: SimpleQDef
calofCapacityQD :: SimpleQDef
calofCapacityQD = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
lRe (QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy (InstanceModel
nonFL InstanceModel
-> Getting QuantityDict InstanceModel QuantityDict -> QuantityDict
forall s a. s -> Getting a s a -> a
^. Getting QuantityDict InstanceModel QuantityDict
forall c. HasOutput c => Getter c QuantityDict
Getter InstanceModel QuantityDict
output) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* QuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy (DataDefinition
glaTyFac DataDefinition
-> Getting QuantityDict DataDefinition QuantityDict -> QuantityDict
forall s a. s -> Getting a s a -> a
^. Getting QuantityDict DataDefinition QuantityDict
forall d. DefinesQuantity d => Getter d QuantityDict
Getter DataDefinition QuantityDict
defLhs) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* DefinedQuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
loadSF)
pbIsSafe :: InstanceModel
pbIsSafe :: InstanceModel
pbIsSafe = ModelKind Expr
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> QuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (String -> NP
nounPhraseSP String
"Safety Req-Pb") SimpleQDef
pbIsSafeQD)
[ConstrainedChunk
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
qwC ConstrainedChunk
probBr RealInterval Expr Expr
probConstraint, UncertainChunk
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
qwC UncertainChunk
pbTol RealInterval Expr Expr
probConstraint] (QuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw QuantityDict
isSafePb) []
[Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
astm2009] String
"isSafePb" [Sentence
pbIsSafeDesc, Sentence
probBRRef, Sentence
pbTolUsr]
pbIsSafeQD :: SimpleQDef
pbIsSafeQD :: SimpleQDef
pbIsSafeQD = QuantityDict -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef QuantityDict
isSafePb (ConstrainedChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrainedChunk
probBr Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$< UncertainChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertainChunk
pbTol)
lrIsSafe :: InstanceModel
lrIsSafe :: InstanceModel
lrIsSafe = ModelKind Expr
-> [(QuantityDict, Maybe (RealInterval Expr Expr))]
-> QuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> SimpleQDef -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (String -> NP
nounPhraseSP String
"Safety Req-LR") SimpleQDef
lrIsSafeQD)
[UnitalChunk
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
qwC UnitalChunk
lRe (RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr)))
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0), UnitalChunk
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q) =>
q
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
qwC UnitalChunk
demand (RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr)))
-> RealInterval Expr Expr
-> (QuantityDict, Maybe (RealInterval Expr Expr))
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)]
(QuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw QuantityDict
isSafeLR) []
[Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
astm2009] String
"isSafeLR"
[Sentence
lrIsSafeDesc, Sentence
capRef, Sentence
qRef]
lrIsSafeQD :: SimpleQDef
lrIsSafeQD :: SimpleQDef
lrIsSafeQD = QuantityDict -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef QuantityDict
isSafeLR (UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
lRe Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$> UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
demand)
iModDesc :: QuantityDict -> Sentence -> Sentence
iModDesc :: QuantityDict -> Sentence -> Sentence
iModDesc QuantityDict
main Sentence
s = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"If", QuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch QuantityDict
main Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"the glass is" Sentence -> Sentence -> Sentence
+:+.
String -> Sentence
S String
"considered safe", Sentence
s Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"either both True or both False"]
instModIntro :: Sentence
instModIntro :: Sentence
instModIntro = [Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
goal), ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
willBreakGS,
String -> Sentence
S String
"is met by", InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
pbIsSafe Sentence -> Sentence -> Sentence
`sC` InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
lrIsSafe]
lrCap :: Sentence
lrCap :: Sentence
lrCap = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
lRe Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"is also called capacity"
pbTolUsr :: Sentence
pbTolUsr :: Sentence
pbTolUsr = UncertainChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertainChunk
pbTol Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"entered by the" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
user
qRef :: Sentence
qRef :: Sentence
qRef = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
demand Sentence -> Sentence -> Sentence
`S.isThe` (ConceptChunk
demandq 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
"as given in" Sentence -> Sentence -> Sentence
+:+. DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
calofDemand
lrIsSafeDesc :: Sentence
lrIsSafeDesc :: Sentence
lrIsSafeDesc = QuantityDict -> Sentence -> Sentence
iModDesc QuantityDict
isSafeLR
(QuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch QuantityDict
isSafePb Sentence -> Sentence -> Sentence
+:+ InstanceModel -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource InstanceModel
pbIsSafe Sentence -> Sentence -> Sentence
`S.and_` QuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch QuantityDict
isSafeLR)
pbIsSafeDesc :: Sentence
pbIsSafeDesc :: Sentence
pbIsSafeDesc = QuantityDict -> Sentence -> Sentence
iModDesc QuantityDict
isSafePb
(QuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch QuantityDict
isSafePb Sentence -> Sentence -> Sentence
`S.and_` QuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch QuantityDict
isSafeLR Sentence -> Sentence -> Sentence
+:+ InstanceModel -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource InstanceModel
lrIsSafe)
capRef, jRef, jtolRef, ldfRef, nonFLRef, probBRRef, qHtRef, qHtTlTolRef,
riskRef :: Sentence
capRef :: Sentence
capRef = InstanceModel -> Sentence -> Sentence
forall r.
(Referable r, HasShortName r, DefinesQuantity r) =>
r -> Sentence -> Sentence
definedIn' InstanceModel
calofCapacity (String -> Sentence
S String
"and is also called capacity")
jRef :: Sentence
jRef = InstanceModel -> Sentence
forall r.
(Referable r, HasShortName r, DefinesQuantity r) =>
r -> Sentence
definedIn InstanceModel
strDisFac
jtolRef :: Sentence
jtolRef = InstanceModel -> Sentence
forall r.
(Referable r, HasShortName r, DefinesQuantity r) =>
r -> Sentence
definedIn InstanceModel
tolStrDisFac
ldfRef :: Sentence
ldfRef = DataDefinition -> Sentence
forall r.
(Referable r, HasShortName r, DefinesQuantity r) =>
r -> Sentence
definedIn DataDefinition
loadDF
nonFLRef :: Sentence
nonFLRef = InstanceModel -> Sentence
forall r.
(Referable r, HasShortName r, DefinesQuantity r) =>
r -> Sentence
definedIn InstanceModel
nonFL
probBRRef :: Sentence
probBRRef = InstanceModel -> Sentence
forall r.
(Referable r, HasShortName r, DefinesQuantity r) =>
r -> Sentence
definedIn InstanceModel
probOfBreak
qHtRef :: Sentence
qHtRef = InstanceModel -> Sentence
forall r.
(Referable r, HasShortName r, DefinesQuantity r) =>
r -> Sentence
definedIn InstanceModel
dimLL
qHtTlTolRef :: Sentence
qHtTlTolRef = InstanceModel -> Sentence
forall r.
(Referable r, HasShortName r, DefinesQuantity r) =>
r -> Sentence
definedIn InstanceModel
tolPre
riskRef :: Sentence
riskRef = InstanceModel -> Sentence
forall r.
(Referable r, HasShortName r, DefinesQuantity r) =>
r -> Sentence
definedIn InstanceModel
risk
interpolating :: (HasUID s, HasSymbol s, Referable f, HasShortName f) => s -> f -> Sentence
interpolating :: forall s f.
(HasUID s, HasSymbol s, Referable f, HasShortName f) =>
s -> f -> Sentence
interpolating s
s f
f = [Sentence] -> Sentence
foldlSent [s -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch s
s Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"obtained by interpolating from",
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
datum, String -> Sentence
S String
"shown" Sentence -> Sentence -> Sentence
`S.in_` f -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS f
f]