module Drasil.GlassBR.IMods (symb, iMods, pbIsSafe, lrIsSafe, instModIntro) 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 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,
gtfRef, hRef, loadDFDD, 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]
abInputConstraints :: [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
abInputConstraints :: [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
abInputConstraints = [UncertQ
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwC UncertQ
plateLen (RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr)))
-> RealInterval Expr Expr
-> (DefinedQuantityDict, 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
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwC UncertQ
plateWidth (RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr)))
-> RealInterval Expr Expr
-> (DefinedQuantityDict, 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
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> DefinedQuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> QDefinition Expr -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (DefinedQuantityDict
riskFun DefinedQuantityDict -> Getting NP DefinedQuantityDict NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP DefinedQuantityDict NP
forall c. NamedIdea c => Lens' c NP
Lens' DefinedQuantityDict NP
term) QDefinition Expr
riskQD)
(UnitalChunk
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitalChunk
modElas (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: DefinedQuantityDict
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC DefinedQuantityDict
loadDF (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: ConstrConcept
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC ConstrConcept
stressDistFac (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
:
(UnitalChunk
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr)))
-> [UnitalChunk]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC [UnitalChunk
sflawParamK, UnitalChunk
sflawParamM, UnitalChunk
minThick] [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. [a] -> [a] -> [a]
++ [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
abInputConstraints)
DefinedQuantityDict
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 :: QDefinition Expr
riskQD = DefinedQuantityDict -> Expr -> QDefinition Expr
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
riskFun ((UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
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
$^ (UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
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 (UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
minThick)) 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
sflawParamM) 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
loadDF Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* Expr -> Expr
forall r. ExprC r => r -> r
exp (ConstrConcept -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
stressDistFac))
strDisFac :: InstanceModel
strDisFac :: InstanceModel
strDisFac = ModelKind Expr
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> DefinedQuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> QDefinition Expr -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (ConstrConcept
stressDistFac ConstrConcept -> Getting NP ConstrConcept NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP ConstrConcept NP
forall c. NamedIdea c => Lens' c NP
Lens' ConstrConcept NP
term) QDefinition Expr
strDisFacQD)
(UncertQ
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwC UncertQ
aspectRatio RealInterval Expr Expr
aspectRatioConstraint (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: [DefinedQuantityDict
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC DefinedQuantityDict
dimlessLoad]) (ConstrConcept -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr ConstrConcept
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"
[ConstrConcept -> LabelledContent -> Sentence
forall s f.
(HasUID s, HasSymbol s, Referable f, HasShortName f) =>
s -> f -> Sentence
interpolating ConstrConcept
stressDistFac LabelledContent
dimlessloadVsARFig, Sentence
arRef, Sentence
qHtRef]
strDisFacQD :: SimpleQDef
strDisFacQD :: QDefinition Expr
strDisFacQD = ConstrConcept -> Expr -> QDefinition Expr
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef ConstrConcept
stressDistFac Expr
strDisFacEq
strDisFacEq :: Expr
strDisFacEq :: Expr
strDisFacEq = DefinedQuantityDict -> [Expr] -> Expr
forall f. (HasUID f, HasSymbol f) => f -> [Expr] -> Expr
forall r f. (ExprC r, HasUID f, HasSymbol f) => f -> [r] -> r
apply DefinedQuantityDict
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, DefinedQuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
dimlessLoad]
nonFL :: InstanceModel
nonFL :: InstanceModel
nonFL = ModelKind Expr
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> DefinedQuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> QDefinition Expr -> 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) QDefinition Expr
nonFLQD)
(DefinedQuantityDict
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC DefinedQuantityDict
tolLoad (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: UnitalChunk
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitalChunk
modElas (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: UnitalChunk
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitalChunk
minThick (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
abInputConstraints)
(UnitalChunk -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr 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 = (DefinedQuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
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
$* (UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
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 :: QDefinition Expr
nonFLQD = UnitalChunk -> Expr -> QDefinition Expr
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef UnitalChunk
nonFactorL Expr
nonFLEq
dimLL :: InstanceModel
dimLL :: InstanceModel
dimLL = ModelKind Expr
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> DefinedQuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> QDefinition Expr -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (DefinedQuantityDict
dimlessLoad DefinedQuantityDict -> Getting NP DefinedQuantityDict NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP DefinedQuantityDict NP
forall c. NamedIdea c => Lens' c NP
Lens' DefinedQuantityDict NP
term) QDefinition Expr
dimLLQD)
(UnitalChunk
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitalChunk
demand (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: UnitalChunk
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitalChunk
modElas (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: UnitalChunk
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitalChunk
minThick (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: DefinedQuantityDict
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC DefinedQuantityDict
gTF (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
abInputConstraints)
DefinedQuantityDict
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
$* (UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
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 :: QDefinition Expr
dimLLQD = DefinedQuantityDict -> Expr -> QDefinition Expr
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
dimlessLoad Expr
dimLLEq
tolPre :: InstanceModel
tolPre :: InstanceModel
tolPre = ModelKind Expr
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> DefinedQuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> QDefinition Expr -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (DefinedQuantityDict
tolLoad DefinedQuantityDict -> Getting NP DefinedQuantityDict NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP DefinedQuantityDict NP
forall c. NamedIdea c => Lens' c NP
Lens' DefinedQuantityDict NP
term) QDefinition Expr
tolPreQD)
[UncertQ
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwC UncertQ
aspectRatio RealInterval Expr Expr
aspectRatioConstraint, DefinedQuantityDict
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC (DefinedQuantityDict
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr)))
-> DefinedQuantityDict
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall a b. (a -> b) -> a -> b
$ InstanceModel
tolStrDisFac 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] DefinedQuantityDict
tolLoad []
[Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
astm2009] String
"tolLoad" [DefinedQuantityDict -> LabelledContent -> Sentence
forall s f.
(HasUID s, HasSymbol s, Referable f, HasShortName f) =>
s -> f -> Sentence
interpolating DefinedQuantityDict
tolLoad LabelledContent
dimlessloadVsARFig, Sentence
arRef,
Sentence
jtolRef]
tolPreEq :: Expr
tolPreEq :: Expr
tolPreEq = DefinedQuantityDict -> [Expr] -> Expr
forall f. (HasUID f, HasSymbol f) => f -> [Expr] -> Expr
forall r f. (ExprC r, HasUID f, HasSymbol f) => f -> [r] -> r
apply DefinedQuantityDict
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, DefinedQuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
sdfTol]
tolPreQD :: SimpleQDef
tolPreQD :: QDefinition Expr
tolPreQD = DefinedQuantityDict -> Expr -> QDefinition Expr
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
tolLoad Expr
tolPreEq
tolStrDisFac :: InstanceModel
tolStrDisFac :: InstanceModel
tolStrDisFac = ModelKind Expr
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> DefinedQuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> QDefinition Expr -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (DefinedQuantityDict
sdfTol DefinedQuantityDict -> Getting NP DefinedQuantityDict NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP DefinedQuantityDict NP
forall c. NamedIdea c => Lens' c NP
Lens' DefinedQuantityDict NP
term) QDefinition Expr
tolStrDisFacQD)
((DefinedQuantityDict
loadDF, Maybe (RealInterval Expr Expr)
forall a. Maybe a
Nothing) (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: UncertQ
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwC UncertQ
pbTol RealInterval Expr Expr
probConstraint (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: UnitalChunk
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC UnitalChunk
modElas (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
abInputConstraints [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. [a] -> [a] -> [a]
++
(UnitalChunk
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr)))
-> [UnitalChunk]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC [UnitalChunk
sflawParamM, UnitalChunk
sflawParamK, UnitalChunk
minThick]) DefinedQuantityDict
sdfTol []
[Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
astm2009] String
"sdfTol" [Sentence
pbTolUsr, Sentence
aGrtrThanB, [UnitalChunk] -> Sentence
forall s. (HasSymbol s, HasUID s) => [s] -> Sentence
stdVals [UnitalChunk
sflawParamM,
UnitalChunk
sflawParamK, UnitalChunk
modElas], Sentence
hRef, Sentence
ldfRef]
tolStrDisFacQD :: SimpleQDef
tolStrDisFacQD :: QDefinition Expr
tolStrDisFacQD = DefinedQuantityDict -> Expr -> QDefinition Expr
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
sdfTol (Expr -> QDefinition Expr) -> Expr -> QDefinition Expr
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
$- UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
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
$^ (UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
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
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 (UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
minThick)) 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
sflawParamM) 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
loadDF)))
probOfBreak :: InstanceModel
probOfBreak :: InstanceModel
probOfBreak = ModelKind Expr
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> DefinedQuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> QDefinition Expr -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (ConstrConcept
probBr ConstrConcept -> Getting NP ConstrConcept NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP ConstrConcept NP
forall c. NamedIdea c => Lens' c NP
Lens' ConstrConcept NP
term) QDefinition Expr
probOfBreakQD)
[DefinedQuantityDict
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC (DefinedQuantityDict
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr)))
-> DefinedQuantityDict
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall a b. (a -> b) -> a -> b
$ InstanceModel
risk 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] (ConstrConcept -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr ConstrConcept
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 :: QDefinition Expr
probOfBreakQD = ConstrConcept -> Expr -> QDefinition Expr
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef ConstrConcept
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
$ DefinedQuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy (DefinedQuantityDict -> Expr) -> DefinedQuantityDict -> Expr
forall a b. (a -> b) -> a -> b
$ InstanceModel
risk 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))
calofCapacity :: InstanceModel
calofCapacity :: InstanceModel
calofCapacity = ModelKind Expr
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> DefinedQuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> QDefinition Expr -> 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) QDefinition Expr
calofCapacityQD)
(DefinedQuantityDict
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC (InstanceModel
nonFL 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) (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: DefinedQuantityDict
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC (DataDefinition
glaTyFac DataDefinition
-> Getting DefinedQuantityDict DataDefinition DefinedQuantityDict
-> DefinedQuantityDict
forall s a. s -> Getting a s a -> a
^. Getting DefinedQuantityDict DataDefinition DefinedQuantityDict
forall c. HasOutput c => Getter c DefinedQuantityDict
Getter DataDefinition DefinedQuantityDict
output) (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
forall a. a -> [a] -> [a]
: [DefinedQuantityDict
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q -> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwUC DefinedQuantityDict
loadSF]) (UnitalChunk -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr 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 :: QDefinition Expr
calofCapacityQD = UnitalChunk -> Expr -> QDefinition Expr
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef UnitalChunk
lRe (DefinedQuantityDict -> 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 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) 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 (DataDefinition
glaTyFac DataDefinition
-> Getting DefinedQuantityDict DataDefinition DefinedQuantityDict
-> DefinedQuantityDict
forall s a. s -> Getting a s a -> a
^. Getting DefinedQuantityDict DataDefinition DefinedQuantityDict
forall d. DefinesQuantity d => Getter d DefinedQuantityDict
Getter DataDefinition DefinedQuantityDict
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
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> DefinedQuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> QDefinition Expr -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (String -> NP
nounPhraseSP String
"Safety Req-Pb") QDefinition Expr
pbIsSafeQD)
[ConstrConcept
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwC ConstrConcept
probBr RealInterval Expr Expr
probConstraint, UncertQ
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwC UncertQ
pbTol RealInterval Expr Expr
probConstraint] DefinedQuantityDict
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 :: QDefinition Expr
pbIsSafeQD = DefinedQuantityDict -> Expr -> QDefinition Expr
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
isSafePb (ConstrConcept -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
probBr 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
pbTol)
lrIsSafe :: InstanceModel
lrIsSafe :: InstanceModel
lrIsSafe = ModelKind Expr
-> [(DefinedQuantityDict, Maybe (RealInterval Expr Expr))]
-> DefinedQuantityDict
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (NP -> QDefinition Expr -> ModelKind Expr
forall e. NP -> QDefinition e -> ModelKind e
equationalModelN (String -> NP
nounPhraseSP String
"Safety Req-LR") QDefinition Expr
lrIsSafeQD)
[UnitalChunk
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwC UnitalChunk
lRe (RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr)))
-> RealInterval Expr Expr
-> (DefinedQuantityDict, 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
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
forall q.
(Quantity q, MayHaveUnit q, Concept q) =>
q
-> RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr))
qwC UnitalChunk
demand (RealInterval Expr Expr
-> (DefinedQuantityDict, Maybe (RealInterval Expr Expr)))
-> RealInterval Expr Expr
-> (DefinedQuantityDict, 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)]
DefinedQuantityDict
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 :: QDefinition Expr
lrIsSafeQD = DefinedQuantityDict -> Expr -> QDefinition Expr
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
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 :: DefinedQuantityDict -> Sentence -> Sentence
iModDesc :: DefinedQuantityDict -> Sentence -> Sentence
iModDesc DefinedQuantityDict
main Sentence
s = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"If", DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
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 = UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
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 = DefinedQuantityDict -> Sentence -> Sentence
iModDesc DefinedQuantityDict
isSafeLR
(DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
isSafePb Sentence -> Sentence -> Sentence
+:+ InstanceModel -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource InstanceModel
pbIsSafe Sentence -> Sentence -> Sentence
`S.and_` DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
isSafeLR)
pbIsSafeDesc :: Sentence
pbIsSafeDesc :: Sentence
pbIsSafeDesc = DefinedQuantityDict -> Sentence -> Sentence
iModDesc DefinedQuantityDict
isSafePb
(DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
isSafePb Sentence -> Sentence -> Sentence
`S.and_` DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
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
loadDFDD
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]