module Drasil.GlassBR.Unitals where
import Language.Drasil
import Language.Drasil.Display (Symbol(..))
import Language.Drasil.ShortHands
import Language.Drasil.Chunk.Concept.NamedCombinators
import Prelude hiding (log)
import Data.Drasil.Concepts.Math (xComp, yComp, zComp)
import Data.Drasil.Constraints (gtZeroConstr, probConstr)
import Data.Drasil.Quantities.Physics (subMax, subMin, subX, subY, subZ)
import Data.Drasil.SI_Units (kilogram, metre, millimetre, pascal, second)
import Drasil.GlassBR.Concepts (aR, annealed, fullyT, glaPlane, glassTypeFac,
heatS, iGlass, lGlass, lResistance, lShareFac, loadDurFactor, nFL, responseTy,
stdOffDist)
import Drasil.GlassBR.References (astm2009, astm2012, astm2016)
import Drasil.GlassBR.Units (sFlawPU)
symbolsWithDefns :: [UnitalChunk]
symbolsWithDefns :: [UnitalChunk]
symbolsWithDefns = [UnitalChunk
modElas]
modElas :: UnitalChunk
modElas :: UnitalChunk
modElas = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"modElas" (String -> NP
nounPhraseSP String
"modulus of elasticity of glass")
(String -> Sentence
S String
"the ratio of tensile stress to tensile strain of glass") Symbol
cE Space
Real UnitDefn
pascal
constrained :: [ConstrainedChunk]
constrained :: [ConstrainedChunk]
constrained = (UncertainChunk -> ConstrainedChunk)
-> [UncertainChunk] -> [ConstrainedChunk]
forall a b. (a -> b) -> [a] -> [b]
map UncertainChunk -> ConstrainedChunk
forall c.
(Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) =>
c -> ConstrainedChunk
cnstrw [UncertainChunk]
inputDataConstraints [ConstrainedChunk] -> [ConstrainedChunk] -> [ConstrainedChunk]
forall a. [a] -> [a] -> [a]
++
[ConstrainedChunk -> ConstrainedChunk
forall c.
(Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) =>
c -> ConstrainedChunk
cnstrw ConstrainedChunk
probBr, ConstrainedChunk -> ConstrainedChunk
forall c.
(Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) =>
c -> ConstrainedChunk
cnstrw ConstrainedChunk
probFail, ConstrainedChunk -> ConstrainedChunk
forall c.
(Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) =>
c -> ConstrainedChunk
cnstrw ConstrainedChunk
stressDistFac, ConstrainedChunk -> ConstrainedChunk
forall c.
(Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) =>
c -> ConstrainedChunk
cnstrw ConstrainedChunk
nomThick, ConstrConcept -> ConstrainedChunk
forall c.
(Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) =>
c -> ConstrainedChunk
cnstrw ConstrConcept
glassTypeCon]
plateLen, plateWidth, aspectRatio, charWeight, standOffDist :: UncertQ
pbTol, tNT :: UncertainChunk
nomThick :: ConstrainedChunk
glassTypeCon :: ConstrConcept
inputs :: [QuantityDict]
inputs :: [QuantityDict]
inputs = (UncertQ -> QuantityDict) -> [UncertQ] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UncertQ -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [UncertQ]
inputsWUnitsUncrtn [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ (UncertainChunk -> QuantityDict)
-> [UncertainChunk] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UncertainChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [UncertainChunk]
inputsWUncrtn [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++
(ConstrainedChunk -> QuantityDict)
-> [ConstrainedChunk] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstrainedChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [ConstrainedChunk]
inputsNoUncrtn [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ (UnitaryChunk -> QuantityDict) -> [UnitaryChunk] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitaryChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [UnitaryChunk]
sdVector
inputsWUnitsUncrtn :: [UncertQ]
inputsWUnitsUncrtn :: [UncertQ]
inputsWUnitsUncrtn = [UncertQ
plateLen, UncertQ
plateWidth, UncertQ
charWeight]
derivedInsWUnitsUncrtn :: [UncertQ]
derivedInsWUnitsUncrtn :: [UncertQ]
derivedInsWUnitsUncrtn = [UncertQ
standOffDist]
inputsWUncrtn :: [UncertainChunk]
inputsWUncrtn :: [UncertainChunk]
inputsWUncrtn = [UncertainChunk
pbTol, UncertainChunk
tNT]
derivedInsWUncrtn :: [UncertQ]
derivedInsWUncrtn :: [UncertQ]
derivedInsWUncrtn = [UncertQ
aspectRatio]
inputsNoUncrtn :: [ConstrainedChunk]
inputsNoUncrtn :: [ConstrainedChunk]
inputsNoUncrtn = [ConstrConcept -> ConstrainedChunk
forall c.
(Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) =>
c -> ConstrainedChunk
cnstrw ConstrConcept
glassTypeCon, ConstrainedChunk
nomThick]
inputDataConstraints :: [UncertainChunk]
inputDataConstraints :: [UncertainChunk]
inputDataConstraints = (UncertQ -> UncertainChunk) -> [UncertQ] -> [UncertainChunk]
forall a b. (a -> b) -> [a] -> [b]
map UncertQ -> UncertainChunk
forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
c -> UncertainChunk
uncrtnw [UncertQ]
inputsWUnitsUncrtn [UncertainChunk] -> [UncertainChunk] -> [UncertainChunk]
forall a. [a] -> [a] -> [a]
++
(UncertainChunk -> UncertainChunk)
-> [UncertainChunk] -> [UncertainChunk]
forall a b. (a -> b) -> [a] -> [b]
map UncertainChunk -> UncertainChunk
forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
c -> UncertainChunk
uncrtnw [UncertainChunk]
inputsWUncrtn [UncertainChunk] -> [UncertainChunk] -> [UncertainChunk]
forall a. [a] -> [a] -> [a]
++ (UncertQ -> UncertainChunk) -> [UncertQ] -> [UncertainChunk]
forall a b. (a -> b) -> [a] -> [b]
map UncertQ -> UncertainChunk
forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
c -> UncertainChunk
uncrtnw [UncertQ]
derivedInsWUnitsUncrtn [UncertainChunk] -> [UncertainChunk] -> [UncertainChunk]
forall a. [a] -> [a] -> [a]
++
(UncertQ -> UncertainChunk) -> [UncertQ] -> [UncertainChunk]
forall a b. (a -> b) -> [a] -> [b]
map UncertQ -> UncertainChunk
forall c.
(HasUncertainty c, Quantity c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
c -> UncertainChunk
uncrtnw [UncertQ]
derivedInsWUncrtn
plateLen :: UncertQ
plateLen = String
-> NP
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqcND String
"plateLen" (String -> NP
nounPhraseSP String
"plate length (long dimension)")
Symbol
lA UnitDefn
metre Space
Real
[ ConstraintE
gtZeroConstr,
RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (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
plateWidth),
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
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
Inc , ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
dimMin) (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
dimMax)] (Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
1.5) Uncertainty
defaultUncrt
plateWidth :: UncertQ
plateWidth = String
-> NP
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqcND String
"plateWidth" (String -> NP
nounPhraseSP String
"plate width (short dimension)")
Symbol
lB UnitDefn
metre Space
Real
[ RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
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),
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
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
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
dimMin) (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
dimMax)] (Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
1.2) Uncertainty
defaultUncrt
aspectRatio :: UncertQ
aspectRatio = ConstrConcept -> Uncertainty -> UncertQ
forall c.
(Quantity c, Constrained c, Concept c, HasReasVal c,
MayHaveUnit c) =>
c -> Uncertainty -> UncertQ
uq (DefinedQuantityDict -> [ConstraintE] -> Expr -> ConstrConcept
forall c.
(Concept c, MayHaveUnit c, Quantity c) =>
c -> [ConstraintE] -> Expr -> ConstrConcept
constrained' (ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit ConceptChunk
aspectRatioCon (String -> Symbol
variable String
"AR") Space
Real)
[ RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (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),
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> RealInterval a b
UpTo (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
arMax)] (Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
1.5)) Uncertainty
defaultUncrt
pbTol :: UncertainChunk
pbTol = String
-> NP
-> Symbol
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertainChunk
uvc String
"pbTol" (String -> NP
nounPhraseSP String
"tolerable probability of breakage")
(Symbol -> Symbol -> Symbol
sub Symbol
cP ([Symbol] -> Symbol
Concat [Symbol
lBreak, Symbol
lTol])) Space
Real
[ConstraintE
probConstr] (Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
0.008) (Double -> Maybe Int -> Uncertainty
uncty Double
0.001 Maybe Int
forall a. Maybe a
Nothing)
charWeight :: UncertQ
charWeight = String
-> NP
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqcND String
"charWeight" (String -> NP
nounPhraseSP String
"charge weight")
Symbol
lW UnitDefn
kilogram Space
Real
[ ConstraintE
gtZeroConstr,
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
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
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
cWeightMin) (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
cWeightMax)]
(Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
42) Uncertainty
defaultUncrt
tNT :: UncertainChunk
tNT = String
-> NP
-> Symbol
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertainChunk
uvc String
"tNT" (String -> NP
nounPhraseSP String
"TNT equivalent factor")
(String -> Symbol
variable String
"TNT") Space
Real
[ ConstraintE
gtZeroConstr ] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1) Uncertainty
defaultUncrt
standOffDist :: UncertQ
standOffDist = ConstrConcept -> Uncertainty -> UncertQ
forall c.
(Quantity c, Constrained c, Concept c, HasReasVal c,
MayHaveUnit c) =>
c -> Uncertainty -> UncertQ
uq (UnitalChunk -> [ConstraintE] -> Expr -> ConstrConcept
forall c.
(Concept c, MayHaveUnit c, Quantity c) =>
c -> [ConstraintE] -> Expr -> ConstrConcept
constrained' (ConceptChunk -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall c u.
(Concept c, IsUnit u) =>
c -> Symbol -> Space -> u -> UnitalChunk
uc ConceptChunk
sD (String -> Symbol
variable String
"SD") Space
Real UnitDefn
metre)
[ ConstraintE
gtZeroConstr,
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
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
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
sdMin) (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
sdMax)] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
45)) Uncertainty
defaultUncrt
nomThick :: ConstrainedChunk
nomThick = String
-> NP
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> ConstrainedChunk
forall u.
IsUnit u =>
String
-> NP
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> ConstrainedChunk
cuc String
"nomThick"
(Sentence -> NP
nounPhraseSent (Sentence -> NP) -> Sentence -> NP
forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"nominal thickness t is in" Sentence -> Sentence -> Sentence
+:+ ModelExpr -> Sentence
eS (Space -> [ModelExpr] -> ModelExpr
forall r. ExprC r => Space -> [r] -> r
mkSet Space
Rational ((Double -> ModelExpr) -> [Double] -> [ModelExpr]
forall a b. (a -> b) -> [a] -> [b]
map Double -> ModelExpr
forall r. LiteralC r => Double -> r
dbl [Double]
nominalThicknesses)))
Symbol
lT UnitDefn
millimetre Space
Rational
[Expr -> ConstraintE
sfwrElem (Expr -> ConstraintE) -> Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ Space -> [Expr] -> Expr
forall r. ExprC r => Space -> [r] -> r
mkSet Space
Rational ((Double -> Expr) -> [Double] -> [Expr]
forall a b. (a -> b) -> [a] -> [b]
map Double -> Expr
forall r. LiteralC r => Double -> r
dbl [Double]
nominalThicknesses)] (Expr -> ConstrainedChunk) -> Expr -> ConstrainedChunk
forall a b. (a -> b) -> a -> b
$ Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
8
glassTypeCon :: ConstrConcept
glassTypeCon = DefinedQuantityDict -> [ConstraintE] -> ConstrConcept
forall c.
(Concept c, MayHaveUnit c, Quantity c) =>
c -> [ConstraintE] -> ConstrConcept
constrainedNRV' (ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit ConceptChunk
glassTy Symbol
lG Space
String)
[Expr -> ConstraintE
sfwrElem (Expr -> ConstraintE) -> Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ Space -> [Expr] -> Expr
forall r. ExprC r => Space -> [r] -> r
mkSet Space
String ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ ((Integer, CI) -> Expr) -> [(Integer, CI)] -> [Expr]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Expr
forall r. LiteralC r => String -> r
str (String -> Expr)
-> ((Integer, CI) -> String) -> (Integer, CI) -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CI -> String
forall c. CommonIdea c => c -> String
abrv (CI -> String) -> ((Integer, CI) -> CI) -> (Integer, CI) -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Integer, CI) -> CI
forall a b. (a, b) -> b
snd) [(Integer, CI)]
glassType]
outputs :: [QuantityDict]
outputs :: [QuantityDict]
outputs = (QuantityDict -> QuantityDict) -> [QuantityDict] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map QuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [QuantityDict
isSafePb, QuantityDict
isSafeLR] [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ [ConstrainedChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrainedChunk
probBr, ConstrainedChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrainedChunk
stressDistFac]
tmSymbols :: [QuantityDict]
tmSymbols :: [QuantityDict]
tmSymbols = (ConstrainedChunk -> QuantityDict)
-> [ConstrainedChunk] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstrainedChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [ConstrainedChunk
probFail, ConstrainedChunk
pbTolfail] [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ (QuantityDict -> QuantityDict) -> [QuantityDict] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map QuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [QuantityDict
isSafeProb, QuantityDict
isSafeLoad]
probBr, probFail, pbTolfail, stressDistFac :: ConstrainedChunk
probBr :: ConstrainedChunk
probBr = String
-> NP
-> Symbol
-> Space
-> [ConstraintE]
-> Maybe Expr
-> ConstrainedChunk
cvc String
"probBr" (String -> NP
nounPhraseSP String
"probability of breakage")
(Symbol -> Symbol -> Symbol
sub Symbol
cP Symbol
lBreak) Space
Real
[ConstraintE
probConstr] (Expr -> Maybe Expr
forall a. a -> Maybe a
Just (Expr -> Maybe Expr) -> Expr -> Maybe Expr
forall a b. (a -> b) -> a -> b
$ Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
0.4)
stressDistFac :: ConstrainedChunk
stressDistFac = String
-> NP
-> Symbol
-> Space
-> [ConstraintE]
-> Maybe Expr
-> ConstrainedChunk
cvc String
"stressDistFac" (String -> NP
nounPhraseSP String
"stress distribution factor (Function)")
Symbol
cJ Space
Real [RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
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
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)] (Expr -> Maybe Expr
forall a. a -> Maybe a
Just (Expr -> Maybe Expr) -> Expr -> Maybe Expr
forall a b. (a -> b) -> a -> b
$ Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
15)
probFail :: ConstrainedChunk
probFail = String
-> NP
-> Symbol
-> Space
-> [ConstraintE]
-> Maybe Expr
-> ConstrainedChunk
cvc String
"probFail" (String -> NP
nounPhraseSP String
"probability of failure")
(Symbol -> Symbol -> Symbol
sub Symbol
cP Symbol
lFail) Space
Real
[ConstraintE
probConstr] (Expr -> Maybe Expr
forall a. a -> Maybe a
Just (Expr -> Maybe Expr) -> Expr -> Maybe Expr
forall a b. (a -> b) -> a -> b
$ Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
0.4)
pbTolfail :: ConstrainedChunk
pbTolfail = String
-> NP
-> Symbol
-> Space
-> [ConstraintE]
-> Maybe Expr
-> ConstrainedChunk
cvc String
"pbTolfail" (String -> NP
nounPhraseSP String
"tolerable probability of failure")
(Symbol -> Symbol -> Symbol
sub Symbol
cP ([Symbol] -> Symbol
Concat [Symbol
lFail, Symbol
lTol])) Space
Real
[ConstraintE
probConstr] (Expr -> Maybe Expr
forall a. a -> Maybe a
Just (Expr -> Maybe Expr) -> Expr -> Maybe Expr
forall a b. (a -> b) -> a -> b
$ Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
0.008)
specParamVals :: [ConstQDef]
specParamVals :: [ConstQDef]
specParamVals = [ConstQDef
dimMax, ConstQDef
dimMin, ConstQDef
arMax, ConstQDef
cWeightMax, ConstQDef
cWeightMin,
ConstQDef
sdMax, ConstQDef
sdMin, ConstQDef
stressDistFacMin, ConstQDef
stressDistFacMax]
dimMax, dimMin, arMax, cWeightMax, cWeightMin, sdMax, stressDistFacMin, stressDistFacMax,
sdMin :: ConstQDef
dimMax :: ConstQDef
dimMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"dimMax"
(String -> NP
nounPhraseSP String
"maximum value for one of the dimensions of the glass plate")
(Symbol -> Symbol
subMax Symbol
lD) UnitDefn
metre Space
Real) (Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
5)
dimMin :: ConstQDef
dimMin = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"dimMin"
(String -> NP
nounPhraseSP String
"minimum value for one of the dimensions of the glass plate")
(Symbol -> Symbol
subMin Symbol
lD) UnitDefn
metre Space
Real) (Double -> Literal
forall r. LiteralC r => Double -> r
dbl Double
0.1)
arMax :: ConstQDef
arMax = QuantityDict -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> Space -> QuantityDict
vc String
"arMax"
(String -> NP
nounPhraseSP String
"maximum aspect ratio")
(Symbol -> Symbol
subMax (String -> Symbol
variable String
"AR")) Space
Real) (Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
5)
cWeightMax :: ConstQDef
cWeightMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"cWeightMax"
(String -> NP
nounPhraseSP String
"maximum permissible input charge weight")
(Symbol -> Symbol
subMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
charWeight)) UnitDefn
kilogram Space
Real) (Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
910)
cWeightMin :: ConstQDef
cWeightMin = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"cWeightMin"
(String -> NP
nounPhraseSP String
"minimum permissible input charge weight")
(Symbol -> Symbol
subMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
charWeight)) UnitDefn
kilogram Space
Real) (Double -> Literal
forall r. LiteralC r => Double -> r
dbl Double
4.5)
sdMax :: ConstQDef
sdMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"sdMax"
(String -> NP
nounPhraseSP String
"maximum stand off distance permissible for input")
(Symbol -> Symbol
subMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
standOffDist)) UnitDefn
metre Space
Real) (Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
130)
sdMin :: ConstQDef
sdMin = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"sdMin"
(String -> NP
nounPhraseSP String
"minimum stand off distance permissible for input")
(Symbol -> Symbol
subMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
standOffDist)) UnitDefn
metre Space
Real) (Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
6)
stressDistFacMin :: ConstQDef
stressDistFacMin = QuantityDict -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> Space -> QuantityDict
vc String
"stressDistFacMin" (String -> NP
nounPhraseSP String
"minimum value for the stress distribution factor")
(Symbol -> Symbol
subMin (ConstrainedChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb ConstrainedChunk
stressDistFac)) Space
Real) (Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
1)
stressDistFacMax :: ConstQDef
stressDistFacMax = QuantityDict -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> Space -> QuantityDict
vc String
"stressDistFacMax" (String -> NP
nounPhraseSP String
"maximum value for the stress distribution factor")
(Symbol -> Symbol
subMax (ConstrainedChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb ConstrainedChunk
stressDistFac)) Space
Real) (Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
32)
symbols :: [UnitaryChunk]
symbols :: [UnitaryChunk]
symbols = [UnitaryChunk
minThick, UnitaryChunk
sflawParamK, UnitaryChunk
sflawParamM, UnitaryChunk
loadDur] [UnitaryChunk] -> [UnitaryChunk] -> [UnitaryChunk]
forall a. [a] -> [a] -> [a]
++
(UnitalChunk -> UnitaryChunk) -> [UnitalChunk] -> [UnitaryChunk]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> UnitaryChunk
forall u. (Unitary u, MayHaveUnit u) => u -> UnitaryChunk
mkUnitary [UnitalChunk
demand, UnitalChunk
tmDemand, UnitalChunk
lRe, UnitalChunk
tmLRe, UnitalChunk
nonFactorL, UnitalChunk
eqTNTWeight]
minThick, sflawParamK, sflawParamM, sdx, sdy, sdz, loadDur :: UnitaryChunk
demand, tmDemand, lRe, tmLRe, nonFactorL, eqTNTWeight :: UnitalChunk
demand :: UnitalChunk
demand = ConceptChunk -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall c u.
(Concept c, IsUnit u) =>
c -> Symbol -> Space -> u -> UnitalChunk
uc ConceptChunk
demandq Symbol
lQ Space
Real UnitDefn
pascal
tmDemand :: UnitalChunk
tmDemand = ConceptChunk -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall c u.
(Concept c, IsUnit u) =>
c -> Symbol -> Space -> u -> UnitalChunk
uc ConceptChunk
load (String -> Symbol
variable String
"Load") Space
Real UnitDefn
pascal
lRe :: UnitalChunk
lRe = ConceptChunk -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall c u.
(Concept c, IsUnit u) =>
c -> Symbol -> Space -> u -> UnitalChunk
uc ConceptChunk
loadResis (String -> Symbol
variable String
"LR") Space
Real UnitDefn
pascal
tmLRe :: UnitalChunk
tmLRe = ConceptChunk -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall c u.
(Concept c, IsUnit u) =>
c -> Symbol -> Space -> u -> UnitalChunk
uc ConceptChunk
capacity (String -> Symbol
variable String
"capacity") Space
Real UnitDefn
pascal
nonFactorL :: UnitalChunk
nonFactorL = ConceptChunk -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall c u.
(Concept c, IsUnit u) =>
c -> Symbol -> Space -> u -> UnitalChunk
uc ConceptChunk
nonFactoredL (String -> Symbol
variable String
"NFL") Space
Real UnitDefn
pascal
eqTNTWeight :: UnitalChunk
eqTNTWeight = ConceptChunk -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall c u.
(Concept c, IsUnit u) =>
c -> Symbol -> Space -> u -> UnitalChunk
uc ConceptChunk
eqTNTChar (Symbol -> Symbol -> Symbol
sub (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
charWeight) (UncertainChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertainChunk
tNT)) Space
Real
UnitDefn
kilogram
loadDur :: UnitaryChunk
loadDur = String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"loadDur" (String -> NP
nounPhraseSP String
"duration of load")
(Symbol -> Symbol -> Symbol
sub Symbol
lT Symbol
lDur) UnitDefn
second Space
Real
minThick :: UnitaryChunk
minThick = String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"minThick" (String -> NP
nounPhraseSP String
"minimum thickness")
Symbol
lH UnitDefn
metre Space
Real
sdx :: UnitaryChunk
sdx = String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"sdx" (Sentence -> NP
nounPhraseSent (Sentence -> NP) -> Sentence -> NP
forall a b. (a -> b) -> a -> b
$ UncertQ -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UncertQ
standOffDist Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
xComp))
(Symbol -> Symbol
subX (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
standOffDist)) UnitDefn
metre Space
Real
sdy :: UnitaryChunk
sdy = String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"sdy" (Sentence -> NP
nounPhraseSent (Sentence -> NP) -> Sentence -> NP
forall a b. (a -> b) -> a -> b
$ UncertQ -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UncertQ
standOffDist Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
yComp))
(Symbol -> Symbol
subY (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
standOffDist)) UnitDefn
metre Space
Real
sdz :: UnitaryChunk
sdz = String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"sdz" (Sentence -> NP
nounPhraseSent (Sentence -> NP) -> Sentence -> NP
forall a b. (a -> b) -> a -> b
$ UncertQ -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UncertQ
standOffDist Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
zComp))
(Symbol -> Symbol
subZ (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
standOffDist)) UnitDefn
metre Space
Real
sflawParamK :: UnitaryChunk
sflawParamK = String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"sflawParamK" (String -> NP
nounPhraseSP String
"surface flaw parameter")
Symbol
lK UnitDefn
sFlawPU Space
Real
sflawParamM :: UnitaryChunk
sflawParamM = String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"sflawParamM" (String -> NP
nounPhraseSP String
"surface flaw parameter")
Symbol
lM UnitDefn
sFlawPU Space
Real
unitless :: [QuantityDict]
unitless :: [QuantityDict]
unitless = [QuantityDict
riskFun, QuantityDict
isSafePb, QuantityDict
isSafeProb, QuantityDict
isSafeLR, QuantityDict
isSafeLoad,
QuantityDict
sdfTol, QuantityDict
dimlessLoad, QuantityDict
tolLoad, QuantityDict
lDurFac] [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ (DefinedQuantityDict -> QuantityDict)
-> [DefinedQuantityDict] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map DefinedQuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [DefinedQuantityDict
gTF, DefinedQuantityDict
loadSF]
interps :: [QuantityDict]
interps :: [QuantityDict]
interps = [QuantityDict
interpY, QuantityDict
interpZ]
riskFun, isSafePb, isSafeProb, isSafeLR, isSafeLoad, sdfTol,
dimlessLoad, tolLoad, lDurFac, interpY, interpZ :: QuantityDict
gTF, loadSF :: DefinedQuantityDict
dimlessLoad :: QuantityDict
dimlessLoad = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"dimlessLoad" (String -> NP
nounPhraseSP String
"dimensionless load") (Symbol -> Symbol
hat Symbol
lQ) Space
Real
gTF :: DefinedQuantityDict
gTF = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit ConceptChunk
glTyFac (String -> Symbol
variable String
"GTF") Space
Integer
isSafePb :: QuantityDict
isSafePb = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"isSafePb" (String -> NP
nounPhraseSP String
"probability of glass breakage safety requirement")
(String -> Symbol
variable String
"isSafePb") Space
Boolean
isSafeProb :: QuantityDict
isSafeProb = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"isSafeProb" (String -> NP
nounPhraseSP String
"probability of failure safety requirement")
(String -> Symbol
variable String
"isSafeProb") Space
Boolean
isSafeLR :: QuantityDict
isSafeLR = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"isSafeLR" (String -> NP
nounPhraseSP String
"3 second load equivalent resistance safety requirement")
(String -> Symbol
variable String
"isSafeLR") Space
Boolean
isSafeLoad :: QuantityDict
isSafeLoad = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"isSafeLoad" (String -> NP
nounPhraseSP String
"load resistance safety requirement")
(String -> Symbol
variable String
"isSafeLoad") Space
Boolean
interpY :: QuantityDict
interpY = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"interpY" (String -> NP
nounPhraseSP String
"interpY") (String -> Symbol
variable String
"interpY") ([Space] -> Space -> Space
mkFunction [Space
String, Space
Real, Space
Real] Space
Real)
interpZ :: QuantityDict
interpZ = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"interpZ" (String -> NP
nounPhraseSP String
"interpZ") (String -> Symbol
variable String
"interpZ") ([Space] -> Space -> Space
mkFunction [Space
String, Space
Real, Space
Real] Space
Real)
lDurFac :: QuantityDict
lDurFac = CI -> Symbol -> Space -> QuantityDict
forall c. Idea c => c -> Symbol -> Space -> QuantityDict
vc'' CI
loadDurFactor (String -> Symbol
variable String
"LDF") Space
Real
loadSF :: DefinedQuantityDict
loadSF = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit ConceptChunk
loadShareFac (String -> Symbol
variable String
"LSF") Space
Real
riskFun :: QuantityDict
riskFun = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"riskFun" (String -> NP
nounPhraseSP String
"risk of failure") Symbol
cB Space
Real
sdfTol :: QuantityDict
sdfTol = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"sdfTol" (String -> NP
nounPhraseSP String
"tolerable stress distribution factor")
(Symbol -> Symbol -> Symbol
sub (ConstrainedChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb ConstrainedChunk
stressDistFac) Symbol
lTol) Space
Real
tolLoad :: QuantityDict
tolLoad = String -> NP -> Symbol -> Space -> QuantityDict
vc String
"tolLoad" (String -> NP
nounPhraseSP String
"tolerable load")
(Symbol -> Symbol -> Symbol
sub (QuantityDict -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb QuantityDict
dimlessLoad) Symbol
lTol) Space
Real
lBreak, lDur, lFail, lTol :: Symbol
lBreak :: Symbol
lBreak = String -> Symbol
label String
"b"
lDur :: Symbol
lDur = String -> Symbol
label String
"d"
lFail :: Symbol
lFail = String -> Symbol
label String
"f"
lTol :: Symbol
lTol = String -> Symbol
label String
"tol"
terms :: [ConceptChunk]
terms :: [ConceptChunk]
terms = [ConceptChunk
aspectRatioCon, ConceptChunk
glBreakage, ConceptChunk
lite, ConceptChunk
glassTy, ConceptChunk
annealedGl, ConceptChunk
fTemperedGl, ConceptChunk
hStrengthGl,
ConceptChunk
glTyFac, ConceptChunk
lateral, ConceptChunk
load, ConceptChunk
specDeLoad, ConceptChunk
loadResis, ConceptChunk
longDurLoad, ConceptChunk
nonFactoredL,
ConceptChunk
glassWL, ConceptChunk
shortDurLoad, ConceptChunk
loadShareFac, ConceptChunk
probBreak, ConceptChunk
specA, ConceptChunk
blastResisGla, ConceptChunk
eqTNTChar,
ConceptChunk
sD, ConceptChunk
blast, ConceptChunk
blastTy, ConceptChunk
glassGeo, ConceptChunk
capacity, ConceptChunk
demandq, ConceptChunk
safeMessage, ConceptChunk
notSafe, ConceptChunk
bomb,
ConceptChunk
explosion]
aspectRatioCon, glBreakage, lite, glassTy, annealedGl, fTemperedGl, hStrengthGl,
glTyFac, lateral, load, specDeLoad, loadResis, longDurLoad, nonFactoredL,
glassWL, shortDurLoad, loadShareFac, probBreak, specA, blastResisGla, eqTNTChar,
sD, blast, blastTy, glassGeo, capacity, demandq, safeMessage, notSafe, bomb,
explosion :: ConceptChunk
annealedGl :: ConceptChunk
annealedGl = CI -> Sentence -> ConceptChunk
forall c. Idea c => c -> Sentence -> ConceptChunk
cc' CI
annealed
(String -> Sentence
S String
"a flat, monolithic, glass lite which has uniform thickness where" Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"the residual surface stresses are almost zero, as defined in"Sentence -> Sentence -> Sentence
+:+ Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
astm2016)
aspectRatioCon :: ConceptChunk
aspectRatioCon = CI -> String -> ConceptChunk
forall c. Idea c => c -> String -> ConceptChunk
cc CI
aR
(String
"the ratio of the long dimension of the glass to the short dimension of " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"the glass. For glass supported on four sides, the aspect ratio is " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"always equal to or greater than 1.0. For glass supported on three " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"sides, the ratio of the length of one of the supported edges " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"perpendicular to the free edge, to the length of the free edge, is " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"equal to or greater than 0.5")
blast :: ConceptChunk
blast = String -> NP -> String -> ConceptChunk
dcc String
"blast" (String -> NP
cn' String
"blast")
String
"any kind of man-made explosion"
blastResisGla :: ConceptChunk
blastResisGla = String -> NP -> String -> ConceptChunk
dcc String
"blastResisGla" (String -> NP
nounPhraseSP String
"blast resistant glazing")
String
"glazing that provides protection against air blast pressure generated by explosions"
blastTy :: ConceptChunk
blastTy = String -> NP -> String -> ConceptChunk
dcc String
"blastTy" (String -> NP
cn' String
"blast type")
(String
"the blast type input includes parameters like weight of charge, TNT " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"equivalent factor, and stand off distance from the point of explosion")
bomb :: ConceptChunk
bomb = String -> NP -> String -> ConceptChunk
dcc String
"bomb" (String -> NP
cn' String
"bomb") (String
"a container filled " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"with a destructive substance designed to exlode on impact or via detonation")
capacity :: ConceptChunk
capacity = String -> NP -> String -> ConceptChunk
dcc String
"capacity" (String -> NP
nounPhraseSP String
"capacity or load resistance")
String
"load resistance calculated"
demandq :: ConceptChunk
demandq = String -> NP -> String -> ConceptChunk
dcc String
"demandq" (String -> NP
nounPhraseSP String
"applied load (demand)")
String
"3 second duration equivalent pressure"
eqTNTChar :: ConceptChunk
eqTNTChar = String -> NP -> String -> ConceptChunk
dcc String
"eqTNTChar" (String -> NP
nounPhraseSP String
"equivalent TNT charge mass")
String
"mass of TNT placed on the ground in a hemisphere that represents the design explosive threat"
explosion :: ConceptChunk
explosion = String -> NP -> String -> ConceptChunk
dcc String
"explosion" (String -> NP
cn' String
"explosion")
String
"a destructive shattering of something"
fTemperedGl :: ConceptChunk
fTemperedGl = CI -> Sentence -> ConceptChunk
forall c. Idea c => c -> Sentence -> ConceptChunk
cc' CI
fullyT
([Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"a flat, monolithic, glass lite of uniform thickness that has",
String -> Sentence
S String
"been subjected to a special heat treatment process where the residual",
String -> Sentence
S String
"surface compression is not less than 69 MPa (10 000 psi) or the edge",
String -> Sentence
S String
"compression not less than 67 MPa (9700 psi), as defined in", Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
astm2012])
glassGeo :: ConceptChunk
glassGeo = String -> NP -> Sentence -> ConceptChunk
dccWDS String
"glassGeo" (String -> NP
cnIES String
"glass geometry")
(String -> Sentence
S String
"the glass geometry based inputs include the dimensions of the" Sentence -> Sentence -> Sentence
+:+
SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List [IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
glaPlane, ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
glassTy, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
responseTy])
glassTy :: ConceptChunk
glassTy = String -> NP -> String -> ConceptChunk
dcc String
"glassTy" (String -> NP
cn' String
"glass type") String
"type of glass"
glassWL :: ConceptChunk
glassWL = String -> NP -> String -> ConceptChunk
dcc String
"glassWL" (String -> NP
nounPhraseSP String
"glass weight load")
String
"the dead load component of the glass weight"
glBreakage :: ConceptChunk
glBreakage = String -> NP -> String -> ConceptChunk
dcc String
"glBreakage" (String -> NP
nounPhraseSP String
"glass breakage")
String
"the fracture or breakage of any lite or ply in monolithic, laminated, or insulating glass"
glTyFac :: ConceptChunk
glTyFac = CI -> Sentence -> ConceptChunk
forall c. Idea c => c -> Sentence -> ConceptChunk
cc' CI
glassTypeFac
([Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"a multiplying factor for adjusting the", CI -> Sentence
getAcc CI
lResistance,
String -> Sentence
S String
"of different glass type, that is,", SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
Options [Sentence]
glassTypeAbbrs
Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"in monolithic glass" Sentence -> Sentence -> Sentence
`sC` CI -> Sentence
getAcc CI
lGlass, Sentence -> Sentence
sParen (CI -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize CI
lGlass) Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"or", CI -> Sentence
getAcc CI
iGlass, Sentence -> Sentence
sParen (CI -> Sentence
forall n. NamedIdea n => n -> Sentence
titleize CI
iGlass), String -> Sentence
S String
"constructions"])
hStrengthGl :: ConceptChunk
hStrengthGl = CI -> Sentence -> ConceptChunk
forall c. Idea c => c -> Sentence -> ConceptChunk
cc' CI
heatS
([Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"a flat, monolithic, glass lite of uniform thickness that has",
String -> Sentence
S String
"been subjected to a special heat treatment process where the residual",
String -> Sentence
S String
"surface compression is not less than 24 MPa (3500psi) or greater than",
String -> Sentence
S String
"52 MPa (7500 psi), as defined in", Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
astm2012])
lateral :: ConceptChunk
lateral = String -> NP -> String -> ConceptChunk
dcc String
"lateral" (String -> NP
nounPhraseSP String
"lateral")
String
"perpendicular to the glass surface"
lite :: ConceptChunk
lite = String -> NP -> String -> ConceptChunk
dcc String
"lite" (String -> NP
cn' String
"lite")
String
"pieces of glass that are cut, prepared, and used to create the window or door"
load :: ConceptChunk
load = String -> NP -> String -> ConceptChunk
dcc String
"load" (String -> NP
nounPhraseSP String
"applied load (demand) or pressure")
String
"a uniformly distributed lateral pressure"
loadResis :: ConceptChunk
loadResis = CI -> Sentence -> ConceptChunk
forall c. Idea c => c -> Sentence -> ConceptChunk
cc' CI
lResistance
([Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"the uniform lateral load that a glass construction can sustain",
String -> Sentence
S String
"based upon a given probability of breakage and load duration as defined in",
Citation -> RefInfo -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> RefInfo -> Sentence
complexRef Citation
astm2009 (RefInfo -> Sentence) -> RefInfo -> Sentence
forall a b. (a -> b) -> a -> b
$ [Int] -> RefInfo
Page [Int
1, Int
53]])
loadShareFac :: ConceptChunk
loadShareFac = CI -> Sentence -> ConceptChunk
forall c. Idea c => c -> Sentence -> ConceptChunk
cc' CI
lShareFac
([Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"a multiplying factor derived from the load sharing between the",
String -> Sentence
S String
"double glazing, of equal or different thicknesses and types (including the",
String -> Sentence
S String
"layered behaviour of", CI -> Sentence
getAcc CI
lGlass, String -> Sentence
S String
"under long duration",
String -> Sentence
S String
"loads), in a sealed", CI -> Sentence
getAcc CI
iGlass, String -> Sentence
S String
"unit"])
longDurLoad :: ConceptChunk
longDurLoad = String -> NP -> String -> ConceptChunk
dcc String
"longDurLoad" (String -> NP
nounPhraseSP String
"long duration load")
String
"any load lasting approximately 30 days"
nonFactoredL :: ConceptChunk
nonFactoredL = CI -> Sentence -> ConceptChunk
forall c. Idea c => c -> Sentence -> ConceptChunk
cc' CI
nFL
([Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"three second duration uniform load associated with a",
String -> Sentence
S String
"probability of breakage less than or equal to 8", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
lite,
String -> Sentence
S String
"per 1000 for monolithic", CI -> Sentence
getAcc CI
annealed, String -> Sentence
S String
"glass"])
notSafe :: ConceptChunk
notSafe = String -> NP -> String -> ConceptChunk
dcc String
"notSafe" (String -> NP
nounPhraseSP String
"not safe")
String
"For the given input parameters, the glass is NOT considered safe."
probBreak :: ConceptChunk
probBreak = ConstrainedChunk -> Sentence -> ConceptChunk
forall c. Idea c => c -> Sentence -> ConceptChunk
cc' ConstrainedChunk
probBr
([Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"the fraction of glass lites or plies that would break at the",
String -> Sentence
S String
"first occurrence of a specified load and duration, typically expressed",
String -> Sentence
S String
"in lites per 1000", Sentence -> Sentence
sParen (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ Citation -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS Citation
astm2016])
safeMessage :: ConceptChunk
safeMessage = String -> NP -> String -> ConceptChunk
dcc String
"safeMessage" (String -> NP
nounPhraseSP String
"safe")
String
"For the given input parameters, the glass is considered safe."
sD :: ConceptChunk
sD = CI -> Sentence -> ConceptChunk
forall c. Idea c => c -> Sentence -> ConceptChunk
cc' CI
stdOffDist
(String -> Sentence
S String
"the distance from the glazing surface to the centroid of a hemispherical" Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"high explosive charge. It is represented by the coordinates" Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen Sentence
sdVectorSent)
shortDurLoad :: ConceptChunk
shortDurLoad = String -> NP -> String -> ConceptChunk
dcc String
"shortDurLoad" (String -> NP
nounPhraseSP String
"short duration load")
String
"any load lasting 3 seconds or less"
specA :: ConceptChunk
specA = String -> NP -> String -> ConceptChunk
dcc String
"specA" (String -> NP
nounPhraseSP String
"specifying authority")
(String
"the design professional responsible for interpreting applicable " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"regulations of authorities having jurisdiction and considering " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"appropriate site specific factors to determine the appropriate " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"values used to calculate the specified design load, and furnishing" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
" other information required to perform this practice")
specDeLoad :: ConceptChunk
specDeLoad = String -> NP -> String -> ConceptChunk
dcc String
"specDeLoad" (String -> NP
nounPhraseSP String
"specified design load")
(String
"the magnitude in Pa (psf), type (for example, wind or snow) and " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"duration of the load given by the specifying authority")
constants :: [ConstQDef]
constants :: [ConstQDef]
constants = [ConstQDef
constantM, ConstQDef
constantK, ConstQDef
constantModElas, ConstQDef
constantLoadDur, ConstQDef
constantLoadSF]
[ConstQDef] -> [ConstQDef] -> [ConstQDef]
forall a. [a] -> [a] -> [a]
++ [ConstQDef]
specParamVals
constantM, constantK, constantModElas, constantLoadDur, constantLoadSF :: ConstQDef
constantK :: ConstQDef
constantK = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitaryChunk
sflawParamK (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Double -> Literal
forall r. LiteralC r => Double -> r
dbl Double
2.86e-53
constantM :: ConstQDef
constantM = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitaryChunk
sflawParamM (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
7
constantModElas :: ConstQDef
constantModElas = UnitalChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
modElas (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Double -> Literal
forall r. LiteralC r => Double -> r
dbl Double
7.17e10
constantLoadDur :: ConstQDef
constantLoadDur = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitaryChunk
loadDur (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
3
constantLoadSF :: ConstQDef
constantLoadSF = DefinedQuantityDict -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
loadSF (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
1
sdVectorSent :: Sentence
sdVectorSent :: Sentence
sdVectorSent = [Sentence] -> Sentence
foldlsC ((UnitaryChunk -> Sentence) -> [UnitaryChunk] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map UnitaryChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch [UnitaryChunk]
sdVector)
sdVector :: [UnitaryChunk]
sdVector :: [UnitaryChunk]
sdVector = [UnitaryChunk
sdx, UnitaryChunk
sdy, UnitaryChunk
sdz]
termsWithDefsOnly, termsWithAccDefn, loadTypes, glassTypes :: [ConceptChunk]
glassTypes :: [ConceptChunk]
glassTypes = [ConceptChunk
annealedGl, ConceptChunk
fTemperedGl, ConceptChunk
hStrengthGl]
termsWithDefsOnly :: [ConceptChunk]
termsWithDefsOnly = [ConceptChunk
glBreakage, ConceptChunk
lateral, ConceptChunk
lite, ConceptChunk
specA, ConceptChunk
blastResisGla, ConceptChunk
eqTNTChar]
termsWithAccDefn :: [ConceptChunk]
termsWithAccDefn = [ConceptChunk
sD, ConceptChunk
loadShareFac, ConceptChunk
glTyFac, ConceptChunk
aspectRatioCon]
loadTypes :: [ConceptChunk]
loadTypes = [ConceptChunk
loadResis, ConceptChunk
nonFactoredL, ConceptChunk
glassWL, ConceptChunk
shortDurLoad, ConceptChunk
specDeLoad, ConceptChunk
longDurLoad]
actualThicknesses :: [Double]
actualThicknesses :: [Double]
actualThicknesses = ((Double, Double) -> Double) -> [(Double, Double)] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map (Double, Double) -> Double
forall a b. (a, b) -> b
snd [(Double, Double)]
glassThickness
nominalThicknesses :: [Double]
nominalThicknesses :: [Double]
nominalThicknesses = ((Double, Double) -> Double) -> [(Double, Double)] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map (Double, Double) -> Double
forall a b. (a, b) -> a
fst [(Double, Double)]
glassThickness
glassTypeFactors :: [Integer]
glassTypeFactors :: [Integer]
glassTypeFactors = ((Integer, CI) -> Integer) -> [(Integer, CI)] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map (Integer, CI) -> Integer
forall a b. (a, b) -> a
fst [(Integer, CI)]
glassType
glassTypeAbbrs :: [Sentence]
glassTypeAbbrs :: [Sentence]
glassTypeAbbrs = ((Integer, CI) -> Sentence) -> [(Integer, CI)] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map (CI -> Sentence
getAcc (CI -> Sentence)
-> ((Integer, CI) -> CI) -> (Integer, CI) -> Sentence
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Integer, CI) -> CI
forall a b. (a, b) -> b
snd) [(Integer, CI)]
glassType
type GlassType = [(Integer, CI)]
type GlassThickness = [(Double, Double)]
glassType :: GlassType
glassType :: [(Integer, CI)]
glassType = [(Integer
1, CI
annealed), (Integer
4, CI
fullyT), (Integer
2, CI
heatS)]
glassThickness :: GlassThickness
glassThickness :: [(Double, Double)]
glassThickness =
[(Double
2.5, Double
2.16),
(Double
2.7, Double
2.59),
(Double
3.0, Double
2.92),
(Double
4.0, Double
3.78),
(Double
5.0, Double
4.57),
(Double
6.0, Double
5.56),
(Double
8.0, Double
7.42),
(Double
10.0, Double
9.02),
(Double
12.0, Double
11.91),
(Double
16.0, Double
15.09),
(Double
19.0, Double
18.26),
(Double
22.0, Double
21.44)]
lateralLoad :: IdeaDict
lateralLoad :: IdeaDict
lateralLoad = ConceptChunk -> ConceptChunk -> IdeaDict
forall a b. (NamedIdea a, NamedIdea b) => a -> b -> IdeaDict
compoundNC ConceptChunk
lateral ConceptChunk
load