{-# LANGUAGE PostfixOperators #-}
module Drasil.GamePhysics.Changes (likelyChgs, unlikelyChgs) where
import Language.Drasil
import qualified Language.Drasil.Sentence.Combinators as S
import Data.Drasil.Concepts.Documentation as Doc (library, likeChgDom, unlikeChgDom)
import qualified Data.Drasil.Concepts.Math as CM (ode, constraint)
import Data.Drasil.Concepts.Computation (algorithm)
import qualified Data.Drasil.Concepts.Physics as CP (collision, damping, joint)
import Drasil.GamePhysics.Assumptions (assumpCT, assumpDI, assumpCAJI)
likelyChangesStmt1, likelyChangesStmt2, likelyChangesStmt3,
likelyChangesStmt4 :: Sentence
likelyChangesStmt1 :: Sentence
likelyChangesStmt1 = (String -> Sentence
S String
"internal" Sentence -> Sentence -> Sentence
+:+ CI -> Sentence
getAcc CI
CM.ode Sentence -> Sentence -> Sentence
:+:
String -> Sentence
S String
"-solving" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
algorithm Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"used by the" Sentence -> Sentence -> Sentence
+:+
IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
library) Sentence -> Sentence -> Sentence
`maybeChanged` String -> Sentence
S String
"in the future"
likelyChangesStmt2 :: Sentence
likelyChangesStmt2 = ConceptInstance -> Sentence -> Sentence
forall x.
(HasShortName x, Referable x) =>
x -> Sentence -> Sentence
chgsStart ConceptInstance
assumpCT (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
library Sentence -> Sentence -> Sentence
`maybeExpanded`
(String -> Sentence
S String
"to deal with edge-to-edge and vertex-to-vertex" Sentence -> Sentence -> Sentence
+:+
ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
CP.collision)
likelyChangesStmt3 :: Sentence
likelyChangesStmt3 = ConceptInstance -> Sentence -> Sentence
forall x.
(HasShortName x, Referable x) =>
x -> Sentence -> Sentence
chgsStart ConceptInstance
assumpDI (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
library Sentence -> Sentence -> Sentence
`maybeExpanded` (
String -> Sentence
S String
"to include motion with" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
CP.damping)
likelyChangesStmt4 :: Sentence
likelyChangesStmt4 = ConceptInstance -> Sentence -> Sentence
forall x.
(HasShortName x, Referable x) =>
x -> Sentence -> Sentence
chgsStart ConceptInstance
assumpCAJI (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$ IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
library Sentence -> Sentence -> Sentence
`maybeExpanded` (
String -> Sentence
S String
"to include" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
CP.joint Sentence -> Sentence -> Sentence
`S.and_` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
CM.constraint)
lcVODES, lcEC, lcID, lcIJC :: ConceptInstance
lcVODES :: ConceptInstance
lcVODES = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"lcVODES" Sentence
likelyChangesStmt1 String
"Variable-ODE-Solver" ConceptChunk
likeChgDom
lcEC :: ConceptInstance
lcEC = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"lcEC" Sentence
likelyChangesStmt2 String
"Expanded-Collisions" ConceptChunk
likeChgDom
lcID :: ConceptInstance
lcID = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"lcID" Sentence
likelyChangesStmt3 String
"Include-Dampening" ConceptChunk
likeChgDom
lcIJC :: ConceptInstance
lcIJC = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"lcIJC" Sentence
likelyChangesStmt4 String
"Include-Joints-Constraints" ConceptChunk
likeChgDom
likelyChgs :: [ConceptInstance]
likelyChgs :: [ConceptInstance]
likelyChgs = [ConceptInstance
lcVODES, ConceptInstance
lcEC, ConceptInstance
lcID, ConceptInstance
lcIJC]
unlikelyChangesStmt1, unlikelyChangesStmt2, unlikelyChangesStmt3, unlikelyChangesStmt4 :: Sentence
unlikelyChangesStmt1 :: Sentence
unlikelyChangesStmt1 = (String -> Sentence
S String
"The goal of the system" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"to simulate the interactions of rigid bodies" !.)
unlikelyChangesStmt2 :: Sentence
unlikelyChangesStmt2 = (String -> Sentence
S String
"There will always be a source of input data external to the software" !.)
unlikelyChangesStmt3 :: Sentence
unlikelyChangesStmt3 = (String -> Sentence
S String
"A Cartesian Coordinate system is used" !.)
unlikelyChangesStmt4 :: Sentence
unlikelyChangesStmt4 = (String -> Sentence
S String
"All objects" Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"rigid bodies" !.)
ucSRB, ucEI, ucCCS, ucORB :: ConceptInstance
ucSRB :: ConceptInstance
ucSRB = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"ucSRB" Sentence
unlikelyChangesStmt1 String
"Simulate-Rigid-Bodies" ConceptChunk
unlikeChgDom
ucEI :: ConceptInstance
ucEI = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"ucEI" Sentence
unlikelyChangesStmt2 String
"External-Input" ConceptChunk
unlikeChgDom
ucCCS :: ConceptInstance
ucCCS = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"ucCCS" Sentence
unlikelyChangesStmt3 String
"Cartesian-Coordinate-System" ConceptChunk
unlikeChgDom
ucORB :: ConceptInstance
ucORB = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"ucORB" Sentence
unlikelyChangesStmt4 String
"Objects-Rigid-Bodies" ConceptChunk
unlikeChgDom
unlikelyChgs :: [ConceptInstance]
unlikelyChgs :: [ConceptInstance]
unlikelyChgs = [ConceptInstance
ucSRB, ConceptInstance
ucEI, ConceptInstance
ucCCS, ConceptInstance
ucORB]