{-# LANGUAGE PostfixOperators #-}
module Drasil.NoPCM.Changes (likelyChgs, unlikelyChgs) where
import Language.Drasil
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.Concepts.Documentation (model, likeChgDom, unlikeChgDom)
import Data.Drasil.Concepts.Thermodynamics (temp)
import Drasil.NoPCM.Assumptions (assumpCTNTD, assumpNIHGBW, assumpWAL)
import Drasil.NoPCM.IMods (eBalanceOnWtr)
import Drasil.SWHS.Concepts (tank, water)
likelyChgs :: [ConceptInstance]
likelyChgs :: [ConceptInstance]
likelyChgs = [ConceptInstance
likeChgDT]
likeChgDT :: ConceptInstance
likeChgDT :: ConceptInstance
likeChgDT = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic "likeChgDT" (
[Sentence] -> Sentence
foldlSent [ConceptInstance -> Sentence -> Sentence
forall x.
(HasShortName x, Referable x) =>
x -> Sentence -> Sentence
chgsStart ConceptInstance
assumpCTNTD (String -> Sentence
S "The"), NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
model,
String -> Sentence
S "currently only accounts for charging of the tank. That is, increasing the",
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
temp ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofThe` ConceptChunk
water), String -> Sentence
S "to match the",(ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
temp Sentence -> Sentence -> Sentence
`S.ofThe` String -> Sentence
S "coil" Sentence -> Sentence
!.),
String -> Sentence
S "A more complete", NamedChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase NamedChunk
model, String -> Sentence
S "would also account for discharging of", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
tank)])
"Discharging-Tank" ConceptChunk
likeChgDom
unlikelyChgs :: [ConceptInstance]
unlikelyChgs :: [ConceptInstance]
unlikelyChgs = [ConceptInstance
unlikeChgWFS, ConceptInstance
unlikeChgNIHG]
unlikeChgWFS :: ConceptInstance
unlikeChgWFS :: ConceptInstance
unlikeChgWFS = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic "unlikeChgWFS" (
[Sentence] -> Sentence
foldlSent [ConceptInstance -> Sentence -> Sentence
forall x.
(HasShortName x, Referable x) =>
x -> Sentence -> Sentence
chgsStart ConceptInstance
assumpWAL (String -> Sentence
S "It is unlikely for the change of"),
ConceptChunk -> Sentence
forall n. (HasUID n, NamedIdea n) => n -> Sentence
phrase ConceptChunk
water, String -> Sentence
S "from liquid to a solid, or from liquid to gas to be considered"])
"Water-Fixed-States" ConceptChunk
unlikeChgDom
unlikeChgNIHG :: ConceptInstance
unlikeChgNIHG :: ConceptInstance
unlikeChgNIHG = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic "unlikeChgNIHG" (
[Sentence] -> Sentence
foldlSent [ConceptInstance -> Sentence -> Sentence
forall x.
(HasShortName x, Referable x) =>
x -> Sentence -> Sentence
chgsStart ConceptInstance
assumpNIHGBW (String -> Sentence
S "Is used for the derivations of"),
InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
eBalanceOnWtr] ) "No-Internal-Heat-Generation" ConceptChunk
unlikeChgDom