{-# LANGUAGE PostfixOperators #-} module Drasil.DblPend.IMods (iMods, angleIM_1, angleIM_2) where import Prelude hiding (cos, sin) import Language.Drasil import Theory.Drasil import Utils.Drasil (weave) import qualified Language.Drasil.Sentence.Combinators as S import Data.Drasil.Concepts.Documentation (condition) import Data.Drasil.Concepts.Math (ode) import Drasil.DblPend.Derivations (angularAccelDerivEqns) import Drasil.DblPend.Expressions (angularAccelExpr_1, angularAccelExpr_2, cosAngleExpr1, cosAngleExpr2, forceDerivExpr1, forceDerivExpr2, sinAngleExpr1, sinAngleExpr2) import Drasil.DblPend.GenDefs (accelXGD_1, accelXGD_2, accelYGD_1, accelYGD_2, xForceGD_1, xForceGD_2, yForceGD_1, yForceGD_2) import Drasil.DblPend.Unitals (angularAccel_1, angularAccel_2, angularVel_1, angularVel_2, lenRod_1, lenRod_2, massObj_1, massObj_2, pendDisAngle_1, pendDisAngle_2) iMods :: [InstanceModel] iMods :: [InstanceModel] iMods = [InstanceModel angleIM_1, InstanceModel angleIM_2] angleDerivSents :: [Sentence] angleDerivSents :: [Sentence] angleDerivSents = [Sentence angleDerivSent1, Sentence EmptyS, Sentence angleDerivSent2, Sentence EmptyS, Sentence angleDerivSent3, Sentence angleDerivSent4, Sentence EmptyS, Sentence angleDerivSent5, Sentence angleDerivSent6] angleDerivSent1, angleDerivSent2, angleDerivSent3, angleDerivSent4, angleDerivSent5, angleDerivSent6 :: Sentence angleDerivSent1 :: Sentence angleDerivSent1 = [Sentence] -> Sentence foldlSentCol [String -> Sentence S String "By solving equations" Sentence -> Sentence -> Sentence +:+ GenDefn -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS GenDefn xForceGD_2 Sentence -> Sentence -> Sentence `S.and_` GenDefn -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS GenDefn yForceGD_2 Sentence -> Sentence -> Sentence `S.for` ModelExpr -> Sentence eS ModelExpr PExpr forceDerivExpr1 Sentence -> Sentence -> Sentence `S.and_` ModelExpr -> Sentence eS ModelExpr PExpr forceDerivExpr2 Sentence -> Sentence -> Sentence `S.and_` String -> Sentence S String "then substituting into equation" Sentence -> Sentence -> Sentence +:+ GenDefn -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS GenDefn xForceGD_1 Sentence -> Sentence -> Sentence `S.and_` GenDefn -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS GenDefn yForceGD_1 Sentence -> Sentence -> Sentence +:+ String -> Sentence S String ", we can get equations 1 and 2"] angleDerivSent2 :: Sentence angleDerivSent2 = [Sentence] -> Sentence foldlSentCol [String -> Sentence S String "Multiply the equation 1 by" Sentence -> Sentence -> Sentence +:+ ModelExpr -> Sentence eS ModelExpr PExpr cosAngleExpr1 Sentence -> Sentence -> Sentence `S.and_` String -> Sentence S String "the equation 2 by" Sentence -> Sentence -> Sentence +:+ ModelExpr -> Sentence eS ModelExpr PExpr sinAngleExpr1 Sentence -> Sentence -> Sentence `S.and_` String -> Sentence S String "rearrange to get"] angleDerivSent3 :: Sentence angleDerivSent3 = String -> Sentence S String "This leads to the equation 3" angleDerivSent4 :: Sentence angleDerivSent4 = [Sentence] -> Sentence foldlSentCol[String -> Sentence S String "Next, multiply equation" Sentence -> Sentence -> Sentence +:+ GenDefn -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS GenDefn xForceGD_2 Sentence -> Sentence -> Sentence +:+ String -> Sentence S String "by" Sentence -> Sentence -> Sentence +:+ ModelExpr -> Sentence eS ModelExpr PExpr cosAngleExpr2 Sentence -> Sentence -> Sentence `S.and_` String -> Sentence S String "equation" Sentence -> Sentence -> Sentence +:+ GenDefn -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS GenDefn yForceGD_2 Sentence -> Sentence -> Sentence +:+ String -> Sentence S String "by" Sentence -> Sentence -> Sentence +:+ ModelExpr -> Sentence eS ModelExpr PExpr sinAngleExpr2 Sentence -> Sentence -> Sentence `S.and_` String -> Sentence S String "rearrange to get"] angleDerivSent5 :: Sentence angleDerivSent5 = String -> Sentence S String "which leads to equation 4" angleDerivSent6 :: Sentence angleDerivSent6 = [Sentence] -> Sentence foldlSentCol[String -> Sentence S String "By giving equations" Sentence -> Sentence -> Sentence +:+ GenDefn -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS GenDefn accelXGD_1 Sentence -> Sentence -> Sentence `S.and_` GenDefn -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS GenDefn accelXGD_2 Sentence -> Sentence -> Sentence `S.and_` GenDefn -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS GenDefn accelYGD_1 Sentence -> Sentence -> Sentence `S.and_` GenDefn -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS GenDefn accelYGD_2 Sentence -> Sentence -> Sentence +:+ String -> Sentence S String "plus additional two equations, 3 and 4, we can get" Sentence -> Sentence -> Sentence +:+ InstanceModel -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS InstanceModel angleIM_1 Sentence -> Sentence -> Sentence `S.and_` InstanceModel -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS InstanceModel angleIM_2 Sentence -> Sentence -> Sentence +:+ String -> Sentence S String "via a computer algebra program"] angleIM_1 :: InstanceModel angleIM_1 :: InstanceModel angleIM_1 = ModelKind Expr -> Inputs -> Output -> OutputConstraints -> Maybe Derivation -> String -> [Sentence] -> InstanceModel imNoRefs ModelKind Expr angleMK_1 [UnitalChunk -> RealInterval Expr Expr -> Input forall q. (Quantity q, MayHaveUnit q) => q -> RealInterval Expr Expr -> Input qwC UnitalChunk lenRod_1 (RealInterval Expr Expr -> Input) -> RealInterval Expr Expr -> Input forall a b. (a -> b) -> a -> b $ (Inclusive, Expr) -> RealInterval Expr Expr forall b a. (Inclusive, b) -> RealInterval a b UpFrom (Inclusive Exc, Integer -> Expr forall r. LiteralC r => Integer -> r exactDbl Integer 0), UnitalChunk -> RealInterval Expr Expr -> Input forall q. (Quantity q, MayHaveUnit q) => q -> RealInterval Expr Expr -> Input qwC UnitalChunk lenRod_2 (RealInterval Expr Expr -> Input) -> RealInterval Expr Expr -> Input forall a b. (a -> b) -> a -> b $ (Inclusive, Expr) -> RealInterval Expr Expr forall b a. (Inclusive, b) -> RealInterval a b UpFrom (Inclusive Exc, Integer -> Expr forall r. LiteralC r => Integer -> r exactDbl Integer 0), UnitalChunk -> RealInterval Expr Expr -> Input forall q. (Quantity q, MayHaveUnit q) => q -> RealInterval Expr Expr -> Input qwC UnitalChunk massObj_1 (RealInterval Expr Expr -> Input) -> RealInterval Expr Expr -> Input forall a b. (a -> b) -> a -> b $ (Inclusive, Expr) -> RealInterval Expr Expr forall b a. (Inclusive, b) -> RealInterval a b UpFrom (Inclusive Exc, Integer -> Expr forall r. LiteralC r => Integer -> r exactDbl Integer 0), UnitalChunk -> RealInterval Expr Expr -> Input forall q. (Quantity q, MayHaveUnit q) => q -> RealInterval Expr Expr -> Input qwC UnitalChunk massObj_2 (RealInterval Expr Expr -> Input) -> RealInterval Expr Expr -> Input forall a b. (a -> b) -> a -> b $ (Inclusive, Expr) -> RealInterval Expr Expr forall b a. (Inclusive, b) -> RealInterval a b UpFrom (Inclusive Exc, Integer -> Expr forall r. LiteralC r => Integer -> r exactDbl Integer 0), UnitalChunk -> Input forall q. (Quantity q, MayHaveUnit q) => q -> Input qwUC UnitalChunk pendDisAngle_1, UnitalChunk -> Input forall q. (Quantity q, MayHaveUnit q) => q -> Input qwUC UnitalChunk pendDisAngle_2] (UnitalChunk -> Output forall q. (Quantity q, MayHaveUnit q) => q -> Output qw UnitalChunk pendDisAngle_1) [] Maybe Derivation forall a. Maybe a Nothing String "calOfAngle1" [[Sentence] -> Sentence foldlSent [UnitalChunk -> Sentence forall c. (HasUID c, HasSymbol c) => c -> Sentence ch UnitalChunk pendDisAngle_1 Sentence -> Sentence -> Sentence `S.is` String -> Sentence S String "calculated by solving the", CI -> Sentence getAcc CI ode, String -> Sentence S String "here together with the initial", IdeaDict -> Sentence forall n. NamedIdea n => n -> Sentence plural IdeaDict condition Sentence -> Sentence -> Sentence `S.and_` InstanceModel -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS InstanceModel angleIM_2]] angleMK_1 :: ModelKind Expr angleMK_1 :: ModelKind Expr angleMK_1 = String -> NP -> QDefinition Expr -> ModelKind Expr forall e. String -> NP -> QDefinition e -> ModelKind e equationalModel String "angleIM1" (String -> NP nounPhraseSP String "calculation of angle of first rod") QDefinition Expr angleFD_1 angleFD_1 :: SimpleQDef angleFD_1 :: QDefinition Expr angleFD_1 = UnitalChunk -> [UnitalChunk] -> Expr -> QDefinition Expr forall c i e. (Quantity c, MayHaveUnit c, HasSpace c, Quantity i, HasSpace i) => c -> [i] -> e -> QDefinition e mkFuncDefByQ UnitalChunk angularAccel_1 [UnitalChunk pendDisAngle_1, UnitalChunk pendDisAngle_2, UnitalChunk angularVel_1, UnitalChunk angularVel_2] Expr PExpr angularAccelExpr_1 angleIM_2 :: InstanceModel angleIM_2 :: InstanceModel angleIM_2 = ModelKind Expr -> Inputs -> Output -> OutputConstraints -> Maybe Derivation -> String -> [Sentence] -> InstanceModel imNoRefs ModelKind Expr angleMK_2 [UnitalChunk -> RealInterval Expr Expr -> Input forall q. (Quantity q, MayHaveUnit q) => q -> RealInterval Expr Expr -> Input qwC UnitalChunk lenRod_1 (RealInterval Expr Expr -> Input) -> RealInterval Expr Expr -> Input forall a b. (a -> b) -> a -> b $ (Inclusive, Expr) -> RealInterval Expr Expr forall b a. (Inclusive, b) -> RealInterval a b UpFrom (Inclusive Exc, Integer -> Expr forall r. LiteralC r => Integer -> r exactDbl Integer 0), UnitalChunk -> RealInterval Expr Expr -> Input forall q. (Quantity q, MayHaveUnit q) => q -> RealInterval Expr Expr -> Input qwC UnitalChunk lenRod_2 (RealInterval Expr Expr -> Input) -> RealInterval Expr Expr -> Input forall a b. (a -> b) -> a -> b $ (Inclusive, Expr) -> RealInterval Expr Expr forall b a. (Inclusive, b) -> RealInterval a b UpFrom (Inclusive Exc, Integer -> Expr forall r. LiteralC r => Integer -> r exactDbl Integer 0), UnitalChunk -> RealInterval Expr Expr -> Input forall q. (Quantity q, MayHaveUnit q) => q -> RealInterval Expr Expr -> Input qwC UnitalChunk massObj_1 (RealInterval Expr Expr -> Input) -> RealInterval Expr Expr -> Input forall a b. (a -> b) -> a -> b $ (Inclusive, Expr) -> RealInterval Expr Expr forall b a. (Inclusive, b) -> RealInterval a b UpFrom (Inclusive Exc, Integer -> Expr forall r. LiteralC r => Integer -> r exactDbl Integer 0), UnitalChunk -> RealInterval Expr Expr -> Input forall q. (Quantity q, MayHaveUnit q) => q -> RealInterval Expr Expr -> Input qwC UnitalChunk massObj_2 (RealInterval Expr Expr -> Input) -> RealInterval Expr Expr -> Input forall a b. (a -> b) -> a -> b $ (Inclusive, Expr) -> RealInterval Expr Expr forall b a. (Inclusive, b) -> RealInterval a b UpFrom (Inclusive Exc, Integer -> Expr forall r. LiteralC r => Integer -> r exactDbl Integer 0), UnitalChunk -> Input forall q. (Quantity q, MayHaveUnit q) => q -> Input qwUC UnitalChunk pendDisAngle_1, UnitalChunk -> Input forall q. (Quantity q, MayHaveUnit q) => q -> Input qwUC UnitalChunk pendDisAngle_2] (UnitalChunk -> Output forall q. (Quantity q, MayHaveUnit q) => q -> Output qw UnitalChunk pendDisAngle_2) [] (Derivation -> Maybe Derivation forall a. a -> Maybe a Just Derivation angleDeriv_2) String "calOfAngle2" [[Sentence] -> Sentence foldlSent [UnitalChunk -> Sentence forall c. (HasUID c, HasSymbol c) => c -> Sentence ch UnitalChunk pendDisAngle_2 Sentence -> Sentence -> Sentence `S.is` String -> Sentence S String "calculated by solving the", CI -> Sentence getAcc CI ode, String -> Sentence S String "here together with the initial", IdeaDict -> Sentence forall n. NamedIdea n => n -> Sentence plural IdeaDict condition Sentence -> Sentence -> Sentence `S.and_` InstanceModel -> Sentence forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence refS InstanceModel angleIM_1]] angleMK_2 :: ModelKind Expr angleMK_2 :: ModelKind Expr angleMK_2 = String -> NP -> QDefinition Expr -> ModelKind Expr forall e. String -> NP -> QDefinition e -> ModelKind e equationalModel String "angleIM2" (String -> NP nounPhraseSP String "calculation of angle of second rod") QDefinition Expr angleFD_2 angleFD_2 :: SimpleQDef angleFD_2 :: QDefinition Expr angleFD_2 = UnitalChunk -> [UnitalChunk] -> Expr -> QDefinition Expr forall c i e. (Quantity c, MayHaveUnit c, HasSpace c, Quantity i, HasSpace i) => c -> [i] -> e -> QDefinition e mkFuncDefByQ UnitalChunk angularAccel_2 [UnitalChunk pendDisAngle_1, UnitalChunk pendDisAngle_2, UnitalChunk angularVel_1, UnitalChunk angularVel_2] Expr PExpr angularAccelExpr_2 angleDeriv_2 :: Derivation angleDeriv_2 :: Derivation angleDeriv_2 = Sentence -> [Sentence] -> Derivation mkDerivName (UnitalChunk -> Sentence forall n. NamedIdea n => n -> Sentence phrase UnitalChunk pendDisAngle_2) ([[Sentence]] -> [Sentence] forall a. [[a]] -> [a] weave [[Sentence] angleDerivSents, (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence] forall a b. (a -> b) -> [a] -> [b] map ModelExpr -> Sentence eS [ModelExpr] angularAccelDerivEqns])