module Drasil.GlassBR.TMods (tMods, pbIsSafe, lrIsSafe) where

import Language.Drasil
import Theory.Drasil (TheoryModel, tm, equationalModel')

import Drasil.GlassBR.References (astm2009)
import Drasil.GlassBR.Unitals (isSafeLoad, isSafeProb, pbTolfail, probFail,
  tmDemand, tmLRe)

{--}

tMods :: [TheoryModel]
tMods :: [TheoryModel]
tMods = [TheoryModel
pbIsSafe, TheoryModel
lrIsSafe]

-- FIXME: This is a hack to see if TheoryModel printing will work. This chunk
-- needs to be updated properly.
-- this is the new function but it still uses the lrIsSafeRC,
-- so basically we have to combine the old function with the new function
-- glass_concept :: [ConceptInstance]
-- glass_concept = []


lrIsSafe :: TheoryModel
lrIsSafe :: TheoryModel
lrIsSafe = forall q c.
(Quantity q, MayHaveUnit q, Concept c) =>
ModelKind ModelExpr
-> [q]
-> [c]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> [DecRef]
-> String
-> [Sentence]
-> TheoryModel
tm (forall e. QDefinition e -> ModelKind e
equationalModel' ModelQDef
lrIsSafeQD)
   [forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw QuantityDict
isSafeLoad, forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
tmLRe, forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
tmDemand] ([] :: [ConceptChunk])
   [ModelQDef
lrIsSafeQD] [] [] [forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
astm2009] 
   String
"isSafeLoad" [Sentence
lrIsSafeDesc]

lrIsSafeQD :: ModelQDef
lrIsSafeQD :: ModelQDef
lrIsSafeQD = forall c e.
(Quantity c, MayHaveUnit c) =>
c -> NP -> e -> QDefinition e
mkQuantDef' QuantityDict
isSafeLoad (String -> NP
nounPhraseSP String
"Safety Load") PExpr
lrIsSafeExpr

lrIsSafeExpr :: PExpr
lrIsSafeExpr :: PExpr
lrIsSafeExpr = forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
tmLRe forall r. ExprC r => r -> r -> r
$> forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
tmDemand

lrIsSafeDesc :: Sentence
lrIsSafeDesc :: Sentence
lrIsSafeDesc = QuantityDict -> Sentence
tModDesc QuantityDict
isSafeLoad

pbIsSafe :: TheoryModel
pbIsSafe :: TheoryModel
pbIsSafe = forall q c.
(Quantity q, MayHaveUnit q, Concept c) =>
ModelKind ModelExpr
-> [q]
-> [c]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> [DecRef]
-> String
-> [Sentence]
-> TheoryModel
tm (forall e. QDefinition e -> ModelKind e
equationalModel' ModelQDef
pbIsSafeQD) 
  [forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw QuantityDict
isSafeProb, forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrainedChunk
probFail, forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw ConstrainedChunk
pbTolfail] ([] :: [ConceptChunk])
  [ModelQDef
pbIsSafeQD] [] [] [forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
astm2009]
  String
"isSafeProb" [Sentence
pbIsSafeDesc]

pbIsSafeQD :: ModelQDef
pbIsSafeQD :: ModelQDef
pbIsSafeQD = forall c e.
(Quantity c, MayHaveUnit c) =>
c -> NP -> e -> QDefinition e
mkQuantDef' QuantityDict
isSafeProb (String -> NP
nounPhraseSP String
"Safety Probability") PExpr
pbIsSafeExpr

pbIsSafeExpr :: PExpr
pbIsSafeExpr :: PExpr
pbIsSafeExpr = forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrainedChunk
probFail forall r. ExprC r => r -> r -> r
$< forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrainedChunk
pbTolfail

pbIsSafeDesc :: Sentence
pbIsSafeDesc :: Sentence
pbIsSafeDesc = QuantityDict -> Sentence
tModDesc QuantityDict
isSafeProb

tModDesc :: QuantityDict -> Sentence
tModDesc :: QuantityDict -> Sentence
tModDesc QuantityDict
main = String -> Sentence
S String
"If" Sentence -> Sentence -> Sentence
+:+. (forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch QuantityDict
main Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"the structure is considered safe")