module Drasil.DblPend.DataDefs where
import Control.Lens ((^.))
import Prelude hiding (sin, cos, sqrt)
import Language.Drasil
import qualified Language.Drasil.Sentence.Combinators as S
import Theory.Drasil (DataDefinition, ddENoRefs, ddMENoRefs)
import Drasil.DblPend.Figures (figMotion)
import Drasil.DblPend.Unitals (pendDisAngle_1, pendDisAngle_2, lenRod_1, lenRod_2, xPos_1, yPos_1, xPos_2, yPos_2)
import Drasil.DblPend.Concepts (horizontalPos, verticalPos)
import Data.Drasil.Quantities.Physics (velocity, position, time, acceleration, force)
import Data.Drasil.Quantities.PhysicalProperties (mass)
dataDefs :: [DataDefinition]
dataDefs :: [DataDefinition]
dataDefs = [DataDefinition
positionGDD, DataDefinition
positionXDD_1, DataDefinition
positionYDD_1, DataDefinition
positionXDD_2, DataDefinition
positionYDD_2, DataDefinition
accelGDD, DataDefinition
forceGDD]
positionGDD :: DataDefinition
positionGDD :: DataDefinition
positionGDD = ModelQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddMENoRefs ModelQDef
positionGQD Maybe Derivation
forall a. Maybe a
Nothing String
"positionGDD" []
positionGQD :: ModelQDef
positionGQD :: ModelQDef
positionGQD = UnitalChunk -> ModelExpr -> ModelQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
velocity ModelExpr
positionGEqn
positionGEqn :: ModelExpr
positionGEqn :: ModelExpr
positionGEqn = 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 -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
position) UnitalChunk
time
positionXDD_1 :: DataDefinition
positionXDD_1 :: DataDefinition
positionXDD_1 = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
positionXQD_1 Maybe Derivation
forall a. Maybe a
Nothing String
"positionXDD1" [Sentence
positionXRef_1, Sentence
positionXFigRef_1]
positionXQD_1 :: SimpleQDef
positionXQD_1 :: SimpleQDef
positionXQD_1 = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
xPos_1 Expr
PExpr
positionXEqn_1
positionXEqn_1 :: PExpr
positionXEqn_1 :: PExpr
positionXEqn_1 = UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
lenRod_1 r -> r -> r
forall r. ExprC r => r -> r -> r
$* r -> r
forall r. ExprC r => r -> r
sin (UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
pendDisAngle_1)
positionXFigRef_1 :: Sentence
positionXFigRef_1 :: Sentence
positionXFigRef_1 = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
xPos_1 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
positionXRef_1 :: Sentence
positionXRef_1 :: Sentence
positionXRef_1 = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
xPos_1 Sentence -> Sentence -> Sentence
`S.isThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
horizontalPos
positionYDD_1 :: DataDefinition
positionYDD_1 :: DataDefinition
positionYDD_1 = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
positionYQD_1 Maybe Derivation
forall a. Maybe a
Nothing String
"positionYDD1" [Sentence
positionYRef_1, Sentence
positionYFigRef_1]
positionYQD_1 :: SimpleQDef
positionYQD_1 :: SimpleQDef
positionYQD_1 = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
yPos_1 Expr
PExpr
positionYEqn_1
positionYEqn_1 :: PExpr
positionYEqn_1 :: PExpr
positionYEqn_1 = r -> r
forall r. ExprC r => r -> r
neg (UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
lenRod_1 r -> r -> r
forall r. ExprC r => r -> r -> r
$* r -> r
forall r. ExprC r => r -> r
cos (UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
pendDisAngle_1))
positionYFigRef_1 :: Sentence
positionYFigRef_1 :: Sentence
positionYFigRef_1 = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
yPos_1 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
positionYRef_1 :: Sentence
positionYRef_1 :: Sentence
positionYRef_1 = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
yPos_1 Sentence -> Sentence -> Sentence
`S.isThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
verticalPos
positionXDD_2 :: DataDefinition
positionXDD_2 :: DataDefinition
positionXDD_2 = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
positionXQD_2 Maybe Derivation
forall a. Maybe a
Nothing String
"positionXDD2" [Sentence
positionXRef_2, Sentence
positionXFigRef_2]
positionXQD_2 :: SimpleQDef
positionXQD_2 :: SimpleQDef
positionXQD_2 = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
xPos_2 Expr
PExpr
positionXEqn_2
positionXEqn_2 :: PExpr
positionXEqn_2 :: PExpr
positionXEqn_2 = QuantityDict -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy (DataDefinition
positionXDD_1 DataDefinition
-> Getting QuantityDict DataDefinition QuantityDict -> QuantityDict
forall s a. s -> Getting a s a -> a
^. Getting QuantityDict DataDefinition QuantityDict
forall d. DefinesQuantity d => Getter d QuantityDict
Getter DataDefinition QuantityDict
defLhs) 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
lenRod_2 r -> r -> r
forall r. ExprC r => r -> r -> r
$* r -> r
forall r. ExprC r => r -> r
sin (UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
pendDisAngle_2))
positionXFigRef_2 :: Sentence
positionXFigRef_2 :: Sentence
positionXFigRef_2 = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
xPos_2 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
positionXRef_2 :: Sentence
positionXRef_2 :: Sentence
positionXRef_2 = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
xPos_2 Sentence -> Sentence -> Sentence
`S.isThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
horizontalPos
positionYDD_2 :: DataDefinition
positionYDD_2 :: DataDefinition
positionYDD_2 = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
positionYQD_2 Maybe Derivation
forall a. Maybe a
Nothing String
"positionYDD2" [Sentence
positionYRef_2, Sentence
positionYFigRef_2]
positionYQD_2 :: SimpleQDef
positionYQD_2 :: SimpleQDef
positionYQD_2 = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
yPos_2 Expr
PExpr
positionYEqn_2
positionYEqn_2 :: PExpr
positionYEqn_2 :: PExpr
positionYEqn_2 = QuantityDict -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy (DataDefinition
positionYDD_1 DataDefinition
-> Getting QuantityDict DataDefinition QuantityDict -> QuantityDict
forall s a. s -> Getting a s a -> a
^. Getting QuantityDict DataDefinition QuantityDict
forall d. DefinesQuantity d => Getter d QuantityDict
Getter DataDefinition QuantityDict
defLhs) r -> r -> r
forall r. ExprC r => r -> r -> r
$+ r -> r
forall r. ExprC r => r -> r
neg (UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
lenRod_2 r -> r -> r
forall r. ExprC r => r -> r -> r
$* r -> r
forall r. ExprC r => r -> r
cos (UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
pendDisAngle_2))
positionYFigRef_2 :: Sentence
positionYFigRef_2 :: Sentence
positionYFigRef_2 = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
yPos_2 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
positionYRef_2 :: Sentence
positionYRef_2 :: Sentence
positionYRef_2 = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
yPos_2 Sentence -> Sentence -> Sentence
`S.isThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
verticalPos
accelGDD :: DataDefinition
accelGDD :: DataDefinition
accelGDD = ModelQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddMENoRefs ModelQDef
accelGQD Maybe Derivation
forall a. Maybe a
Nothing String
"accelerationGDD" []
accelGQD :: ModelQDef
accelGQD :: ModelQDef
accelGQD = UnitalChunk -> ModelExpr -> ModelQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
acceleration ModelExpr
accelGEqn
accelGEqn :: ModelExpr
accelGEqn :: ModelExpr
accelGEqn = 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 -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
velocity) UnitalChunk
time
forceGDD :: DataDefinition
forceGDD :: DataDefinition
forceGDD = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
forceGQD Maybe Derivation
forall a. Maybe a
Nothing String
"forceGDD" []
forceGQD :: SimpleQDef
forceGQD :: SimpleQDef
forceGQD = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
force Expr
PExpr
forceGEqn
forceGEqn :: PExpr
forceGEqn :: PExpr
forceGEqn = r -> r -> r
forall r. ExprC r => r -> r -> r
vScale (UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
mass) (UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
acceleration)