| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Apecs.Physics
Description
apecs-physics prelude
Synopsis
- data Physics
- newtype Gravity = Gravity Vec
- newtype Iterations = Iterations Int
- stepPhysics :: Has w IO Physics => Double -> System w ()
- earthGravity :: Gravity
- data Body
- newtype Position = Position WVec
- newtype Velocity = Velocity WVec
- newtype Angle = Angle Double
- newtype AngularVelocity = AngularVelocity Double
- newtype Force = Force Vec
- newtype BodyMass = BodyMass Double
- newtype Moment = Moment Double
- newtype CenterOfGravity = CenterOfGravity BVec
- newtype Torque = Torque Double
- data Convex = Convex [BVec] Double
- data Shape
- newtype Mass = Mass Double
- newtype Density = Density Double
- newtype Sensor = Sensor Bool
- newtype Friction = Friction Double
- newtype Elasticity = Elasticity Double
- newtype SurfaceVelocity = SurfaceVelocity Vec
- data CollisionFilter = CollisionFilter {
- filterGroup :: CollisionGroup
- filterCategories :: Bitmask
- filterMask :: Bitmask
- maskAll :: Bitmask
- maskNone :: Bitmask
- maskList :: [Int] -> Bitmask
- defaultFilter :: CollisionFilter
- boxShape :: Double -> Double -> Vec -> Convex
- data Constraint
- data ConstraintType
- = PinJoint BVec BVec
- | SlideJoint BVec BVec Double Double
- | PivotJoint WVec
- | PivotJoint2 BVec BVec
- | GrooveJoint BVec BVec BVec
- | DampedSpring BVec BVec Double Double Double
- | DampedRotarySpring Double Double Double
- | RotaryLimitJoint Double Double
- | RatchetJoint Double Double
- | GearJoint Double Double
- | SimpleMotor Double
- newtype MaxForce = MaxForce Double
- newtype MaxBias = MaxBias Double
- newtype ErrorBias = ErrorBias Double
- newtype CollideBodies = CollideBodies Bool
- data Collision = Collision {
- collisionNormal :: Vec
- collisionA :: Entity
- collisionB :: Entity
- data CollisionHandler = CollisionHandler {}
- defaultHandler :: CollisionHandler
- data CollisionSource
- data BeginCB
- data SeparateCB
- data PreSolveCB
- data PostSolveCB
- mkBeginCB :: (Collision -> System w Bool) -> System w BeginCB
- mkSeparateCB :: (Collision -> System w ()) -> System w SeparateCB
- mkPreSolveCB :: (Collision -> System w Bool) -> System w PreSolveCB
- mkPostSolveCB :: (Collision -> System w ()) -> System w PostSolveCB
- data PointQueryResult = PointQueryResult {
- pqShape :: Entity
- pqPoint :: WVec
- pqDistance :: Double
- pqGradient :: Double
- pointQuery :: Has w IO Physics => WVec -> Double -> CollisionFilter -> System w (Maybe PointQueryResult)
- vertices :: Convex -> [BVec]
- mapVertices :: (BVec -> BVec) -> Convex -> Convex
- shift :: BVec -> Convex -> Convex
- getRadius :: Convex -> Double
- setRadius :: Double -> Convex -> Convex
- cCircle :: Double -> Convex
- zCircle :: Double -> Convex
- oCircle :: BVec -> Double -> Convex
- hLine :: Double -> Convex
- vLine :: Double -> Convex
- cRectangle :: BVec -> Convex
- oRectangle :: BVec -> BVec -> Convex
- zRectangle :: BVec -> Convex
- toEdges :: Convex -> [Convex]
- gridLines :: Vec -> Int -> Int -> [Convex]
- module Apecs
- module Linear.V2
General
Uninhabited data type for constructing a world with a chipmunk space.
Space
Gravity force vector, global value
Constructors
| Gravity Vec |
newtype Iterations Source #
Number of iterations per step, global value
Constructors
| Iterations Int |
Instances
| Component Iterations # | |
Defined in Apecs.Physics.Space Associated Types type Storage Iterations :: * # | |
| Has w IO Physics => Has w IO Iterations # | |
Defined in Apecs.Physics.Space | |
| type Storage Iterations # | |
Defined in Apecs.Physics.Space | |
Body
Added to a component to add it to the physics space.
Deleting it will also delete all associated shapes and constraints.
A body has a number of subcomponents: Position, Velocity, Force, Torque, BodyMass, Moment, Angle, AngularVelocity, and CenterOfGravity.
These components cannot be added or removed from an entity, but rather are present as long as the entity has a Body.
Constructors
| DynamicBody | |
| KinematicBody | |
| StaticBody |
Constructors
| Position WVec |
Constructors
| Velocity WVec |
newtype AngularVelocity Source #
Constructors
| AngularVelocity Double |
Instances
| Component AngularVelocity # | |
Defined in Apecs.Physics.Body Associated Types type Storage AngularVelocity :: * # | |
| Has w IO Physics => Has w IO AngularVelocity # | |
Defined in Apecs.Physics.Body | |
| type Storage AngularVelocity # | |
Defined in Apecs.Physics.Body | |
Constructors
| Force Vec |
newtype CenterOfGravity Source #
Constructors
| CenterOfGravity BVec |
Instances
| Component CenterOfGravity # | |
Defined in Apecs.Physics.Body Associated Types type Storage CenterOfGravity :: * # | |
| Has w IO Physics => Has w IO CenterOfGravity # | |
Defined in Apecs.Physics.Body | |
| type Storage CenterOfGravity # | |
Defined in Apecs.Physics.Body | |
Shape
A convex polygon. Consists of a list of vertices, and a radius.
Shape component.
Adding a shape to an entity that has no Body is a noop.
Constructors
| Shape Convex | |
| ShapeExtend Entity Convex |
newtype Elasticity Source #
Constructors
| Elasticity Double |
Instances
| Eq Elasticity Source # | |
Defined in Apecs.Physics.Types | |
| Show Elasticity Source # | |
Defined in Apecs.Physics.Types Methods showsPrec :: Int -> Elasticity -> ShowS # show :: Elasticity -> String # showList :: [Elasticity] -> ShowS # | |
| Component Elasticity # | |
Defined in Apecs.Physics.Shape Associated Types type Storage Elasticity :: * # | |
| Has w IO Physics => Has w IO Elasticity # | |
Defined in Apecs.Physics.Shape | |
| type Storage Elasticity # | |
Defined in Apecs.Physics.Shape | |
newtype SurfaceVelocity Source #
Constructors
| SurfaceVelocity Vec |
Instances
| Eq SurfaceVelocity Source # | |
Defined in Apecs.Physics.Types Methods (==) :: SurfaceVelocity -> SurfaceVelocity -> Bool # (/=) :: SurfaceVelocity -> SurfaceVelocity -> Bool # | |
| Show SurfaceVelocity Source # | |
Defined in Apecs.Physics.Types Methods showsPrec :: Int -> SurfaceVelocity -> ShowS # show :: SurfaceVelocity -> String # showList :: [SurfaceVelocity] -> ShowS # | |
| Component SurfaceVelocity # | |
Defined in Apecs.Physics.Shape Associated Types type Storage SurfaceVelocity :: * # | |
| Has w IO Physics => Has w IO SurfaceVelocity # | |
Defined in Apecs.Physics.Shape | |
| type Storage SurfaceVelocity # | |
Defined in Apecs.Physics.Shape | |
data CollisionFilter Source #
Constructors
| CollisionFilter | |
Fields
| |
Instances
| Eq CollisionFilter Source # | |
Defined in Apecs.Physics.Types Methods (==) :: CollisionFilter -> CollisionFilter -> Bool # (/=) :: CollisionFilter -> CollisionFilter -> Bool # | |
| Show CollisionFilter Source # | |
Defined in Apecs.Physics.Types Methods showsPrec :: Int -> CollisionFilter -> ShowS # show :: CollisionFilter -> String # showList :: [CollisionFilter] -> ShowS # | |
| Component CollisionFilter # | |
Defined in Apecs.Physics.Shape Associated Types type Storage CollisionFilter :: * # | |
| Has w IO Physics => Has w IO CollisionFilter # | |
Defined in Apecs.Physics.Shape | |
| type Storage CollisionFilter # | |
Defined in Apecs.Physics.Shape | |
Constraint
data Constraint Source #
Constructors
| Constraint Entity ConstraintType | |
| ConstraintExtend Entity Entity ConstraintType | |
| ConstraintRead |
Instances
| Component Constraint # | |
Defined in Apecs.Physics.Constraint Associated Types type Storage Constraint :: * # | |
| Has w IO Physics => Has w IO Constraint # | |
Defined in Apecs.Physics.Constraint | |
| type Storage Constraint # | |
Defined in Apecs.Physics.Constraint | |
data ConstraintType Source #
Constructors
| PinJoint BVec BVec | Maintains a fixed distance between two anchor points |
| SlideJoint BVec BVec Double Double | |
| PivotJoint WVec | Creates a pivot point at the given world coordinate |
| PivotJoint2 BVec BVec | Creates a pivot point at the given body coordinates |
| GrooveJoint BVec BVec BVec | |
| DampedSpring BVec BVec Double Double Double | |
| DampedRotarySpring Double Double Double | |
| RotaryLimitJoint Double Double | |
| RatchetJoint Double Double | |
| GearJoint Double Double | |
| SimpleMotor Double |
newtype CollideBodies Source #
Constructors
| CollideBodies Bool |
Instances
| Component CollideBodies # | |
Defined in Apecs.Physics.Constraint Associated Types type Storage CollideBodies :: * # | |
| Has w IO Physics => Has w IO CollideBodies # | |
Defined in Apecs.Physics.Constraint | |
| type Storage CollideBodies # | |
Defined in Apecs.Physics.Constraint | |
Collision
Constructors
| Collision | |
Fields
| |
data CollisionHandler Source #
Constructors
| CollisionHandler | |
Fields | |
Instances
| Component CollisionHandler # | |
Defined in Apecs.Physics.Collision Associated Types type Storage CollisionHandler :: * # | |
| Has w IO Physics => Has w IO CollisionHandler # | |
Defined in Apecs.Physics.Collision | |
| type Storage CollisionHandler # | |
Defined in Apecs.Physics.Collision | |
data CollisionSource Source #
data SeparateCB Source #
data PreSolveCB Source #
data PostSolveCB Source #
mkSeparateCB :: (Collision -> System w ()) -> System w SeparateCB Source #
mkPreSolveCB :: (Collision -> System w Bool) -> System w PreSolveCB Source #
mkPostSolveCB :: (Collision -> System w ()) -> System w PostSolveCB Source #
Query
data PointQueryResult Source #
Constructors
| PointQueryResult | |
Fields
| |
Instances
| Eq PointQueryResult Source # | |
Defined in Apecs.Physics.Types Methods (==) :: PointQueryResult -> PointQueryResult -> Bool # (/=) :: PointQueryResult -> PointQueryResult -> Bool # | |
| Show PointQueryResult Source # | |
Defined in Apecs.Physics.Types Methods showsPrec :: Int -> PointQueryResult -> ShowS # show :: PointQueryResult -> String # showList :: [PointQueryResult] -> ShowS # | |
| Storable PointQueryResult # | |
Defined in Apecs.Physics.Query Methods sizeOf :: PointQueryResult -> Int # alignment :: PointQueryResult -> Int # peekElemOff :: Ptr PointQueryResult -> Int -> IO PointQueryResult # pokeElemOff :: Ptr PointQueryResult -> Int -> PointQueryResult -> IO () # peekByteOff :: Ptr b -> Int -> IO PointQueryResult # pokeByteOff :: Ptr b -> Int -> PointQueryResult -> IO () # peek :: Ptr PointQueryResult -> IO PointQueryResult # poke :: Ptr PointQueryResult -> PointQueryResult -> IO () # | |
pointQuery :: Has w IO Physics => WVec -> Double -> CollisionFilter -> System w (Maybe PointQueryResult) Source #
Geometry
mapVertices :: (BVec -> BVec) -> Convex -> Convex Source #
Map a function over all vertices
shift :: BVec -> Convex -> Convex Source #
Translates all vertices. The name shift is to prevent collisions with gloss
cRectangle :: BVec -> Convex Source #
Centered rectangle with a given size
oRectangle :: BVec -> BVec -> Convex Source #
Rectangle with a given origin and size
zRectangle :: BVec -> Convex Source #
Rectangle with origin 0 and given size
toEdges :: Convex -> [Convex] Source #
Split a shape into its edges. Will return no edges for points, but returns 2 for a line (in opposite directions)
gridLines :: Vec -> Int -> Int -> [Convex] Source #
A set of lines forming a grid. Returns (r + c + 2) segments.
module Apecs
module Linear.V2