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, nFL, responseTy,
stdOffDist, lDurFac)
import Drasil.GlassBR.References (astm2009, astm2012, astm2016)
import Drasil.GlassBR.Units (sFlawPU)
constrained :: [ConstrConcept]
constrained :: [ConstrConcept]
constrained = (UncertQ -> ConstrConcept) -> [UncertQ] -> [ConstrConcept]
forall a b. (a -> b) -> [a] -> [b]
map UncertQ -> ConstrConcept
forall c.
(Quantity c, Concept c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
c -> ConstrConcept
cnstrw' [UncertQ]
dataConstraints [ConstrConcept] -> [ConstrConcept] -> [ConstrConcept]
forall a. [a] -> [a] -> [a]
++ (ConstrConcept -> ConstrConcept)
-> [ConstrConcept] -> [ConstrConcept]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> ConstrConcept
forall c.
(Quantity c, Concept c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
c -> ConstrConcept
cnstrw' [ConstrConcept
nomThick, ConstrConcept
glassTypeCon]
plateLen, plateWidth, aspectRatio, charWeight, standOffDist :: UncertQ
pbTol, tNT :: UncertQ
glassTypeCon, nomThick :: ConstrConcept
inputs :: [DefinedQuantityDict]
inputs :: [DefinedQuantityDict]
inputs = (UncertQ -> DefinedQuantityDict)
-> [UncertQ] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UncertQ -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [UncertQ]
inputsWUnitsUncrtn [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ (UncertQ -> DefinedQuantityDict)
-> [UncertQ] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UncertQ -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [UncertQ]
inputsWUncrtn [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++
(ConstrConcept -> DefinedQuantityDict)
-> [ConstrConcept] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [ConstrConcept]
inputsNoUncrtn [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ (UnitalChunk -> DefinedQuantityDict)
-> [UnitalChunk] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [UnitalChunk]
sdVector
inputsWUnitsUncrtn :: [UncertQ]
inputsWUnitsUncrtn :: [UncertQ]
inputsWUnitsUncrtn = [UncertQ
plateLen, UncertQ
plateWidth, UncertQ
charWeight]
inputsWUncrtn :: [UncertQ]
inputsWUncrtn :: [UncertQ]
inputsWUncrtn = [UncertQ
pbTol, UncertQ
tNT]
inputsNoUncrtn :: [ConstrConcept]
inputsNoUncrtn :: [ConstrConcept]
inputsNoUncrtn = (ConstrConcept -> ConstrConcept)
-> [ConstrConcept] -> [ConstrConcept]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> ConstrConcept
forall c.
(Quantity c, Concept c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
c -> ConstrConcept
cnstrw' [ConstrConcept
glassTypeCon, ConstrConcept
nomThick]
derivedInsWUnitsUncrtn :: [UncertQ]
derivedInsWUnitsUncrtn :: [UncertQ]
derivedInsWUnitsUncrtn = [UncertQ
standOffDist]
derivedInsWUncrtn :: [UncertQ]
derivedInsWUncrtn :: [UncertQ]
derivedInsWUncrtn = [UncertQ
aspectRatio]
inputDataConstraints :: [UncertQ]
inputDataConstraints :: [UncertQ]
inputDataConstraints = [UncertQ]
inputsWUnitsUncrtn [UncertQ] -> [UncertQ] -> [UncertQ]
forall a. [a] -> [a] -> [a]
++ [UncertQ]
inputsWUncrtn
derivedInputDataConstraints :: [UncertQ]
derivedInputDataConstraints :: [UncertQ]
derivedInputDataConstraints = [UncertQ]
derivedInsWUnitsUncrtn
[UncertQ] -> [UncertQ] -> [UncertQ]
forall a. [a] -> [a] -> [a]
++ [UncertQ]
derivedInsWUncrtn
dataConstraints :: [UncertQ]
dataConstraints :: [UncertQ]
dataConstraints = [UncertQ]
inputDataConstraints [UncertQ] -> [UncertQ] -> [UncertQ]
forall a. [a] -> [a] -> [a]
++ [UncertQ]
derivedInputDataConstraints
plateLen :: UncertQ
plateLen = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"plateLen" (String -> NP
nounPhraseSP String
"plate length (long dimension)")
String
"the length (long dimension) of the glass plate" 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
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"plateWidth" (String -> NP
nounPhraseSP String
"plate width (short dimension)")
String
"the width (short dimension) of the glass plate" 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 :: UncertQ
pbTol = 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 (String -> NP -> String -> ConceptChunk
dcc String
"pbTol" (String -> NP
nounPhraseSP String
"tolerable probability of breakage")
String
"the tolerable probability of breakage of the glass plate")
(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 :: UncertQ
tNT = 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 (String -> NP -> String -> ConceptChunk
dcc String
"tNT" (String -> NP
nounPhraseSP String
"TNT equivalent factor")
String
"the 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 :: ConstrConcept
nomThick = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
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)))
String
"the specified standard thickness of the glass plate" 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 -> ConstrConcept) -> Expr -> ConstrConcept
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 :: [DefinedQuantityDict]
outputs :: [DefinedQuantityDict]
outputs = (DefinedQuantityDict -> DefinedQuantityDict)
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map DefinedQuantityDict -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [DefinedQuantityDict
isSafePb, DefinedQuantityDict
isSafeLR] [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ (ConstrConcept -> DefinedQuantityDict)
-> [ConstrConcept] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [ConstrConcept
probBr, ConstrConcept
stressDistFac]
tmSymbols :: [DefinedQuantityDict]
tmSymbols :: [DefinedQuantityDict]
tmSymbols = (ConstrConcept -> DefinedQuantityDict)
-> [ConstrConcept] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [ConstrConcept
probFail, ConstrConcept
pbTolfail]
probBr, probFail, pbTolfail, stressDistFac :: ConstrConcept
probBr :: ConstrConcept
probBr = DefinedQuantityDict -> [ConstraintE] -> Expr -> ConstrConcept
forall c.
(Concept c, MayHaveUnit c, Quantity c) =>
c -> [ConstraintE] -> Expr -> ConstrConcept
constrained' (ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit ConceptChunk
probBreak
(Symbol -> Symbol -> Symbol
sub Symbol
cP Symbol
lBreak) Space
Real)
[ConstraintE
probConstr] (Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
0.4)
stressDistFac :: ConstrConcept
stressDistFac = String
-> NP
-> String
-> Symbol
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
cucNoUnit' String
"stressDistFac" (String -> NP
nounPhraseSP String
"stress distribution factor (Function)")
String
"the stress distribution factor of the glass plate"
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)] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
15)
probFail :: ConstrConcept
probFail = String
-> NP
-> String
-> Symbol
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
cucNoUnit' String
"probFail" (String -> NP
nounPhraseSP String
"probability of failure")
String
"the probability of failure of the glass plate"
(Symbol -> Symbol -> Symbol
sub Symbol
cP Symbol
lFail) Space
Real
[ConstraintE
probConstr] (Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
0.4)
pbTolfail :: ConstrConcept
pbTolfail = String
-> NP
-> String
-> Symbol
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
cucNoUnit' String
"pbTolfail" (String -> NP
nounPhraseSP String
"tolerable probability of failure")
String
"the tolerable probability of failure of the glass plate"
(Symbol -> Symbol -> Symbol
sub Symbol
cP ([Symbol] -> Symbol
Concat [Symbol
lFail, Symbol
lTol])) Space
Real
[ConstraintE
probConstr] (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 = UnitalChunk -> Literal -> ConstQDef
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef (String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"dimMax"
(String -> NP
nounPhraseSP String
"maximum value for one of the dimensions of the glass plate")
(String -> Sentence
S String
"the maximum value for one of the dimensions of the glass plate")
(Symbol -> Symbol
subMax Symbol
lD) Space
Real UnitDefn
metre) (Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
5)
dimMin :: ConstQDef
dimMin = UnitalChunk -> Literal -> ConstQDef
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef (String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"dimMin"
(String -> NP
nounPhraseSP String
"minimum value for one of the dimensions of the glass plate")
(String -> Sentence
S String
"the minimum value for one of the dimensions of the glass plate")
(Symbol -> Symbol
subMin Symbol
lD) Space
Real UnitDefn
metre) (Double -> Literal
forall r. LiteralC r => Double -> r
dbl Double
0.1)
arMax :: ConstQDef
arMax = DefinedQuantityDict -> Literal -> ConstQDef
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef (ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit (String -> NP -> String -> ConceptChunk
dcc String
"arMax"
(String -> NP
nounPhraseSP String
"maximum aspect ratio")
String
"the 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 = UnitalChunk -> Literal -> ConstQDef
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef (String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"cWeightMax"
(String -> NP
nounPhraseSP String
"maximum permissible input charge weight")
(String -> Sentence
S String
"the maximum permissible input charge weight")
(Symbol -> Symbol
subMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
charWeight)) Space
Real UnitDefn
kilogram) (Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
910)
cWeightMin :: ConstQDef
cWeightMin = UnitalChunk -> Literal -> ConstQDef
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef (String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"cWeightMin"
(String -> NP
nounPhraseSP String
"minimum permissible input charge weight")
(String -> Sentence
S String
"the minimum permissible input charge weight")
(Symbol -> Symbol
subMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
charWeight)) Space
Real UnitDefn
kilogram) (Double -> Literal
forall r. LiteralC r => Double -> r
dbl Double
4.5)
sdMax :: ConstQDef
sdMax = UnitalChunk -> Literal -> ConstQDef
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef (String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"sdMax"
(String -> NP
nounPhraseSP String
"maximum stand off distance permissible for input")
(String -> Sentence
S String
"the maximum stand off distance permissible for input")
(Symbol -> Symbol
subMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
standOffDist)) Space
Real UnitDefn
metre) (Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
130)
sdMin :: ConstQDef
sdMin = UnitalChunk -> Literal -> ConstQDef
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef (String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"sdMin"
(String -> NP
nounPhraseSP String
"minimum stand off distance permissible for input")
(String -> Sentence
S String
"the minimum stand off distance permissible for input")
(Symbol -> Symbol
subMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
standOffDist)) Space
Real UnitDefn
metre) (Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
6)
stressDistFacMin :: ConstQDef
stressDistFacMin = DefinedQuantityDict -> Literal -> ConstQDef
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef (ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit (String -> NP -> String -> ConceptChunk
dcc String
"stressDistFacMin"
(String -> NP
nounPhraseSP String
"minimum value for the stress distribution factor")
String
"the minimum value for the stress distribution factor")
(Symbol -> Symbol
subMin (ConstrConcept -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb ConstrConcept
stressDistFac)) Space
Real) (Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
1)
stressDistFacMax :: ConstQDef
stressDistFacMax = DefinedQuantityDict -> Literal -> ConstQDef
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef (ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit (String -> NP -> String -> ConceptChunk
dcc String
"stressDistFacMax"
(String -> NP
nounPhraseSP String
"maximum value for the stress distribution factor")
String
"the maximum value for the stress distribution factor")
(Symbol -> Symbol
subMax (ConstrConcept -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb ConstrConcept
stressDistFac)) Space
Real) (Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
32)
unitalSymbols :: [UnitalChunk]
unitalSymbols :: [UnitalChunk]
unitalSymbols = [UnitalChunk
demand, UnitalChunk
tmDemand, UnitalChunk
lRe, UnitalChunk
tmLRe, UnitalChunk
nonFactorL, UnitalChunk
eqTNTWeight,
UnitalChunk
sflawParamK, UnitalChunk
sflawParamM, UnitalChunk
loadDur, UnitalChunk
minThick]
sdx, sdy, sdz :: UnitalChunk
demand, tmDemand, lRe, tmLRe, minThick, nonFactorL, eqTNTWeight,
sflawParamM, sflawParamK, loadDur, modElas :: 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) (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
tNT)) Space
Real
UnitDefn
kilogram
modElas :: UnitalChunk
modElas = ConceptChunk -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall c u.
(Concept c, IsUnit u) =>
c -> Symbol -> Space -> u -> UnitalChunk
uc ConceptChunk
modE Symbol
cE Space
Real UnitDefn
pascal
minThick :: UnitalChunk
minThick = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"minThick" (String -> NP
nounPhraseSP String
"minimum thickness")
(String -> Sentence
S String
"minimum thickness of the glass plate") Symbol
lH Space
Real UnitDefn
metre
sflawParamK :: UnitalChunk
sflawParamK = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"sflawParamK" (String -> NP
nounPhraseSP String
"surface flaw parameter")
(String -> Sentence
S (String
"surface flaw parameter related to the coefficient of " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"variation of the glass strength data")) Symbol
lK Space
Real UnitDefn
sFlawPU
sflawParamM :: UnitalChunk
sflawParamM = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"sflawParamM" (String -> NP
nounPhraseSP String
"surface flaw parameter")
(String -> Sentence
S String
"surface flaw parameter related to the mean of the glass strength data")
Symbol
lM Space
Real UnitDefn
sFlawPU
loadDur :: UnitalChunk
loadDur = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"loadDur" (String -> NP
nounPhraseSP String
"duration of load")
(String -> Sentence
S String
"the amount of time that a load is applied to the glass plate")
(Symbol -> Symbol -> Symbol
sub Symbol
lT Symbol
lDur) Space
Real UnitDefn
second
sdx :: UnitalChunk
sdx = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' 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))
(String -> Sentence
S String
"the x-component of the stand off distance") (Symbol -> Symbol
subX (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
standOffDist)) Space
Real UnitDefn
metre
sdy :: UnitalChunk
sdy = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' 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))
(String -> Sentence
S String
"the y-component of the stand off distance") (Symbol -> Symbol
subY (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
standOffDist)) Space
Real UnitDefn
metre
sdz :: UnitalChunk
sdz = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' 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))
(String -> Sentence
S String
"the x-component of the stand off distance") (Symbol -> Symbol
subZ (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
standOffDist)) Space
Real UnitDefn
metre
unitless :: [DefinedQuantityDict]
unitless :: [DefinedQuantityDict]
unitless = [DefinedQuantityDict
riskFun, DefinedQuantityDict
isSafePb, DefinedQuantityDict
isSafeProb, DefinedQuantityDict
isSafeLR, DefinedQuantityDict
isSafeLoad,
DefinedQuantityDict
sdfTol, DefinedQuantityDict
dimlessLoad, DefinedQuantityDict
tolLoad, DefinedQuantityDict
gTF, DefinedQuantityDict
loadSF, DefinedQuantityDict
loadDF]
interps :: [DefinedQuantityDict]
interps :: [DefinedQuantityDict]
interps = [DefinedQuantityDict
interpY, DefinedQuantityDict
interpZ]
riskFun, isSafePb, isSafeProb, isSafeLR, isSafeLoad, sdfTol,
dimlessLoad, tolLoad, interpY, interpZ :: DefinedQuantityDict
gTF, loadSF, loadDF :: DefinedQuantityDict
dimlessLoad :: DefinedQuantityDict
dimlessLoad = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit (String -> NP -> String -> ConceptChunk
dcc String
"dimlessLoad" (String -> NP
nounPhraseSP String
"dimensionless load")
String
"the 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 :: DefinedQuantityDict
isSafePb = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit (String -> NP -> String -> ConceptChunk
dcc String
"isSafePb" (String -> NP
nounPhraseSP String
"probability of glass breakage safety requirement")
String
"the probability of glass breakage safety requirement") (String -> Symbol
variable String
"isSafePb") Space
Boolean
isSafeProb :: DefinedQuantityDict
isSafeProb = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit (String -> NP -> String -> ConceptChunk
dcc String
"isSafeProb" (String -> NP
nounPhraseSP String
"probability of failure safety requirement")
String
"the probability of failure safety requirement") (String -> Symbol
variable String
"isSafeProb") Space
Boolean
isSafeLR :: DefinedQuantityDict
isSafeLR = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit (String -> NP -> String -> ConceptChunk
dcc String
"isSafeLR" (String -> NP
nounPhraseSP String
"3 second load equivalent resistance safety requirement")
String
"the 3 second load equivalent resistance safety requirement") (String -> Symbol
variable String
"isSafeLR") Space
Boolean
isSafeLoad :: DefinedQuantityDict
isSafeLoad = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit (String -> NP -> String -> ConceptChunk
dcc String
"isSafeLoad" (String -> NP
nounPhraseSP String
"load resistance safety requirement")
String
"the load resistance safety requirement") (String -> Symbol
variable String
"isSafeLoad") Space
Boolean
interpY :: DefinedQuantityDict
interpY = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit (String -> NP -> String -> ConceptChunk
dcc String
"interpY" (String -> NP
nounPhraseSP String
"interpY")
String
"interpolated y") (String -> Symbol
variable String
"interpY") ([Space] -> Space -> Space
mkFunction [Space
String, Space
Real, Space
Real] Space
Real)
interpZ :: DefinedQuantityDict
interpZ = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit (String -> NP -> String -> ConceptChunk
dcc String
"interpZ" (String -> NP
nounPhraseSP String
"interpZ")
String
"interpolated z") (String -> Symbol
variable String
"interpZ") ([Space] -> Space -> Space
mkFunction [Space
String, Space
Real, Space
Real] Space
Real)
loadDF :: DefinedQuantityDict
loadDF = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit ConceptChunk
loadDurFac (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 :: DefinedQuantityDict
riskFun = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit (String -> NP -> String -> ConceptChunk
dcc String
"riskFun" (String -> NP
nounPhraseSP String
"risk of failure")
String
"the percentage risk of the glass slab failing to resist the blast") Symbol
cB Space
Real
sdfTol :: DefinedQuantityDict
sdfTol = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit (String -> NP -> String -> ConceptChunk
dcc String
"sdfTol" (String -> NP
nounPhraseSP String
"tolerable stress distribution factor")
String
"the tolerable stress distribution factor") (Symbol -> Symbol -> Symbol
sub (ConstrConcept -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb ConstrConcept
stressDistFac) Symbol
lTol) Space
Real
tolLoad :: DefinedQuantityDict
tolLoad = ConceptChunk -> Symbol -> Space -> DefinedQuantityDict
dqdNoUnit (String -> NP -> String -> ConceptChunk
dcc String
"tolLoad" (String -> NP
nounPhraseSP String
"tolerable load")
String
"the tolerable load") (Symbol -> Symbol -> Symbol
sub (DefinedQuantityDict -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb DefinedQuantityDict
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"
concepts :: [ConceptChunk]
concepts :: [ConceptChunk]
concepts = [ConceptChunk
glBreakage, ConceptChunk
lite, ConceptChunk
annealedGl, ConceptChunk
fTemperedGl, ConceptChunk
hStrengthGl, ConceptChunk
lateral,
ConceptChunk
specDeLoad, ConceptChunk
longDurLoad, ConceptChunk
glassWL, ConceptChunk
shortDurLoad, ConceptChunk
specA, ConceptChunk
blastResisGla, ConceptChunk
blast,
ConceptChunk
blastTy, ConceptChunk
glassGeo, ConceptChunk
safeMessage, ConceptChunk
notSafe, ConceptChunk
bomb, ConceptChunk
explosion]
aspectRatioCon, glBreakage, lite, glassTy, annealedGl, fTemperedGl, hStrengthGl,
glTyFac, lateral, load, specDeLoad, loadDurFac, loadResis, longDurLoad, modE, 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
forall c. Idea c => c -> Sentence
short 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
forall c. Idea c => c -> Sentence
short 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
forall c. Idea c => c -> Sentence
short 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"
loadDurFac :: ConceptChunk
loadDurFac = CI -> Sentence -> ConceptChunk
forall c. Idea c => c -> Sentence -> ConceptChunk
cc' CI
lDurFac (String -> Sentence
S String
"factor related to the effect of sustained loading on glass strength")
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
forall c. Idea c => c -> Sentence
short CI
lGlass, String -> Sentence
S String
"under long duration",
String -> Sentence
S String
"loads), in a sealed", CI -> Sentence
forall c. Idea c => c -> Sentence
short 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"
modE :: ConceptChunk
modE = String -> NP -> String -> ConceptChunk
dcc String
"modElas" (String -> NP
nounPhraseSP String
"modulus of elasticity of glass")
String
"the ratio of tensile stress to tensile strain of glass"
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
forall c. Idea c => c -> Sentence
short 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 = String -> NP -> Sentence -> ConceptChunk
dccWDS String
"probBr" (String -> NP
nounPhraseSP String
"probability of breakage")
([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")
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
constantM :: ConstQDef
constantM = UnitalChunk -> Literal -> ConstQDef
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef UnitalChunk
sflawParamM (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
7
constantK :: ConstQDef
constantK = UnitalChunk -> Literal -> ConstQDef
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef UnitalChunk
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
constantModElas :: ConstQDef
constantModElas = UnitalChunk -> Literal -> ConstQDef
forall c e.
(Quantity c, MayHaveUnit c, Concept 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 = UnitalChunk -> Literal -> ConstQDef
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef UnitalChunk
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, Concept 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
sdVector :: [UnitalChunk]
sdVector :: [UnitalChunk]
sdVector = [UnitalChunk
sdx, UnitalChunk
sdy, UnitalChunk
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
forall c. Idea c => c -> Sentence
short (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