module Drasil.Projectile.DataDefs (dataDefs, speedIX, speedIY) where
import Prelude hiding (sin, cos)
import Language.Drasil
import qualified Language.Drasil.Sentence.Combinators as S
import Theory.Drasil (DataDefinition, ddENoRefs)
import Data.Drasil.Quantities.Physics (iSpeed, ixVel, iyVel)
import Data.Drasil.Theories.Physics (vecMag)
import Drasil.Projectile.Figures (figLaunch)
import Drasil.Projectile.Unitals (launAngle)
dataDefs :: [DataDefinition]
dataDefs :: [DataDefinition]
dataDefs = [DataDefinition
vecMag, DataDefinition
speedIX, DataDefinition
speedIY]
speedIX, speedIY :: DataDefinition
speedIX :: DataDefinition
speedIX = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
speedIXQD Maybe Derivation
forall a. Maybe a
Nothing String
"speedIX" [Sentence
speedRef, Sentence
figRef]
speedIY :: DataDefinition
speedIY = SimpleQDef
-> Maybe Derivation -> String -> [Sentence] -> DataDefinition
ddENoRefs SimpleQDef
speedIYQD Maybe Derivation
forall a. Maybe a
Nothing String
"speedIY" [Sentence
speedRef, Sentence
figRef]
speedIXQD, speedIYQD :: SimpleQDef
speedIXQD :: SimpleQDef
speedIXQD = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
ixVel (Expr -> SimpleQDef) -> Expr -> SimpleQDef
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
iSpeed Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* Expr -> Expr
forall r. ExprC r => r -> r
cos (ConstrConcept -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
launAngle)
speedIYQD :: SimpleQDef
speedIYQD = UnitalChunk -> Expr -> SimpleQDef
forall c e. (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e
mkQuantDef UnitalChunk
iyVel (Expr -> SimpleQDef) -> Expr -> SimpleQDef
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
iSpeed Expr -> Expr -> Expr
forall r. ExprC r => r -> r -> r
$* Expr -> Expr
forall r. ExprC r => r -> r
sin (ConstrConcept -> Expr
forall c. (HasUID c, HasSymbol c) => c -> Expr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
launAngle)
speedRef :: Sentence
speedRef :: Sentence
speedRef = UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
iSpeed 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
vecMag
figRef :: Sentence
figRef :: Sentence
figRef = ConstrConcept -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch ConstrConcept
launAngle 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
figLaunch