apecs-physics-0.4.2: 2D physics for apecs

Safe HaskellNone
LanguageHaskell2010

Apecs.Physics

Contents

Description

apecs-physics prelude

Synopsis

General

data Physics Source #

Uninhabited, should be added to the world as a component to add a physics space.

Instances
Component Physics Source # 
Instance details

Defined in Apecs.Physics.Space

Associated Types

type Storage Physics :: Type #

type Storage Physics Source # 
Instance details

Defined in Apecs.Physics.Space

Space

newtype Gravity Source #

Gravity force vector, global value

Constructors

Gravity Vec 
Instances
Eq Gravity Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

(==) :: Gravity -> Gravity -> Bool #

(/=) :: Gravity -> Gravity -> Bool #

Show Gravity Source # 
Instance details

Defined in Apecs.Physics.Types

Component Gravity Source # 
Instance details

Defined in Apecs.Physics.Space

Associated Types

type Storage Gravity :: Type #

Has w IO Physics => Has w IO Gravity Source # 
Instance details

Defined in Apecs.Physics.Space

type Storage Gravity Source # 
Instance details

Defined in Apecs.Physics.Space

newtype Iterations Source #

Number of iterations per step, global value

Constructors

Iterations Int 
Instances
Eq Iterations Source # 
Instance details

Defined in Apecs.Physics.Types

Show Iterations Source # 
Instance details

Defined in Apecs.Physics.Types

Component Iterations Source # 
Instance details

Defined in Apecs.Physics.Space

Associated Types

type Storage Iterations :: Type #

Has w IO Physics => Has w IO Iterations Source # 
Instance details

Defined in Apecs.Physics.Space

type Storage Iterations Source # 
Instance details

Defined in Apecs.Physics.Space

Body

When you give an entity a Body component in 'apecs-physics', the physics engine will also give this entity a number of sub-components. These sub-components may be read and written separately from the actualy Body itself, which makes the library both more expressive (as you can only write about the parts of a physics body you actually want to view or change) and more performant (as only the changed parts of a body actually need to be updated when you write to them).

data Body Source #

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.

Instances
Enum Body Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

succ :: Body -> Body #

pred :: Body -> Body #

toEnum :: Int -> Body #

fromEnum :: Body -> Int #

enumFrom :: Body -> [Body] #

enumFromThen :: Body -> Body -> [Body] #

enumFromTo :: Body -> Body -> [Body] #

enumFromThenTo :: Body -> Body -> Body -> [Body] #

Eq Body Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

(==) :: Body -> Body -> Bool #

(/=) :: Body -> Body -> Bool #

Ord Body Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

compare :: Body -> Body -> Ordering #

(<) :: Body -> Body -> Bool #

(<=) :: Body -> Body -> Bool #

(>) :: Body -> Body -> Bool #

(>=) :: Body -> Body -> Bool #

max :: Body -> Body -> Body #

min :: Body -> Body -> Body #

Component Body Source # 
Instance details

Defined in Apecs.Physics.Body

Associated Types

type Storage Body :: Type #

Has w IO Physics => Has w IO Body Source # 
Instance details

Defined in Apecs.Physics.Body

type Storage Body Source # 
Instance details

Defined in Apecs.Physics.Body

newtype Position Source #

A subcomponent of Body representing where it is in world coordinates.

Constructors

Position WVec 
Instances
Component Position Source # 
Instance details

Defined in Apecs.Physics.Body

Associated Types

type Storage Position :: Type #

Has w IO Physics => Has w IO Position Source # 
Instance details

Defined in Apecs.Physics.Body

type Storage Position Source # 
Instance details

Defined in Apecs.Physics.Body

newtype Velocity Source #

A subcomponent of Body representing where it is going in world coordinates

Constructors

Velocity WVec 
Instances
Component Velocity Source # 
Instance details

Defined in Apecs.Physics.Body

Associated Types

type Storage Velocity :: Type #

Has w IO Physics => Has w IO Velocity Source # 
Instance details

Defined in Apecs.Physics.Body

type Storage Velocity Source # 
Instance details

Defined in Apecs.Physics.Body

newtype Angle Source #

Constructors

Angle Double 
Instances
Eq Angle Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

(==) :: Angle -> Angle -> Bool #

(/=) :: Angle -> Angle -> Bool #

Show Angle Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

showsPrec :: Int -> Angle -> ShowS #

show :: Angle -> String #

showList :: [Angle] -> ShowS #

Component Angle Source # 
Instance details

Defined in Apecs.Physics.Body

Associated Types

type Storage Angle :: Type #

Has w IO Physics => Has w IO Angle Source # 
Instance details

Defined in Apecs.Physics.Body

type Storage Angle Source # 
Instance details

Defined in Apecs.Physics.Body

newtype AngularVelocity Source #

Constructors

AngularVelocity Double 
Instances
Component AngularVelocity Source # 
Instance details

Defined in Apecs.Physics.Body

Associated Types

type Storage AngularVelocity :: Type #

Has w IO Physics => Has w IO AngularVelocity Source # 
Instance details

Defined in Apecs.Physics.Body

type Storage AngularVelocity Source # 
Instance details

Defined in Apecs.Physics.Body

newtype Force Source #

A component used to apply a force to a Body. The force is applied to the body's center of gravity. This component is reset to Vec 0 0 after every stimulation step, so it is mainly used to apply a force as opposed to being read.

Constructors

Force Vec 
Instances
Component Force Source # 
Instance details

Defined in Apecs.Physics.Body

Associated Types

type Storage Force :: Type #

Has w IO Physics => Has w IO Force Source # 
Instance details

Defined in Apecs.Physics.Body

type Storage Force Source # 
Instance details

Defined in Apecs.Physics.Body

newtype BodyMass Source #

A component representing the mass of the Body overall.

Constructors

BodyMass Double 
Instances
Eq BodyMass Source # 
Instance details

Defined in Apecs.Physics.Types

Show BodyMass Source # 
Instance details

Defined in Apecs.Physics.Types

Component BodyMass Source # 
Instance details

Defined in Apecs.Physics.Body

Associated Types

type Storage BodyMass :: Type #

Has w IO Physics => Has w IO BodyMass Source # 
Instance details

Defined in Apecs.Physics.Body

type Storage BodyMass Source # 
Instance details

Defined in Apecs.Physics.Body

newtype Moment Source #

The moment of inertia of the Body. This is basically the body's tendency to resist angular acceleration.

Constructors

Moment Double 
Instances
Eq Moment Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

(==) :: Moment -> Moment -> Bool #

(/=) :: Moment -> Moment -> Bool #

Show Moment Source # 
Instance details

Defined in Apecs.Physics.Types

Component Moment Source # 
Instance details

Defined in Apecs.Physics.Body

Associated Types

type Storage Moment :: Type #

Has w IO Physics => Has w IO Moment Source # 
Instance details

Defined in Apecs.Physics.Body

type Storage Moment Source # 
Instance details

Defined in Apecs.Physics.Body

newtype CenterOfGravity Source #

Where the Body's center of gravity is, in body-local coordinates. Can be read and written to.

Constructors

CenterOfGravity BVec 
Instances
Component CenterOfGravity Source # 
Instance details

Defined in Apecs.Physics.Body

Associated Types

type Storage CenterOfGravity :: Type #

Has w IO Physics => Has w IO CenterOfGravity Source # 
Instance details

Defined in Apecs.Physics.Body

type Storage CenterOfGravity Source # 
Instance details

Defined in Apecs.Physics.Body

newtype Torque Source #

A component used to apply a torque to a Body. The torque is applied to the entire body at once. This component is reset to 0 after every simulation step, so it is mainly used to apply a torque as opposed to being read.

Constructors

Torque Double 
Instances
Component Torque Source # 
Instance details

Defined in Apecs.Physics.Body

Associated Types

type Storage Torque :: Type #

Has w IO Physics => Has w IO Torque Source # 
Instance details

Defined in Apecs.Physics.Body

type Storage Torque Source # 
Instance details

Defined in Apecs.Physics.Body

newtype ShapeList Source #

The Shapes belonging to a body. Read-only.

Constructors

ShapeList [Entity] 
Instances
Component ShapeList Source # 
Instance details

Defined in Apecs.Physics.Body

Associated Types

type Storage ShapeList :: Type #

Has w IO Physics => Has w IO ShapeList Source # 
Instance details

Defined in Apecs.Physics.Body

type Storage ShapeList Source # 
Instance details

Defined in Apecs.Physics.Body

newtype ConstraintList Source #

The Constraints belonging to a body. Read-only.

Constructors

ConstraintList [Entity] 
Instances
Component ConstraintList Source # 
Instance details

Defined in Apecs.Physics.Body

Associated Types

type Storage ConstraintList :: Type #

Has w IO Physics => Has w IO ConstraintList Source # 
Instance details

Defined in Apecs.Physics.Body

type Storage ConstraintList Source # 
Instance details

Defined in Apecs.Physics.Body

Shape

data Convex Source #

A convex polygon. Consists of a list of vertices, and a radius.

Constructors

Convex [BVec] Double 
Instances
Eq Convex Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

(==) :: Convex -> Convex -> Bool #

(/=) :: Convex -> Convex -> Bool #

Show Convex Source # 
Instance details

Defined in Apecs.Physics.Types

data Shape Source #

Shape component. Adding a shape to an entity that has no Body is a noop.

Constructors

Shape Entity Convex 
Instances
Component Shape Source # 
Instance details

Defined in Apecs.Physics.Shape

Associated Types

type Storage Shape :: Type #

Has w IO Physics => Has w IO Shape Source # 
Instance details

Defined in Apecs.Physics.Shape

type Storage Shape Source # 
Instance details

Defined in Apecs.Physics.Shape

newtype Mass Source #

The mass of a shape is technically a measure of how much resistance it has to being accelerated, but it's generally easier to understand it as being how "heavy" something is.

The physics engine lets you set this, and it will calculate the Density and other components for you.

See https://en.wikipedia.org/wiki/Mass for more information.

Constructors

Mass Double 
Instances
Eq Mass Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

(==) :: Mass -> Mass -> Bool #

(/=) :: Mass -> Mass -> Bool #

Show Mass Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

showsPrec :: Int -> Mass -> ShowS #

show :: Mass -> String #

showList :: [Mass] -> ShowS #

Component Mass Source # 
Instance details

Defined in Apecs.Physics.Shape

Associated Types

type Storage Mass :: Type #

Has w IO Physics => Has w IO Mass Source # 
Instance details

Defined in Apecs.Physics.Shape

type Storage Mass Source # 
Instance details

Defined in Apecs.Physics.Shape

newtype Density Source #

The density of a shape is a measure of how much mass an object has in a given volume.

The physics engine lets you set this, and it will calculate the Mass and other components for you.

See https://en.wikipedia.org/wiki/Density for more information.

Constructors

Density Double 
Instances
Eq Density Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

(==) :: Density -> Density -> Bool #

(/=) :: Density -> Density -> Bool #

Show Density Source # 
Instance details

Defined in Apecs.Physics.Types

Component Density Source # 
Instance details

Defined in Apecs.Physics.Shape

Associated Types

type Storage Density :: Type #

Has w IO Physics => Has w IO Density Source # 
Instance details

Defined in Apecs.Physics.Shape

type Storage Density Source # 
Instance details

Defined in Apecs.Physics.Shape

newtype Sensor Source #

If a body is a Sensor, it exists only to trigger collision responses. It won't phyiscally interact with other bodies in any way, but it will cause collision handlers to run.

Constructors

Sensor Bool 
Instances
Eq Sensor Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

(==) :: Sensor -> Sensor -> Bool #

(/=) :: Sensor -> Sensor -> Bool #

Show Sensor Source # 
Instance details

Defined in Apecs.Physics.Types

Component Sensor Source # 
Instance details

Defined in Apecs.Physics.Shape

Associated Types

type Storage Sensor :: Type #

Has w IO Physics => Has w IO Sensor Source # 
Instance details

Defined in Apecs.Physics.Shape

type Storage Sensor Source # 
Instance details

Defined in Apecs.Physics.Shape

newtype Friction Source #

The friction of an object is a measure of how much it resists movement. Shapes with high friction will naturally slow down more quickly over time than objects with low friction.

See https://en.wikipedia.org/wiki/Friction for more information.

Constructors

Friction Double 
Instances
Eq Friction Source # 
Instance details

Defined in Apecs.Physics.Types

Show Friction Source # 
Instance details

Defined in Apecs.Physics.Types

Component Friction Source # 
Instance details

Defined in Apecs.Physics.Shape

Associated Types

type Storage Friction :: Type #

Has w IO Physics => Has w IO Friction Source # 
Instance details

Defined in Apecs.Physics.Shape

type Storage Friction Source # 
Instance details

Defined in Apecs.Physics.Shape

newtype Elasticity Source #

The elasticity of a shape. Higher elasticities will create more elastic collisions, IE, will be bouncier.

See https://en.wikipedia.org/wiki/Elasticity_(physics) for more information.

Constructors

Elasticity Double 
Instances
Eq Elasticity Source # 
Instance details

Defined in Apecs.Physics.Types

Show Elasticity Source # 
Instance details

Defined in Apecs.Physics.Types

Component Elasticity Source # 
Instance details

Defined in Apecs.Physics.Shape

Associated Types

type Storage Elasticity :: Type #

Has w IO Physics => Has w IO Elasticity Source # 
Instance details

Defined in Apecs.Physics.Shape

type Storage Elasticity Source # 
Instance details

Defined in Apecs.Physics.Shape

data CollisionFilter Source #

Collision Filters determine what shapes this shape collides with. Shapes in the same filterGroup will never collide with one another. This is used to ignore collisions between parts on a complex object.

filterCategories is a bitmask that determines what categories a shape belongs to. filterMask is a bitmask that determines what categories it collides with. See https://chipmunk-physics.net/release/ChipmunkLatest-Docs/#cpShape-Filtering for more information.

Constructors

CollisionFilter 

Fields

newtype CollisionType Source #

A Shape can have a CollisionType. CollisionTypes are used by callbacks for filtering, also see CollisionSource. The difference between CollisionType and CollisionFilter is that a CollisionFilter determines whether two shapes in the physics engine collide, or pass through one another, whereas a CollisionType determines what callback is called. In general, if you don't want any special checks to happen, use CollisionFilter.

Constructors

CollisionType CUIntPtr 

maskList :: [Int] -> Bitmask Source #

Makes a bitmask from a list of indices

boxShape :: Double -> Double -> Vec -> Convex Source #

A box with the given height, width, and center point

Constraint

data Constraint Source #

Instances
Eq Constraint Source # 
Instance details

Defined in Apecs.Physics.Types

Show Constraint Source # 
Instance details

Defined in Apecs.Physics.Types

Component Constraint Source # 
Instance details

Defined in Apecs.Physics.Constraint

Associated Types

type Storage Constraint :: Type #

Has w IO Physics => Has w IO Constraint Source # 
Instance details

Defined in Apecs.Physics.Constraint

type Storage Constraint Source # 
Instance details

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

A PinJoint with minimum and maximum distance

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

The first two vectors are the start and end of the groove on body A, the third argument is the anchor point on body B.

DampedSpring BVec BVec Double Double Double

Spring between two anchor points, with given rest length, stiffness, and damping.

DampedRotarySpring Double Double Double

Rotary sping, with given rest angle, stiffness, and damping.

RotaryLimitJoint Double Double

Joint with minimum and maximum angle

RatchetJoint Double Double

Rathet joint with given phase and ratchet (distance between clicks).

GearJoint Double Double 
SimpleMotor Double

Keeps relative angular velocity constant

newtype MaxForce Source #

Constructors

MaxForce Double 
Instances
Eq MaxForce Source # 
Instance details

Defined in Apecs.Physics.Types

Show MaxForce Source # 
Instance details

Defined in Apecs.Physics.Types

Component MaxForce Source # 
Instance details

Defined in Apecs.Physics.Constraint

Associated Types

type Storage MaxForce :: Type #

Has w IO Physics => Has w IO MaxForce Source # 
Instance details

Defined in Apecs.Physics.Constraint

type Storage MaxForce Source # 
Instance details

Defined in Apecs.Physics.Constraint

newtype MaxBias Source #

Constructors

MaxBias Double 
Instances
Eq MaxBias Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

(==) :: MaxBias -> MaxBias -> Bool #

(/=) :: MaxBias -> MaxBias -> Bool #

Show MaxBias Source # 
Instance details

Defined in Apecs.Physics.Types

Component MaxBias Source # 
Instance details

Defined in Apecs.Physics.Constraint

Associated Types

type Storage MaxBias :: Type #

Has w IO Physics => Has w IO MaxBias Source # 
Instance details

Defined in Apecs.Physics.Constraint

type Storage MaxBias Source # 
Instance details

Defined in Apecs.Physics.Constraint

newtype ErrorBias Source #

Constructors

ErrorBias Double 
Instances
Eq ErrorBias Source # 
Instance details

Defined in Apecs.Physics.Types

Show ErrorBias Source # 
Instance details

Defined in Apecs.Physics.Types

Component ErrorBias Source # 
Instance details

Defined in Apecs.Physics.Constraint

Associated Types

type Storage ErrorBias :: Type #

Has w IO Physics => Has w IO ErrorBias Source # 
Instance details

Defined in Apecs.Physics.Constraint

type Storage ErrorBias Source # 
Instance details

Defined in Apecs.Physics.Constraint

newtype Impulse Source #

Constructors

Impulse Double 
Instances
Eq Impulse Source # 
Instance details

Defined in Apecs.Physics.Types

Methods

(==) :: Impulse -> Impulse -> Bool #

(/=) :: Impulse -> Impulse -> Bool #

Show Impulse Source # 
Instance details

Defined in Apecs.Physics.Types

Component Impulse Source # 
Instance details

Defined in Apecs.Physics.Constraint

Associated Types

type Storage Impulse :: Type #

Has w IO Physics => Has w IO Impulse Source # 
Instance details

Defined in Apecs.Physics.Constraint

type Storage Impulse Source # 
Instance details

Defined in Apecs.Physics.Constraint

Collision

data CollisionHandler Source #

Constructors

CollisionHandler 

Fields

  • source :: CollisionSource
     
  • beginCB :: Maybe BeginCB

    A callback called when two bodies start touching for the first time. If it returns True, the physics engine will process the collision normally. If it returns False, the physics engine will ignore the collision entirely.

  • separateCB :: Maybe SeparateCB

    A callback called when two bodies have just stopped touching. This will always be called if beginCB is, regardless of the return value of beginCB.

  • preSolveCB :: Maybe PreSolveCB

    A callback called when two bodies are touching during a physics step. If this function returns True, the collision will be processed normally. If it returns 'False, then the physics engine will stop processing the collision for this step.

  • postSolveCB :: Maybe PostSolveCB

    A callback called when two bodies are touching after the response to the collision has been processed. This means that you can determine the collision impulse or kinetic energy in this callback, if you need that for processing.

Instances
Component CollisionHandler Source # 
Instance details

Defined in Apecs.Physics.Collision

Associated Types

type Storage CollisionHandler :: Type #

Has w IO Physics => Has w IO CollisionHandler Source # 
Instance details

Defined in Apecs.Physics.Collision

type Storage CollisionHandler Source # 
Instance details

Defined in Apecs.Physics.Collision

data CollisionSource Source #

A CollisionSource determines what types of collisions a callback handles. Also see CollisionType

Query

data PointQueryResult Source #

Constructors

PointQueryResult 

Fields

  • pqShape :: Entity

    What entity did this query connect with?

  • pqPoint :: WVec

    The closest point on the shape's surface (in world space)

  • pqDistance :: Double

    The distance to the queried point

  • pqGradient :: Vec

    The gradient of the distance function. This should be similar to 'pqPoint'/'pqDistance' but accurate even for very small distances.

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.

type BVec = Vec Source #

Type synonym indicating that a vector is expected to be in body-space coordinates

type WVec = Vec Source #

Type synonym indicating that a vector is expected to be in world-space coordinates

module Apecs

module Linear.V2