Skip to content

Commit

Permalink
Merge pull request #1428 from JacquesCarette/projectileSRS
Browse files Browse the repository at this point in the history
[Review] Start on Projectile SRS
  • Loading branch information
smiths authored Jun 27, 2019
2 parents a654a7a + 33f099e commit af2acf8
Show file tree
Hide file tree
Showing 61 changed files with 5,192 additions and 260 deletions.
Binary file added code/datafiles/Projectile/Launch.jpg
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
11 changes: 10 additions & 1 deletion code/datafiles/README.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
--------------------------------------------------
### Summary of Folder Structure and File Contents
Last updated: July 26, 2018
Last updated: June 14, 2019
--------------------------------------------------

**GamePhysics**
Expand All @@ -9,8 +9,17 @@ Last updated: July 26, 2018
**GlassBR**
- Contains additional "helper" files for the GlassBR example

**NoPCM**
- Contains additional "helper" files for the NoPCM example

**Projectile**
- Contains additional "helper" files for the Projectile example

**SSP**
- Contains additional "helper" files for the SSP example

**SWHS**
- Contains additional "helper" files for the SWHS example

README.md
- This file
35 changes: 27 additions & 8 deletions code/drasil-data/Data/Drasil/Concepts/Math.hs
Original file line number Diff line number Diff line change
@@ -1,31 +1,37 @@
module Data.Drasil.Concepts.Math where

import Language.Drasil hiding (number)
import Language.Drasil.ShortHands (lX, lY, lZ)
import Data.Drasil.IdeaDicts
import Utils.Drasil

import Control.Lens ((^.))

mathcon :: [ConceptChunk]
mathcon = [angle, area, calculation, diameter, equation, euclidN, euclidSpace, gradient,
graph, law, matrix, norm, normal, normalV, number, orient, parameter, perp,
perpV, pi_, probability, shape, surArea, surface, unit_, unitV, vector, rate,
change, rOfChng, constraint]
mathcon = [angle, area, calculation, cartesian, change, constraint, diameter,
equation, euclidN, euclidSpace, gradient, graph, law, matrix, norm, normal,
normalV, number, orient, parameter, perp, perpV, pi_, probability, rOfChng,
rate, rightHand, shape, surArea, surface, unitV, unit_, vector, xAxis, xComp,
xDir, yAxis, yComp, yDir, zAxis, zComp, zDir]

mathcon' :: [CI]
mathcon' = [pde, ode, de]

angle, area, calculation, diameter, equation, euclidN, euclidSpace, gradient,
graph, law, matrix, norm, normal, normalV, number, orient, parameter, perp,
perpV, pi_, probability, shape, surArea, surface, unit_, unitV, vector, rate,
change, rOfChng, constraint :: ConceptChunk
angle, area, calculation, cartesian, change, constraint, diameter, equation,
euclidN, euclidSpace, gradient, graph, law, matrix, norm, normal, normalV,
number, orient, parameter, perp, perpV, pi_, probability, rOfChng, rate,
rightHand, shape, surArea, surface, unitV, unit_, vector, xAxis, xComp, xDir,
yAxis, yComp, yDir, zAxis, zComp, zDir :: ConceptChunk

pde, ode, de :: CI

angle = dcc "angle" (cn' "angle") ("The amount of rotation needed to bring one line or plane into" ++
"coincidence with another")
area = dcc "area" (cn' "area") "A part of an object or surface"
calculation = dcc "calculation" (cn' "calculation") "A mathematical determination of the size or number of something"
cartesian = dcc "cartesian" (pn' "Cartesian coordinate system") ("A coordinate system that specifies each point uniquely in a plane by a set " ++
"of numerical coordinates, which are the signed distances to the point from " ++
"two fixed perpendicular oriented lines, measured in the same unit of length.")
change = dcc "change" (cn' "change") "Difference between relative start and end states of an object"
constraint = dcc "constraint" (cn' "constraint") "A condition that the solution must satisfy"
diameter = dcc "diameter" (cn' "diameter") ("Any straight line segment that passes through the center of the circle" ++
Expand All @@ -47,12 +53,25 @@ perp = dcc "perp" (cn' "perpendicular") "At right angl
pi_ = dcc "pi" (cn' "ratio of circumference to diameter for any circle") "The ratio of a circle's circumference to its diameter"
probability = dcc "probability" (cnIES "probability") "The likelihood of an event to occur"
rate = dcc "rate" (cn' "rate") "Ratio that compares two quantities having different units of measure"
rightHand = dcc "rightHand" (cn' "right-handed coordinate system") "A coordinate system where the positive z-axis comes out of the screen."
shape = dcc "shape" (cn' "shape") "The outline of an area or figure"
surface = dcc "surface" (cn' "surface") "The outer or topmost boundary of an object"
unit_ = dcc "unit" (cn' "unit") "Identity element"
vector = dcc "vector" (cn' "vector") "Object with magnitude and direction"
orient = dcc "orientation" (cn' "orientation") "The relative physical position or direction of something"

xAxis = dcc "xAxis" (nounPhraseSent $ P lX :+: S "-axis") "the primary axis of a system of coordinates"
yAxis = dcc "yAxis" (nounPhraseSent $ P lY :+: S "-axis") "the secondary axis of a system of coordinates"
zAxis = dcc "zAxis" (nounPhraseSent $ P lZ :+: S "-axis") "the tertiary axis of a system of coordinates"

xComp = dcc "xComp" (nounPhraseSent $ P lX :+: S "-component") "the component of a vector in the x-direction"
yComp = dcc "yComp" (nounPhraseSent $ P lY :+: S "-component") "the component of a vector in the y-direction"
zComp = dcc "zComp" (nounPhraseSent $ P lZ :+: S "-component") "the component of a vector in the z-direction"

xDir = dcc "xDir" (nounPhraseSent $ P lX :+: S "-direction") "the direction aligned with the x-axis"
yDir = dcc "yDir" (nounPhraseSent $ P lY :+: S "-direction") "the direction aligned with the y-axis"
zDir = dcc "zDir" (nounPhraseSent $ P lZ :+: S "-direction") "the direction aligned with the z-axis"

--FIXME: use nounphrase instead of cn'
de = commonIdeaWithDict "de" (cn' "differential equation") "DE" [mathematics]
ode = commonIdeaWithDict "ode" (cn' "Ordinary Differential Equation") "ODE" [mathematics]
Expand Down
87 changes: 65 additions & 22 deletions code/drasil-data/Data/Drasil/Concepts/Physics.hs
Original file line number Diff line number Diff line change
@@ -1,33 +1,39 @@
module Data.Drasil.Concepts.Physics where

--This is obviously a bad name, but for now it will do until we come
-- up with a better one.
import Language.Drasil
import Utils.Drasil

import Data.Drasil.IdeaDicts (mathematics, physics)
import Data.Drasil.Concepts.Documentation (property, value)
import Data.Drasil.Concepts.Math (xComp, xDir, yComp, yDir)
import Control.Lens((^.)) --need for parametrization hack

physicCon :: [ConceptChunk]
physicCon = [rigidBody, velocity, friction, elasticity, energy, mechEnergy, collision, space,
cartesian, rightHand, restitutionCoef, acceleration, height,
momentOfInertia, force, impulseS, impulseV, displacement,
gravitationalAccel, gravitationalConst, position, distance,
time, torque, weight, fbd, linear, angular, tension, compression, stress,
strain, angDisp, angVelo, angAccel, linDisp, linVelo, linAccel,
joint, damping, pressure, cohesion, isotropy, kEnergy, chgInVelocity, potEnergy]
physicCon = [acceleration, angAccel, angDisp, angVelo, angular, chgInVelocity,
cohesion, collision, compression, constAccel, constAccelV, damping,
displacement, distance, elasticity, energy, fSpeed, fVel, fbd, force,
friction, gravity, gravitationalAccel, gravitationalConst, height, iPos,
iSpeed, iVel, impulseS, impulseV, isotropy, ixPos, ixVel, iyPos, iyVel,
joint, kEnergy, linAccel, linDisp, linVelo, linear, mechEnergy,
momentOfInertia, position, potEnergy, pressure, restitutionCoef, rectilinear,
rigidBody, scalarAccel, scalarPos, space, speed, strain, stress, tension,
time, torque, velocity, weight, xAccel, xConstAccel, xDist, xPos, xVel,
yAccel, yConstAccel, yDist, yPos, yVel]

physicCon' :: [CI]
physicCon' = [oneD, twoD, threeD]

rigidBody, velocity, friction, elasticity, energy, mechEnergy, collision, space,
cartesian, rightHand, restitutionCoef, acceleration, height,
momentOfInertia, force, impulseS, impulseV, displacement,
gravitationalAccel, gravitationalConst, position, distance,
time, torque, weight, fbd, linear, angular, tension, compression, stress,
strain, angDisp, angVelo, angAccel, linDisp, linVelo, linAccel,
joint, damping, pressure,cohesion, isotropy, kEnergy, chgInVelocity, potEnergy:: ConceptChunk
acceleration, angAccel, angDisp, angVelo, angular, chgInVelocity, cohesion,
collision, compression, constAccel, constAccelV, damping, displacement,
distance, elasticity, energy, fSpeed, fVel, fbd, force, friction, gravity,
gravitationalAccel, gravitationalConst, height, iPos, iSpeed, iVel, impulseS,
impulseV, isotropy, ixPos, ixVel, iyPos, iyVel, joint, kEnergy, linAccel,
linDisp, linVelo, linear, mechEnergy, momentOfInertia, position, potEnergy,
pressure, rectilinear, restitutionCoef, rigidBody, scalarAccel, scalarPos,
space, speed, strain, stress, tension, time, torque, velocity, weight,
xAccel, xConstAccel, xDist, xPos, xVel, yAccel, yConstAccel, yDist,
yPos, yVel :: ConceptChunk

oneD, twoD, threeD :: CI
oneD = commonIdeaWithDict "oneD" (cn "one-dimensional") "1D" [mathematics, physics]
Expand All @@ -38,6 +44,8 @@ rigidBody = dcc "rigidBody" (cnIES "rigid body")
"A solid body in which deformation is neglected."
velocity = dccWDS "velocity" (cnIES "velocity")
(S "The rate of change of a body's" +:+ phrase position)
speed = dccWDS "speed" (cn' "speed")
(S "The magnitude of the" +:+ phrase velocity +:+ S "vector")
friction = dcc "friction" (cn' "friction")
"The force resisting the relative motion of two surfaces."
elasticity = dcc "elasticity" (cnIES "elasticity")
Expand All @@ -53,11 +61,8 @@ collision = dcc "collision" (cn' "collision")
space = dcc "space" (cn' "space")
("A two-dimensional extent where objects and " ++
"events have relative positions and directions.")
cartesian = dcc "cartesian" (pn' "Cartesian coordinate system")
("A coordinate system that specifies each point uniquely in a plane by a " ++
"pair of numerical coordinates.")
rightHand = dcc "rightHand" (cn' "right-handed coordinate system")
"A coordinate system where the positive z-axis comes out of the screen."
rectilinear = dcc "rectilinear" (cn "rectilinear")
"Occuring in one dimension."

joint = dcc "joint" (cn' "joint") ("a connection between two rigid " ++
"bodies which allows movement with one or more degrees of freedom")
Expand All @@ -66,8 +71,12 @@ kEnergy = dccWDS "kEnergy" (cn "kinetic energy")
S "a body possess due to its motion.")
position = dcc "position" (cn' "position")
"An object's location relative to a reference point"
scalarPos = dccWDS "scalarPos" (cn' "scalar position")
(S "The magnitude of the " +:+ phrase position +:+ S "vector")
acceleration = dccWDS "acceleration" (cn' "acceleration")
(S "The rate of change of a body's" +:+ phrase velocity)
scalarAccel = dccWDS "scalarAccel" (cn' "scalar acceleration")
(S "The magnitude of the " +:+ phrase acceleration +:+ S "vector")
displacement = dccWDS "displacement" (cn' "displacement")
(S "The change in" +:+ (position ^. defn))
force = dcc "force" (cn' "force")
Expand All @@ -90,6 +99,38 @@ pressure = dccWDS "pressure" (cn' "pressure")
height = dccWDS "height" (cn' "height") (S "The" +:+ phrase distance +:+
S "above a reference point for a point of interest.")

-- Some variants of distance, speed, velocity, and scalar acceleration
-- FIXME: Complete all variants?
-- FIXME: Pull out commonalities?

xDist = dccWDS "xDist" (nounPhraseSent $ phrase distance +:+ S "in the" +:+ phrase xDir) (atStart distance +:+ S "in the" +:+ phrase xDir)
yDist = dccWDS "yDist" (nounPhraseSent $ phrase distance +:+ S "in the" +:+ phrase yDir) (atStart distance +:+ S "in the" +:+ phrase yDir)

iPos = dccWDS "iPos" (cn "initial position") (S "The" +:+ phrase position +:+ S "at the body's initial point")
xPos = dccWDS "xPos" (nounPhraseSent $ phrase xComp `sOf` phrase position) (S "The" +:+ phrase xComp `sOf` phrase position)
yPos = dccWDS "yPos" (nounPhraseSent $ phrase yComp `sOf` phrase position) (S "The" +:+ phrase yComp `sOf` phrase position)

ixPos = dccWDS "ixPos" (nounPhraseSent $ phrase xComp `sOf` phrase iPos) (S "The" +:+ phrase xComp `sOf` phrase iPos)
iyPos = dccWDS "iyPos" (nounPhraseSent $ phrase yComp `sOf` phrase iPos) (S "The" +:+ phrase yComp `sOf` phrase iPos)

fSpeed = dccWDS "fSpeed" (cn "final speed") (S "The" +:+ phrase speed +:+ S "at the body's final point")
iSpeed = dccWDS "iSpeed" (cn "initial speed") (S "The" +:+ phrase speed +:+ S "at the body's initial point")

fVel = dccWDS "fVel" (cn "final velocity") (S "The" +:+ phrase velocity +:+ S "at the body's final point")
iVel = dccWDS "iVel" (cn "initial velocity") (S "The" +:+ phrase velocity +:+ S "at the body's initial point")
xVel = dccWDS "xVel" (nounPhraseSent $ phrase xComp `sOf` phrase velocity) (S "The" +:+ phrase xComp `sOf` phrase velocity)
yVel = dccWDS "yVel" (nounPhraseSent $ phrase yComp `sOf` phrase velocity) (S "The" +:+ phrase yComp `sOf` phrase velocity)

ixVel = dccWDS "ixVel" (nounPhraseSent $ phrase xComp `sOf` phrase iVel) (S "The" +:+ phrase xComp `sOf` phrase iVel)
iyVel = dccWDS "iyVel" (nounPhraseSent $ phrase yComp `sOf` phrase iVel) (S "The" +:+ phrase yComp `sOf` phrase iVel)

xAccel = dccWDS "xScalAcc" (nounPhraseSent $ phrase xComp `sOf` phrase acceleration) (S "The" +:+ phrase xComp `sOf` phrase acceleration)
yAccel = dccWDS "yScalAcc" (nounPhraseSent $ phrase yComp `sOf` phrase acceleration) (S "The" +:+ phrase yComp `sOf` phrase acceleration)

constAccelV = dccWDS "constAccelV" (cn "constant acceleration vector") (S "The" +:+ phrase constAccel +:+ S "vector")
xConstAccel = dccWDS "xConstAccel" (nounPhraseSent $ phrase xComp `sOf` phrase constAccel) (S "The" +:+ phrase xComp `sOf` phrase constAccel)
yConstAccel = dccWDS "yConstAccel" (nounPhraseSent $ phrase yComp `sOf` phrase constAccel) (S "The" +:+ phrase yComp `sOf` phrase constAccel)

potEnergy = dccWDS "potEnergy" (cn "potential energy")
(S "The measure of the" +:+ phrase energy +:+
S "held by an object because of its" +:+ phrase position)
Expand All @@ -104,6 +145,8 @@ angVelo = dcc "angularVelocity"
angAccel = dcc "angularAcceleration"
(compoundPhrase' (angular ^. term) (acceleration ^. term))
"The rate of change of angular velocity"
constAccel = dcc "constantAcceleration"
(cn "constant acceleration") "A one-dimensional acceleration that is constant"
linDisp = dcc "linearDisplacement"
(compoundPhrase' (linear ^. term) (displacement ^. term))
"Movement in one direction along a single axis"
Expand All @@ -127,6 +170,7 @@ impulseV = dcc "impulseV" (cn "impulse (vector)")
"A force acting briefly on a body and producing a finite change of momentum in a given direction"
impulseS = dcc "impulseS" (cn "impulse (scalar)") "A force acting briefly on a body and producing a finite change of momentum"

gravity = dcc "gravity" (cn "gravity") "The force that attracts one physical body with mass to another."
gravitationalAccel = dcc "gravitationalAccel"
(cn "gravitational acceleration") "An expression used in physics to indicate the intensity of a gravitational field"
gravitationalConst = dcc "gravitationalConst" (cn "gravitational constant" )
Expand All @@ -152,8 +196,7 @@ damping = dcc "damping" (cn' "damping")
"An effect that tends to reduce the amplitude of vibrations"

cohesion = dccWDS "cohesion" (cn "cohesion") (S "An attractive" +:+
phrase force +:+ S "between adjacent particles that holds the matter" +:+
S "together.")
phrase force +:+. S "between adjacent particles that holds the matter together")

isotropy = dccWDS "isotropy" (cn "isotropy") (S "A condition where the" +:+
phrase value `sOf` S "a" +:+ phrase property +:+ S "is independent of" +:+
Expand Down
3 changes: 2 additions & 1 deletion code/drasil-data/Data/Drasil/People.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ spencerSmith, henryFrankis, nKoothoor, dParnas, daAruliah, gWilson,
wlBeason, tlKohutek, jmBracci, qhQian, dyZhu, cfLee, grChen, dgFredlund,
jKrahn, dStolle, yCLi, ymChen, tltZhan, ssLing, pjCleall, pGuo,
mCampidelli, dmWiess, sPalmer, scottSmith, bKarchewski, rHuston,
hJosephs, nrMorgenstern, vePrice, samCrawford :: Person
hJosephs, nrMorgenstern, vePrice, samCrawford, rcHibbeler :: Person

pjAgerfalk = person "PJ" "Agerfalk"
daAruliah = personWM "D" ["A"] "Aruliah"
Expand All @@ -32,6 +32,7 @@ rGuy = personWM "Richard" ["T"] "Guy"
pGuo = person "Peijun" "Guo"
shdHaddock = personWM "Steven" ["H", "D"] "Haddock"
alex = person "Alex" "Halliwushka"
rcHibbeler = personWM' "R" ["C"] "Hibbeler"
rHuston = person "Ronald" "Huston"
nChueHong = personWM "Neil" ["P"] "Chue Hong"
kdHuff = personWM "Kathryn" ["D"] "Huff"
Expand Down
Loading

0 comments on commit af2acf8

Please sign in to comment.