module Drasil.GlassBR.Assumptions (assumpGT, assumpGC, assumpES, assumpSV,
  assumpGL, assumpBC, assumpRT, assumpLDFC, assumptionConstants,
  assumptions) where

import Language.Drasil hiding (organization)
import qualified Drasil.DocLang.SRS as SRS (valsOfAuxCons)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.NounPhrase.Combinators as NP
import qualified Language.Drasil.Sentence.Combinators as S

import Data.Drasil.Concepts.Documentation as Doc (assumpDom, condition,
  constant, practice, reference, scenario, system, value)
import Data.Drasil.Concepts.Math (calculation, surface, shape)
import Data.Drasil.Concepts.PhysicalProperties (materialProprty)

import Drasil.GlassBR.Concepts (beam, cantilever, edge, glaSlab, glass, glassBR, 
  lShareFac, plane, responseTy)
import Drasil.GlassBR.References (astm2009)
import Drasil.GlassBR.Unitals (constantK, constantLoadDur, 
  constantLoadSF, constantM, constantModElas, explosion, lateral, lDurFac,
  loadDur)

assumptions :: [ConceptInstance]
assumptions :: [ConceptInstance]
assumptions = [ConceptInstance
assumpGT, ConceptInstance
assumpGC, ConceptInstance
assumpES, ConceptInstance
assumpSV, ConceptInstance
assumpGL, ConceptInstance
assumpBC,
  ConceptInstance
assumpRT, ConceptInstance
assumpLDFC]

assumptionConstants :: [ConstQDef]
assumptionConstants :: [ConstQDef]
assumptionConstants = [ConstQDef
constantM, ConstQDef
constantK, ConstQDef
constantModElas,
  ConstQDef
constantLoadDur, ConstQDef
constantLoadSF]

assumpGT, assumpGC, assumpES, assumpSV, assumpGL, assumpBC, assumpRT, assumpLDFC :: ConceptInstance
assumpGT :: ConceptInstance
assumpGT           = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic "assumpGT"   Sentence
glassTypeDesc                     "glassType"           ConceptChunk
Doc.assumpDom
assumpGC :: ConceptInstance
assumpGC           = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic "assumpGC"   Sentence
glassConditionDesc                "glassCondition"      ConceptChunk
Doc.assumpDom
assumpES :: ConceptInstance
assumpES           = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic "assumpES"   Sentence
explainScenarioDesc               "explainScenario"     ConceptChunk
Doc.assumpDom
assumpSV :: ConceptInstance
assumpSV           = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic "assumpSV"   (UnitaryChunk -> Sentence
standardValuesDesc UnitaryChunk
loadDur)      "standardValues"      ConceptChunk
Doc.assumpDom
assumpGL :: ConceptInstance
assumpGL           = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic "assumpGL"   Sentence
glassLiteDesc                     "glassLite"           ConceptChunk
Doc.assumpDom
assumpBC :: ConceptInstance
assumpBC           = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic "assumpBC"   Sentence
boundaryConditionsDesc            "boundaryConditions"  ConceptChunk
Doc.assumpDom
assumpRT :: ConceptInstance
assumpRT           = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic "assumpRT"   Sentence
responseTypeDesc                  "responseType"        ConceptChunk
Doc.assumpDom
assumpLDFC :: ConceptInstance
assumpLDFC         = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic "assumpLDFC" (QuantityDict -> Sentence
ldfConstantDesc QuantityDict
lDurFac)         "ldfConstant"         ConceptChunk
Doc.assumpDom

glassTypeDesc :: Sentence
glassTypeDesc :: Sentence
glassTypeDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S "The standard E1300-09a for",
  ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
calculation, String -> Sentence
S "applies only to", SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
Options ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ (String -> Sentence) -> [String] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map String -> Sentence
S ["monolithic",
  "laminated", "insulating"], String -> Sentence
S "glass constructions" Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S "rectangular", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
shape, 
  String -> Sentence
S "with continuous", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
lateral, String -> Sentence
S "support along",
  SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
Options ((String -> Sentence) -> [String] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map String -> Sentence
S ["one", "two", "three", "four"]) Sentence -> Sentence -> Sentence
+:+.
  NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
edge, String -> Sentence
S "This", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
practice Sentence -> Sentence -> Sentence
+: String -> Sentence
S "assumes that",
  EnumType
-> WrapType -> SepType -> FoldType -> [Sentence] -> Sentence
foldlEnumList EnumType
Numb WrapType
Parens SepType
SemiCol FoldType
List ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent_
  [[String -> Sentence
S "the supported glass", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
edge, String -> Sentence
S "for two, three" Sentence -> Sentence -> Sentence
`S.and_`
  String -> Sentence
S "four-sided support", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
condition, String -> Sentence
S "are simply supported" Sentence -> Sentence -> Sentence
`S.and_`
  String -> Sentence
S "free to slip in", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
plane], 
  [String -> Sentence
S "glass supported on two sides acts as a simply supported", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
beam], 
  [String -> Sentence
S "glass supported on one side acts as a", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
cantilever]]]

glassConditionDesc :: Sentence
glassConditionDesc :: Sentence
glassConditionDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S "Following", Citation -> RefInfo -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> RefInfo -> Sentence
complexRef Citation
astm2009 ([Int] -> RefInfo
Page [1]) Sentence -> Sentence -> Sentence
`sC` 
  String -> Sentence
S "this", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
practice, String -> Sentence
S "does not apply to any form of", SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
Options ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ (String -> Sentence) -> [String] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map String -> Sentence
S ["wired",
  "patterned", "etched", "sandblasted", "drilled", "notched", "grooved glass"], String -> Sentence
S "with", 
  ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
surface Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S "edge treatments that alter the glass strength"]

explainScenarioDesc :: Sentence
explainScenarioDesc :: Sentence
explainScenarioDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S "This", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
system, String -> Sentence
S "only considers the external", 
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NamedChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI ConceptChunk
explosion NamedChunk
scenario), String -> Sentence
S "for its", ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural ConceptChunk
calculation]

standardValuesDesc :: UnitaryChunk -> Sentence
standardValuesDesc :: UnitaryChunk -> Sentence
standardValuesDesc mainIdea :: UnitaryChunk
mainIdea = [Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (NamedChunk -> NP
forall t. NamedIdea t => t -> NP
the NamedChunk
value), String -> Sentence
S "provided in",
  Section -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS (Section -> Sentence) -> Section -> Sentence
forall a b. (a -> b) -> a -> b
$ [Contents] -> [Section] -> Section
SRS.valsOfAuxCons ([]::[Contents]) ([]::[Section]), String -> Sentence
S "are assumed for the", UnitaryChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase UnitaryChunk
mainIdea, 
  Sentence -> Sentence
sParen (UnitaryChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitaryChunk
mainIdea) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S "and the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
materialProprty Sentence -> Sentence -> Sentence
`S.of_` 
  SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List ((ConstQDef -> Sentence) -> [ConstQDef] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ConstQDef -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch (Int -> [ConstQDef] -> [ConstQDef]
forall a. Int -> [a] -> [a]
take 3 [ConstQDef]
assumptionConstants))]

glassLiteDesc :: Sentence
glassLiteDesc :: Sentence
glassLiteDesc = [Sentence] -> Sentence
foldlSent [NamedChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart NamedChunk
glass, String -> Sentence
S "under consideration is assumed to be a single", 
  String -> Sentence
S "lite; hence, the", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
value Sentence -> Sentence -> Sentence
`S.of_` CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
lShareFac, String -> Sentence
S "is equal to 1 for all",
  ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural ConceptChunk
calculation Sentence -> Sentence -> Sentence
`S.in_` CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
glassBR]

boundaryConditionsDesc :: Sentence
boundaryConditionsDesc :: Sentence
boundaryConditionsDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S "Boundary", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural NamedChunk
condition, String -> Sentence
S "for the",
  NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
glaSlab, String -> Sentence
S "are assumed to be 4-sided support for",
  ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
plural ConceptChunk
calculation]

responseTypeDesc :: Sentence
responseTypeDesc :: Sentence
responseTypeDesc = [Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NamedChunk -> NP
forall t. NamedIdea t => t -> NP
the NamedChunk
responseTy), String -> Sentence
S "considered in",
  CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
glassBR, String -> Sentence
S "is flexural"]

ldfConstantDesc :: QuantityDict -> Sentence
ldfConstantDesc :: QuantityDict -> Sentence
ldfConstantDesc mainConcept :: QuantityDict
mainConcept = [Sentence] -> Sentence
foldlSent [String -> Sentence
S "With", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
reference, String -> Sentence
S "to",
  ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpSV Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NP -> NP
NP.the (NamedChunk
value NamedChunk -> QuantityDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`of_`
  QuantityDict
mainConcept)), Sentence -> Sentence
sParen (QuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch QuantityDict
mainConcept) Sentence -> Sentence -> Sentence
`S.is` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NamedChunk -> NP
forall t. NamedIdea t => t -> NP
a_ NamedChunk
constant)
  Sentence -> Sentence -> Sentence
`S.in_` CI -> Sentence
forall c. (Idea c, HasUID c) => c -> Sentence
short CI
glassBR]