module Drasil.SWHS.IMods (iMods, eBalanceOnWtr, eBalanceOnWtrDerivDesc1,
eBalanceOnWtrDerivDesc3, eBalanceOnPCM, heatEInWtr, heatEInPCM, instModIntro) where
import Language.Drasil
import Utils.Drasil (weave)
import Theory.Drasil (InstanceModel, im, imNoDeriv, qwC, qwUC, deModel',
equationalModel, ModelKind)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.NounPhrase.Combinators as NP
import qualified Language.Drasil.Sentence.Combinators as S
import Control.Lens((^.))
import Data.Drasil.Concepts.Documentation (assumption, condition, constraint,
goal, input_, solution, output_)
import Data.Drasil.Concepts.Math (change, equation, ode, rightSide, rOfChng, surArea)
import Data.Drasil.Concepts.PhysicalProperties (liquid, mass, solid, vol)
import Data.Drasil.Concepts.Thermodynamics (boilPt, boiling, heat, heatCapSpec,
heatTrans, htFlux, latentHeat, melting, phaseChange, sensHeat, temp)
import Data.Drasil.Quantities.Physics (energy, time)
import Drasil.SWHS.Assumptions (assumpCTNOD, assumpSITWP, assumpPIS, assumpWAL,
assumpPIT, assumpNIHGBWP, assumpVCMPN, assumpNGSP, assumpAPT, assumpTHCCoL,
assumpCWTAT, assumpTPCAV)
import Drasil.SWHS.Concepts (coil, phsChgMtrl, tank, water)
import Drasil.SWHS.DataDefs (ddHtFusion, ddMeltFrac, balanceDecayRate,
balanceDecayTime, balanceSolidPCM, balanceLiquidPCM)
import Drasil.SWHS.Derivations
import Drasil.SWHS.GenDefs (htFluxWaterFromCoil, htFluxPCMFromWater, rocTempSimp)
import Drasil.SWHS.Goals (waterTempGS, pcmTempGS, waterEnergyGS, pcmEnergyGS)
import Drasil.SWHS.References (koothoor2013)
import Drasil.SWHS.TMods (sensHtE, latentHtE)
import Drasil.SWHS.Unitals (coilHTC, coilSA, eta, htFluxC, htFluxP, htCapLP,
htCapSP, htCapW, htFusion, latentEP, meltFrac, pcmE, pcmHTC, pcmInitMltE,
pcmMass, pcmSA, pcmVol, tInitMelt, tauLP, tauSP, tauW, tempC, tempInit,
tempMeltP, tempPCM, tempW, timeFinal, volHtGen, watE, wMass, wVol)
iMods :: [InstanceModel]
iMods :: [InstanceModel]
iMods = [InstanceModel
eBalanceOnWtr, InstanceModel
eBalanceOnPCM, InstanceModel
heatEInWtr, InstanceModel
heatEInPCM]
eBalanceOnWtr :: InstanceModel
eBalanceOnWtr :: InstanceModel
eBalanceOnWtr = ModelKind Relation
-> Inputs
-> Output
-> OutputConstraints
-> [DecRef]
-> Maybe Derivation
-> String
-> [Sentence]
-> InstanceModel
im (RelationConcept -> ModelKind Relation
forall e. RelationConcept -> ModelKind e
deModel' RelationConcept
eBalanceOnWtrRC)
[UnitalChunk -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UnitalChunk
wMass, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
htCapW, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
coilHTC, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
pcmSA, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
pcmHTC, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
coilSA
,ConstrConcept -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC ConstrConcept
tempPCM, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
timeFinal, UncertQ -> RealInterval Relation Relation -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Relation Relation -> Input
qwC UncertQ
tempC (RealInterval Relation Relation -> Input)
-> RealInterval Relation Relation -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Relation) -> RealInterval Relation Relation
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempInit)
,UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
tempInit]
(ConstrConcept -> Output
forall q. (Quantity q, MayHaveUnit q) => q -> Output
qw ConstrConcept
tempW) []
[Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
koothoor2013] (Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
eBalanceOnWtrDeriv) String
"eBalanceOnWtr" [Sentence]
balWtrDesc
eBalanceOnWtrRC :: RelationConcept
eBalanceOnWtrRC :: RelationConcept
eBalanceOnWtrRC = String -> NP -> Sentence -> ModelExpr -> RelationConcept
forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
"eBalanceOnWtrRC" (String -> NP
nounPhraseSP (String -> NP) -> String -> NP
forall a b. (a -> b) -> a -> b
$ String
"Energy balance on " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"water to find the temperature of the water") (ConstrConcept
tempW ConstrConcept
-> Getting Sentence ConstrConcept Sentence -> Sentence
forall s a. s -> Getting a s a -> a
^. Getting Sentence ConstrConcept Sentence
forall c. Definition c => Lens' c Sentence
Lens' ConstrConcept Sentence
defn) ModelExpr
balWtrRel
balWtrRel :: ModelExpr
balWtrRel :: ModelExpr
balWtrRel = ModelExpr -> UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => ModelExpr -> c -> ModelExpr
forall r c. (ModelExprC r, HasUID c, HasSymbol c) => r -> c -> r
deriv (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
tempW) UnitalChunk
time ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= Relation -> ModelExpr
forall c. Express c => c -> ModelExpr
express Relation
balWtrExpr
balWtrExpr :: Expr
balWtrExpr :: Relation
balWtrExpr = Relation -> Relation
forall r. (ExprC r, LiteralC r) => r -> r
recip_ (UnitalChunk -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
tauW) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* ((UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempC Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- ConstrConcept -> UnitalChunk -> Relation
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempW UnitalChunk
time) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+
(DefinedQuantityDict -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
eta Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* (ConstrConcept -> UnitalChunk -> Relation
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempPCM UnitalChunk
time Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- ConstrConcept -> UnitalChunk -> Relation
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempW UnitalChunk
time)))
balWtrDesc :: [Sentence]
balWtrDesc :: [Sentence]
balWtrDesc = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent [
[ConstrConcept -> Sentence
forall t. Express t => t -> Sentence
eS' ConstrConcept
tempPCM Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"defined by", InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
eBalanceOnPCM],
[NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
input_), IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
constraint, ModelExpr -> Sentence
eS (ModelExpr -> Sentence) -> ModelExpr -> Sentence
forall a b. (a -> b) -> a -> b
$ UncertQ -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempInit ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$<= UncertQ -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempC,
String -> Sentence
S String
"comes from", ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpCTNOD],
[UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
tauW Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"calculated from", DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
balanceDecayRate],
[DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
eta Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"calculated from", DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
balanceDecayTime],
[String -> Sentence
S String
"The initial", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
condition, String -> Sentence
S String
"for the", CI -> Sentence
getAcc CI
ode Sentence -> Sentence -> Sentence
`S.are`
ModelExpr -> Sentence
eS (ConstrConcept -> [ModelExpr] -> ModelExpr
forall f. (HasUID f, HasSymbol f) => f -> [ModelExpr] -> ModelExpr
forall r f. (ExprC r, HasUID f, HasSymbol f) => f -> [r] -> r
apply ConstrConcept
tempW [Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0] ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= ConstrConcept -> [ModelExpr] -> ModelExpr
forall f. (HasUID f, HasSymbol f) => f -> [ModelExpr] -> ModelExpr
forall r f. (ExprC r, HasUID f, HasSymbol f) => f -> [r] -> r
apply ConstrConcept
tempPCM [Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0] ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= UncertQ -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempInit) Sentence -> ConceptInstance -> Sentence
forall r.
(Referable r, HasShortName r) =>
Sentence -> r -> Sentence
`follows` ConceptInstance
assumpSITWP],
[String -> Sentence
S String
"The", CI -> Sentence
getAcc CI
ode, String -> Sentence
S String
"applies as long as the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
water Sentence -> Sentence -> Sentence
`S.is` Sentence
EmptyS Sentence -> Sentence -> Sentence
`S.in_`
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
liquid, String -> Sentence
S String
"form" Sentence -> Sentence -> Sentence
`sC` ModelExpr -> Sentence
eS (ConstrConcept -> RealInterval ModelExpr ModelExpr -> ModelExpr
forall c.
HasUID c =>
c -> RealInterval ModelExpr ModelExpr -> ModelExpr
forall r c. (ExprC r, HasUID c) => c -> RealInterval r r -> r
realInterval ConstrConcept
tempW ((Inclusive, ModelExpr)
-> (Inclusive, ModelExpr) -> RealInterval ModelExpr ModelExpr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
100))),
Sentence -> Sentence
sParen (Maybe UnitDefn -> Sentence
unwrap (Maybe UnitDefn -> Sentence) -> Maybe UnitDefn -> Sentence
forall a b. (a -> b) -> a -> b
$ ConstrConcept -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit ConstrConcept
tempW), String -> Sentence
S String
"where", ModelExpr -> Sentence
eS (Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0), Sentence -> Sentence
sParen (Maybe UnitDefn -> Sentence
unwrap (Maybe UnitDefn -> Sentence) -> Maybe UnitDefn -> Sentence
forall a b. (a -> b) -> a -> b
$ ConstrConcept -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit ConstrConcept
tempW) Sentence -> Sentence -> Sentence
`S.and_`
ModelExpr -> Sentence
eS (Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
100), Sentence -> Sentence
sParen (Maybe UnitDefn -> Sentence
unwrap (Maybe UnitDefn -> Sentence) -> Maybe UnitDefn -> Sentence
forall a b. (a -> b) -> a -> b
$ ConstrConcept -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit ConstrConcept
tempW) Sentence -> Sentence -> Sentence
`S.are` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (NP -> NP
NP.the ((ConceptChunk
melting ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_`
ConceptChunk
boilPt) NP -> ConceptChunk -> NP
forall c d. (NounPhrase c, NamedIdea d) => c -> d -> NP
`of_PSNPNI` ConceptChunk
water)) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"respectively",
[ConceptInstance] -> Sentence
forall r. (Referable r, HasShortName r) => [r] -> Sentence
fromSources [ConceptInstance
assumpWAL, ConceptInstance
assumpAPT]]]
eBalanceOnWtrDeriv :: Derivation
eBalanceOnWtrDeriv :: Derivation
eBalanceOnWtrDeriv = Sentence -> [Sentence] -> Derivation
mkDerivName (NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
energy) Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"balance on water")
([[Sentence]] -> [Sentence]
forall a. [[a]] -> [a]
weave [[Sentence]
eBalanceOnWtrDerivSentences, (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr]
eBalanceOnWtrDerivEqnsIM1])
eBalanceOnWtrDerivSentences :: [Sentence]
eBalanceOnWtrDerivSentences :: [Sentence]
eBalanceOnWtrDerivSentences = [Sentence -> Sentence -> Sentence -> ConceptInstance -> Sentence
eBalanceOnWtrDerivDesc1 Sentence
htTransEnd Sentence
overAreas Sentence
extraAssumps ConceptInstance
assumpNIHGBWP,
Sentence
eBalanceOnWtrDerivDesc2, Sentence
eBalanceOnWtrDerivDesc3, Sentence
eBalanceOnWtrDerivDesc4,
Sentence
eBalanceOnWtrDerivDesc5, Sentence
eBalanceOnWtrDerivDesc6, Relation -> Sentence
eBalanceOnWtrDerivDesc7 Relation
eq2]
eBalanceOnWtrDerivDesc1 :: Sentence -> Sentence-> Sentence -> ConceptInstance -> Sentence
eBalanceOnWtrDerivDesc1 :: Sentence -> Sentence -> Sentence -> ConceptInstance -> Sentence
eBalanceOnWtrDerivDesc1 Sentence
htEnd Sentence
oa Sentence
ea ConceptInstance
htA = [Sentence] -> Sentence
foldlSentCol [
String -> Sentence
S String
"To find the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
rOfChng Sentence -> Sentence -> Sentence
`S.of_` ConstrConcept -> Sentence
forall t. Express t => t -> Sentence
eS' ConstrConcept
tempW Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"we look at the", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
energy, String -> Sentence
S String
"balance on" Sentence -> Sentence -> Sentence
+:+. ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
water, NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
vol),
String -> Sentence
S String
"being considered" Sentence -> Sentence -> Sentence
`S.isThe` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
vol ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`of_` ConceptChunk
water) Sentence -> Sentence -> Sentence
`S.inThe`
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
tank, UnitalChunk -> Sentence
forall t. Express t => t -> Sentence
eS' UnitalChunk
wVol Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"which has", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
mass Sentence -> Sentence -> Sentence
+:+. (UnitalChunk -> Sentence
forall t. Express t => t -> Sentence
eS' UnitalChunk
wMass Sentence -> Sentence -> Sentence
`S.and_`
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
heatCapSpec Sentence -> Sentence -> Sentence
`sC` UncertQ -> Sentence
forall t. Express t => t -> Sentence
eS' UncertQ
htCapW), ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart ConceptChunk
heatTrans, String -> Sentence
S String
"occurs in the",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
water, String -> Sentence
S String
"from the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
coil, String -> Sentence
S String
"as", UnitalChunk -> Sentence
forall t. Express t => t -> Sentence
eS' UnitalChunk
htFluxC,
Sentence -> Sentence
sParen (GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
htFluxWaterFromCoil) Sentence -> Sentence -> Sentence
+:+ Sentence
htEnd Sentence -> Sentence -> Sentence
`sC` Sentence
EmptyS Sentence -> Sentence -> Sentence
+:+. Sentence
oa, Sentence
ea, String -> Sentence
S String
"No", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
heatTrans, String -> Sentence
S String
"occurs to", String -> Sentence
S String
"outside" Sentence -> Sentence -> Sentence
`S.the_ofThe`
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
tank Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"since it has been assumed to be perfectly insulated" Sentence -> Sentence -> Sentence
+:+.
Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpPIT), String -> Sentence
S String
"Since the", CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
assumption Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"made that no internal heat" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"generated" Sentence -> Sentence -> Sentence
+:+.
(Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
htA) Sentence -> Sentence -> Sentence
`sC` ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
volHtGen ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)),
String -> Sentence
S String
"Therefore" Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
equation) Sentence -> Sentence -> Sentence
`S.for`
GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
rocTempSimp, String -> Sentence
S String
"can be written as"]
htTransEnd :: Sentence
htTransEnd :: Sentence
htTransEnd = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"and from the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
water, String -> Sentence
S String
"into the",
CI -> Sentence
getAcc CI
phsChgMtrl, String -> Sentence
S String
"as", UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
htFluxP, Sentence -> Sentence
sParen (GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
htFluxPCMFromWater)]
overAreas :: Sentence
overAreas :: Sentence
overAreas = String -> Sentence
S String
"over areas" Sentence -> Sentence -> Sentence
+:+ UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
coilSA Sentence -> Sentence -> Sentence
`S.and_` UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
pcmSA Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"respectively"
extraAssumps :: Sentence
= [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"The thermal flux" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"constant over", UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
coilSA Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"since", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
temp ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
coil) Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"assumed to not vary along its length",
Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpTHCCoL) Sentence -> Sentence -> Sentence
`sC` Sentence
EmptyS Sentence -> Sentence -> Sentence
`S.andThe` String -> Sentence
S String
"thermal flux" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"constant over",
UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
pcmSA Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"since", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
temp Sentence -> Sentence -> Sentence
`S.the_ofThe` CI -> Sentence
getAcc CI
phsChgMtrl Sentence -> Sentence -> Sentence
`S.isThe`
String -> Sentence
S String
"same throughout its", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
vol, Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpTPCAV) Sentence -> Sentence -> Sentence
`S.andThe`
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
water Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"fully mixed", Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpCWTAT)]
eBalanceOnWtrDerivDesc2 :: Sentence
eBalanceOnWtrDerivDesc2 :: Sentence
eBalanceOnWtrDerivDesc2 = [Sentence] -> Sentence
foldlSentCol [String -> Sentence
S String
"Using", GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
htFluxWaterFromCoil Sentence -> Sentence -> Sentence
`S.for`
UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
htFluxC Sentence -> Sentence -> Sentence
`S.and_` GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
htFluxPCMFromWater Sentence -> Sentence -> Sentence
`S.for` UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
htFluxP Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"this can be written as"]
eBalanceOnWtrDerivDesc3 :: Sentence
eBalanceOnWtrDerivDesc3 :: Sentence
eBalanceOnWtrDerivDesc3 = [Sentence] -> Sentence
foldlSentCol [String -> Sentence
S String
"Dividing", Int -> Sentence
eqN Int
2, String -> Sentence
S String
"by", Relation -> Sentence
forall t. Express t => t -> Sentence
eS' Relation
eq1 Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"we obtain"]
eBalanceOnWtrDerivDesc4 :: Sentence
eBalanceOnWtrDerivDesc4 :: Sentence
eBalanceOnWtrDerivDesc4 = [Sentence] -> Sentence
foldlSentCol [String -> Sentence
S String
"Factoring the negative sign out" Sentence -> Sentence -> Sentence
`S.of_`
(String -> Sentence
S String
"second term" Sentence -> Sentence -> Sentence
`S.the_ofThe` (CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
rightSide Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
rightSide)))
Sentence -> Sentence -> Sentence
`S.of_` Int -> Sentence
eqN Int
3 Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"multiplying it by", UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
coilHTC, UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
coilSA, String -> Sentence
S String
"/", UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
coilHTC,
UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
coilSA, String -> Sentence
S String
"yields"]
eBalanceOnWtrDerivDesc5 :: Sentence
eBalanceOnWtrDerivDesc5 :: Sentence
eBalanceOnWtrDerivDesc5 = String -> Sentence
S String
"Rearranging this" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation Sentence -> Sentence -> Sentence
+: String -> Sentence
S String
"gives us"
eBalanceOnWtrDerivDesc6 :: Sentence
eBalanceOnWtrDerivDesc6 :: Sentence
eBalanceOnWtrDerivDesc6 = [DataDefinition] -> Sentence
forall r.
(Referable r, HasShortName r, DefinesQuantity r) =>
[r] -> Sentence
substitute [DataDefinition
balanceDecayRate, DataDefinition
balanceDecayTime]
eBalanceOnWtrDerivDesc7 :: Expr -> Sentence
eBalanceOnWtrDerivDesc7 :: Relation -> Sentence
eBalanceOnWtrDerivDesc7 Relation
eq22 = [Sentence] -> Sentence
foldlSentCol [String -> Sentence
S String
"Finally, factoring out", Relation -> Sentence
forall t. Express t => t -> Sentence
eS' Relation
eq22 Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"we" Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"left with the governing", CI -> Sentence
getAcc CI
ode Sentence -> Sentence -> Sentence
`S.for` InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
eBalanceOnWtr]
eq1, eq2 :: Expr
eq1 :: Relation
eq1 = UnitalChunk -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
wMass Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
htCapW
eq2 :: Relation
eq2 = Relation -> Relation
forall r. (ExprC r, LiteralC r) => r -> r
recip_ (Relation -> Relation) -> Relation -> Relation
forall a b. (a -> b) -> a -> b
$ UnitalChunk -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
tauW
eBalanceOnPCM :: InstanceModel
eBalanceOnPCM :: InstanceModel
eBalanceOnPCM = ModelKind Relation
-> Inputs
-> Output
-> OutputConstraints
-> [DecRef]
-> Maybe Derivation
-> String
-> [Sentence]
-> InstanceModel
im (RelationConcept -> ModelKind Relation
forall e. RelationConcept -> ModelKind e
deModel' RelationConcept
eBalanceOnPCMRC) [UncertQ -> RealInterval Relation Relation -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Relation Relation -> Input
qwC UncertQ
tempMeltP (RealInterval Relation Relation -> Input)
-> RealInterval Relation Relation -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Relation) -> RealInterval Relation Relation
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempInit)
, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
timeFinal, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
tempInit, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
pcmSA
, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
pcmHTC, UnitalChunk -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UnitalChunk
pcmMass, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
htCapSP, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
htCapLP]
(ConstrConcept -> Output
forall q. (Quantity q, MayHaveUnit q) => q -> Output
qw ConstrConcept
tempPCM) []
[Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
koothoor2013] (Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
eBalanceOnPCMDeriv) String
"eBalanceOnPCM" [Sentence]
balPCMNotes
eBalanceOnPCMRC :: RelationConcept
eBalanceOnPCMRC :: RelationConcept
eBalanceOnPCMRC = String -> NP -> Sentence -> ModelExpr -> RelationConcept
forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
"eBalanceOnPCMRC" (String -> NP
nounPhraseSP
String
"Energy Balance on PCM to find temperature of PCM")
(ConstrConcept
tempPCM ConstrConcept
-> Getting Sentence ConstrConcept Sentence -> Sentence
forall s a. s -> Getting a s a -> a
^. Getting Sentence ConstrConcept Sentence
forall c. Definition c => Lens' c Sentence
Lens' ConstrConcept Sentence
defn) ModelExpr
balPCMRel
balPCMRel :: ModelExpr
balPCMRel :: ModelExpr
balPCMRel = ModelExpr -> UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => ModelExpr -> c -> ModelExpr
forall r c. (ModelExprC r, HasUID c, HasSymbol c) => r -> c -> r
deriv (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
tempPCM) UnitalChunk
time ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= ModelExpr
PExpr
balPCMExpr
balPCMExpr :: PExpr
balPCMExpr :: PExpr
balPCMExpr = [(r, r)] -> r
forall r. ExprC r => [(r, r)] -> r
completeCase [(r, r)
case1, (r, r)
case2, (r, r)
case3]
where case1 :: (r, r)
case1 = (r -> r
forall r. (ExprC r, LiteralC r) => r -> r
recip_ (UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
tauSP) r -> r -> r
forall r. ExprC r => r -> r -> r
$* (ConstrConcept -> UnitalChunk -> r
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempW UnitalChunk
time r -> r -> r
forall r. ExprC r => r -> r -> r
$-
ConstrConcept -> UnitalChunk -> r
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempPCM UnitalChunk
time), ConstrConcept -> RealInterval r r -> r
forall c. HasUID c => c -> RealInterval r r -> r
forall r c. (ExprC r, HasUID c) => c -> RealInterval r r -> r
realInterval ConstrConcept
tempPCM ((Inclusive, r) -> RealInterval r r
forall a b. (Inclusive, a) -> RealInterval a b
UpTo (Inclusive
Exc, UncertQ -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempMeltP)))
case2 :: (r, r)
case2 = (r -> r
forall r. (ExprC r, LiteralC r) => r -> r
recip_ (UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
tauLP) r -> r -> r
forall r. ExprC r => r -> r -> r
$* (ConstrConcept -> UnitalChunk -> r
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempW UnitalChunk
time r -> r -> r
forall r. ExprC r => r -> r -> r
$-
ConstrConcept -> UnitalChunk -> r
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempPCM UnitalChunk
time), ConstrConcept -> RealInterval r r -> r
forall c. HasUID c => c -> RealInterval r r -> r
forall r c. (ExprC r, HasUID c) => c -> RealInterval r r -> r
realInterval ConstrConcept
tempPCM ((Inclusive, r) -> RealInterval r r
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc,UncertQ -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempMeltP)))
case3 :: (r, r)
case3 = (Integer -> r
forall r. LiteralC r => Integer -> r
exactDbl Integer
0, ConstrConcept -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
tempPCM r -> r -> r
forall r. ExprC r => r -> r -> r
$= UncertQ -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempMeltP r -> r -> r
forall r. ExprC r => r -> r -> r
$&& DefinedQuantityDict -> RealInterval r r -> r
forall c. HasUID c => c -> RealInterval r r -> r
forall r c. (ExprC r, HasUID c) => c -> RealInterval r r -> r
realInterval DefinedQuantityDict
meltFrac ((Inclusive, r) -> (Inclusive, r) -> RealInterval r r
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> r
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, Integer -> r
forall r. LiteralC r => Integer -> r
exactDbl Integer
1)))
balPCMNotes :: [Sentence]
balPCMNotes :: [Sentence]
balPCMNotes = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent [
[ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
tempW Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"defined by", InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
eBalanceOnWtr],
[NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
input_), IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
constraint, ModelExpr -> Sentence
eS (ModelExpr -> Sentence) -> ModelExpr -> Sentence
forall a b. (a -> b) -> a -> b
$ UncertQ -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempInit ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$<= UncertQ -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempMeltP,
String -> Sentence
S String
"comes from", ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpPIS],
[NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
temp), String -> Sentence
S String
"remains constant at", UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
tempMeltP Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"even with the heating", Sentence -> Sentence
sParen (String -> Sentence
S String
"or cooling") Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"until the",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
phaseChange, String -> Sentence
S String
"has occurred for all" Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"the material; that" Sentence -> Sentence -> Sentence
`S.is`
String -> Sentence
S String
"as long as" Sentence -> Sentence -> Sentence
+:+. ModelExpr -> Sentence
eS (DefinedQuantityDict
-> RealInterval ModelExpr ModelExpr -> ModelExpr
forall c.
HasUID c =>
c -> RealInterval ModelExpr ModelExpr -> ModelExpr
forall r c. (ExprC r, HasUID c) => c -> RealInterval r r -> r
realInterval DefinedQuantityDict
meltFrac (RealInterval ModelExpr ModelExpr -> ModelExpr)
-> RealInterval ModelExpr ModelExpr -> ModelExpr
forall a b. (a -> b) -> a -> b
$ (Inclusive, ModelExpr)
-> (Inclusive, ModelExpr) -> RealInterval ModelExpr ModelExpr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1)), DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
meltFrac,
DataDefinition -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource DataDefinition
ddMeltFrac Sentence -> Sentence -> Sentence
`S.is`
String -> Sentence
S String
"determined as part" Sentence -> Sentence -> Sentence
`S.ofThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
heat, UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
energy Sentence -> Sentence -> Sentence
`S.inThe`
CI -> Sentence
getAcc CI
phsChgMtrl Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"as given" Sentence -> Sentence -> Sentence
`S.in_` Sentence -> Sentence
sParen (InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
heatEInPCM)],
[UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
tauSP Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"calculated" Sentence -> Sentence -> Sentence
`S.in_` DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
balanceSolidPCM],
[UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
tauLP Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"calculated" Sentence -> Sentence -> Sentence
`S.in_` DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
balanceLiquidPCM],
[String -> Sentence
S String
"The initial", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
condition, String -> Sentence
S String
"for the", CI -> Sentence
getAcc CI
ode Sentence -> Sentence -> Sentence
`S.are`
ModelExpr -> Sentence
eS (ConstrConcept -> [ModelExpr] -> ModelExpr
forall f. (HasUID f, HasSymbol f) => f -> [ModelExpr] -> ModelExpr
forall r f. (ExprC r, HasUID f, HasSymbol f) => f -> [r] -> r
apply ConstrConcept
tempW [Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0] ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= ConstrConcept -> [ModelExpr] -> ModelExpr
forall f. (HasUID f, HasSymbol f) => f -> [ModelExpr] -> ModelExpr
forall r f. (ExprC r, HasUID f, HasSymbol f) => f -> [r] -> r
apply ConstrConcept
tempPCM [Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0] ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= UncertQ -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempInit) Sentence -> ConceptInstance -> Sentence
forall r.
(Referable r, HasShortName r) =>
Sentence -> r -> Sentence
`follows` ConceptInstance
assumpSITWP]]
eBalanceOnPCMDeriv :: Derivation
eBalanceOnPCMDeriv :: Derivation
eBalanceOnPCMDeriv = Sentence -> [Sentence] -> Derivation
mkDerivName (NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
energy) Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"balance on the PCM during sensible heating phase")
([[Sentence]] -> [Sentence]
forall a. [[a]] -> [a]
weave [[Sentence]
eBalanceOnPCMDerivSentences, (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr]
eBalanceOnPCMDerivEqnsIM2]
[Sentence] -> [Sentence] -> [Sentence]
forall a. [a] -> [a] -> [a]
++ [Sentence
eBalanceOnPCMDerivDesc5, Sentence
eBalanceOnPCMDerivDesc6, Sentence
eBalanceOnPCMDerivDesc7])
eBalanceOnPCMDerivSentences :: [Sentence]
eBalanceOnPCMDerivSentences :: [Sentence]
eBalanceOnPCMDerivSentences = [Sentence
eBalanceOnPCMDerivDesc1, Sentence
eBalanceOnPCMDerivDesc2,
Sentence
eBalanceOnPCMDerivDesc3, Sentence
eBalanceOnPCMDerivDesc4]
eBalanceOnPCMDerivDesc1 :: Sentence
eBalanceOnPCMDerivDesc1 :: Sentence
eBalanceOnPCMDerivDesc1 = [Sentence] -> Sentence
foldlSentCol [
String -> Sentence
S String
"To find the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
rOfChng Sentence -> Sentence -> Sentence
`S.of_` ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
tempPCM Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"we look at the",
UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
energy, String -> Sentence
S String
"balance on the" Sentence -> Sentence -> Sentence
+:+. CI -> Sentence
getAcc CI
phsChgMtrl, String -> Sentence
S String
"The", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
vol,
String -> Sentence
S String
"being considered" Sentence -> Sentence -> Sentence
`S.isThe` UncertQ -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UncertQ
pcmVol Sentence -> Sentence -> Sentence
+:+. Sentence -> Sentence
sParen (UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
pcmVol),
String -> Sentence
S String
"The derivation that follows" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"initially" Sentence -> Sentence -> Sentence
`S.for` String -> Sentence
S String
"the solid" Sentence -> Sentence -> Sentence
+:+. CI -> Sentence
getAcc CI
phsChgMtrl,
String -> Sentence
S String
"The" Sentence -> Sentence -> Sentence
+:+. (UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
pcmMass Sentence -> Sentence -> Sentence
`S.is` UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
pcmMass Sentence -> Sentence -> Sentence
`S.andThe` UncertQ -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UncertQ
htCapSP Sentence -> Sentence -> Sentence
`S.is` UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
htCapSP),
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
htFluxP) Sentence -> Sentence -> Sentence
`S.is` UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
htFluxP, Sentence -> Sentence
sParen (GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
htFluxPCMFromWater),
String -> Sentence
S String
"over", UncertQ -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UncertQ
pcmSA Sentence -> Sentence -> Sentence
+:+. UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
pcmSA, String -> Sentence
S String
"The thermal flux" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"constant over",
UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
pcmSA Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"since", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
temp Sentence -> Sentence -> Sentence
`S.the_ofThe` CI -> Sentence
getAcc CI
phsChgMtrl Sentence -> Sentence -> Sentence
`S.isThe`
String -> Sentence
S String
"same throughout its", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
vol, Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpTPCAV) Sentence -> Sentence -> Sentence
`S.andThe`
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
water Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"fully mixed" Sentence -> Sentence -> Sentence
+:+. Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpCWTAT),
String -> Sentence
S String
"There is no", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
htFlux, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
output_, String -> Sentence
S String
"from the" Sentence -> Sentence -> Sentence
+:+. CI -> Sentence
getAcc CI
phsChgMtrl,
String -> Sentence
S String
"Assuming no volumetric", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
heat, String -> Sentence
S String
"generation per unit", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
vol,
Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpNIHGBWP) Sentence -> Sentence -> Sentence
`sC` ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
volHtGen ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$= Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"the equation for", GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
rocTempSimp, String -> Sentence
S String
"can be written as"]
eBalanceOnPCMDerivDesc2 :: Sentence
eBalanceOnPCMDerivDesc2 :: Sentence
eBalanceOnPCMDerivDesc2 = [Sentence] -> Sentence
foldlSentCol [String -> Sentence
S String
"Using", GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
htFluxPCMFromWater Sentence -> Sentence -> Sentence
`S.for`
UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
htFluxP Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"this", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation, String -> Sentence
S String
"can be written as"]
eBalanceOnPCMDerivDesc3 :: Sentence
eBalanceOnPCMDerivDesc3 :: Sentence
eBalanceOnPCMDerivDesc3 = [Sentence] -> Sentence
foldlSentCol [String -> Sentence
S String
"Dividing by", UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
pcmMass, UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
htCapSP, String -> Sentence
S String
"we obtain"]
eBalanceOnPCMDerivDesc4 :: Sentence
eBalanceOnPCMDerivDesc4 :: Sentence
eBalanceOnPCMDerivDesc4 = [DataDefinition] -> Sentence
forall r.
(Referable r, HasShortName r, DefinesQuantity r) =>
[r] -> Sentence
substitute [DataDefinition
balanceSolidPCM]
eBalanceOnPCMDerivDesc5 :: Sentence
eBalanceOnPCMDerivDesc5 :: Sentence
eBalanceOnPCMDerivDesc5 = [Sentence] -> Sentence
foldlSent [
Int -> Sentence
eqN Int
4, String -> Sentence
S String
"applies for the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
solid Sentence -> Sentence -> Sentence
+:+. CI -> Sentence
getAcc CI
phsChgMtrl, String -> Sentence
S String
"In the case where all" Sentence -> Sentence -> Sentence
`S.ofThe`
CI -> Sentence
getAcc CI
phsChgMtrl Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"melted" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"the same derivation applies" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"except that",
UncertQ
htCapSP UncertQ -> UncertQ -> Sentence
forall {c} {c}.
(HasUID c, HasUID c, HasSymbol c, HasSymbol c) =>
c -> c -> Sentence
`isReplacedBy` UncertQ
htCapLP Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"and thus" Sentence -> Sentence -> Sentence
+:+. (UnitalChunk
tauSP UnitalChunk -> UnitalChunk -> Sentence
forall {c} {c}.
(HasUID c, HasUID c, HasSymbol c, HasSymbol c) =>
c -> c -> Sentence
`isReplacedBy` UnitalChunk
tauLP),
String -> Sentence
S String
"Although a small change in", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
surArea, String -> Sentence
S String
"would be expected with", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
melting Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"this is not included" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"since the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
vol, String -> Sentence
S String
"change" Sentence -> Sentence -> Sentence
`S.ofThe` CI -> Sentence
getAcc CI
phsChgMtrl,
String -> Sentence
S String
"with", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
melting Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"assumed to be negligible", Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpVCMPN)]
where isReplacedBy :: c -> c -> Sentence
isReplacedBy c
a c
b = c -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch c
a Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"replaced by" Sentence -> Sentence -> Sentence
+:+ c -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch c
b
eBalanceOnPCMDerivDesc6 :: Sentence
eBalanceOnPCMDerivDesc6 :: Sentence
eBalanceOnPCMDerivDesc6 = [Sentence] -> Sentence
foldlSent [
String -> Sentence
S String
"In the case where", Relation -> Sentence
forall t. Express t => t -> Sentence
eS' Relation
eq6_1 Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"not all" Sentence -> Sentence -> Sentence
`S.ofThe` CI -> Sentence
getAcc CI
phsChgMtrl Sentence -> Sentence -> Sentence
`S.is`
String -> Sentence
S String
"melted" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"the", ConstrConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConstrConcept
tempPCM Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"does not change", String -> Sentence
S String
"Therefore" Sentence -> Sentence -> Sentence
`sC` Sentence
eq6_2]
eBalanceOnPCMDerivDesc7 :: Sentence
eBalanceOnPCMDerivDesc7 :: Sentence
eBalanceOnPCMDerivDesc7 = [Sentence] -> Sentence
foldlSent [
String -> Sentence
S String
"This derivation does not consider", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
boiling Sentence -> Sentence -> Sentence
`S.the_ofThe` CI -> Sentence
getAcc CI
phsChgMtrl Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"as the PCM" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"assumed to either be in a", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
solid, String -> Sentence
S String
"state or a",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
liquid, String -> Sentence
S String
"state", Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpNGSP)]
eq6_1 :: Expr
eq6_1 :: Relation
eq6_1 = ConstrConcept -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
tempPCM Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempMeltP
eq6_2 :: Sentence
eq6_2 :: Sentence
eq6_2 = [Sentence] -> Sentence
foldlSent_ [String -> Sentence
S String
"d", ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
tempPCM, String -> Sentence
S String
"/ d", UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
time, String -> Sentence
S String
"= 0"]
heatEInWtr :: InstanceModel
heatEInWtr :: InstanceModel
heatEInWtr = ModelKind Relation
-> Inputs
-> Output
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv ModelKind Relation
heatEInWtrMK
[UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
tempInit, UnitalChunk -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UnitalChunk
wMass, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
htCapW, UnitalChunk -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UnitalChunk
wMass]
(ConstrConcept -> Output
forall q. (Quantity q, MayHaveUnit q) => q -> Output
qw ConstrConcept
watE) [] [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
koothoor2013]
String
"heatEInWtr" [Sentence]
htWtrNotes
heatEInWtrMK :: ModelKind Expr
heatEInWtrMK :: ModelKind Relation
heatEInWtrMK = String -> NP -> QDefinition Relation -> ModelKind Relation
forall e. String -> NP -> QDefinition e -> ModelKind e
equationalModel String
"heatEInWtrIM"
(String -> NP
nounPhraseSP String
"Heat energy in the water") QDefinition Relation
heatEInWtrFD
heatEInWtrFD :: SimpleQDef
heatEInWtrFD :: QDefinition Relation
heatEInWtrFD = ConstrConcept -> [UnitalChunk] -> Relation -> QDefinition Relation
forall c i e.
(Quantity c, MayHaveUnit c, HasSpace c, Quantity i, HasSpace i) =>
c -> [i] -> e -> QDefinition e
mkFuncDefByQ ConstrConcept
watE [UnitalChunk
time] Relation
htWtrExpr
htWtrExpr :: Expr
htWtrExpr :: Relation
htWtrExpr = UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
htCapW Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
wMass Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$*
(ConstrConcept -> UnitalChunk -> Relation
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempW UnitalChunk
time Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempInit)
htWtrNotes :: [Sentence]
htWtrNotes :: [Sentence]
htWtrNotes = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent [
[String -> Sentence
S String
"The above", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"derived using", TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
sensHtE],
[NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NP -> NP
NP.the (ConceptChunk
change ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`in_`ConceptChunk
temp)) Sentence -> Sentence -> Sentence
`S.isThe` String -> Sentence
S String
"difference between the",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
temp, String -> Sentence
S String
"at", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
time, UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
time, Sentence -> Sentence
sParen (Maybe UnitDefn -> Sentence
unwrap (Maybe UnitDefn -> Sentence) -> Maybe UnitDefn -> Sentence
forall a b. (a -> b) -> a -> b
$ UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
tInitMelt) Sentence -> Sentence -> Sentence
`sC`
ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
tempW Sentence -> Sentence -> Sentence
`S.andThe` UncertQ -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UncertQ
tempInit Sentence -> Sentence -> Sentence
`sC` UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
tempInit, Sentence -> Sentence
sParen (Maybe UnitDefn -> Sentence
unwrap (Maybe UnitDefn -> Sentence) -> Maybe UnitDefn -> Sentence
forall a b. (a -> b) -> a -> b
$ UncertQ -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UncertQ
tempInit)],
[String -> Sentence
S String
"This", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation, String -> Sentence
S String
"applies as long as",
ModelExpr -> Sentence
eS (ConstrConcept -> RealInterval ModelExpr ModelExpr -> ModelExpr
forall c.
HasUID c =>
c -> RealInterval ModelExpr ModelExpr -> ModelExpr
forall r c. (ExprC r, HasUID c) => c -> RealInterval r r -> r
realInterval ConstrConcept
tempW ((Inclusive, ModelExpr)
-> (Inclusive, ModelExpr) -> RealInterval ModelExpr ModelExpr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
100))) Sentence -> Sentence -> Sentence
:+:
Maybe UnitDefn -> Sentence
unwrap (ConstrConcept -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit ConstrConcept
tempW), Sentence -> Sentence
sParen (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpWAL Sentence -> Sentence -> Sentence
`sC` ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpAPT]]
heatEInPCM :: InstanceModel
heatEInPCM :: InstanceModel
heatEInPCM = ModelKind Relation
-> Inputs
-> Output
-> OutputConstraints
-> [DecRef]
-> String
-> [Sentence]
-> InstanceModel
imNoDeriv (RelationConcept -> ModelKind Relation
forall e. RelationConcept -> ModelKind e
deModel' RelationConcept
heatEInPCMRC) [UncertQ -> RealInterval Relation Relation -> Input
forall q.
(Quantity q, MayHaveUnit q) =>
q -> RealInterval Relation Relation -> Input
qwC UncertQ
tempMeltP (RealInterval Relation Relation -> Input)
-> RealInterval Relation Relation -> Input
forall a b. (a -> b) -> a -> b
$ (Inclusive, Relation) -> RealInterval Relation Relation
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempInit)
, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
timeFinal, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
tempInit, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
pcmSA, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
pcmHTC
, UnitalChunk -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UnitalChunk
pcmMass, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
htCapSP, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
htCapLP, ConstrConcept -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC ConstrConcept
tempPCM, UncertQ -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UncertQ
htFusion, UnitalChunk -> Input
forall q. (Quantity q, MayHaveUnit q) => q -> Input
qwUC UnitalChunk
tInitMelt]
(ConstrConcept -> Output
forall q. (Quantity q, MayHaveUnit q) => q -> Output
qw ConstrConcept
pcmE)
[] [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
koothoor2013]
String
"heatEInPCM" [Sentence]
htPCMNotes
heatEInPCMRC :: RelationConcept
heatEInPCMRC :: RelationConcept
heatEInPCMRC = String -> NP -> Sentence -> Relation -> RelationConcept
forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
"heatEInPCMRC" (String -> NP
nounPhraseSP String
"Heat energy in the PCM")
(ConstrConcept
pcmE ConstrConcept
-> Getting Sentence ConstrConcept Sentence -> Sentence
forall s a. s -> Getting a s a -> a
^. Getting Sentence ConstrConcept Sentence
forall c. Definition c => Lens' c Sentence
Lens' ConstrConcept Sentence
defn) Relation
htPCMRel
htPCMRel :: Relation
htPCMRel :: Relation
htPCMRel = ConstrConcept -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
pcmE Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= [(Relation, Relation)] -> Relation
forall r. ExprC r => [(r, r)] -> r
completeCase [(Relation, Relation)
case1, (Relation, Relation)
case2, (Relation, Relation)
case3]
where case1 :: (Relation, Relation)
case1 = (UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
htCapSP Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
pcmMass Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* (ConstrConcept -> UnitalChunk -> Relation
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempPCM UnitalChunk
time Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$-
UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempInit), ConstrConcept -> RealInterval Relation Relation -> Relation
forall c.
HasUID c =>
c -> RealInterval Relation Relation -> Relation
forall r c. (ExprC r, HasUID c) => c -> RealInterval r r -> r
realInterval ConstrConcept
tempPCM ((Inclusive, Relation) -> RealInterval Relation Relation
forall a b. (Inclusive, a) -> RealInterval a b
UpTo (Inclusive
Exc, UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempMeltP)))
case2 :: (Relation, Relation)
case2 = (UnitalChunk -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
pcmInitMltE Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ (UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
htFusion Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
pcmMass) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+
(UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
htCapLP Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
pcmMass Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* (ConstrConcept -> UnitalChunk -> Relation
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 ConstrConcept
tempPCM UnitalChunk
time Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$-
UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempMeltP)), ConstrConcept -> RealInterval Relation Relation -> Relation
forall c.
HasUID c =>
c -> RealInterval Relation Relation -> Relation
forall r c. (ExprC r, HasUID c) => c -> RealInterval r r -> r
realInterval ConstrConcept
tempPCM ((Inclusive, Relation) -> RealInterval Relation Relation
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Exc, UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempMeltP)))
case3 :: (Relation, Relation)
case3 = (UnitalChunk -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
pcmInitMltE Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ UnitalChunk -> UnitalChunk -> Relation
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
latentEP UnitalChunk
time,
ConstrConcept -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
tempPCM Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempMeltP Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$&& DefinedQuantityDict -> RealInterval Relation Relation -> Relation
forall c.
HasUID c =>
c -> RealInterval Relation Relation -> Relation
forall r c. (ExprC r, HasUID c) => c -> RealInterval r r -> r
realInterval DefinedQuantityDict
meltFrac ((Inclusive, Relation)
-> (Inclusive, Relation) -> RealInterval Relation Relation
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> Relation
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, Integer -> Relation
forall r. LiteralC r => Integer -> r
exactDbl Integer
1)))
htPCMNotes :: [Sentence]
htPCMNotes :: [Sentence]
htPCMNotes = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent [
[String -> Sentence
S String
"The above", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"derived using",
TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
sensHtE Sentence -> Sentence -> Sentence
`S.and_` TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
latentHtE],
[ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
pcmE, String -> Sentence
S String
"for the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
solid, CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"found using",
TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
sensHtE Sentence -> Sentence -> Sentence
`S.for` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
sensHeat Sentence -> Sentence -> Sentence
:+: String -> Sentence
S String
"ing, with",
NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
heatCapSpec ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
solid), CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl Sentence -> Sentence -> Sentence
`sC` UncertQ -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UncertQ
htCapSP,
Sentence -> Sentence
sParen (Maybe UnitDefn -> Sentence
unwrap (Maybe UnitDefn -> Sentence) -> Maybe UnitDefn -> Sentence
forall a b. (a -> b) -> a -> b
$ UncertQ -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UncertQ
htCapSP) Sentence -> Sentence -> Sentence
`S.andThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
change Sentence -> Sentence -> Sentence
`S.inThe`
CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl, ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
temp, String -> Sentence
S String
"from the", UncertQ -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UncertQ
tempInit, Sentence -> Sentence
sParen (Maybe UnitDefn -> Sentence
unwrap (Maybe UnitDefn -> Sentence) -> Maybe UnitDefn -> Sentence
forall a b. (a -> b) -> a -> b
$ UncertQ -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UncertQ
tempInit)],
[ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
pcmE, String -> Sentence
S String
"for the melted", CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl, Sentence -> Sentence
sParen (ModelExpr -> Sentence
eS (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
tempPCM ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$> UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
pcmInitMltE)),
String -> Sentence
S String
"is found using", TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
sensHtE Sentence -> Sentence -> Sentence
`S.for` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
sensHeat ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofThe` ConceptChunk
liquid),
CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl, String -> Sentence
S String
"plus the", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
energy, String -> Sentence
S String
"when", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
melting, String -> Sentence
S String
"starts" Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"plus", (UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
energy Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"required to melt all") Sentence -> Sentence -> Sentence
`S.the_ofThe` CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl],
[NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
energy), String -> Sentence
S String
"required to melt all" Sentence -> Sentence -> Sentence
`S.ofThe` CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl Sentence -> Sentence -> Sentence
`S.is`
ModelExpr -> Sentence
eS (UncertQ -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
htFusion ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
pcmMass), Sentence -> Sentence
sParen (Maybe UnitDefn -> Sentence
unwrap (Maybe UnitDefn -> Sentence) -> Maybe UnitDefn -> Sentence
forall a b. (a -> b) -> a -> b
$ UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
pcmInitMltE),
DataDefinition -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource DataDefinition
ddHtFusion],
[NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NP -> NP
NP.the (ConceptChunk
change ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`in_` ConceptChunk
temp)) Sentence -> Sentence -> Sentence
`S.is` ModelExpr -> Sentence
eS (ConstrConcept -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
tempPCM ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$- UncertQ -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempMeltP),
Sentence -> Sentence
sParen (Maybe UnitDefn -> Sentence
unwrap (Maybe UnitDefn -> Sentence) -> Maybe UnitDefn -> Sentence
forall a b. (a -> b) -> a -> b
$ UncertQ -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UncertQ
tempMeltP)],
[ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
pcmE, String -> Sentence
S String
"during", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
melting Sentence -> Sentence -> Sentence
`S.ofThe` CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"found using the",
UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
energy, String -> Sentence
S String
"required at", String -> Sentence
S String
"instant" Sentence -> Sentence -> Sentence
+:+
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
melting Sentence -> Sentence -> Sentence
`S.the_ofThe` CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl, String -> Sentence
S String
"begins" Sentence -> Sentence -> Sentence
`sC` UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
pcmInitMltE, String -> Sentence
S String
"plus the",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
latentHeat, UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
energy, String -> Sentence
S String
"added" Sentence -> Sentence -> Sentence
`S.toThe` CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl Sentence -> Sentence -> Sentence
`sC`
UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
latentEP, Sentence -> Sentence
sParen (Maybe UnitDefn -> Sentence
unwrap (Maybe UnitDefn -> Sentence) -> Maybe UnitDefn -> Sentence
forall a b. (a -> b) -> a -> b
$ UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
latentEP), String -> Sentence
S String
"since the", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
time, String -> Sentence
S String
"when",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
melting, String -> Sentence
S String
"began", UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
tInitMelt, Sentence -> Sentence
sParen (Maybe UnitDefn -> Sentence
unwrap (Maybe UnitDefn -> Sentence) -> Maybe UnitDefn -> Sentence
forall a b. (a -> b) -> a -> b
$ UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
tInitMelt)],
[NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NP -> NP
NP.the (ConceptChunk -> UnitalChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI ConceptChunk
heat UnitalChunk
energy)) Sentence -> Sentence -> Sentence
`S.for` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
boiling Sentence -> Sentence -> Sentence
`S.ofThe` CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl,
String -> Sentence
S String
"is not detailed" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"since the", CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
phsChgMtrl Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"assumed to either be in a",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
solid Sentence -> Sentence -> Sentence
`S.or_` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
liquid, String -> Sentence
S String
"state", Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpNGSP),
Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpPIS)]]
instModIntro :: Sentence
instModIntro :: Sentence
instModIntro = [Sentence] -> Sentence
foldlSent [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
goal), SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List
((ConceptInstance -> Sentence) -> [ConceptInstance] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS [ConceptInstance
waterTempGS, ConceptInstance
pcmTempGS, ConceptInstance
waterEnergyGS, ConceptInstance
pcmEnergyGS]) Sentence -> Sentence -> Sentence
`S.are`
String -> Sentence
S String
"solved by" Sentence -> Sentence -> Sentence
+:+. SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List ((InstanceModel -> Sentence) -> [InstanceModel] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS
[InstanceModel
eBalanceOnWtr, InstanceModel
eBalanceOnPCM, InstanceModel
heatEInWtr, InstanceModel
heatEInPCM]), NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
solution)
Sentence -> Sentence -> Sentence
`S.for` InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
eBalanceOnWtr Sentence -> Sentence -> Sentence
`S.and_`
InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
eBalanceOnPCM Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"coupled since the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
solution
Sentence -> Sentence -> Sentence
`S.for` ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
tempW Sentence -> Sentence -> Sentence
`S.and_` ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
tempPCM Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"depend on one another",
InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
heatEInWtr, String -> Sentence
S String
"can be solved once", InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
eBalanceOnWtr Sentence -> Sentence -> Sentence
+:+.
String -> Sentence
S String
"has been solved", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
solution) Sentence -> Sentence -> Sentence
`S.of_` InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
eBalanceOnPCM Sentence -> Sentence -> Sentence
`S.and_`
InstanceModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS InstanceModel
heatEInPCM Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"also coupled" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"since the",
ConstrConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConstrConcept
tempPCM Sentence -> Sentence -> Sentence
`S.andThe` ConstrConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConstrConcept
pcmE,String -> Sentence
S String
"depend on the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
phaseChange]