{-# LANGUAGE PostfixOperators #-}
module Drasil.SWHS.TMods (PhaseChange(Liquid), consThermE, latentHtE,
nwtnCooling, sensHtE, sensHtETemplate, tMods) where
import qualified Data.List.NonEmpty as NE
import Language.Drasil
import Control.Lens ((^.))
import Theory.Drasil (ConstraintSet, mkConstraintSet,
TheoryModel, tm, equationalModel', equationalConstraints',
ModelKind, equationalModel)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.Concepts.Documentation (system)
import Data.Drasil.Concepts.Math (equation, rate, rOfChng)
import Data.Drasil.Concepts.Physics (mechEnergy)
import Data.Drasil.Concepts.Thermodynamics (heatTrans, lawConsEnergy,
lawConvCooling, phaseChange, thermalEnergy)
import Data.Drasil.Quantities.Math (gradient)
import Data.Drasil.Quantities.PhysicalProperties (density, mass)
import Data.Drasil.Quantities.Physics (energy, time)
import Data.Drasil.Quantities.Thermodynamics (boilPt, heatCapSpec,
htFlux, latentHeat, meltPt, sensHeat, temp)
import Drasil.SWHS.Assumptions (assumpHTCC, assumpTEO)
import Drasil.SWHS.Concepts (transient)
import Drasil.SWHS.DataDefs (ddMeltFrac)
import Drasil.SWHS.References (incroperaEtAl2007)
import Drasil.SWHS.Unitals (deltaT, htCapL, htCapS, htCapV, htTransCoeff,
meltFrac, tau, tempEnv, thFluxVect, volHtGen)
tMods :: [TheoryModel]
tMods :: [TheoryModel]
tMods = [TheoryModel
consThermE, TheoryModel
sensHtE, TheoryModel
latentHtE, TheoryModel
nwtnCooling]
consThermE :: TheoryModel
consThermE :: TheoryModel
consThermE = ModelKind ModelExpr
-> [QuantityDict]
-> [ConceptChunk]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> [DecRef]
-> String
-> [Sentence]
-> TheoryModel
forall q c.
(Quantity q, MayHaveUnit q, Concept c) =>
ModelKind ModelExpr
-> [q]
-> [c]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> [DecRef]
-> String
-> [Sentence]
-> TheoryModel
tm (ConstraintSet ModelExpr -> ModelKind ModelExpr
forall e. ConstraintSet e -> ModelKind e
equationalConstraints' ConstraintSet ModelExpr
consThermECS)
[UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
thFluxVect, DefinedQuantityDict -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw DefinedQuantityDict
gradient, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
volHtGen,
UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
density, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
heatCapSpec, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
temp, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
time] ([] :: [ConceptChunk])
[] [ModelExpr -> ModelExpr
forall c. Express c => c -> ModelExpr
express ModelExpr
consThermERel] [] [Reference -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Reference
consThemESrc] String
"consThermE" [Sentence]
consThermENotes
consThermECS :: ConstraintSet ModelExpr
consThermECS :: ConstraintSet ModelExpr
consThermECS = ConceptChunk -> NonEmpty ModelExpr -> ConstraintSet ModelExpr
forall e. ConceptChunk -> NonEmpty e -> ConstraintSet e
mkConstraintSet ConceptChunk
consCC NonEmpty ModelExpr
rels
where consCC :: ConceptChunk
consCC = String -> NP -> Sentence -> ConceptChunk
dccWDS String
"consThermECS"
(String -> NP
nounPhraseSP String
"Conservation of thermal energy") (ConceptChunk
lawConsEnergy ConceptChunk -> Getting Sentence ConceptChunk Sentence -> Sentence
forall s a. s -> Getting a s a -> a
^. Getting Sentence ConceptChunk Sentence
forall c. Definition c => Lens' c Sentence
Lens' ConceptChunk Sentence
defn)
rels :: NonEmpty ModelExpr
rels = [ModelExpr] -> NonEmpty ModelExpr
forall a. HasCallStack => [a] -> NonEmpty a
NE.fromList [ModelExpr
consThermERel]
consThermERel :: ModelExpr
consThermERel :: ModelExpr
consThermERel = ModelExpr -> ModelExpr
forall r. ExprC r => r -> r
negVec (DefinedQuantityDict -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
gradient) 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
thFluxVect 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
volHtGen 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
density 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
heatCapSpec ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$* ModelExpr -> UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => ModelExpr -> c -> ModelExpr
forall r c. (ModelExprC r, HasUID c, HasSymbol c) => r -> c -> r
pderiv (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
temp) UnitalChunk
time
consThemESrc :: Reference
consThemESrc :: Reference
consThemESrc = String -> String -> ShortName -> Reference
makeURI String
"consThemESrc"
String
"http://www.efunda.com/formulae/heat_transfer/conduction/overview_cond.cfm" (ShortName -> Reference) -> ShortName -> Reference
forall a b. (a -> b) -> a -> b
$
Sentence -> ShortName
shortname' (Sentence -> ShortName) -> Sentence -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"Fourier Law of Heat Conduction and Heat Equation"
consThermENotes :: [Sentence]
consThermENotes :: [Sentence]
consThermENotes = ([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, String -> Sentence
S String
"gives the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
lawConsEnergy,
String -> Sentence
S String
"for", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
transient, ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
heatTrans, String -> Sentence
S String
"in a given material"],
[String -> Sentence
S String
"For this", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation, String -> Sentence
S String
"to apply" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"other forms" Sentence -> Sentence -> Sentence
`S.of_`
UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
energy Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"such as", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
mechEnergy Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"are assumed",
String -> Sentence
S String
"to be negligible" Sentence -> Sentence -> Sentence
`S.inThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
system, Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpTEO)]]
sensHtE :: TheoryModel
sensHtE :: TheoryModel
sensHtE = PhaseChange -> Sentence -> TheoryModel
sensHtETemplate PhaseChange
AllPhases Sentence
sensHtEdesc
data PhaseChange = AllPhases
| Liquid
sensHtETemplate :: PhaseChange -> Sentence -> TheoryModel
sensHtETemplate :: PhaseChange -> Sentence -> TheoryModel
sensHtETemplate PhaseChange
pc Sentence
desc = ModelKind ModelExpr
-> [QuantityDict]
-> [ConceptChunk]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> [DecRef]
-> String
-> [Sentence]
-> TheoryModel
forall q c.
(Quantity q, MayHaveUnit q, Concept c) =>
ModelKind ModelExpr
-> [q]
-> [c]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> [DecRef]
-> String
-> [Sentence]
-> TheoryModel
tm (ModelQDef -> ModelKind ModelExpr
forall e. QDefinition e -> ModelKind e
equationalModel' ModelQDef
qd)
[UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
sensHeat, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
htCapS, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
mass,
UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
deltaT, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
meltPt, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
temp, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
htCapL, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
boilPt, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
htCapV] ([] :: [ConceptChunk])
[ModelQDef
qd] [] [] [Reference -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Reference
sensHtESrc] String
"sensHtE" [Sentence
desc]
where
qd :: ModelQDef
qd = PhaseChange -> ModelExpr -> Sentence -> ModelQDef
sensHtEQD PhaseChange
pc ModelExpr
eqn Sentence
desc
eqn :: ModelExpr
eqn = PhaseChange -> ModelExpr
sensHtEEqn PhaseChange
pc
sensHtEQD :: PhaseChange -> ModelExpr -> Sentence -> ModelQDef
sensHtEQD :: PhaseChange -> ModelExpr -> Sentence -> ModelQDef
sensHtEQD PhaseChange
pc ModelExpr
eqn Sentence
desc = String
-> NP
-> Sentence
-> (Stage -> Symbol)
-> Space
-> ModelExpr
-> ModelQDef
forall e.
String
-> NP
-> Sentence
-> (Stage -> Symbol)
-> Space
-> e
-> QDefinition e
fromEqnSt'' String
"sensHeat" NP
np Sentence
desc (UnitalChunk -> Stage -> Symbol
forall c. HasSymbol c => c -> Stage -> Symbol
symbol UnitalChunk
sensHeat) (UnitalChunk
sensHeat UnitalChunk -> Getting Space UnitalChunk Space -> Space
forall s a. s -> Getting a s a -> a
^. Getting Space UnitalChunk Space
forall c. HasSpace c => Getter c Space
Getter UnitalChunk Space
typ) ModelExpr
eqn
where np :: NP
np = String -> NP
nounPhraseSP (String
"Sensible heat energy" String -> String -> String
forall a. [a] -> [a] -> [a]
++ case PhaseChange
pc of
PhaseChange
Liquid -> String
" (no state change)"
PhaseChange
AllPhases -> String
"")
sensHtESrc :: Reference
sensHtESrc :: Reference
sensHtESrc = String -> String -> ShortName -> Reference
makeURI String
"sensHtESrc"
String
"http://en.wikipedia.org/wiki/Sensible_heat" (ShortName -> Reference) -> ShortName -> Reference
forall a b. (a -> b) -> a -> b
$
Sentence -> ShortName
shortname' (Sentence -> ShortName) -> Sentence -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"Definition of Sensible Heat"
sensHtEEqn :: PhaseChange -> ModelExpr
sensHtEEqn :: PhaseChange -> ModelExpr
sensHtEEqn PhaseChange
pChange = case PhaseChange
pChange of
PhaseChange
Liquid -> ModelExpr
liquidFormula
PhaseChange
AllPhases -> [(ModelExpr, ModelExpr)] -> ModelExpr
forall r. ExprC r => [(r, r)] -> r
incompleteCase [(UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
htCapS 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
mass 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
deltaT,
UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
temp 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
meltPt), (ModelExpr
liquidFormula, UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
meltPt 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
temp 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
boilPt), (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
htCapV 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
mass 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
deltaT, UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
boilPt 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
temp)]
where
liquidFormula :: ModelExpr
liquidFormula = UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
htCapL 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
mass 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
deltaT
sensHtEdesc :: Sentence
sensHtEdesc :: Sentence
sensHtEdesc = [Sentence] -> Sentence
foldlSent [
UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart UnitalChunk
sensHeat Sentence -> Sentence -> Sentence
:+: String -> Sentence
S String
"ing occurs as long as the material does not reach a",
UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
temp, String -> Sentence
S String
"where a", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
phaseChange, (String -> Sentence
S String
"occurs" !.), NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall c. NamedIdea c => c -> NP
a_ ConceptChunk
phaseChange),
String -> Sentence
S String
"occurs if" Sentence -> Sentence -> Sentence
+:+. (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
temp 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
boilPt) Sentence -> Sentence -> Sentence
`S.or_` 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
temp 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
meltPt)),
String -> Sentence
S String
"If this is the case" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"refer to", TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
latentHtE]
latentHtE :: TheoryModel
latentHtE :: TheoryModel
latentHtE = ModelKind ModelExpr
-> [QuantityDict]
-> [ConceptChunk]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> [DecRef]
-> String
-> [Sentence]
-> TheoryModel
forall q c.
(Quantity q, MayHaveUnit q, Concept c) =>
ModelKind ModelExpr
-> [q]
-> [c]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> [DecRef]
-> String
-> [Sentence]
-> TheoryModel
tm ModelKind ModelExpr
latentHtEMK
[UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
latentHeat, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
time, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
tau] ([] :: [ConceptChunk])
[] [ModelQDef -> ModelExpr
forall c. Express c => c -> ModelExpr
express ModelQDef
latentHtEFD] [] [Reference -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Reference
latHtESrc] String
"latentHtE" [Sentence]
latentHtENotes
latentHtEMK :: ModelKind ModelExpr
latentHtEMK :: ModelKind ModelExpr
latentHtEMK = String -> NP -> ModelQDef -> ModelKind ModelExpr
forall e. String -> NP -> QDefinition e -> ModelKind e
equationalModel String
"latentHtETM"
(String -> NP
nounPhraseSP String
"Latent heat energy") ModelQDef
latentHtEFD
latentHtEFD :: ModelQDef
latentHtEFD :: ModelQDef
latentHtEFD = UnitalChunk -> [UnitalChunk] -> ModelExpr -> ModelQDef
forall c i e.
(Quantity c, MayHaveUnit c, HasSpace c, Quantity i, HasSpace i) =>
c -> [i] -> e -> QDefinition e
mkFuncDefByQ UnitalChunk
latentHeat [UnitalChunk
time] ModelExpr
latentHtEExpr
latentHtEExpr :: ModelExpr
latentHtEExpr :: ModelExpr
latentHtEExpr = Symbol -> ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => Symbol -> r -> r -> r -> r
defint (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
tau) (Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
time) (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 (UnitalChunk -> UnitalChunk -> ModelExpr
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
latentHeat UnitalChunk
tau) UnitalChunk
tau)
latHtESrc :: Reference
latHtESrc :: Reference
latHtESrc = String -> String -> ShortName -> Reference
makeURI String
"latHtESrc" String
"http://en.wikipedia.org/wiki/Latent_heat" (ShortName -> Reference) -> ShortName -> Reference
forall a b. (a -> b) -> a -> b
$
Sentence -> ShortName
shortname' (Sentence -> ShortName) -> Sentence -> ShortName
forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
"Definition of Latent Heat"
latentHtENotes :: [Sentence]
latentHtENotes :: [Sentence]
latentHtENotes = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent [
[UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
latentHeat Sentence -> Sentence -> Sentence
`S.isThe` String -> Sentence
S String
"change" Sentence -> Sentence -> Sentence
`S.in_` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
thermalEnergy,
Sentence -> Sentence
sParen (UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
latentHeat Sentence -> Sentence -> Sentence
+:+ UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
energy)],
[ModelQDef -> Sentence
forall t. Express t => t -> Sentence
eS' ModelQDef
latentHtEFD Sentence -> Sentence -> Sentence
`S.isThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
rOfChng Sentence -> Sentence -> Sentence
`S.of_` UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
latentHeat Sentence -> Sentence -> Sentence
`S.wrt`
UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
time, UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
tau],
[UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
time Sentence -> Sentence -> Sentence
`S.isThe` UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
time, String -> Sentence
S String
"elapsed" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"as long as the",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
phaseChange, String -> Sentence
S String
"is not complete"],
[String -> Sentence
S String
"status" Sentence -> Sentence -> Sentence
`S.the_ofTheC` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
phaseChange, String -> Sentence
S String
"depends on the",
DefinedQuantityDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase DefinedQuantityDict
meltFrac, Sentence -> Sentence
sParen (String -> Sentence
S String
"from" Sentence -> Sentence -> Sentence
+:+ DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
ddMeltFrac)],
[UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart UnitalChunk
latentHeat Sentence -> Sentence -> Sentence
:+: String -> Sentence
S String
"ing stops when all material has changed to the new phase"]]
nwtnCooling :: TheoryModel
nwtnCooling :: TheoryModel
nwtnCooling = ModelKind ModelExpr
-> [QuantityDict]
-> [ConceptChunk]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> [DecRef]
-> String
-> [Sentence]
-> TheoryModel
forall q c.
(Quantity q, MayHaveUnit q, Concept c) =>
ModelKind ModelExpr
-> [q]
-> [c]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> [DecRef]
-> String
-> [Sentence]
-> TheoryModel
tm ModelKind ModelExpr
nwtnCoolingMK
[UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
latentHeat, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
time, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
htTransCoeff, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
deltaT] ([] :: [ConceptChunk])
[] [ModelQDef -> ModelExpr
forall c. Express c => c -> ModelExpr
express ModelQDef
nwtnCoolingFD] [] [Citation -> RefInfo -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> RefInfo -> DecRef
dRefInfo Citation
incroperaEtAl2007 (RefInfo -> DecRef) -> RefInfo -> DecRef
forall a b. (a -> b) -> a -> b
$ [Int] -> RefInfo
Page [Int
8]]
String
"nwtnCooling" [Sentence]
nwtnCoolingNotes
nwtnCoolingMK :: ModelKind ModelExpr
nwtnCoolingMK :: ModelKind ModelExpr
nwtnCoolingMK = String -> NP -> ModelQDef -> ModelKind ModelExpr
forall e. String -> NP -> QDefinition e -> ModelKind e
equationalModel String
"nwtnCoolingTM"
(String -> NP
nounPhraseSP String
"Newton's law of cooling") ModelQDef
nwtnCoolingFD
nwtnCoolingFD :: ModelQDef
nwtnCoolingFD :: ModelQDef
nwtnCoolingFD = UnitalChunk -> [UnitalChunk] -> ModelExpr -> ModelQDef
forall c i e.
(Quantity c, MayHaveUnit c, HasSpace c, Quantity i, HasSpace i) =>
c -> [i] -> e -> QDefinition e
mkFuncDefByQ UnitalChunk
htFlux [UnitalChunk
time] ModelExpr
nwtnCoolingExpr
nwtnCoolingExpr :: ModelExpr
nwtnCoolingExpr :: ModelExpr
nwtnCoolingExpr = UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
htTransCoeff ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> UnitalChunk -> ModelExpr
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
deltaT UnitalChunk
time
nwtnCoolingNotes :: [Sentence]
nwtnCoolingNotes :: [Sentence]
nwtnCoolingNotes = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSent [
[ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart ConceptChunk
lawConvCooling Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"describes convective cooling from a surface" Sentence -> Sentence -> Sentence
+:
String -> Sentence
S String
"The law is stated as", String -> Sentence
S String
"the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
rate Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"heat loss from a body" Sentence -> Sentence -> Sentence
`S.is`
String -> Sentence
S String
"proportional to the difference in", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
temp, String -> Sentence
S String
"between the body and its surroundings"],
[UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
htTransCoeff, String -> Sentence
S String
"is assumed to be independent" Sentence -> Sentence -> Sentence
`S.of_` UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
temp,
Sentence -> Sentence
sParen (String -> Sentence
S String
"from" Sentence -> Sentence -> Sentence
+:+ ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpHTCC)],
[ModelExpr -> Sentence
E (ModelExpr -> ModelExpr -> ModelExpr
forall r. ModelExprC r => r -> r -> r
defines (UnitalChunk -> UnitalChunk -> ModelExpr
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
deltaT UnitalChunk
time) (UnitalChunk -> UnitalChunk -> ModelExpr
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
temp UnitalChunk
time ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> UnitalChunk -> ModelExpr
forall r f a.
(ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) =>
f -> a -> r
apply1 UnitalChunk
tempEnv UnitalChunk
time)) Sentence -> Sentence -> Sentence
`S.isThe`
String -> Sentence
S String
"time-dependant thermal gradient between the environment and the object"]]