module Drasil.SWHS.Concepts where
import Control.Lens ((^.))
import Language.Drasil
import Language.Drasil.Chunk.Concept.NamedCombinators
import Data.Drasil.Concepts.Documentation (assumption, goalStmt,
likelyChg, physSyst, requirement, refBy, refName, srs, typUnc, unlikelyChg)
import Data.Drasil.Concepts.Math (ode, parameter, rightSide)
import Data.Drasil.Domains (materialEng)
import Data.Drasil.TheoryConcepts (dataDefn, genDefn, inModel, thModel)
con :: [ConceptChunk]
con :: [ConceptChunk]
con = [ConceptChunk
charging, ConceptChunk
coil, ConceptChunk
discharging, ConceptChunk
gaussDiv,
ConceptChunk
perfectInsul, ConceptChunk
phaseChangeMaterial, ConceptChunk
tank,
ConceptChunk
tankPCM, ConceptChunk
transient, ConceptChunk
water, ConceptChunk
sWHT, ConceptChunk
tankParam]
acronyms :: [CI]
acronyms :: [CI]
acronyms = [CI
assumption, CI
dataDefn, CI
genDefn, CI
goalStmt, CI
inModel, CI
likelyChg, CI
ode,
CI
physSyst, CI
requirement, CI
refBy, CI
refName, CI
srs, CI
thModel, CI
typUnc, CI
unlikelyChg]
acronymsFull :: [CI]
acronymsFull :: [CI]
acronymsFull = [CI]
acronyms [CI] -> [CI] -> [CI]
forall a. [a] -> [a] -> [a]
++ [CI
phsChgMtrl, CI
rightSide, CI
progName]
phsChgMtrl, progName :: CI
phsChgMtrl :: CI
phsChgMtrl = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict String
"phsChgMtrl" (String -> String -> NP
nounPhrase String
"phase change material"
String
"phase change materials") String
"PCM" [IdeaDict
materialEng]
progName :: CI
progName = String -> NP -> String -> [IdeaDict] -> CI
commonIdeaWithDict String
"swhsName" (String -> String -> NP
nounPhrase String
"solar water heating system"
String
"solar water heating systems") String
"SWHS" [IdeaDict
materialEng]
full :: IdeaDict
full :: IdeaDict
full = String -> NP -> IdeaDict
nc String
"full" (CI
progName CI -> CI -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`with` CI
phsChgMtrl)
charging, coil, discharging, gaussDiv,
perfectInsul, phaseChangeMaterial, tank,
tankPCM, transient, water, sWHT, tankParam :: ConceptChunk
charging :: ConceptChunk
charging = String -> NP -> String -> ConceptChunk
dcc String
"charging" (String -> NP
nounPhraseSP String
"charging") String
"charging of the tank"
coil :: ConceptChunk
coil = String -> NP -> String -> ConceptChunk
dcc String
"coil" (String -> NP
cn' String
"heating coil")
String
"coil in tank that heats by absorbing solar energy"
discharging :: ConceptChunk
discharging = String -> NP -> String -> ConceptChunk
dcc String
"discharging" (String -> NP
nounPhraseSP String
"discharging")
String
"discharging of the tank"
transient :: ConceptChunk
transient = String -> NP -> String -> ConceptChunk
dcc String
"transient" (String -> NP
nounPhraseSP String
"transient") String
"changing with time"
gaussDiv :: ConceptChunk
gaussDiv = String -> NP -> String -> ConceptChunk
dcc String
"gaussDiv" (String -> NP
nounPhraseSP String
"gauss's divergence theorem")
(String
"a result that relates the flow of a vector field through a surface" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"to the behavior of the vector field inside the surface")
perfectInsul :: ConceptChunk
perfectInsul = String -> NP -> String -> ConceptChunk
dcc String
"perfectInsul" (String -> NP
nounPhraseSP String
"perfectly insulated")
(String
"describes the property of a material not allowing" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"heat transfer through its boundaries")
phaseChangeMaterial :: ConceptChunk
phaseChangeMaterial = String -> NP -> String -> ConceptChunk
dcc String
"pcm" (CI
phsChgMtrl CI -> Getting NP CI NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP CI NP
forall c. NamedIdea c => Lens' c NP
Lens' CI NP
term)
(String
"a substance that uses phase changes (such as melting) to absorb or " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"release large amounts of heat at a constant temperature")
tankParam :: ConceptChunk
tankParam = String -> NP -> String -> ConceptChunk
dcc String
"tankParam" (NP -> NP -> NP
compoundPhrase' (ConceptChunk
tank ConceptChunk -> Getting NP ConceptChunk NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP ConceptChunk NP
forall c. NamedIdea c => Lens' c NP
Lens' ConceptChunk NP
term)
(ConceptChunk
parameter ConceptChunk -> Getting NP ConceptChunk NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP ConceptChunk NP
forall c. NamedIdea c => Lens' c NP
Lens' ConceptChunk NP
term))
String
"values associated with the tank"
tank :: ConceptChunk
tank = String -> NP -> String -> ConceptChunk
dcc String
"tank" (String -> NP
cn' String
"tank") String
"enclosure containing some kind of substance"
sWHT :: ConceptChunk
sWHT = String -> NP -> String -> ConceptChunk
dcc String
"sWHT" (String -> NP
cn' String
"solar water heating tank") String
"solar water heating tank"
water :: ConceptChunk
water = String -> NP -> String -> ConceptChunk
dcc String
"water" (String -> NP
cn' String
"water") String
"the liquid with which the tank is filled"
tankPCM :: ConceptChunk
tankPCM = String -> NP -> String -> ConceptChunk
dcc String
"tankPCM" (Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase''
(ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
sWHT Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"incorporating" Sentence -> Sentence -> Sentence
+:+ CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl)
(ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
sWHT Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"incorporating" Sentence -> Sentence -> Sentence
+:+ CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl)
CapitalizationRule
CapFirst CapitalizationRule
CapWords)
String
"solar water heating tank incorporating phase change material"
swhsPCM :: CI
swhsPCM :: CI
swhsPCM = String -> NP -> String -> [UID] -> CI
commonIdea String
"swhsPCM" (Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase''
(String -> Sentence
S String
"solar water heating systems" Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"incorporating" Sentence -> Sentence -> Sentence
+:+ CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl)
(String -> Sentence
S String
"solar water heating systems" Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"incorporating" Sentence -> Sentence -> Sentence
+:+ CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl)
CapitalizationRule
CapFirst CapitalizationRule
CapWords)
String
"SWHS"
[]