module Drasil.SglPend.DataDefs (dataDefs, positionIY, positionIX, angFrequencyDD,
frequencyDD, periodSHMDD) where
import Prelude hiding (sin, cos, sqrt)
import Language.Drasil
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.SI_Units (second)
import Theory.Drasil (DataDefinition, ddENoRefs)
import Drasil.SglPend.Figures (figMotion)
import qualified Data.Drasil.Quantities.Physics as QP (ixPos, iyPos,
frequency, period, angularFrequency)
import Drasil.SglPend.Unitals (lenRod, initialPendAngle)
import qualified Data.Drasil.Quantities.Math as QM (pi_)
import Drasil.DblPend.Concepts (horizontalPos, verticalPos)
dataDefs :: [DataDefinition]
dataDefs :: [DataDefinition]
dataDefs = [DataDefinition
positionIX, DataDefinition
positionIY, DataDefinition
frequencyDD, DataDefinition
angFrequencyDD, DataDefinition
periodSHMDD]
positionIX :: DataDefinition
positionIX :: DataDefinition
positionIX = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
positionIXQD Maybe Derivation
forall a. Maybe a
Nothing String
"positionIX" [Sentence
positionRef, Sentence
figRef]
positionIXQD :: SimpleQDef
positionIXQD :: SimpleQDef
positionIXQD = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.ixPos Expr
positionIXEqn
positionIXEqn :: Expr
positionIXEqn :: Expr
positionIXEqn = UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
lenRod Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* Expr -> Expr
forall r. ExprC r => r -> r
sin (UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
initialPendAngle)
figRef :: Sentence
figRef :: Sentence
figRef = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
QP.ixPos Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"shown in" Sentence -> Sentence -> Sentence
+:+. LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
figMotion
positionRef :: Sentence
positionRef :: Sentence
positionRef = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
QP.ixPos Sentence -> Sentence -> Sentence
`S.isThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
horizontalPos
positionIY :: DataDefinition
positionIY :: DataDefinition
positionIY = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
positionIYQD Maybe Derivation
forall a. Maybe a
Nothing String
"positionIY" [Sentence
positionReff, Sentence
figReff]
positionIYQD :: SimpleQDef
positionIYQD :: SimpleQDef
positionIYQD = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.iyPos Expr
positionIYEqn
positionIYEqn :: Expr
positionIYEqn :: Expr
positionIYEqn = Expr -> Expr
forall r. ExprC r => r -> r
neg (UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
lenRod Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* Expr -> Expr
forall r. ExprC r => r -> r
cos (UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
initialPendAngle))
figReff :: Sentence
figReff :: Sentence
figReff = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
QP.iyPos Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"shown in" Sentence -> Sentence -> Sentence
+:+. LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
figMotion
positionReff :: Sentence
positionReff :: Sentence
positionReff = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
QP.iyPos Sentence -> Sentence -> Sentence
`S.isThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
verticalPos
frequencyDD :: DataDefinition
frequencyDD :: DataDefinition
frequencyDD = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
frequencyDDQD Maybe Derivation
forall a. Maybe a
Nothing String
"frequencyDD" [Sentence
frequencyRef]
frequencyDDQD :: SimpleQDef
frequencyDDQD :: SimpleQDef
frequencyDDQD = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.frequency Expr
frequencyDDEqn
frequencyDDEqn :: Expr
frequencyDDEqn :: Expr
frequencyDDEqn = Expr -> Expr
forall r. (ExprC r, LiteralC r) => r -> r
recip_ (Expr -> Expr) -> Expr -> Expr
forall a b. (a -> b) -> a -> b
$ UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.period
frequencyRef :: Sentence
frequencyRef :: Sentence
frequencyRef = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
QP.frequency Sentence -> Sentence -> Sentence
`S.isThe` String -> Sentence
S String
"number of back and forth swings in one" Sentence -> Sentence -> Sentence
+:+ UnitDefn -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitDefn
second
angFrequencyDD :: DataDefinition
angFrequencyDD :: DataDefinition
angFrequencyDD = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
angFrequencyDDQD Maybe Derivation
forall a. Maybe a
Nothing String
"angFrequencyDD" [Sentence
angFrequencyRef]
angFrequencyDDQD :: SimpleQDef
angFrequencyDDQD :: SimpleQDef
angFrequencyDDQD = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.angularFrequency Expr
angFrequencyDDEqn
angFrequencyDDEqn :: Expr
angFrequencyDDEqn :: Expr
angFrequencyDDEqn = Integer -> Expr
forall r. LiteralC r => Integer -> r
exactDbl Integer
2 Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* DefinedQuantityDict -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
QM.pi_ 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
QP.period
angFrequencyRef :: Sentence
angFrequencyRef :: Sentence
angFrequencyRef = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
QP.period Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"from" Sentence -> Sentence -> Sentence
+:+ DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
periodSHMDD
periodSHMDD :: DataDefinition
periodSHMDD :: DataDefinition
periodSHMDD = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
periodSHMDDQD Maybe Derivation
forall a. Maybe a
Nothing String
"periodSHMDD" [Sentence
periodSHMRef]
periodSHMDDQD :: SimpleQDef
periodSHMDDQD :: SimpleQDef
periodSHMDDQD = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
QP.period Expr
periodSHMDDEqn
periodSHMDDEqn :: Expr
periodSHMDDEqn :: Expr
periodSHMDDEqn = Expr -> Expr
forall r. (ExprC r, LiteralC r) => r -> r
recip_ (Expr -> Expr) -> Expr -> Expr
forall a b. (a -> b) -> a -> b
$ UnitalChunk -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
QP.frequency
periodSHMRef :: Sentence
periodSHMRef :: Sentence
periodSHMRef = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
QP.period Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"from" Sentence -> Sentence -> Sentence
+:+ DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
frequencyDD