module Drasil.SWHS.Unitals where
import Language.Drasil
import Language.Drasil.Display (Symbol(Atop), Decoration(Delta))
import Language.Drasil.ShortHands
import Language.Drasil.Chunk.Concept.NamedCombinators
import Data.Drasil.Concepts.Documentation (simulation)
import Data.Drasil.Constraints (gtZeroConstr)
import Data.Drasil.Quantities.Math (gradient, pi_, surArea, surface, uNormalVect)
import Data.Drasil.Quantities.PhysicalProperties (mass, density, vol)
import Data.Drasil.Quantities.Physics (subMax, subMin, supMax, supMin, time)
import Data.Drasil.Quantities.Thermodynamics (sensHeat, temp, meltPt,
htFlux, latentHeat, boilPt, heatCapSpec)
import Data.Drasil.SI_Units (m_2, second, kilogram, metre, joule,
centigrade, m_3, specificE)
import Data.Drasil.Units.PhysicalProperties (densityU)
import qualified Data.Drasil.Units.Thermodynamics as UT (heatTransferCoef,
heatCapSpec, thermalFlux, volHtGenU)
import Drasil.SWHS.Concepts (water)
import Control.Lens ((^.))
symbols :: [DefinedQuantityDict]
symbols :: [DefinedQuantityDict]
symbols = DefinedQuantityDict
pi_ DefinedQuantityDict
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. a -> [a] -> [a]
: (UnitalChunk -> DefinedQuantityDict)
-> [UnitalChunk] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [UnitalChunk]
units [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ (DefinedQuantityDict -> DefinedQuantityDict)
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map DefinedQuantityDict -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [DefinedQuantityDict]
unitless [DefinedQuantityDict]
-> [DefinedQuantityDict] -> [DefinedQuantityDict]
forall a. [a] -> [a] -> [a]
++ (ConstrConcept -> DefinedQuantityDict)
-> [ConstrConcept] -> [DefinedQuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr [ConstrConcept]
constrained
symbolsAll :: [QuantityDict]
symbolsAll :: [QuantityDict]
symbolsAll = (DefinedQuantityDict -> QuantityDict)
-> [DefinedQuantityDict] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map DefinedQuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [DefinedQuantityDict]
symbols [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ (ConstQDef -> QuantityDict) -> [ConstQDef] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstQDef -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [ConstQDef]
specParamValList [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++
(ConstQDef -> QuantityDict) -> [ConstQDef] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map ConstQDef -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [ConstQDef
htFusionMin, ConstQDef
htFusionMax, ConstQDef
coilSAMax] [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++
(UncertainChunk -> QuantityDict)
-> [UncertainChunk] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UncertainChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [UncertainChunk
absTol, UncertainChunk
relTol]
units :: [UnitalChunk]
units :: [UnitalChunk]
units = (UnitalChunk -> UnitalChunk) -> [UnitalChunk] -> [UnitalChunk]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> UnitalChunk
forall c. (Unitary c, Concept c, MayHaveUnit c) => c -> UnitalChunk
ucw [UnitalChunk
inSA, UnitalChunk
outSA, UnitalChunk
heatCapSpec, UnitalChunk
htCapL,
UnitalChunk
htCapS, UnitalChunk
htCapV, UnitalChunk
sensHeat, UnitalChunk
pcmInitMltE,
UnitalChunk
volHtGen, UnitalChunk
htTransCoeff, UnitalChunk
pcmMass, UnitalChunk
wMass, UnitalChunk
htFlux, UnitalChunk
latentHeat,
UnitalChunk
thFluxVect, UnitalChunk
htFluxC, UnitalChunk
htFluxIn, UnitalChunk
htFluxOut, UnitalChunk
htFluxP, UnitalChunk
latentEP,
UnitalChunk
temp, UnitalChunk
boilPt, UnitalChunk
tempEnv, UnitalChunk
meltPt, UnitalChunk
tInitMelt,
UnitalChunk
tFinalMelt, UnitalChunk
vol, UnitalChunk
tankVol, UnitalChunk
wVol, UnitalChunk
deltaT,
UnitalChunk
density, UnitalChunk
tau, UnitalChunk
tauLP, UnitalChunk
tauSP, UnitalChunk
tauW, UnitalChunk
thickness] [UnitalChunk] -> [UnitalChunk] -> [UnitalChunk]
forall a. [a] -> [a] -> [a]
++
(UnitalChunk -> UnitalChunk) -> [UnitalChunk] -> [UnitalChunk]
forall a b. (a -> b) -> [a] -> [b]
map UnitalChunk -> UnitalChunk
forall c. (Unitary c, Concept c, MayHaveUnit c) => c -> UnitalChunk
ucw [UnitalChunk
mass, UnitalChunk
time]
unitalChuncks :: [UnitalChunk]
unitalChuncks :: [UnitalChunk]
unitalChuncks = [UnitalChunk
inSA, UnitalChunk
outSA, UnitalChunk
htCapL, UnitalChunk
htCapS, UnitalChunk
htCapV,
UnitalChunk
pcmInitMltE, UnitalChunk
volHtGen, UnitalChunk
htTransCoeff,
UnitalChunk
pcmMass, UnitalChunk
wMass,
UnitalChunk
thFluxVect, UnitalChunk
htFluxC, UnitalChunk
htFluxIn, UnitalChunk
htFluxOut, UnitalChunk
htFluxP, UnitalChunk
latentEP,
UnitalChunk
tempEnv, UnitalChunk
tInitMelt,
UnitalChunk
tFinalMelt, UnitalChunk
tankVol, UnitalChunk
wVol, UnitalChunk
deltaT,
UnitalChunk
tau, UnitalChunk
tauLP, UnitalChunk
tauSP, UnitalChunk
tauW, UnitalChunk
simTime, UnitalChunk
thickness]
inSA, outSA, htCapL, htCapS, htCapV,
pcmInitMltE, volHtGen, htTransCoeff,
pcmMass, wMass,
thFluxVect, htFluxC, htFluxIn, htFluxOut, htFluxP, latentEP,
tempEnv, tInitMelt,
tFinalMelt, tankVol, wVol, deltaT,
tau, tauLP, tauSP, tauW, simTime, thickness:: UnitalChunk
inSA :: UnitalChunk
inSA = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"inSA" (String -> NP
nounPhraseSP
String
"surface area over which heat is transferred in")
(String -> Sentence
S String
"surface area over which thermal energy is transferred into an object")
(Symbol -> Symbol -> Symbol
sub Symbol
cA Symbol
lIn) Space
Real UnitDefn
m_2
outSA :: UnitalChunk
outSA = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"outSA" (String -> NP
nounPhraseSP
String
"surface area over which heat is transferred out")
(String -> Sentence
S String
"surface area over which thermal energy is transferred out of an object")
(Symbol -> Symbol -> Symbol
sub Symbol
cA Symbol
lOut) Space
Real UnitDefn
m_2
htCapL :: UnitalChunk
htCapL = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"htCapL" (String -> NP
nounPhraseSP String
"specific heat capacity of a liquid")
(String -> Sentence
S (String -> Sentence) -> String -> Sentence
forall a b. (a -> b) -> a -> b
$ String
"the amount of energy required to raise the temperature of a given " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"unit mass of a given liquid by a given amount")
(Symbol -> Symbol -> Symbol
sup (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
heatCapSpec) Symbol
lLiquid) Space
Real UnitDefn
UT.heatCapSpec
htCapS :: UnitalChunk
htCapS = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"htCapS"
(String -> NP
nounPhraseSP String
"specific heat capacity of a solid")
(String -> Sentence
S (String -> Sentence) -> String -> Sentence
forall a b. (a -> b) -> a -> b
$ String
"the amount of energy required to raise the temperature of " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"a given unit mass of a given solid by a given amount")
(Symbol -> Symbol -> Symbol
sup (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
heatCapSpec) Symbol
lSolid) Space
Real UnitDefn
UT.heatCapSpec
htCapV :: UnitalChunk
htCapV = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"htCapV"
(String -> NP
nounPhraseSP String
"specific heat capacity of a vapour")
(String -> Sentence
S (String -> Sentence) -> String -> Sentence
forall a b. (a -> b) -> a -> b
$ String
"the amount of energy required to raise the temperature of a given " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"unit mass of vapour by a given amount")
(Symbol -> Symbol -> Symbol
sup (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
heatCapSpec) Symbol
lVapour) Space
Real UnitDefn
UT.heatCapSpec
pcmInitMltE :: UnitalChunk
pcmInitMltE = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"pcmInitMltE" (String -> NP
nounPhraseSP
String
"change in heat energy in the PCM at the instant when melting begins")
(String -> Sentence
S String
"change in thermal energy in the phase change material at the melting point")
(Symbol -> Symbol -> Symbol
sup (Symbol -> Symbol -> Symbol
sub (Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
sensHeat) Symbol
lPCM) Symbol
lMelt) Symbol
lInit) Space
Real UnitDefn
joule
volHtGen :: UnitalChunk
volHtGen = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"volHtGen"
(String -> NP
nounPhraseSP String
"volumetric heat generation per unit volume")
(String -> Sentence
S String
"amount of thermal energy generated per unit volume") Symbol
lG Space
Real UnitDefn
UT.volHtGenU
htTransCoeff :: UnitalChunk
htTransCoeff = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"htTransCoeff"
(String -> NP
nounPhraseSP String
"convective heat transfer coefficient")
(String -> Sentence
S (String -> Sentence) -> String -> Sentence
forall a b. (a -> b) -> a -> b
$ String
"the proportionality constant between the heat flux and the " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"thermodynamic driving force for the flow of thermal energy")
Symbol
lH Space
Real UnitDefn
UT.heatTransferCoef
pcmMass :: UnitalChunk
pcmMass = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"pcmMass" (String -> NP
nounPhraseSP String
"mass of phase change material")
(String -> Sentence
S String
"the quantity of matter within the phase change material")
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
mass) Symbol
lPCM) Space
Real UnitDefn
kilogram
wMass :: UnitalChunk
wMass = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"wMass" (String -> NP
nounPhraseSP String
"mass of water")
(String -> Sentence
S String
"the quantity of matter within the water") (Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
mass) Symbol
lWater) Space
Real UnitDefn
kilogram
thFluxVect :: UnitalChunk
thFluxVect = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"thFluxVect" (String -> NP
nounPhraseSP String
"thermal flux vector")
(String -> Sentence
S String
"vector denoting the direction of thermal flux through a surface")
(Symbol -> Symbol
vec Symbol
lQ) Space
Real UnitDefn
UT.thermalFlux
htFluxC :: UnitalChunk
htFluxC = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"htFluxC"
(String -> NP
nounPhraseSP String
"heat flux into the water from the coil")
(String -> Sentence
S String
"the rate of heat energy transfer into the water from the coil per unit time")
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
htFlux) Symbol
lCoil) Space
Real UnitDefn
UT.thermalFlux
htFluxIn :: UnitalChunk
htFluxIn = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"htFluxIn" (String -> NP
nounPhraseSP String
"heat flux input")
(String -> Sentence
S String
"the rate of heat energy transfer into an object per unit time")
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
htFlux) Symbol
lIn) Space
Real UnitDefn
UT.thermalFlux
htFluxOut :: UnitalChunk
htFluxOut = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"htFluxOut" (String -> NP
nounPhraseSP String
"heat flux output")
(String -> Sentence
S String
"the rate of heat energy transfer into an object per unit time")
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
htFlux) Symbol
lOut) Space
Real UnitDefn
UT.thermalFlux
htFluxP :: UnitalChunk
htFluxP = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"htFluxP" (String -> NP
nounPhraseSP String
"heat flux into the PCM from water")
(String -> Sentence
S (String -> Sentence) -> String -> Sentence
forall a b. (a -> b) -> a -> b
$ String
"the rate of heat energy transfer into the phase" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"change material from the water per unit time")
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
htFlux) Symbol
lPCM) Space
Real UnitDefn
UT.thermalFlux
latentEP :: UnitalChunk
latentEP = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"latentEP" (String -> NP
nounPhraseSP String
"latent heat energy added to PCM")
(String -> Sentence
S (String -> Sentence) -> String -> Sentence
forall a b. (a -> b) -> a -> b
$ String
"energy released or absorbed, by a body or a thermodynamic system, "String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"during a constant-temperature process and absorbed by the phase" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"change material") (Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
latentHeat) Symbol
lPCM) Space
Real UnitDefn
joule
tempEnv :: UnitalChunk
tempEnv = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"tempEnv" (String -> NP
nounPhraseSP String
"temperature of the environment")
(String -> Sentence
S String
"the tempature of a given environment")
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
temp) Symbol
lEnv) Space
Real UnitDefn
centigrade
tInitMelt :: UnitalChunk
tInitMelt = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"tInitMelt"
(String -> NP
nounPhraseSP String
"time at which melting of PCM begins")
(String -> Sentence
S (String -> Sentence) -> String -> Sentence
forall a b. (a -> b) -> a -> b
$ String
"time at which the phase change material " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"begins changing from a solid to a liquid")
(Symbol -> Symbol -> Symbol
sup (Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
time) Symbol
lMelt) Symbol
lInit) Space
Real UnitDefn
second
tFinalMelt :: UnitalChunk
tFinalMelt = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"tFinalMelt"
(String -> NP
nounPhraseSP String
"time at which melting of PCM ends")
(String -> Sentence
S (String -> Sentence) -> String -> Sentence
forall a b. (a -> b) -> a -> b
$ String
"time at which the phase change material " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"finishes changes from a solid to a liquid")
(Symbol -> Symbol -> Symbol
sup (Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
time) Symbol
lMelt) Symbol
lFinal) Space
Real UnitDefn
second
tankVol :: UnitalChunk
tankVol = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"tankVol" (String -> NP
nounPhraseSP String
"volume of the cylindrical tank")
(String -> Sentence
S String
"the amount of space encompassed by a tank")
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
vol) Symbol
lTank) Space
Real UnitDefn
m_3
wVol :: UnitalChunk
wVol = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"wVol" (UnitalChunk
vol UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`of_` ConceptChunk
water)
(String -> Sentence
S String
"the amount of space occupied by a given quantity of water")
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
vol) Symbol
lWater) Space
Real UnitDefn
m_3
deltaT :: UnitalChunk
deltaT = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"deltaT" (String -> NP
nounPhraseSP String
"change in temperature")
(String -> Sentence
S String
"change in the average kinetic energy of a given material")
(Decoration -> Symbol -> Symbol
Atop Decoration
Delta (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
temp) Space
Real UnitDefn
centigrade
tau :: UnitalChunk
tau = String
-> NP
-> Sentence
-> (Stage -> Symbol)
-> Space
-> UnitDefn
-> UnitalChunk
forall u.
IsUnit u =>
String
-> NP -> Sentence -> (Stage -> Symbol) -> Space -> u -> UnitalChunk
ucStaged' String
"tau" (String -> NP
nounPhraseSP String
"dummy variable for integration over time")
(String -> Sentence
S String
"binary value representing the presence or absence of integration over time")
(Symbol -> Stage -> Symbol
autoStage Symbol
lTau) Space
Real UnitDefn
second
tauLP :: UnitalChunk
tauLP = String
-> NP
-> Sentence
-> (Stage -> Symbol)
-> Space
-> UnitDefn
-> UnitalChunk
forall u.
IsUnit u =>
String
-> NP -> Sentence -> (Stage -> Symbol) -> Space -> u -> UnitalChunk
ucStaged' String
"tauLP" (String -> NP
nounPhraseSP String
"ODE parameter for liquid PCM")
(String -> Sentence
S (String -> Sentence) -> String -> Sentence
forall a b. (a -> b) -> a -> b
$ String
"derived through melting of phase change material, which " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"changes ODE parameter for solid PCM into parameter for liquid")
(Symbol -> Stage -> Symbol
autoStage (Symbol -> Stage -> Symbol) -> Symbol -> Stage -> Symbol
forall a b. (a -> b) -> a -> b
$ Symbol -> Symbol -> Symbol
sup (Symbol -> Symbol -> Symbol
sub Symbol
lTau Symbol
lPCM) Symbol
lLiquid) Space
Real UnitDefn
second
tauSP :: UnitalChunk
tauSP = String
-> NP
-> Sentence
-> (Stage -> Symbol)
-> Space
-> UnitDefn
-> UnitalChunk
forall u.
IsUnit u =>
String
-> NP -> Sentence -> (Stage -> Symbol) -> Space -> u -> UnitalChunk
ucStaged' String
"tauSP" (String -> NP
nounPhraseSP String
"ODE parameter for solid PCM")
(String -> Sentence
S String
"derived parameter based on rate of change of temperature of phase change material")
(Symbol -> Stage -> Symbol
autoStage (Symbol -> Stage -> Symbol) -> Symbol -> Stage -> Symbol
forall a b. (a -> b) -> a -> b
$ Symbol -> Symbol -> Symbol
sup (Symbol -> Symbol -> Symbol
sub Symbol
lTau Symbol
lPCM) Symbol
lSolid) Space
Real UnitDefn
second
tauW :: UnitalChunk
tauW = String
-> NP
-> Sentence
-> (Stage -> Symbol)
-> Space
-> UnitDefn
-> UnitalChunk
forall u.
IsUnit u =>
String
-> NP -> Sentence -> (Stage -> Symbol) -> Space -> u -> UnitalChunk
ucStaged' String
"tauW" (String -> NP
nounPhraseSP String
"ODE parameter for water related to decay time")
(String -> Sentence
S String
"derived parameter based on rate of change of temperature of water")
(Symbol -> Stage -> Symbol
autoStage (Symbol -> Stage -> Symbol) -> Symbol -> Stage -> Symbol
forall a b. (a -> b) -> a -> b
$ Symbol -> Symbol -> Symbol
sub Symbol
lTau Symbol
lWater) Space
Real UnitDefn
second
simTime :: UnitalChunk
simTime = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"simTime" (NP -> NP -> NP
compoundPhrase' (IdeaDict
simulation IdeaDict -> Getting NP IdeaDict NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP IdeaDict NP
forall c. NamedIdea c => Lens' c NP
Lens' IdeaDict NP
term)
(UnitalChunk
time UnitalChunk -> Getting NP UnitalChunk NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP UnitalChunk NP
forall c. NamedIdea c => Lens' c NP
Lens' UnitalChunk NP
term)) (String -> Sentence
S String
"time over which the simulation runs")
Symbol
lT Space
Real UnitDefn
second
thickness :: UnitalChunk
thickness = String
-> NP -> Sentence -> Symbol -> Space -> UnitDefn -> UnitalChunk
forall u.
IsUnit u =>
String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk
uc' String
"thickness" (String -> NP
nounPhraseSP String
"Minimum thickness of a sheet of PCM")
(String -> Sentence
S String
"the minimum thickness of a sheet of PCM")
(Symbol -> Symbol
subMin Symbol
lH) Space
Real UnitDefn
metre
unitless :: [DefinedQuantityDict]
unitless :: [DefinedQuantityDict]
unitless = [DefinedQuantityDict
uNormalVect, UnitalChunk -> DefinedQuantityDict
forall c.
(Quantity c, Concept c, MayHaveUnit c) =>
c -> DefinedQuantityDict
dqdWr UnitalChunk
surface, DefinedQuantityDict
eta, DefinedQuantityDict
meltFrac, DefinedQuantityDict
gradient, DefinedQuantityDict
fracMin, DefinedQuantityDict
consTol,
DefinedQuantityDict
aspectRatio, DefinedQuantityDict
aspectRatioMin, DefinedQuantityDict
aspectRatioMax]
eta, meltFrac, fracMin, consTol, aspectRatio, aspectRatioMin, aspectRatioMax :: DefinedQuantityDict
eta :: DefinedQuantityDict
eta = ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
dqd' (String -> NP -> String -> ConceptChunk
dcc String
"eta" (String -> NP
nounPhraseSP String
"ODE parameter related to decay rate")
String
"derived parameter based on rate of change of temperature of water")
(Symbol -> Stage -> Symbol
forall a b. a -> b -> a
const Symbol
lEta) Space
Real Maybe UnitDefn
forall a. Maybe a
Nothing
meltFrac :: DefinedQuantityDict
meltFrac = ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
dqd' (String -> NP -> String -> ConceptChunk
dcc String
"meltFrac" (String -> NP
nounPhraseSP String
"melt fraction")
String
"ratio of thermal energy to amount of mass melted")
(Symbol -> Stage -> Symbol
forall a b. a -> b -> a
const Symbol
lPhi) Space
Real Maybe UnitDefn
forall a. Maybe a
Nothing
fracMin :: DefinedQuantityDict
fracMin = ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
dqd' (String -> NP -> String -> ConceptChunk
dcc String
"fracMin"
(String -> NP
nounPhraseSP String
"minimum fraction of the tank volume taken up by the PCM")
String
"minimum fraction of the tank volume taken up by the PCM")
(Symbol -> Stage -> Symbol
forall a b. a -> b -> a
const (Symbol -> Stage -> Symbol) -> Symbol -> Stage -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
variable String
"MINFRACT") Space
Real Maybe UnitDefn
forall a. Maybe a
Nothing
consTol :: DefinedQuantityDict
consTol = ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
dqd' (String -> NP -> String -> ConceptChunk
dcc String
"consTol"
(String -> NP
nounPhraseSP String
"relative tolerance for conservation of energy")
String
"relative tolerance for conservation of energy")
(Symbol -> Stage -> Symbol
forall a b. a -> b -> a
const (Symbol -> Stage -> Symbol) -> Symbol -> Stage -> Symbol
forall a b. (a -> b) -> a -> b
$ Symbol -> Symbol -> Symbol
sub Symbol
cC Symbol
lTol) Space
Real Maybe UnitDefn
forall a. Maybe a
Nothing
aspectRatio :: DefinedQuantityDict
aspectRatio = ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
dqd' (String -> NP -> String -> ConceptChunk
dcc String
"aspectRatio"
(String -> NP
nounPhraseSP String
"aspect ratio")
String
"ratio of tank diameter to tank length")
(Symbol -> Stage -> Symbol
forall a b. a -> b -> a
const (Symbol -> Stage -> Symbol) -> Symbol -> Stage -> Symbol
forall a b. (a -> b) -> a -> b
$ String -> Symbol
variable String
"AR") Space
Real Maybe UnitDefn
forall a. Maybe a
Nothing
aspectRatioMin :: DefinedQuantityDict
aspectRatioMin = ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
dqd' (String -> NP -> String -> ConceptChunk
dcc String
"aspectRatioMin"
(String -> NP
nounPhraseSP String
"minimum aspect ratio") String
"minimum aspect ratio")
(Symbol -> Stage -> Symbol
forall a b. a -> b -> a
const (Symbol -> Stage -> Symbol) -> Symbol -> Stage -> Symbol
forall a b. (a -> b) -> a -> b
$ Symbol -> Symbol
subMin (DefinedQuantityDict -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb DefinedQuantityDict
aspectRatio)) Space
Real Maybe UnitDefn
forall a. Maybe a
Nothing
aspectRatioMax :: DefinedQuantityDict
aspectRatioMax = ConceptChunk
-> (Stage -> Symbol)
-> Space
-> Maybe UnitDefn
-> DefinedQuantityDict
dqd' (String -> NP -> String -> ConceptChunk
dcc String
"aspectRatioMax"
(String -> NP
nounPhraseSP String
"maximum aspect ratio") String
"maximum aspect ratio")
(Symbol -> Stage -> Symbol
forall a b. a -> b -> a
const (Symbol -> Stage -> Symbol) -> Symbol -> Stage -> Symbol
forall a b. (a -> b) -> a -> b
$ Symbol -> Symbol
subMax (DefinedQuantityDict -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb DefinedQuantityDict
aspectRatio)) Space
Real Maybe UnitDefn
forall a. Maybe a
Nothing
constrained :: [ConstrConcept]
constrained :: [ConstrConcept]
constrained = (UncertQ -> ConstrConcept) -> [UncertQ] -> [ConstrConcept]
forall a b. (a -> b) -> [a] -> [b]
map UncertQ -> ConstrConcept
forall c.
(Quantity c, Concept c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
c -> ConstrConcept
cnstrw' [UncertQ]
inputConstraints [ConstrConcept] -> [ConstrConcept] -> [ConstrConcept]
forall a. [a] -> [a] -> [a]
++ (ConstrConcept -> ConstrConcept)
-> [ConstrConcept] -> [ConstrConcept]
forall a b. (a -> b) -> [a] -> [b]
map ConstrConcept -> ConstrConcept
forall c.
(Quantity c, Concept c, Constrained c, HasReasVal c,
MayHaveUnit c) =>
c -> ConstrConcept
cnstrw' [ConstrConcept]
outputs
inputs :: [QuantityDict]
inputs :: [QuantityDict]
inputs = (UncertQ -> QuantityDict) -> [UncertQ] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UncertQ -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [UncertQ]
inputConstraints [QuantityDict] -> [QuantityDict] -> [QuantityDict]
forall a. [a] -> [a] -> [a]
++ (UncertainChunk -> QuantityDict)
-> [UncertainChunk] -> [QuantityDict]
forall a b. (a -> b) -> [a] -> [b]
map UncertainChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [UncertainChunk
absTol, UncertainChunk
relTol]
inputConstraints :: [UncertQ]
inputConstraints :: [UncertQ]
inputConstraints = [UncertQ
tankLength, UncertQ
diam, UncertQ
pcmVol, UncertQ
pcmSA, UncertQ
pcmDensity,
UncertQ
tempMeltP, UncertQ
htCapSP, UncertQ
htCapLP, UncertQ
htFusion, UncertQ
coilSA, UncertQ
tempC,
UncertQ
wDensity, UncertQ
htCapW, UncertQ
coilHTC, UncertQ
pcmHTC, UncertQ
tempInit, UncertQ
timeStep, UncertQ
timeFinal]
tankLength, diam, pcmVol, pcmSA, pcmDensity, tempMeltP,
htCapSP, htCapLP, htFusion, coilSA, tempC, wDensity,
htCapW, coilHTC, pcmHTC, tempInit, timeStep, timeFinal :: UncertQ
tempPCM, tempW, watE, pcmE :: ConstrConcept
tankLength :: UncertQ
tankLength = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"tankLength" (String -> NP
nounPhraseSP String
"length of tank")
String
"the length of the tank" Symbol
cL UnitDefn
metre Space
Real
[ConstraintE
gtZeroConstr,
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
tankLengthMin) (Inclusive
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
tankLengthMax)] (Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
1.5)
Uncertainty
defaultUncrt
diam :: UncertQ
diam = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"diam" (String -> NP
nounPhraseSP String
"diameter of tank")
String
"the diameter of the tank" Symbol
cD UnitDefn
metre Space
Real
[ConstraintE
gtZeroConstr, RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
arMin) (Inclusive
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
arMax)]
(Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
0.412) Uncertainty
defaultUncrt
pcmVol :: UncertQ
pcmVol = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"pcmVol" (String -> NP
nounPhraseSP String
"volume of PCM")
String
"the amount of space occupied by a given quantity of phase change material"
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
vol) Symbol
lPCM) UnitDefn
m_3 Space
Real
[RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
tankVol),
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Inc, DefinedQuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
fracMin Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
tankVol)]
(Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
0.05) Uncertainty
defaultUncrt
pcmSA :: UncertQ
pcmSA = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"pcmSA"
(NP -> NP -> NP
forall a b. (NounPhrase a, NounPhrase b) => a -> b -> NP
compoundPhrase (Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (String -> Sentence
S String
"phase change material")
(String -> Sentence
S String
"phase change material")
CapitalizationRule
CapFirst CapitalizationRule
CapWords) (Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
surArea) (UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
surArea)
CapitalizationRule
CapFirst CapitalizationRule
CapWords))
String
"area covered by the outermost layer of the phase change material"
(Symbol -> Symbol -> Symbol
sub Symbol
cA Symbol
lPCM) UnitDefn
m_2 Space
Real
[ConstraintE
gtZeroConstr,
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Inc, UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
pcmVol) (Inclusive
Inc, (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
2 Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$/ UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
thickness) Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
tankVol)]
(Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
1.2) Uncertainty
defaultUncrt
pcmDensity :: UncertQ
pcmDensity = ConstrConcept -> Uncertainty -> UncertQ
forall c.
(Quantity c, Constrained c, Concept c, HasReasVal c,
MayHaveUnit c) =>
c -> Uncertainty -> UncertQ
uq (String
-> NP
-> String
-> (Stage -> Symbol)
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
forall u.
IsUnit u =>
String
-> NP
-> String
-> (Stage -> Symbol)
-> u
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
cuc'' String
"pcmDensity" (String -> NP
nounPhraseSP String
"density of PCM")
String
"Mass per unit volume of the phase change material"
(Symbol -> Stage -> Symbol
autoStage (Symbol -> Stage -> Symbol) -> Symbol -> Stage -> Symbol
forall a b. (a -> b) -> a -> b
$ Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
density) Symbol
lPCM) UnitDefn
densityU Space
Real
[ConstraintE
gtZeroConstr, RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
pcmDensityMin) (Inclusive
Exc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
pcmDensityMax)]
(Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1007)) Uncertainty
defaultUncrt
tempMeltP :: UncertQ
tempMeltP = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"tempMeltP"
(String -> NP
nounPhraseSP String
"melting point temperature for PCM")
String
"temperature at which the phase change material transitions from a solid to a liquid"
(Symbol -> Symbol -> Symbol
sup (Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
temp) Symbol
lMelt) Symbol
lPCM) UnitDefn
centigrade Space
Real
[RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempC)] (Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
44.2) Uncertainty
defaultUncrt
htCapSP :: UncertQ
htCapSP = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"htCapSP"
(String -> NP
nounPhraseSP String
"specific heat capacity of PCM as a solid")
(String
"the amount of energy required to raise the temperature of a " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"given unit mass of solid phase change material by a given amount")
(Symbol -> Symbol -> Symbol
sup (Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
heatCapSpec) Symbol
lPCM) Symbol
lSolid) UnitDefn
UT.heatCapSpec Space
Real
[ConstraintE
gtZeroConstr,
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
htCapSPMin) (Inclusive
Exc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
htCapSPMax)]
(Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1760) Uncertainty
defaultUncrt
htCapLP :: UncertQ
htCapLP = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"htCapLP"
(String -> NP
nounPhraseSP String
"specific heat capacity of PCM as a liquid")
(String
"the amount of energy required to raise the temperature of a " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"given unit mass of liquid phase change material by a given amount")
(Symbol -> Symbol -> Symbol
sup (Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
heatCapSpec) Symbol
lPCM) Symbol
lLiquid) UnitDefn
UT.heatCapSpec Space
Real
[ConstraintE
gtZeroConstr,
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
htCapLPMin) (Inclusive
Exc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
htCapLPMax )]
(Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
2270) Uncertainty
defaultUncrt
htFusion :: UncertQ
htFusion = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"htFusion" (String -> NP
nounPhraseSP String
"specific latent heat of fusion")
String
"amount of thermal energy required to completely melt a unit mass of a substance"
(Symbol -> Symbol -> Symbol
sub Symbol
cH Symbol
lFusion) UnitDefn
specificE Space
Real
[ConstraintE
gtZeroConstr,
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
htFusionMin) (Inclusive
Exc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
htFusionMax)] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
211600) Uncertainty
defaultUncrt
coilSA :: UncertQ
coilSA = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"coilSA"
(NP -> NP -> NP
forall a b. (NounPhrase a, NounPhrase b) => a -> b -> NP
compoundPhrase (Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (String -> Sentence
S String
"heating coil") (String -> Sentence
S String
"heating coil") CapitalizationRule
CapFirst CapitalizationRule
CapWords)
(Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
surArea) (UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
surArea) CapitalizationRule
CapFirst CapitalizationRule
CapWords))
String
"area covered by the outermost layer of the coil" (Symbol -> Symbol -> Symbol
sub Symbol
cA Symbol
lCoil) UnitDefn
m_2 Space
Real
[ConstraintE
gtZeroConstr,
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> RealInterval a b
UpTo (Inclusive
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
coilSAMax)] (Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
0.12) Uncertainty
defaultUncrt
tempC :: UncertQ
tempC = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"tempC" (String -> NP
nounPhraseSP String
"temperature of the heating coil")
String
"the average kinetic energy of the particles within the coil"
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
temp) Symbol
lCoil) UnitDefn
centigrade Space
Real
[RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
100)] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
50) Uncertainty
defaultUncrt
wDensity :: UncertQ
wDensity = ConstrConcept -> Uncertainty -> UncertQ
forall c.
(Quantity c, Constrained c, Concept c, HasReasVal c,
MayHaveUnit c) =>
c -> Uncertainty -> UncertQ
uq (String
-> NP
-> String
-> (Stage -> Symbol)
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
forall u.
IsUnit u =>
String
-> NP
-> String
-> (Stage -> Symbol)
-> u
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
cuc'' String
"wDensity" (UnitalChunk
density UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`of_` ConceptChunk
water)
String
"mass per unit volume of water" (Symbol -> Stage -> Symbol
autoStage (Symbol -> Stage -> Symbol) -> Symbol -> Stage -> Symbol
forall a b. (a -> b) -> a -> b
$ Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
density) Symbol
lWater) UnitDefn
densityU Space
Real
[ConstraintE
gtZeroConstr, RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
wDensityMin) (Inclusive
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
wDensityMax)]
(Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1000)) Uncertainty
defaultUncrt
htCapW :: UncertQ
htCapW = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"htCapW" (UnitalChunk
heatCapSpec UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`of_` ConceptChunk
water)
(String
"the amount of energy required to raise the " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"temperature of a given unit mass of water by a given amount")
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
heatCapSpec) Symbol
lWater) UnitDefn
UT.heatCapSpec Space
Real
[ConstraintE
gtZeroConstr,
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
htCapWMin) (Inclusive
Exc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
htCapWMax)] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
4186) Uncertainty
defaultUncrt
coilHTC :: UncertQ
coilHTC = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"coilHTC" (String -> NP
nounPhraseSP
String
"convective heat transfer coefficient between coil and water")
(String
"the convective heat transfer coefficient that models " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"the thermal flux from the coil to the surrounding water")
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
htTransCoeff) Symbol
lCoil)
UnitDefn
UT.heatTransferCoef Space
Real
[ConstraintE
gtZeroConstr,
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
coilHTCMin) (Inclusive
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
coilHTCMax)] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1000) Uncertainty
defaultUncrt
pcmHTC :: UncertQ
pcmHTC = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"pcmHTC"
(String -> NP
nounPhraseSP String
"convective heat transfer coefficient between PCM and water")
(String
"the convective heat transfer coefficient that models " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"the thermal flux from the phase change material to the surrounding water")
(Symbol -> Symbol -> Symbol
sub Symbol
lH Symbol
lPCM) UnitDefn
UT.heatTransferCoef Space
Real
[ConstraintE
gtZeroConstr,
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
pcmHTCMin) (Inclusive
Inc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
pcmHTCMax)] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1000) Uncertainty
defaultUncrt
tempInit :: UncertQ
tempInit = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"tempInit" (String -> NP
nounPhraseSP String
"initial temperature")
String
"the temperature at the beginning of the simulation"
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
temp) Symbol
lInit) UnitDefn
centigrade Space
Real
[RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
meltPt)] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
40) Uncertainty
defaultUncrt
timeFinal :: UncertQ
timeFinal = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"timeFinal" (String -> NP
nounPhraseSP String
"final time")
(String
"the amount of time elapsed from the beginning of the " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"simulation to its conclusion") (Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
time)
Symbol
lFinal) UnitDefn
second Space
Real
[ConstraintE
gtZeroConstr,
RealInterval Expr Expr -> ConstraintE
sfwrRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> RealInterval a b
UpTo (Inclusive
Exc, ConstQDef -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstQDef
timeFinalMax)] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
50000) Uncertainty
defaultUncrt
timeStep :: UncertQ
timeStep = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertQ
uqc String
"timeStep" (String -> NP
nounPhraseSP String
"time step for simulation")
(String
"the finite discretization of time used in the numerical method " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"for solving the computational model")
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
time) Symbol
lStep) UnitDefn
second Space
Real
[RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
timeFinal)]
(Double -> Expr
forall r. LiteralC r => Double -> r
dbl Double
0.01) Uncertainty
defaultUncrt
outputs :: [ConstrConcept]
outputs :: [ConstrConcept]
outputs = [ConstrConcept
tempW, ConstrConcept
tempPCM, ConstrConcept
watE, ConstrConcept
pcmE]
tempW :: ConstrConcept
tempW = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
cuc' String
"tempW"
(String -> NP
nounPhraseSP String
"temperature of the water")
String
"the average kinetic energy of the particles within the water"
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
temp) Symbol
lWater) UnitDefn
centigrade (Space -> Space
Vect Space
Real)
[RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Inc, UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempInit) (Inclusive
Inc, UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempC)] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
tempPCM :: ConstrConcept
tempPCM = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
cuc' String
"tempPCM"
(String -> NP
nounPhraseSP String
"temperature of the phase change material")
String
"the average kinetic energy of the particles within the phase change material"
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
temp) Symbol
lPCM) UnitDefn
centigrade Space
Real
[RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Inc, UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempInit) (Inclusive
Inc, UncertQ -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
tempC)] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
watE :: ConstrConcept
watE = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
cuc' String
"watE" (String -> NP
nounPhraseSP String
"change in heat energy in the water")
String
"change in thermal energy within the water"
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
sensHeat) Symbol
lWater) UnitDefn
joule Space
Real
[RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Inc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
pcmE :: ConstrConcept
pcmE = String
-> NP
-> String
-> Symbol
-> UnitDefn
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
forall u.
IsUnit u =>
String
-> NP
-> String
-> Symbol
-> u
-> Space
-> [ConstraintE]
-> Expr
-> ConstrConcept
cuc' String
"pcmE" (String -> NP
nounPhraseSP String
"change in heat energy in the PCM")
String
"change in thermal energy within the phase change material"
(Symbol -> Symbol -> Symbol
sub (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
sensHeat) Symbol
lPCM) UnitDefn
joule Space
Real
[RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> RealInterval Expr Expr
forall b a. (Inclusive, b) -> RealInterval a b
UpFrom (Inclusive
Inc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)] (Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0)
absTol, relTol :: UncertainChunk
absTol :: UncertainChunk
absTol = String
-> NP
-> Symbol
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertainChunk
uvc String
"absTol" (String -> NP
nounPhraseSP String
"absolute tolerance")
(Symbol -> Symbol -> Symbol
sub Symbol
cA Symbol
lTol) Space
Real
[RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1)]
(Double -> Expr
forall r. LiteralC r => Double -> r
dbl (Double
10.0Double -> Double -> Double
forall a. Floating a => a -> a -> a
**(-Double
10))) (Double -> Maybe Int -> Uncertainty
uncty Double
0.01 Maybe Int
forall a. Maybe a
Nothing)
relTol :: UncertainChunk
relTol = String
-> NP
-> Symbol
-> Space
-> [ConstraintE]
-> Expr
-> Uncertainty
-> UncertainChunk
uvc String
"relTol" (String -> NP
nounPhraseSP String
"relative tolerance")
(Symbol -> Symbol -> Symbol
sub Symbol
cR Symbol
lTol) Space
Real
[RealInterval Expr Expr -> ConstraintE
physRange (RealInterval Expr Expr -> ConstraintE)
-> RealInterval Expr Expr -> ConstraintE
forall a b. (a -> b) -> a -> b
$ (Inclusive, Expr) -> (Inclusive, Expr) -> RealInterval Expr Expr
forall a b. (Inclusive, a) -> (Inclusive, b) -> RealInterval a b
Bounded (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (Inclusive
Exc, Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
1)]
(Double -> Expr
forall r. LiteralC r => Double -> r
dbl (Double
10.0Double -> Double -> Double
forall a. Floating a => a -> a -> a
**(-Double
10))) (Double -> Maybe Int -> Uncertainty
uncty Double
0.01 Maybe Int
forall a. Maybe a
Nothing)
specParamValList :: [ConstQDef]
specParamValList :: [ConstQDef]
specParamValList = [ConstQDef
tankLengthMin, ConstQDef
tankLengthMax, ConstQDef
pcmDensityMin, ConstQDef
pcmDensityMax,
ConstQDef
wDensityMin, ConstQDef
wDensityMax, ConstQDef
htCapSPMin, ConstQDef
htCapSPMax, ConstQDef
htCapLPMin, ConstQDef
htCapLPMax,
ConstQDef
htFusionMin, ConstQDef
htFusionMax, ConstQDef
coilSAMax, ConstQDef
htCapWMin, ConstQDef
htCapWMax, ConstQDef
coilHTCMin,
ConstQDef
coilHTCMax, ConstQDef
pcmHTCMin, ConstQDef
pcmHTCMax, ConstQDef
timeFinalMax, ConstQDef
fracMinAux, ConstQDef
consTolAux,
ConstQDef
arMin, ConstQDef
arMax]
tankLengthMin, tankLengthMax, pcmDensityMin,
pcmDensityMax, wDensityMin, wDensityMax, htCapSPMin, htCapSPMax, htCapLPMin,
htCapLPMax, htFusionMin, htFusionMax, coilSAMax, htCapWMin, htCapWMax,
coilHTCMin, coilHTCMax, pcmHTCMin, pcmHTCMax, timeFinalMax, fracMinAux,
consTolAux, arMin, arMax :: ConstQDef
consTolAux :: ConstQDef
consTolAux = DefinedQuantityDict -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
consTol (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Literal
forall r. LiteralC r => Integer -> Integer -> r
perc Integer
1 Integer
5
tankLengthMin :: ConstQDef
tankLengthMin = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"tankLengthMin"
(String -> NP
nounPhraseSP String
"minimum length of tank")
(Symbol -> Symbol
subMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
tankLength)) UnitDefn
metre Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Double -> Literal
forall r. LiteralC r => Double -> r
dbl Double
0.1
tankLengthMax :: ConstQDef
tankLengthMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"tankLengthMax"
(String -> NP
nounPhraseSP String
"maximum length of tank")
(Symbol -> Symbol
subMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
tankLength)) UnitDefn
metre Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
50
fracMinAux :: ConstQDef
fracMinAux = DefinedQuantityDict -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
fracMin (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Double -> Literal
forall r. LiteralC r => Double -> r
dbl Double
1.0e-6
arMin :: ConstQDef
arMin = DefinedQuantityDict -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
aspectRatioMin (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Double -> Literal
forall r. LiteralC r => Double -> r
dbl Double
0.01
arMax :: ConstQDef
arMax = DefinedQuantityDict -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef DefinedQuantityDict
aspectRatioMax (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
100
pcmDensityMin :: ConstQDef
pcmDensityMin = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String
-> NP -> (Stage -> Symbol) -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> (Stage -> Symbol) -> u -> Space -> UnitaryChunk
unitary' String
"pcmDensityMin"
(String -> NP
nounPhraseSP String
"minimum density of PCM") (Symbol -> Symbol -> Stage -> Symbol
staged (Symbol -> Symbol
supMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
pcmDensity))
(Symbol -> Symbol
subMin (Symbol -> Symbol
unicodeConv (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
pcmDensity))) UnitDefn
densityU Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
500
pcmDensityMax :: ConstQDef
pcmDensityMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String
-> NP -> (Stage -> Symbol) -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> (Stage -> Symbol) -> u -> Space -> UnitaryChunk
unitary' String
"pcmDensityMax"
(String -> NP
nounPhraseSP String
"maximum density of PCM") (Symbol -> Symbol -> Stage -> Symbol
staged (Symbol -> Symbol
supMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
pcmDensity))
(Symbol -> Symbol
subMax (Symbol -> Symbol
unicodeConv (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
pcmDensity))) UnitDefn
densityU Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
20000
htCapSPMin :: ConstQDef
htCapSPMin = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"htCapSPMin"
(String -> NP
nounPhraseSP String
"minimum specific heat capacity of PCM as a solid")
(Symbol -> Symbol
subMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
htCapSP)) UnitDefn
UT.heatCapSpec Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
100
htCapSPMax :: ConstQDef
htCapSPMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"htCapSPMax"
(String -> NP
nounPhraseSP String
"maximum specific heat capacity of PCM as a solid")
(Symbol -> Symbol
subMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
htCapSP)) UnitDefn
UT.heatCapSpec Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
4000
htCapLPMin :: ConstQDef
htCapLPMin = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"htCapLPMin"
(String -> NP
nounPhraseSP String
"minimum specific heat capacity of PCM as a liquid")
(Symbol -> Symbol
subMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
htCapLP)) UnitDefn
UT.heatCapSpec Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
100
htCapLPMax :: ConstQDef
htCapLPMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"htCapLPMax"
(String -> NP
nounPhraseSP String
"maximum specific heat capacity of PCM as a liquid")
(Symbol -> Symbol
subMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
htCapLP)) UnitDefn
UT.heatCapSpec Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
5000
htFusionMin :: ConstQDef
htFusionMin = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"htFusionMin"
(String -> NP
nounPhraseSP String
"minimum specific latent heat of fusion")
(Symbol -> Symbol
subMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
htFusion)) UnitDefn
UT.heatCapSpec Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
0
htFusionMax :: ConstQDef
htFusionMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String -> NP -> Symbol -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> Symbol -> u -> Space -> UnitaryChunk
unitary String
"htFusionMax"
(String -> NP
nounPhraseSP String
"maximum specific latent heat of fusion")
(Symbol -> Symbol
subMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
htFusion)) UnitDefn
UT.heatCapSpec Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
1000000
coilSAMax :: ConstQDef
coilSAMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String
-> NP -> (Stage -> Symbol) -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> (Stage -> Symbol) -> u -> Space -> UnitaryChunk
unitary' String
"coilSAMax"
(String -> NP
nounPhraseSP String
"maximum surface area of coil") (Symbol -> Symbol -> Stage -> Symbol
staged (Symbol -> Symbol
supMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
coilSA))
(Symbol -> Symbol
subMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
coilSA))) UnitDefn
m_2 Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
100000
wDensityMin :: ConstQDef
wDensityMin = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String
-> NP -> (Stage -> Symbol) -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> (Stage -> Symbol) -> u -> Space -> UnitaryChunk
unitary' String
"wDensityMin"
(String -> NP
nounPhraseSP String
"minimum density of water") (Symbol -> Symbol -> Stage -> Symbol
staged (Symbol -> Symbol
supMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
wDensity))
(Symbol -> Symbol
subMin (Symbol -> Symbol
unicodeConv (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
wDensity))) UnitDefn
densityU Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
950
wDensityMax :: ConstQDef
wDensityMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String
-> NP -> (Stage -> Symbol) -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> (Stage -> Symbol) -> u -> Space -> UnitaryChunk
unitary' String
"wDensityMax"
(String -> NP
nounPhraseSP String
"maximum density of water") (Symbol -> Symbol -> Stage -> Symbol
staged (Symbol -> Symbol
supMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
wDensity))
(Symbol -> Symbol
subMax (Symbol -> Symbol
unicodeConv (Symbol -> Symbol) -> Symbol -> Symbol
forall a b. (a -> b) -> a -> b
$ UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
wDensity))) UnitDefn
densityU Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
1000
htCapWMin :: ConstQDef
htCapWMin = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String
-> NP -> (Stage -> Symbol) -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> (Stage -> Symbol) -> u -> Space -> UnitaryChunk
unitary' String
"htCapWMin"
(String -> NP
nounPhraseSP String
"minimum specific heat capacity of water")
(Symbol -> Symbol -> Stage -> Symbol
staged (Symbol -> Symbol
supMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
htCapW)) (Symbol -> Symbol
subMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
htCapW))) UnitDefn
UT.heatCapSpec
Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
4170
htCapWMax :: ConstQDef
htCapWMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String
-> NP -> (Stage -> Symbol) -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> (Stage -> Symbol) -> u -> Space -> UnitaryChunk
unitary' String
"htCapWMax"
(String -> NP
nounPhraseSP String
"maximum specific heat capacity of water")
(Symbol -> Symbol -> Stage -> Symbol
staged (Symbol -> Symbol
supMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
htCapW)) (Symbol -> Symbol
subMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
htCapW))) UnitDefn
UT.heatCapSpec
Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
4210
coilHTCMin :: ConstQDef
coilHTCMin = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String
-> NP -> (Stage -> Symbol) -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> (Stage -> Symbol) -> u -> Space -> UnitaryChunk
unitary' String
"coilHTCMin"
(String -> NP
nounPhraseSP (String -> NP) -> String -> NP
forall a b. (a -> b) -> a -> b
$ String
"minimum convective heat " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"transfer coefficient between coil and water")
(Symbol -> Symbol -> Stage -> Symbol
staged (Symbol -> Symbol
supMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
coilHTC)) (Symbol -> Symbol
subMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
coilHTC)))
UnitDefn
UT.heatTransferCoef Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
10
coilHTCMax :: ConstQDef
coilHTCMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String
-> NP -> (Stage -> Symbol) -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> (Stage -> Symbol) -> u -> Space -> UnitaryChunk
unitary' String
"coilHTCMax"
(String -> NP
nounPhraseSP (String -> NP) -> String -> NP
forall a b. (a -> b) -> a -> b
$ String
"maximum convective heat " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"transfer coefficient between coil and water")
(Symbol -> Symbol -> Stage -> Symbol
staged (Symbol -> Symbol
supMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
coilHTC)) (Symbol -> Symbol
subMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
coilHTC)))
UnitDefn
UT.heatTransferCoef Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
10000
pcmHTCMin :: ConstQDef
pcmHTCMin = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String
-> NP -> (Stage -> Symbol) -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> (Stage -> Symbol) -> u -> Space -> UnitaryChunk
unitary' String
"pcmHTCMin"
(String -> NP
nounPhraseSP (String -> NP) -> String -> NP
forall a b. (a -> b) -> a -> b
$ String
"minimum convective heat " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"transfer coefficient between PCM and water")
(Symbol -> Symbol -> Stage -> Symbol
staged (Symbol -> Symbol
supMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
pcmHTC)) (Symbol -> Symbol
subMin (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
pcmHTC)))
UnitDefn
UT.heatTransferCoef Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
10
pcmHTCMax :: ConstQDef
pcmHTCMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String
-> NP -> (Stage -> Symbol) -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> (Stage -> Symbol) -> u -> Space -> UnitaryChunk
unitary' String
"pcmHTCMax"
(String -> NP
nounPhraseSP (String -> NP) -> String -> NP
forall a b. (a -> b) -> a -> b
$ String
"maximum convective heat " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"transfer coefficient between PCM and water")
(Symbol -> Symbol -> Stage -> Symbol
staged (Symbol -> Symbol
supMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
pcmHTC)) (Symbol -> Symbol
subMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
pcmHTC)))
UnitDefn
UT.heatTransferCoef Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
10000
timeFinalMax :: ConstQDef
timeFinalMax = UnitaryChunk -> Literal -> ConstQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef (String
-> NP -> (Stage -> Symbol) -> UnitDefn -> Space -> UnitaryChunk
forall u.
IsUnit u =>
String -> NP -> (Stage -> Symbol) -> u -> Space -> UnitaryChunk
unitary' String
"timeFinalMax"
(String -> NP
nounPhraseSP String
"maximum final time")
(Symbol -> Symbol -> Stage -> Symbol
staged (Symbol -> Symbol
supMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
timeFinal)) (Symbol -> Symbol
subMax (UncertQ -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UncertQ
timeFinal))) UnitDefn
second
Space
Real) (Literal -> ConstQDef) -> Literal -> ConstQDef
forall a b. (a -> b) -> a -> b
$ Integer -> Literal
forall r. LiteralC r => Integer -> r
exactDbl Integer
86400
lCoil, lEnv, lFinal, lFusion, lIn, lInit, lLiquid, lMelt, lOut, lPCM, lSolid,
lStep, lTank, lTol, lVapour, lWater :: Symbol
lCoil :: Symbol
lCoil = String -> Symbol
label String
"C"
lEnv :: Symbol
lEnv = String -> Symbol
label String
"env"
lFinal :: Symbol
lFinal = String -> Symbol
label String
"final"
lFusion :: Symbol
lFusion = String -> Symbol
label String
"f"
lIn :: Symbol
lIn = String -> Symbol
label String
"in"
lInit :: Symbol
lInit = String -> Symbol
label String
"init"
lLiquid :: Symbol
lLiquid = String -> Symbol
label String
"L"
lMelt :: Symbol
lMelt = String -> Symbol
label String
"melt"
lOut :: Symbol
lOut = String -> Symbol
label String
"out"
lPCM :: Symbol
lPCM = String -> Symbol
label String
"P"
lSolid :: Symbol
lSolid = String -> Symbol
label String
"S"
lStep :: Symbol
lStep = String -> Symbol
label String
"step"
lTank :: Symbol
lTank = String -> Symbol
label String
"tank"
lTol :: Symbol
lTol = String -> Symbol
label String
"tol"
lVapour :: Symbol
lVapour = String -> Symbol
label String
"V"
lWater :: Symbol
lWater = String -> Symbol
label String
"W"