module Data.Drasil.Theories.Physics where
import Language.Drasil
import Utils.Drasil (weave)
import Theory.Drasil
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.Citations (velocityWiki, accelerationWiki)
import Data.Drasil.Concepts.Documentation (component, material_, value, constant)
import Data.Drasil.Concepts.Math (cartesian, equation, vector)
import Data.Drasil.Concepts.Physics (gravity, twoD, rigidBody)
import qualified Data.Drasil.Quantities.PhysicalProperties as QPP (density,
mass, specWeight, vol)
import qualified Data.Drasil.Quantities.Physics as QP (acceleration, velocity, position,
force, gravitationalAccel, pressure, torque, weight, positionVec, time, momentOfInertia,
angularAccel, speed)
import Data.Drasil.Equations.Defining.Physics
import Data.Drasil.Equations.Defining.Derivations
physicsTMs :: [TheoryModel]
physicsTMs :: [TheoryModel]
physicsTMs = [TheoryModel
newtonSL]
newtonSL :: TheoryModel
newtonSL :: TheoryModel
newtonSL = ModelKind ModelExpr
-> [QuantityDict]
-> [ConceptChunk]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> String
-> [Sentence]
-> TheoryModel
forall q c.
(Quantity q, MayHaveUnit q, Concept c) =>
ModelKind ModelExpr
-> [q]
-> [c]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> String
-> [Sentence]
-> TheoryModel
tmNoRefs (String -> ModelQDef -> ModelKind ModelExpr
forall e. String -> QDefinition e -> ModelKind e
equationalModelU String
"newtonSL" ModelQDef
newtonSLQD)
[UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
QP.force, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
QPP.mass, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
QP.acceleration] ([] :: [ConceptChunk])
[ModelQDef
newtonSLQD] [] [] String
"NewtonSecLawMot" [Sentence
newtonSLDesc]
weightGD :: GenDefn
weightGD :: GenDefn
weightGD = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd (ModelQDef -> ModelKind ModelExpr
forall e. QDefinition e -> ModelKind e
equationalModel' ModelQDef
weightQD) (UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
QP.weight) (Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
weightDeriv) [Reference -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Reference
weightSrc]
String
"weight" []
weightQD :: ModelQDef
weightQD :: ModelQDef
weightQD = UnitalChunk -> NP -> ModelExpr -> ModelQDef
forall c e.
(Quantity c, MayHaveUnit c) =>
c -> NP -> e -> QDefinition e
mkQuantDef' UnitalChunk
QP.weight (String -> NP
nounPhraseSP String
"weight") ModelExpr
forall r. ExprC r => r
weightEqn
weightSrc :: Reference
weightSrc :: Reference
weightSrc = String -> String -> ShortName -> Reference
makeURI String
"weightSrc" String
"https://en.wikipedia.org/wiki/Weight" (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 Weight"
weightDeriv :: Derivation
weightDeriv :: Derivation
weightDeriv = Sentence -> [Sentence] -> Derivation
mkDerivName (UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.weight) ([Sentence] -> Derivation) -> [Sentence] -> Derivation
forall a b. (a -> b) -> a -> b
$ [[Sentence]] -> [Sentence]
forall a. [[a]] -> [a]
weave [[Sentence]
weightDerivSentences, [Sentence]
weightDerivEqns]
weightDerivSentences, weightDerivEqns :: [Sentence]
weightDerivSentences :: [Sentence]
weightDerivSentences = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSentCol [[Sentence]
weightDerivAccelSentence,
[Sentence]
weightDerivNewtonSentence, [Sentence]
weightDerivReplaceMassSentence,
[Sentence]
weightDerivSpecWeightSentence]
weightDerivEqns :: [Sentence]
weightDerivEqns = (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr
weightDerivAccelEqn, ModelExpr
weightDerivNewtonEqn,
ModelExpr
weightDerivReplaceMassEqn, ModelExpr
weightDerivSpecWeightEqn]
weightDerivAccelSentence :: [Sentence]
weightDerivAccelSentence :: [Sentence]
weightDerivAccelSentence = [String -> Sentence
S String
"Under the influence" Sentence -> Sentence -> Sentence
`S.of_` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
gravity Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"and assuming a", CI -> Sentence
forall c. Idea c => c -> Sentence
short CI
twoD, ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
cartesian, String -> Sentence
S String
"with down as positive" Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"an object has an", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.acceleration, ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
vector, String -> Sentence
S String
"of"]
weightDerivNewtonSentence :: [Sentence]
weightDerivNewtonSentence :: [Sentence]
weightDerivNewtonSentence = [String -> Sentence
S String
"Since there is only one non-zero",
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
vector, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
component Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"the scalar", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
value,
UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
QP.weight, String -> Sentence
S String
"will be used for the" Sentence -> Sentence -> Sentence
+:+. UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.weight,
String -> Sentence
S String
"In this scenario" Sentence -> Sentence -> Sentence
`sC` TheoryModel -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase TheoryModel
newtonSL, String -> Sentence
S String
"from", TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
newtonSL,
String -> Sentence
S String
"can be expressed as"]
weightDerivReplaceMassSentence :: [Sentence]
weightDerivReplaceMassSentence :: [Sentence]
weightDerivReplaceMassSentence = [UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart UnitalChunk
QPP.mass, String -> Sentence
S String
"can be expressed as",
UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QPP.density, String -> Sentence
S String
"multiplied by", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QPP.vol Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"resulting in"]
weightDerivSpecWeightSentence :: [Sentence]
weightDerivSpecWeightSentence :: [Sentence]
weightDerivSpecWeightSentence = [String -> Sentence
S String
"Substituting", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QPP.specWeight,
String -> Sentence
S String
"as the product" Sentence -> Sentence -> Sentence
`S.of_` UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QPP.density Sentence -> Sentence -> Sentence
`S.and_` UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.gravitationalAccel,
String -> Sentence
S String
"yields"]
hsPressureGD :: GenDefn
hsPressureGD :: GenDefn
hsPressureGD = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd (ModelQDef -> ModelKind ModelExpr
forall e. QDefinition e -> ModelKind e
equationalModel' ModelQDef
hsPressureQD) (UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
QP.pressure) Maybe Derivation
forall a. Maybe a
Nothing
[Reference -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Reference
hsPressureSrc] String
"hsPressure" [Sentence
hsPressureNotes]
hsPressureQD :: ModelQDef
hsPressureQD :: ModelQDef
hsPressureQD = UnitalChunk -> NP -> ModelExpr -> ModelQDef
forall c e.
(Quantity c, MayHaveUnit c) =>
c -> NP -> e -> QDefinition e
mkQuantDef' UnitalChunk
QP.pressure (String -> NP
nounPhraseSP String
"hydrostatic pressure") ModelExpr
forall r. ExprC r => r
hsPressureEqn
hsPressureSrc :: Reference
hsPressureSrc :: Reference
hsPressureSrc = String -> String -> ShortName -> Reference
makeURI String
"hsPressureSrc" String
"https://en.wikipedia.org/wiki/Pressure" (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 Pressure"
hsPressureNotes :: Sentence
hsPressureNotes :: Sentence
hsPressureNotes = String -> Sentence
S String
"This" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"is derived from" Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"Bernoulli's" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"for a slow moving fluid" Sentence -> Sentence -> Sentence
+:+
String -> Sentence
S String
"through a porous" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
material_
torqueDD :: DataDefinition
torqueDD :: DataDefinition
torqueDD = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
torque Maybe Derivation
forall a. Maybe a
Nothing String
"torque" [Sentence
torqueDesc]
torque :: SimpleQDef
torque :: SimpleQDef
torque = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.torque Expr
torqueEqn
torqueEqn :: Expr
torqueEqn :: Expr
torqueEqn = UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.positionVec Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
`cross` UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.force
torqueDesc :: Sentence
torqueDesc :: Sentence
torqueDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"The", SimpleQDef -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase SimpleQDef
torque,
String -> Sentence
S String
"on a body measures the", String -> Sentence
S String
"tendency" Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"a", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.force,
String -> Sentence
S String
"to rotate the body around an axis or pivot"]
vecMagQD :: SimpleQDef
vecMagQD :: SimpleQDef
vecMagQD = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.speed Expr
forall r. ExprC r => r
speedEqn
magNote :: Sentence
magNote :: Sentence
magNote = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"For a given", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.velocity, String -> Sentence
S String
"vector", UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
QP.velocity Sentence -> Sentence -> Sentence
`sC`
String -> Sentence
S String
"the magnitude of the vector", Sentence -> Sentence
sParen (ModelExpr -> Sentence
eS ModelExpr
forall r. ExprC r => r
speedEqn) Sentence -> Sentence -> Sentence
`S.isThe`
String -> Sentence
S String
"scalar called", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.speed]
vecMag :: DataDefinition
vecMag :: DataDefinition
vecMag = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
vecMagQD Maybe Derivation
forall a. Maybe a
Nothing String
"vecMag" [Sentence
magNote]
newtonSLR :: TheoryModel
newtonSLR :: TheoryModel
newtonSLR = ModelKind ModelExpr
-> [QuantityDict]
-> [ConceptChunk]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> String
-> [Sentence]
-> TheoryModel
forall q c.
(Quantity q, MayHaveUnit q, Concept c) =>
ModelKind ModelExpr
-> [q]
-> [c]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> String
-> [Sentence]
-> TheoryModel
tmNoRefs (String -> ModelQDef -> ModelKind ModelExpr
forall e. String -> QDefinition e -> ModelKind e
equationalModelU String
"newtonSLR" ModelQDef
newtonSLRQD)
[UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
QP.torque, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
QP.momentOfInertia, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
QP.angularAccel]
([] :: [ConceptChunk]) [ModelQDef
newtonSLRQD] [] [] String
"NewtonSecLawRotMot" [Sentence]
newtonSLRNotes
newtonSLRQD :: ModelQDef
newtonSLRQD :: ModelQDef
newtonSLRQD = UnitalChunk -> NP -> ModelExpr -> ModelQDef
forall c e.
(Quantity c, MayHaveUnit c) =>
c -> NP -> e -> QDefinition e
mkQuantDef' UnitalChunk
QP.torque (String -> NP
nounPhraseSP String
"Newton's second law for rotational motion") ModelExpr
forall r. ExprC r => r
newtonSLRExpr
newtonSLRExpr :: ExprC r => r
newtonSLRExpr :: forall r. ExprC r => r
newtonSLRExpr = UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.momentOfInertia r -> r -> r
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.angularAccel
newtonSLRNotes :: [Sentence]
newtonSLRNotes :: [Sentence]
newtonSLRNotes = [[Sentence] -> Sentence
foldlSent
[String -> Sentence
S String
"The net", UnitalChunk -> Sentence
forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
QP.torque, String -> Sentence
S String
"on a", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
rigidBody Sentence -> Sentence -> Sentence
`S.is`
String -> Sentence
S String
"proportional to its", UnitalChunk -> Sentence
forall a. Quantity a => a -> Sentence
getTandS UnitalChunk
QP.angularAccel Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"where",
UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
QP.momentOfInertia, String -> Sentence
S String
"denotes", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
QP.momentOfInertia Sentence -> Sentence -> Sentence
`S.the_ofThe`
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
rigidBody, String -> Sentence
S String
"as the", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
constant Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"proportionality"]]
accelerationTM :: TheoryModel
accelerationTM :: TheoryModel
accelerationTM = 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 (String -> ModelQDef -> ModelKind ModelExpr
forall e. String -> QDefinition e -> ModelKind e
equationalModelU String
"accelerationTM" ModelQDef
accelerationQD)
[UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
QP.acceleration, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
QP.velocity, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
QP.time] ([] :: [ConceptChunk]) [ModelQDef
accelerationQD] [] []
[Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
accelerationWiki] String
"acceleration" []
velocityTM :: TheoryModel
velocityTM :: TheoryModel
velocityTM = 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 (String -> ModelQDef -> ModelKind ModelExpr
forall e. String -> QDefinition e -> ModelKind e
equationalModelU String
"velocityTM" ModelQDef
velocityQD)
[UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
QP.velocity, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
QP.position, UnitalChunk -> QuantityDict
forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw UnitalChunk
QP.time] ([] :: [ConceptChunk]) [ModelQDef
velocityQD] [] []
[Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
velocityWiki] String
"velocity" []