{-# LANGUAGE PostfixOperators #-}
module Drasil.SWHSNoPCM.Assumptions where
import Language.Drasil
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 (model, assumpDom, material_)
import Data.Drasil.Quantities.PhysicalProperties (vol)
import Data.Drasil.Quantities.Physics (pressure)
import Data.Drasil.Quantities.Thermodynamics (boilPt, meltPt)
import Data.Drasil.Concepts.Thermodynamics as CT (heat)
import qualified Data.Drasil.Quantities.Thermodynamics as QT (temp)
import Drasil.SWHS.Assumptions (assumpTEO, assumpHTCC, assumpCWTAT,
assumpLCCCW, assumpTHCCoT, assumpTHCCoL, assumpS14, assumpPIT, assumpVCN)
import Drasil.SWHS.Concepts (tank, water)
import Drasil.SWHS.Unitals (volHtGen, tempC, tempInit, tempW, htCapW, wDensity)
assumptions :: [ConceptInstance]
assumptions :: [ConceptInstance]
assumptions = [ConceptInstance
assumpTEO, ConceptInstance
assumpHTCC, ConceptInstance
assumpCWTAT, ConceptInstance
assumpDWCoW, ConceptInstance
assumpSHECoW,
ConceptInstance
assumpLCCCW, ConceptInstance
assumpTHCCoT, ConceptInstance
assumpTHCCoL, ConceptInstance
assumpCTNTD, ConceptInstance
assumpWAL, ConceptInstance
assumpPIT,
ConceptInstance
assumpNIHGBW, ConceptInstance
assumpAPT, ConceptInstance
assumpVCN]
assumpS3, assumpS4, assumpS5, assumpS9_npcm, assumpS12, assumpS13 :: Sentence
assumpDWCoW, assumpSHECoW, assumpCTNTD, assumpNIHGBW, assumpAPT,
assumpWAL :: ConceptInstance
assumpS3 :: Sentence
assumpS3 =
[Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NP -> NP
NP.the (ConceptChunk
water ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`inThe` ConceptChunk
tank)),
String -> Sentence
S String
"is fully mixed" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so the", ConstrConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConstrConcept
tempW Sentence -> Sentence -> Sentence
`S.isThe`
String -> Sentence
S String
"same throughout the entire", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
tank]
assumpS4 :: Sentence
assumpS4 =
[Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UncertQ -> NP
forall t. NamedIdea t => t -> NP
the UncertQ
wDensity), String -> Sentence
S String
"has no spatial variation; that is"
Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"it is constant over their entire", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
vol]
assumpDWCoW :: ConceptInstance
assumpDWCoW = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"assumpDWCoW" Sentence
assumpS4
String
"Density-Water-Constant-over-Volume" ConceptChunk
assumpDom
assumpS5 :: Sentence
assumpS5 =
[Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UncertQ -> NP
forall t. NamedIdea t => t -> NP
the UncertQ
htCapW), String -> Sentence
S String
"has no spatial variation; that",
String -> Sentence
S String
"is" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"it is constant over its entire", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
vol]
assumpSHECoW :: ConceptInstance
assumpSHECoW = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"assumpSHECoW" Sentence
assumpS5
String
"Specific-Heat-Energy-Constant-over-Volume" ConceptChunk
assumpDom
assumpS9_npcm :: Sentence
assumpS9_npcm =
[Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
model), String -> Sentence
S String
"only accounts for charging",
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
tank) Sentence -> Sentence -> Sentence
`sC` (String -> Sentence
S String
"not discharging" !.), NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConstrConcept -> NP
forall t. NamedIdea t => t -> NP
the ConstrConcept
tempW), String -> Sentence
S String
"can only",
String -> Sentence
S String
"increase" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"or remain constant; it cannot decrease. This implies that the",
UncertQ -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UncertQ
tempInit Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"less than (or equal to) the", UncertQ -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UncertQ
tempC]
assumpCTNTD :: ConceptInstance
assumpCTNTD = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"assumpCTNTD" Sentence
assumpS9_npcm
String
"Charging-Tank-No-Temp-Discharge" ConceptChunk
assumpDom
assumpS12 :: Sentence
assumpS12 =
String -> Sentence
S String
"No internal" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
heat Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"generated by the water; therefore, the"
Sentence -> Sentence -> Sentence
+:+ UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
volHtGen Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"is zero"
assumpNIHGBW :: ConceptInstance
assumpNIHGBW = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"assumpNIHGBW" Sentence
assumpS12
String
"No-Internal-Heat-Generation-By-Water" ConceptChunk
assumpDom
assumpWAL :: ConceptInstance
assumpWAL = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"assumpWAL" (Sentence -> Sentence
assumpS14 (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
material_ Sentence -> Sentence -> Sentence
+:+
Sentence -> Sentence
sParen (ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
water Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"in this case")) String
"Water-Always-Liquid" ConceptChunk
assumpDom
assumpS13 :: Sentence
assumpS13 =
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NP -> NP
NP.the (UnitalChunk
pressure UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`inThe` ConceptChunk
tank)) Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"atmospheric" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so the" Sentence -> Sentence -> Sentence
+:+
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
meltPt UnitalChunk -> UnitalChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` UnitalChunk
boilPt) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"of water are" Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S (Integer -> String
forall a. Show a => a -> String
show (Integer
0 :: Integer)) Sentence -> Sentence -> Sentence
:+: USymb -> Sentence
Sy (UnitalChunk -> USymb
forall c. Unitary c => c -> USymb
unit_symb UnitalChunk
QT.temp) Sentence -> Sentence -> Sentence
`S.and_`
String -> Sentence
S (Integer -> String
forall a. Show a => a -> String
show (Integer
100 :: Integer)) Sentence -> Sentence -> Sentence
:+: USymb -> Sentence
Sy (UnitalChunk -> USymb
forall c. Unitary c => c -> USymb
unit_symb UnitalChunk
QT.temp) Sentence -> Sentence -> Sentence
`sC` (String -> Sentence
S String
"respectively" !.)
assumpAPT :: ConceptInstance
assumpAPT = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"assumpAPT" Sentence
assumpS13
String
"Atmospheric-Pressure-Tank" ConceptChunk
assumpDom