chiphunk-0.1.1.0: Haskell bindings for Chipmunk2D physics engine

Safe HaskellNone
LanguageHaskell2010

Chiphunk.Low

Contents

Description

Chiphunk is a low-level Haskell bindings for the Chipmunk2D physics engine. It includes most (almost all) of the functions mentioned in the main documentation for Chipmunk2D, except for some (relatively) exotic ones, which may be added later per request.

Synopsis

Disclaymer

This bindings are so low-level so that they even require you to free the memory the Chipmunk2D has allocated for your objects. Module with more high-level api can be built around this low-level bingings at some point, in the meantime, however, you're advised to provide wrapper layer for your games so that you do not have to keep track of such things in the core of your game's logic.

See below for an adoptation of the original Chipmunk documentation available here. I've skipped some sections not related to the bindings, like the reason author chose C language in the first place and limitations of the C api. Obviously, it's thanks to that choice that I was able to write bindings around the library in Haskell.

Howling Moon Software is not affiliated with this bindings. In all of the following "I" refers to the original documentation author for Chipmunk2D.

Chipmunk2D 7.0.2

Chipmunk2D is a 2D rigid body physics library distributed under the MIT license. It is blazingly fast, portable, numerically stable, and easy to use. For this reason it has been used in hundreds of games across just about every system you can name. This includes top quality titles such as Night Sky for the Wii and many #1 sellers on the iPhone App Store! I’ve put thousands of hours of work over many years to make Chipmunk2D what it is today. If you find Chipmunk2D has saved you a lot of time, please consider donating. You’ll make an indie game developer very happy!

First of all, I would like to give a Erin Catto a big thank you, as Chipmunk2D’s impulse solver was directly inspired by his example code way back in 2006. (Now a full fledged physics engine all its own: Box2D.org). His contact persistence idea allows for stable stacks of objects with very few iterations of the solver. My previous solver produced mushy piles of objects or required a large amount of CPU to operate stably.

Support

The best way to get support is to visit the Chipmunk Forums. There are plenty of people around using Chipmunk on the just about every platform I’ve ever heard of. If you are working on a commercial project, Howling Moon Software (my company) is available for contracting. We can help with implementing custom Chipmunk behaviors, as well as priority bug fixes and performance tuning.

Contact

If you find any bugs in Chipmunk, errors or broken links in this document, or have a question or comment about Chipmunk you can contact me at slembcke(at)gmail(dot)com. (email or GTalk)

License

Chipmunk is licensed under the MIT license.

Copyright (c) 2007-2015 Scott Lembcke and Howling Moon Software

Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the Software), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:

The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
SOFTWARE.

This means that you do not have to buy a license or pay to use Chipmunk in commercial projects. (Though we really appreciate donations)

Links

  • Chipmunk Forums – The official forum Chipmunk2D forum.
  • Howling Moon Software – The software company I co-founded. (We are available for contract work!)
  • Games – A small list of games we know that use Chipmunk.

Hello Chipmunk (World)

Hello world Chipmunk style. Create a simple simulation where a ball falls onto a static line segment, then rolls off. Print out the coordinates of the ball.

main :: IO ()
main = do
  let gravity = Vect 0 (-100)

  -- Create an empty space.
  space <- spaceNew
  spaceGravity space $= gravity

  -- Add a static line segment shape for the ground.
  -- We'll make it slightly tilted so the ball will roll off.
  -- We attach it to a static body to tell Chipmunk it shouldn't be movable.
  static <- get $ spaceStaticBody space
  ground <- segmentShapeNew static (Vect (-20) 5) (Vect 20 (-5)) 0
  shapeFriction ground $= 1
  spaceAddShape space ground

  -- Now let's make a ball that falls onto the line and rolls off.
  -- First we need to make a cpBody to hold the physical properties of the object.
  -- These include the mass, position, velocity, angle, etc. of the object.
  -- Then we attach collision shapes to the Body to give it a size and shape.

  let radius = 5
  let mass = 1

  -- The moment of inertia is like mass for rotation
  -- Use the momentFor* functions to help you approximate it.
  let moment = momentForCircle mass 0 radius (Vect 0 0)

  -- The spaceAdd* functions return the thing that you are adding.
  ballBody <- bodyNew mass moment
  spaceAddBody space ballBody
  bodyPosition ballBody $= Vect 0 15

  -- Now we create the collision shape for the ball.
  -- You can create multiple collision shapes that point to the same body.
  -- They will all be attached to the body and move around to follow it.
  ballShape <- circleShapeNew ballBody radius (Vect 0 0)
  spaceAddShape space ballShape
  shapeFriction ballShape $= 0.7

  -- Now that it's all set up, we simulate all the objects in the space by
  -- stepping forward through time in small increments called steps.
  -- It is *highly* recommended to use a fixed size time step.
  let timeStep = 1/60
  runFor 2 timeStep $ time -> do
    pos <- get $ bodyPosition ballBody
    vel <- get $ bodyVelocity ballBody
    printf "Time is %4.2f. ballBody is at (%6.2f, %6.2f), it's velocity is (%6.2f, %6.2f).n"
           time (vX pos) (vY pos) (vX vel) (vY vel)

    spaceStep space timeStep

  shapeFree ballShape
  bodyFree ballBody
  shapeFree ground
  spaceFree space
  where
    runFor time step inner = go time
      where
        go time'
          | time' <= 0 = pure ()
          | otherwise  = inner (time - time') *> go (time' - step)

Chipmunk2D Basics

Overview

There are 4 basic object types you will use in Chipmunk.

  • Rigid Bodies (Body): A rigid body holds the physical properties of an object. (mass, position, rotation, velocity, etc.) It does not have a shape until you attach one or more collision shapes to it. If you’ve done physics with particles before, rigid bodies differ in that they are able to rotate. Rigid bodies generally tend to have a 1:1 correlation to sprites in a game. You should structure your game so that you use the position and rotation of the rigid body for drawing your sprite.
  • Collision Shapes (Shape): By attaching shapes to bodies, you can define the a body’s shape. You can attach as many shapes to a single body as you need to in order to define a complex shape. Shapes contain the surface properties of an object such as how much friction or elasticity it has.
  • Constraints/Joints (Constraint): Constraints and joints describe how bodies are attached to each other.
  • Spaces (Space): Spaces are containers for simulating objects in Chipmunk. You add bodies, shapes and joints to a space and then update the space as a whole. They control how all the rigid bodies, shapes, and constraints interact together.

There is often confusion between rigid bodies and their collision shapes in Chipmunk and how they relate to sprites. A sprite would be a visual representation of an object, while a collision shape is an invisible property that defines how objects should collide. Both the sprite’s and the collision shape’s position and rotation are controlled by the motion of a rigid body. Generally you want to create a game object type that ties these things all together.

Memory Management the Chipmunk way

For most of the structures you will use, Chipmunk uses a more or less standard and straightforward set of memory management functions. Take the Space struct for example:

You are responsible for freeing any structs that you allocate. Chipmunk does not do reference counting or garbage collection. If you call a new function, you must call the matching free function or you will leak memory.

Math the Chipmunk way

First of all, Chipmunk uses double precision floating point numbers throughout its calculations by default. This is likely to be faster on most modern desktop processors, and means you don’t have to worry as much about floating point accuracy.

However, there are a few unique functions you will probably find very useful:

fClamp Source #

Arguments

:: Double

f

-> Double

min

-> Double

max

-> Double 

Clamp f to be between min and max

fLerp Source #

Arguments

:: Double

f1

-> Double

f2

-> Double 
-> Double 

Linearly interpolate between f1 and f2

fLerpConst Source #

Arguments

:: Double

f1

-> Double

f2

-> Double

d

-> Double 

Linearly interpolate from f1 towards f2 by no more than d.

Chipmunk Vectors

Struct Definition, Constants and Constructors

data Vect Source #

2D vector packed into a struct.

Constructors

Vect 

Fields

Instances
Eq Vect Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

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

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

Ord Vect Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

compare :: Vect -> Vect -> Ordering #

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

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

(>) :: Vect -> Vect -> Bool #

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

max :: Vect -> Vect -> Vect #

min :: Vect -> Vect -> Vect #

Show Vect Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

showsPrec :: Int -> Vect -> ShowS #

show :: Vect -> String #

showList :: [Vect] -> ShowS #

Generic Vect Source # 
Instance details

Defined in Chiphunk.Low.Types

Associated Types

type Rep Vect :: Type -> Type #

Methods

from :: Vect -> Rep Vect x #

to :: Rep Vect x -> Vect #

Storable Vect Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

sizeOf :: Vect -> Int #

alignment :: Vect -> Int #

peekElemOff :: Ptr Vect -> Int -> IO Vect #

pokeElemOff :: Ptr Vect -> Int -> Vect -> IO () #

peekByteOff :: Ptr b -> Int -> IO Vect #

pokeByteOff :: Ptr b -> Int -> Vect -> IO () #

peek :: Ptr Vect -> IO Vect #

poke :: Ptr Vect -> Vect -> IO () #

Hashable Vect Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

hashWithSalt :: Int -> Vect -> Int #

hash :: Vect -> Int #

HasCross2 Vect Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

cross2 :: Vect -> Vect #

VectorSpace Vect Source # 
Instance details

Defined in Chiphunk.Low.Types

Associated Types

type Scalar Vect :: Type #

Methods

(*^) :: Scalar Vect -> Vect -> Vect #

InnerSpace Vect Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

(<.>) :: Vect -> Vect -> Scalar Vect #

AdditiveGroup Vect Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

zeroV :: Vect #

(^+^) :: Vect -> Vect -> Vect #

negateV :: Vect -> Vect #

(^-^) :: Vect -> Vect -> Vect #

type Rep Vect Source # 
Instance details

Defined in Chiphunk.Low.Types

type Rep Vect = D1 (MetaData "Vect" "Chiphunk.Low.Types" "chiphunk-0.1.1.0-I8qACn0ilueBvyWZpW4e9s" False) (C1 (MetaCons "Vect" PrefixI True) (S1 (MetaSel (Just "vX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "vY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)))
type Scalar Vect Source # 
Instance details

Defined in Chiphunk.Low.Types

vZero :: Vect Source #

Constant for the zero vector.

Alias for zeroV

cpv :: Double -> Double -> Vect Source #

Convenience constructor for creating new cpVect structs. Alias for Vect

Operations

(Note for bindings: Most of these are Chipmunk2D-style aliases for Vect typeclasses methods: Eq, AdditiveGroup, VectorSpace, InnerSpace, HasCross2)

vEql :: Vect -> Vect -> Bool Source #

Check if two vectors are equal. (Be careful when comparing floating point numbers!)

Alias for ==.

vAdd :: Vect -> Vect -> Vect Source #

Add two vectors.

Alias for ^+^.

vSub :: Vect -> Vect -> Vect Source #

Subtract two vectors.

Alias for ^-^.

vNeg :: Vect -> Vect Source #

Negate a vector.

Alias for negateV.

vMult :: Vect -> Double -> Vect Source #

Scalar multiplication.

Alias for ^*.

vDot :: Vect -> Vect -> Double Source #

Vector dot product.

Alias for <.>.

vCross :: Vect -> Vect -> Double Source #

2D vector cross product analog. The cross product of 2D vectors results in a 3D vector with only a z component. This function returns the value along the z-axis.

vPerp :: Vect -> Vect Source #

Returns a perpendicular vector. (90 degree rotation)

Alias for cross2.

vRPerp :: Vect -> Vect Source #

Returns a perpendicular vector. (-90 degree rotation)

vProject Source #

Arguments

:: Vect

v1

-> Vect

v2

-> Vect 

Returns the vector projection of v1 onto v2.

Alias for project.

vRotate Source #

Arguments

:: Vect

v1

-> Vect

v2

-> Vect 

Uses complex multiplication to rotate v1 by v2. Scaling will occur if v1 is not a unit vector.

vUnRotate :: Vect -> Vect -> Vect Source #

Inverse of vRotate.

vLength :: Vect -> Double Source #

Returns the length of v.

Alias for magnitude.

vLengthSq :: Vect -> Double Source #

Returns the squared length of v. Faster than vLength when you only need to compare lengths.

Alias for magnitudeSq.

vLerp Source #

Arguments

:: Vect

v1

-> Vect

v2

-> Double 
-> Vect 

Linearly interpolate between v1 and v2.

Alias for lerp.

vLerpConst Source #

Arguments

:: Vect

v1

-> Vect

v2

-> Double

d

-> Vect 

Linearly interpolate between v1 towards v2 by distance d.

vSLerp Source #

Arguments

:: Vect

v1

-> Vect

v2

-> Double 
-> Vect 

Spherical linearly interpolate between v1 and v2.

vSLerpConst Source #

Arguments

:: Vect

v1

-> Vect

v2

-> Double

a

-> Vect 

Spherical linearly interpolate between v1 towards v2 by no more than angle a in radians.

vNormalize :: Vect -> Vect Source #

Returns a normalized copy of v. As a special case, it returns vZero when called on vZero.

Alias for normalized.

vClamp Source #

Arguments

:: Vect

v

-> Double

len

-> Vect 

Clamp v to length len.

vDist Source #

Arguments

:: Vect

v1

-> Vect

v2

-> Double 

Returns the distance between v1 and v2.

vDistSq Source #

Arguments

:: Vect

v1

-> Vect

v2

-> Double 

Returns the squared distance between v1 and v2. Faster than vDist when you only need to compare distances.

vNear Source #

Arguments

:: Vect

v1

-> Vect

v2

-> Double

dist

-> Bool 

Returns true if the distance between v1 and v2 is less than dist.

vForAngle :: Double -> Vect Source #

Returns the unit length vector for the given angle (in radians).

vToAngle Source #

Arguments

:: Vect

v

-> Double 

Returns the angular direction v is pointing in (in radians).

Chipmunk Axis Aligned Bounding Boxes

Struct Definition and Constructors

data BB Source #

Simple bounding box struct. Stored as left, bottom, right, top values.

Constructors

BB 

Fields

Instances
Eq BB Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

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

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

Ord BB Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

compare :: BB -> BB -> Ordering #

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

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

(>) :: BB -> BB -> Bool #

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

max :: BB -> BB -> BB #

min :: BB -> BB -> BB #

Show BB Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

showsPrec :: Int -> BB -> ShowS #

show :: BB -> String #

showList :: [BB] -> ShowS #

Generic BB Source # 
Instance details

Defined in Chiphunk.Low.Types

Associated Types

type Rep BB :: Type -> Type #

Methods

from :: BB -> Rep BB x #

to :: Rep BB x -> BB #

Storable BB Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

sizeOf :: BB -> Int #

alignment :: BB -> Int #

peekElemOff :: Ptr BB -> Int -> IO BB #

pokeElemOff :: Ptr BB -> Int -> BB -> IO () #

peekByteOff :: Ptr b -> Int -> IO BB #

pokeByteOff :: Ptr b -> Int -> BB -> IO () #

peek :: Ptr BB -> IO BB #

poke :: Ptr BB -> BB -> IO () #

Hashable BB Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

hashWithSalt :: Int -> BB -> Int #

hash :: BB -> Int #

type Rep BB Source # 
Instance details

Defined in Chiphunk.Low.Types

bbNew :: Double -> Double -> Double -> Double -> BB Source #

Convenience constructor for BB structs.

bbNewForExtents Source #

Arguments

:: Vect

Center point

-> Double

Half width

-> Double

Half height

-> BB 

Convenience constructor for making a BB fitting with a center point and half width and height.

bbNewForCircle Source #

Arguments

:: Vect

p

-> Double

r

-> BB 

Convenience constructor for making a BB fitting a circle at position p with radius r.

Operations

bbIntersects :: BB -> BB -> Bool Source #

Returns true if the bounding boxes intersect.

bbContainsBB Source #

Arguments

:: BB

bb

-> BB

other

-> Bool 

Returns true if bb completely contains other.

bbContainsVect Source #

Arguments

:: BB

bb

-> Vect

v

-> Bool 

Returns true if bb contains v.

bbMerge Source #

Arguments

:: BB

a

-> BB

b

-> BB 

Return the minimal bounding box that contains both a and b.

bbExpand Source #

Arguments

:: BB

bb

-> Vect

v

-> BB 

Return the minimal bounding box that contains both bb and v.

bbCenter Source #

Arguments

:: BB

bb

-> Vect 

Return the center of bb.

bbArea Source #

Arguments

:: BB

bb

-> Double 

Return the area of bb.

bbMergedArea Source #

Arguments

:: BB

a

-> BB

b

-> Double 

Merges a and b then returns the area of the merged bounding box.

bbSegmentQuery Source #

Arguments

:: BB

Box

-> Vect

One segment end

-> Vect

Other segment end

-> Double 

Returns the fraction along the segment query the BB is hit. Returns INFINITY if it doesn’t hit.

bbIntersectsSegment Source #

Arguments

:: BB

bb

-> Vect

a

-> Vect

b

-> Bool 

Returns true if the segment defined by endpoints a and b intersect bb.

bbClampVect Source #

Arguments

:: BB

bb

-> Vect

v

-> Vect 

Returns a copy of v clamped to the bounding box bb.

bbWrapVect Source #

Arguments

:: BB

bb

-> Vect

v

-> Vect 

Returns a copy of v wrapped to the bounding box bb.

Chipmunk Rigid Bodies

data Body Source #

Rigid body somewhere in C code.

Instances
Eq Body Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

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

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

Ord Body Source # 
Instance details

Defined in Chiphunk.Low.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 #

Generic Body Source # 
Instance details

Defined in Chiphunk.Low.Types

Associated Types

type Rep Body :: Type -> Type #

Methods

from :: Body -> Rep Body x #

to :: Rep Body x -> Body #

Storable Body Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

sizeOf :: Body -> Int #

alignment :: Body -> Int #

peekElemOff :: Ptr Body -> Int -> IO Body #

pokeElemOff :: Ptr Body -> Int -> Body -> IO () #

peekByteOff :: Ptr b -> Int -> IO Body #

pokeByteOff :: Ptr b -> Int -> Body -> IO () #

peek :: Ptr Body -> IO Body #

poke :: Ptr Body -> Body -> IO () #

Hashable Body Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

hashWithSalt :: Int -> Body -> Int #

hash :: Body -> Int #

type Rep Body Source # 
Instance details

Defined in Chiphunk.Low.Types

type Rep Body = D1 (MetaData "Body" "Chiphunk.Low.Types" "chiphunk-0.1.1.0-I8qACn0ilueBvyWZpW4e9s" True) (C1 (MetaCons "Body" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ptr Body))))

Dynamic, Kinematic, and Static Bodies

data BodyType Source #

Chipmunk supports three different types of bodies with unique behavioral and performance characteristics.

Constructors

BodyTypeDynamic

Dynamic bodies are the default body type. They react to collisions, are affected by forces and gravity, and have a finite amount of mass. These are the type of bodies that you want the physics engine to simulate for you. Dynamic bodies interact with all types of bodies and can generate collision callbacks.

BodyTypeKimenatic

Kinematic bodies are bodies that are controlled from your code instead of inside the physics engine. They arent affected by gravity and they have an infinite amount of mass so they don’t react to collisions or forces with other bodies. Kinematic bodies are controlled by setting their velocity, which will cause them to move. Good examples of kinematic bodies might include things like moving platforms. Objects that are touching or jointed to a kinematic body are never allowed to fall asleep.

BodyTypeStatic

Static bodies are bodies that never (or rarely) move. Using static bodies for things like terrain offers a big performance boost over other body types — because Chipmunk doesn’t need to check for collisions between static objects and it never needs to update their collision information. Additionally, because static bodies don’t move, Chipmunk knows it’s safe to let objects that are touching or jointed to them fall asleep. Generally all of your level geometry will be attached to a static body except for things like moving platforms or doors. Every space provide a built-in static body for your convenience. Static bodies can be moved, but there is a performance penalty as the collision information is recalculated. There is no penalty for having multiple static bodies, and it can be useful for simplifying your code by allowing different parts of your static geometry to be initialized or moved separately.

Movement, Teleportation, and Velocity

A graphics engine only needs to know the position of an object for each frame that its drawn. For a physics engine, this isn’t enough information to calculate a collision response. When you set the position of a body, you are effectively asking it to teleport itself. This means that it will instantly move to its new position instead of moving through space and time like a normal object. If you teleport an object so that it overlaps another one, the best the physics engine can do is to attempt to push the objects apart again since there is no information about their movement. This generally results in very mushy looking collisions. So instead of setting the position of an object, it’s better to set its velocity and allow the physics engine to update the position. That way it can resolve any resulting colisions natuarally since it knows how the objects were moving. This is why kinematic bodies work the way they do. You set the velocity, and the physics updates their position so the two are never out of sync.

For dynamic bodies, setting the velocity explicitly every frame can cause problems. For example, a problem occurs when a light dynamic body (like a person) is pressed against a heavy dynamic body (like a car), and you set velocity of the small object so that it’s pushing it into the big body. To the physics engine, the change in velocity is the same as applying a large impulse (a very short, very large force). Even if the velocity is low, the large force can allow the small body to push the big body, even when it normally wouldn’t be able to. For example, a person walking into a car can overpower the car’s friction and cause it to creep along the ground slowly. Additionally, when you set the velocity of an object that is already in contact, it can cause the two objects to overlap by a small amount. The easiest way to avoid both of these problems is to make smaller changes to the body’s velocity, accelerating it over a fraction of a second instead of a single frame. An even better solution, which is covered more thoroughly later, is to use constraints to move the object.

Memory Management Functions

Standard set of Chipmunk memory management functions.

bodyNew Source #

Arguments

:: Double

Mass of the body. Guessing is usually fine.

-> Double

Moment of inertia of the body. Guessing a moment of inertia can lead to a very poor simulation so it’s recommended to use Chipmunk’s moment calculations to estimate the moment for you.

-> IO Body 

Creates body of type BodyTypeDynamic.

bodyNewStatic :: IO Body Source #

Create body of type BodyTypeStatic.

bodyFree :: Body -> IO () Source #

Be careful not to free a body before any shapes or constraints attached to it have been removed from a space.

Creating Dynamic Bodies

There are two ways to set up a dynamic body. The easiest option is to create a body with a mass and moment of 0, and set the mass or density of each collision shape added to the body. Chipmunk will automatically calculate the mass, moment of inertia, and center of gravity for you. This is probably preferred in most cases.

The other option is to set the mass of the body when it’s created, and leave the mass of the shapes added to it as 0.0. This approach is more flexible, but is not as easy to use. Don’t set the mass of both the body and the shapes. If you do so, it will recalculate and overwite your custom mass value when the shapes are added to the body.

Properties

Chipmunk provides getter/setter functions for a number of properties on rigid bodies. Setting most properties automatically wakes the rigid bodies up if they were sleeping.

bodyType :: Body -> StateVar BodyType Source #

Type of a body (dynamic, kinematic, static). When changing an body to a dynamic body, the mass and moment of inertia are recalculated from the shapes added to the body. Custom calculated moments of inertia are not preseved when changing types. This function cannot be called directly in a collision callback.

bodyMass :: Body -> StateVar Double Source #

Mass of the body.

bodyMoment :: Body -> StateVar Double Source #

Moment of inertia (MoI or sometimes just moment) of the body. The moment is like the rotational mass of a body. See below for function to help calculate the moment.

bodyPosition :: Body -> StateVar Vect Source #

Position of the body. When changing the position you may also want to call spaceReindexShapesForBody to update the collision detection information for the attached shapes if plan to make any queries against the space.

bodyCenterOfGravity :: Body -> StateVar Vect Source #

Location of the center of gravity in body local coordinates. The default value is (0, 0), meaning the center of gravity is the same as the position of the body.

bodyVelocity :: Body -> StateVar Vect Source #

Linear velocity of the center of gravity of the body.

bodyForce :: Body -> StateVar Vect Source #

Force applied to the center of gravity of the body. This value is reset for every time step.

bodyAngle :: Body -> StateVar Double Source #

Set rotation of the body in radians. When changing the rotation you may also want to call spaceReindexShapesForBody to update the collision detection information for the attached shapes if you plan to make any queries against the space. A body rotates around its center of gravity, not its position.

bodyAngularVelocity :: Body -> StateVar Double Source #

Angular velocity of the body in radians per second.

bodyTorque :: Body -> StateVar Double Source #

Torque applied to the body. This value is reset for every time step.

bodyRotation :: Body -> GettableStateVar Vect Source #

The rotation vector for the body. Can be used with vRotate or vUnRotate to perform fast rotations.

bodySpace :: Body -> GettableStateVar Space Source #

The Space that body has been added to.

bodyUserData :: Body -> StateVar DataPtr Source #

User data pointer. Use this pointer to get a reference to the game object that owns this body from callbacks.

Moment of Inertia and Area Helper Functions

Use the following functions to approximate the moment of inertia for your body, adding the results together if you want to use more than one.

momentForCircle Source #

Arguments

:: Double

Mass

-> Double

r1

-> Double

r2

-> Vect

Offset

-> Double 

Calculate the moment of inertia for a hollow circle, r1 and r2 are the inner and outer diameters in no particular order. (A solid circle has an inner diameter of 0)

momentForSegment Source #

Arguments

:: Double

Mass

-> Vect

a

-> Vect

b

-> Double

Thickness

-> Double 

Calculate the moment of inertia for a line segment. The endpoints a and b are relative to the body.

momentForPoly Source #

Arguments

:: Double

Mass

-> [Vect]

Vertexes

-> Vect

Offset

-> Double

Thickness

-> Double 

Calculate the moment of inertia for a solid polygon shape assuming its center of gravity is at its centroid. The offset is added to each vertex.

momentForBox Source #

Arguments

:: Double

Mass

-> Double

Width

-> Double

Height

-> Double 

Calculate the moment of inertia for a solid box centered on the body.

Use the following functions to get the area for common Chipmunk shapes if you want to approximate masses or density or whatnot.

areaForCircle Source #

Arguments

:: Double

r1

-> Double

r2

-> Double 

Area of a hollow circle.

areaForSegment Source #

Arguments

:: Vect

One end

-> Vect

Other end

-> Double

Thickness

-> Double 

Area of a beveled segment. (Will always be zero if radius is zero)

areaForPoly Source #

Arguments

:: [Vect]

Vertexes

-> Double

Thickness

-> Double 

Signed area of a polygon shape. Returns a negative number for polygons with a clockwise winding.

Coordinate Conversion Functions

Many things are defined in coordinates local to a body meaning that the (0,0) is at the center of gravity of the body and the axis rotate along with the body.

bodyLocalToWorld :: Body -> Vect -> IO Vect Source #

Convert from body local coordinates to world space coordinates.

bodyWorldToLocal :: Body -> Vect -> IO Vect Source #

Convert from world space coordinates to body local coordinates.

Velocity Conversion Functions

It’s often useful to know the absolute velocity of a point on the surface of a body since the angular velocity affects everything except the center of gravity.

bodyVelocityAtWorldPoint :: Body -> Vect -> GettableStateVar Vect Source #

Absolute velocity of the rigid body at the given world point.

Applying Forces and Torques

People are sometimes confused by the difference between a force and an impulse. An impulse is a very large force applied over a very short period of time. Some examples are a ball hitting a wall or cannon firing. Chipmunk treats impulses as if they occur instantaneously by adding directly to the velocity of an object. Both impulses and forces are affected the mass of an object. Doubling the mass of the object will halve the effect.

bodyApplyForceAtWorldPoint Source #

Arguments

:: Body

body

-> Vect

force

-> Vect

point

-> IO () 

Add the force to body as if applied from the world point.

bodyApplyForceAtLocalPoint Source #

Arguments

:: Body

body

-> Vect

force

-> Vect

point

-> IO () 

Add the local force to body as if applied from the body local point.

bodyApplyImpulseAtWorldPoint Source #

Arguments

:: Body

body

-> Vect

impulse

-> Vect

point

-> IO () 

Add the impulse to body as if applied from the world point.

bodyApplyImpulseAtLocalPoint Source #

Arguments

:: Body

body

-> Vect

impulse

-> Vect

point

-> IO () 

Add the local impulse to body as if applied from the body local point.

Sleeping Functions

Chipmunk supports a sleeping feature which improves performance by not simulating groups of objects that aren’t moving. Read more about it in the Space section.

bodyIsSleeping :: Body -> IO Bool Source #

Returns true if body is sleeping.

bodyActivate :: Body -> IO () Source #

Reset the idle timer on a body. If it was sleeping, wake it and any other bodies it was touching.

bodySleep :: Body -> IO () Source #

Forces a body to fall asleep immediately even if it’s in midair. Cannot be called from a callback.

bodyActivateStatic Source #

Arguments

:: Body

body

-> Shape

filter

-> IO () 

Activates all bodies touching body. If filter is not nullPtr, then only bodies touching through filter will be awoken.

bodySleepWithGroup Source #

Arguments

:: Body

body

-> Body

group

-> IO () 

When objects in Chipmunk sleep, they sleep as a group of all objects that are touching or jointed together. When an object is woken up, all of the objects in its group are woken up. bodySleepWithGroup allows you group sleeping objects together. It acts identically to bodySleep if you pass nullPtr as group by starting a new group. If you pass a sleeping body for group, body will be awoken when group is awoken. You can use this to initialize levels and start stacks of objects in a pre-sleeping state.

Iterators

type BodyShapeIteratorFunc = Body -> Shape -> Ptr () -> IO () Source #

Type of callback which can be used to iterate all Shapes in a Body.

bodyEachShape Source #

Arguments

:: Body

body

-> BodyShapeIteratorFunc

func

-> Ptr ()

data

-> IO () 

Call func once for each shape that is attached to body and added to a space. data is passed along as a context value. It is safe to remove shapes using these callbacks.

type BodyConstraintIteratorFunc = Body -> Constraint -> Ptr () -> IO () Source #

Type of callback which can be used to iterate all Constraints in a Body.

bodyEachConstraint Source #

Arguments

:: Body

body

-> BodyConstraintIteratorFunc

func

-> Ptr ()

data

-> IO () 

Call func once for each constraint that is attached to body and added to a space. data is passed along as a context value. It is safe to remove constraints using thes callbacks.

type BodyArbiterIteratorFunc = Body -> Arbiter -> Ptr () -> IO () Source #

Type of callback which can be used to iterate all Arbiters in a Body.

bodyEachArbiter Source #

Arguments

:: Body

body

-> BodyArbiterIteratorFunc

func

-> Ptr ()

data

-> IO () 

This one is more interesting. Calls func once for each collision pair that body is involved in. Calling 'arbiterGetBodies'/'arbiterGetShapes' will return the body or shape for body as the first argument. You can use this to check all sorts of collision information for a body like if it’s touching the ground, another particular object, how much collision force is being applied to an object, etc.

Sensor shapes and arbiters that have been rejected by a collision handler callback or arbiterIgnore are not tracked by the contact graph.

Chipmunk Collision Shapes

data Shape Source #

There are currently 3 collision shape types:

  • Circles: Fastest and simplest collision shape.
  • Line segments: Meant mainly as a static shape. Can be beveled in order to give them a thickness.
  • Convex polygons: Slowest, but most flexible collision shape.

You can add as many shapes to a body as you wish. That is why the two types are separate.

Combining multiple shapes gives you the flexibility to make any object you want as well as providing different areas of the same object with different friction, elasticity or callback values.

Instances
Eq Shape Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

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

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

Ord Shape Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

compare :: Shape -> Shape -> Ordering #

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

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

(>) :: Shape -> Shape -> Bool #

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

max :: Shape -> Shape -> Shape #

min :: Shape -> Shape -> Shape #

Generic Shape Source # 
Instance details

Defined in Chiphunk.Low.Types

Associated Types

type Rep Shape :: Type -> Type #

Methods

from :: Shape -> Rep Shape x #

to :: Rep Shape x -> Shape #

Storable Shape Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

sizeOf :: Shape -> Int #

alignment :: Shape -> Int #

peekElemOff :: Ptr Shape -> Int -> IO Shape #

pokeElemOff :: Ptr Shape -> Int -> Shape -> IO () #

peekByteOff :: Ptr b -> Int -> IO Shape #

pokeByteOff :: Ptr b -> Int -> Shape -> IO () #

peek :: Ptr Shape -> IO Shape #

poke :: Ptr Shape -> Shape -> IO () #

Hashable Shape Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

hashWithSalt :: Int -> Shape -> Int #

hash :: Shape -> Int #

type Rep Shape Source # 
Instance details

Defined in Chiphunk.Low.Types

type Rep Shape = D1 (MetaData "Shape" "Chiphunk.Low.Types" "chiphunk-0.1.1.0-I8qACn0ilueBvyWZpW4e9s" True) (C1 (MetaCons "Shape" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ptr Shape))))

Properties

Chipmunk provides getter/setter functions for a number of properties on collision shapes. Setting most properties will automatically wake the attached rigid body, if it’s sleeping.

shapeBody :: Shape -> StateVar Body Source #

The rigid body the shape is attached to. Can only be set when the shape is not added to a space.

shapeBB :: Shape -> GettableStateVar BB Source #

The bounding box of the shape. Only guaranteed to be valid after shapeCacheBB or spaceStep is called. Moving a body that a shape is connected to does not update its bounding box. For shapes used for queries that aren’t attached to bodies, you can also use shapeUpdate.

shapeSensor :: Shape -> StateVar Bool Source #

A boolean value if this shape is a sensor or not. Sensors only call collision callbacks, and never generate real collisions.

shapeElasticity :: Shape -> StateVar Double Source #

Elasticity of the shape. A value of 0.0 gives no bounce, while a value of 1.0 will give a “perfect” bounce. However due to inaccuracies in the simulation using 1.0 or greater is not recommended however.

The elasticity for a collision is found by multiplying the elasticity of the individual shapes together.

shapeFriction :: Shape -> StateVar Double Source #

Friction coefficient. Chipmunk uses the Coulomb friction model, a value of 0.0 is frictionless.

The friction for a collision is found by multiplying the friction of the individual shapes together. Table of friction coefficients.

shapeSurfaceVelocity :: Shape -> StateVar Vect Source #

The surface velocity of the object. Useful for creating conveyor belts or players that move around. This value is only used when calculating friction, not resolving the collision.

shapeCollisionType :: Shape -> StateVar CollisionType Source #

Collision type of this shape. | You can assign types to Chipmunk collision shapes that trigger callbacks when objects of certain types touch. See the callbacks section for more information.

data ShapeFilter Source #

Fast collision filtering type that is used to determine if two objects collide before calling collision or query callbacks.

Constructors

ShapeFilter 

shapeFilter :: Shape -> StateVar ShapeFilter Source #

The collision filter for this shape. See Filtering Collisions for more information.

shapeSpace :: Shape -> GettableStateVar Space Source #

The Space that shape has been added to.

shapeUserData :: Shape -> StateVar DataPtr Source #

A user definable data pointer. If you set this to point at the game object the shapes is for, then you can access your game object from Chipmunk callbacks.

Fast Collision Filtering using ShapeFilter

Chipmunk has two primary means of ignoring collisions: groups and category masks.

Groups are used to ignore collisions between parts on a complex object. A ragdoll is a good example. When jointing an arm onto the torso, you’ll want them to allow them to overlap. Groups allow you to do exactly that. Shapes that have the same group don’t generate collisions. So by placing all of the shapes in a ragdoll in the same group, you’ll prevent it from colliding against other parts of itself. Category masks allow you to mark which categories an object belongs to and which categories it collidies with.

For example, a game has four collision categories: player (0), enemy (1), player bullet (2), and enemy bullet (3). Neither players nor enemies should not collide with their own bullets, and bullets should not collide with other bullets. However, players collide with enemy bullets, and enemies collide with player bullets.

Object Object Category Category Mask
"Player" 1 4, 5
"Enemy" 2 2, 3, 5
"Player Bullet" 3 1, 5
"Enemy Bullet" 4 2, 5
"Walls" 5 1, 2, 3, 4

Note that everything in this example collides with walls. Additionally, the enemies collide with eachother.

By default, objects exist in every category and collide with every category.

Objects can fall into multiple categories. For instance, you might have a category for a red team, and have a red player bullet. In the above example, each object only has one category.

There is one last way of filtering collisions using collision handlers. See the section on callbacks for more information. Collision handlers can be more flexible, but can be slower. Fast collision filtering rejects collisions before running the expensive collision detection code, so using groups or category masks is preferred.

Memory Management Functions

shapeFree :: Shape -> IO () Source #

Deallocates shape.

Misc functions

shapeCacheBB Source #

Arguments

:: Shape

shape

-> IO BB 

Synchronizes shape with the body its attached to.

shapeUpdate Source #

Arguments

:: Shape
shape
-> Transform 
-> IO BB 

Sets the position and rotation of the shape

Working With Circle Shapes

circleShapeNew Source #

Arguments

:: Body

The body to attach the circle to.

-> Double

Radius of the circle.

-> Vect

Offset from the body's center of gravity in body local coordinates.

-> IO Shape 

Create new circle-like shape.

Working With Segment Shapes

segmentShapeNew Source #

Arguments

:: Body

The body to attach the segment to.

-> Vect

One endpoint.

-> Vect

Another endpoint.

-> Double

The thickness of the segment.

-> IO Shape 

Create new segment-shaped shape.

segmentShapeNeighbors :: Shape -> SettableStateVar (Vect, Vect) Source #

When you have a number of segment shapes that are all joined together, things can still collide with the “cracks” between the segments. By setting the neighbor segment endpoints you can tell Chipmunk to avoid colliding with the inner parts of the crack.

Working With Polygon Shapes

polyShapeNew Source #

Arguments

:: Body

The body to attach the poly to.

-> [Vect]

The array of Vect structs.

-> Transform

The transform that will be applied to every vertex.

-> Double

Radius.

-> IO Shape 

A convex hull will be calculated from the vertexes automatically. The polygon shape will be created with a radius, increasing the size of the shape.

polyShapeNewRaw :: Body -> [Vect] -> Double -> IO Shape Source #

Alternate constructors for poly shapes. This version does not apply a transform nor does it create a convex hull. Verticies must be provided with a counter-clockwise winding.

Boxes

Because boxes are so common in physics games, Chipmunk provides shortcuts to create box shaped polygons. The boxes will always be centered at the center of gravity of the body you are attaching them to. Adding a small radius will bevel the corners and can significantly reduce problems where the box gets stuck on seams in your geometry. If you want to create an off-center box, you will need to use polyShapeNew.

boxShapeNew Source #

Arguments

:: Body

The body to attach to

-> Double

Box width

-> Double

Box height

-> Double

Radius

-> IO Shape 

Createa box shape from dimensions.

boxShapeNew2 Source #

Arguments

:: Body

The body to attach to

-> BB

Shape size

-> Double

Radius

-> IO Shape 

Alternative to boxShapeNew using BB to set size.

Poly Shape Helper Functions

centroidForPoly :: [Vect] -> Vect Source #

Calculate the centroid for a polygon.

Convex Hull Helper Functions

convexHull Source #

Arguments

:: [Vect]

Set of vertexes

-> Double

Allowed amount to shrink the hull when simplifying it. A tolerance of 0 creates an exact hull.

-> ([Vect], Int)

Second element is index of first output vertex in input list.

Calculate the convex hull of a given set of points.

Modifying Shapes

The short answer is that you can’t because the changes would be only picked up as a change to the position of the shape’s surface, but not its velocity.

Notes

  • You can attach multiple collision shapes to a rigid body. This should allow you to create almost any shape you could possibly need.
  • Shapes attached to the same rigid body will never generate collisions. You don’t have to worry about overlap when attaching multiple shapes to a rigid body.
  • Make sure you add both the body and its collision shapes to a space.

Chipmunk Spaces

data Space Source #

Spaces in Chipmunk are the basic unit of simulation. You add rigid bodies, shapes, and constraints to the space and then step them all forward through time together.

Instances
Eq Space Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

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

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

Ord Space Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

compare :: Space -> Space -> Ordering #

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

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

(>) :: Space -> Space -> Bool #

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

max :: Space -> Space -> Space #

min :: Space -> Space -> Space #

Generic Space Source # 
Instance details

Defined in Chiphunk.Low.Types

Associated Types

type Rep Space :: Type -> Type #

Methods

from :: Space -> Rep Space x #

to :: Rep Space x -> Space #

Storable Space Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

sizeOf :: Space -> Int #

alignment :: Space -> Int #

peekElemOff :: Ptr Space -> Int -> IO Space #

pokeElemOff :: Ptr Space -> Int -> Space -> IO () #

peekByteOff :: Ptr b -> Int -> IO Space #

pokeByteOff :: Ptr b -> Int -> Space -> IO () #

peek :: Ptr Space -> IO Space #

poke :: Ptr Space -> Space -> IO () #

Hashable Space Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

hashWithSalt :: Int -> Space -> Int #

hash :: Space -> Int #

type Rep Space Source # 
Instance details

Defined in Chiphunk.Low.Types

type Rep Space = D1 (MetaData "Space" "Chiphunk.Low.Types" "chiphunk-0.1.1.0-I8qACn0ilueBvyWZpW4e9s" True) (C1 (MetaCons "Space" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ptr Space))))

What Are Iterations, and Why Should I Care?

Chipmunk uses an iterative solver to figure out the forces between objects in the space. What this means is that it builds a big list of all of the collisions, joints, and other constraints between the bodies and makes several passes over the list considering each one individually. The number of passes it makes is the iteration count, and each iteration makes the solution more accurate. If you use too many iterations, the physics should look nice and solid, but may use up too much CPU time. If you use too few iterations, the simulation may seem mushy or bouncy when the objects should be solid. Setting the number of iterations lets you balance between CPU usage and the accuracy of the physics. Chipmunk’s default of 10 iterations is sufficient for most simple games.

Sleeping

Spaces can disable entire groups of objects that have stopped moving to save CPU time and battery life. In order to use this feature you must do two things. You must enable sleeping explicitly by choosing a time threshold value with spaceSetSleepTimeThreshold. This threshold is the amount of time something must be idle before it falls asleep. spaceSetIdleSpeedThreshold defines what is considered idle. If you do not set idle speed threshold explicitly, a value will be chosen automatically based on the current amount of gravity. Be mindful that objects cannot fall asleep if they are touching or jointed to a kinematic body.

Properties

spaceIterations :: Space -> StateVar Int Source #

Iterations allow you to control the accuracy of the solver. Defaults to 10. See above for more information.

spaceGravity :: Space -> StateVar Vect Source #

Global gravity applied to the space. Defaults to vZero. Can be overridden on a per body basis by writing custom integration functions. Changing the gravity will activate all sleeping bodies in the space.

spaceDamping :: Space -> StateVar Double Source #

Amount of simple damping to apply to the space. A value of 0.9 means that each body will lose 10% of its velocity per second. Defaults to 1. Like gravity, it can be overridden on a per body basis.

spaceIdleSpeedThreshold :: Space -> StateVar Double Source #

Speed threshold for a body to be considered idle. The default value of 0 means the space estimates a good threshold based on gravity.

spaceSleepTimeThreshold :: Space -> StateVar Double Source #

Time a group of bodies must remain idle in order to fall asleep. The default value of INFINITY disables the sleeping feature.

spaceCollisionSlop :: Space -> StateVar Double Source #

Amount of overlap between shapes that is allowed. To improve stability, set this as high as you can without noticable overlapping. It defaults to 0.1.

spaceCollisionBias :: Space -> StateVar Double Source #

Chipmunk allows fast moving objects to overlap, then fixes the overlap over time. Overlapping objects are unavoidable even if swept collisions are supported, and this is an efficient and stable way to deal with overlapping objects. The bias value controls what percentage of overlap remains unfixed after a second and defaults to ~0.2%.

Valid values are in the range from 0 to 1, but using 0 is not recommended for stability reasons.

The default value is calculated as (1.0 - 0.1) ^ 60 meaning that Chipmunk attempts to correct 10% of error ever 1/60th of a second.

Note: Very very few games will need to change this value.

spaceCollisionPersistence :: Space -> StateVar Word32 Source #

The number of frames the space keeps collision solutions around for. Helps prevent jittering contacts from getting worse. This defaults to 3 and very very very few games will need to change this value.

spaceCurrentTimeStep :: Space -> GettableStateVar Double Source #

The current (if you are in a callback from spaceStep) or most recent (outside of a spaceStep call) timestep.

spaceIsLocked :: Space -> IO Bool Source #

Returns true when you cannot add/remove objects from the space. In particular, spaces are locked when in a collision callback. Instead, run your code in a post-step callback instead.

spaceUserData :: Space -> StateVar DataPtr Source #

A user definable data pointer. It is often useful to point this at the gamestate object or scene management object that owns the space.

spaceStaticBody :: Space -> GettableStateVar Body Source #

A dedicated static body for the space. You don’t have to use it, but because its memory is managed automatically with the space its very convenient. You can set its user data pointer to something helpful if you want for callbacks.

Memory Management Functions

More standard Chipmunk memory functions.

spaceNew :: IO Space Source #

Standard Chipmunk allocation function.

spaceFree :: Space -> IO () Source #

Standard Chipmunk deallocation function.

Operations

These functions add and remove shapes, bodies and constraints from space. The add/remove functions cannot be called from within a callback other than a postStep callback (which is different than a postSolve callback!). Attempting to add or remove objects from the space while spaceStep is still executing will throw an assertion. See the callbacks section for more information. Be careful not to free bodies before removing shapes and constraints attached to them or you will cause crashes.. The contains functions allow you to check if an object has been added to the space or not.

spaceAddShape :: Space -> Shape -> IO () Source #

Add shape to the space.

spaceAddBody :: Space -> Body -> IO () Source #

Add body to the space.

spaceAddConstraint :: Space -> Constraint -> IO () Source #

Add constraint to the space.

spaceRemoveShape :: Space -> Shape -> IO () Source #

Remove shape from the space.

spaceRemoveBody :: Space -> Body -> IO () Source #

Remove body from the space.

spaceRemoveConstraint :: Space -> Constraint -> IO () Source #

Remove constraint from the space.

spaceContainsShape :: Space -> Shape -> IO Bool Source #

Check if shape is attached to the space.

spaceContainsBody :: Space -> Body -> IO Bool Source #

Check if body is attached to the space.

spaceContainsConstraint :: Space -> Constraint -> IO Bool Source #

Check if constraint is attached to the space.

Spatial Indexing

Occasionally, you might want to update the collision detection data for a shape. If you move a static shape or a static body you must do this to let Chipmunk know it needs to have its collision detection data updated. You may also want to manually update the collision data for normal shapes if you move them and still want to perform queries against them before the next call to spaceStep.

spaceReindexShape :: Space -> Shape -> IO () Source #

Reindex a specific shape.

spaceReindexShapesForBody :: Space -> Body -> IO () Source #

Reindex all the shapes for a certain body.

spaceReindexStatic :: Space -> IO () Source #

Reindex all static shapes. Generally updating only the shapes that changed is faster.

Iterators

type SpaceBodyIteratorFunc = Body -> Ptr () -> IO () Source #

Type of callback which can be used to iterate all Bodys in a Space.

spaceEachBody Source #

Arguments

:: Space

space

-> SpaceBodyIteratorFunc

func

-> Ptr ()

data

-> IO () 

Call func for each body in the space also passing along your data pointer. Sleeping bodies are included, but static and kinematic bodies are not as they aren’t added to the space.

type SpaceShapeIteratorFunc = Shape -> Ptr () -> IO () Source #

Type of callback which can be used to iterate all Shapes in a Space.

spaceEachShape Source #

Arguments

:: Space

space

-> SpaceShapeIteratorFunc

func

-> Ptr ()

data

-> IO () 

Call func for each shape in the space also passing along your data pointer. Sleeping and static shapes are included.

type SpaceConstraintIteratorFunc = Constraint -> Ptr () -> IO () Source #

Type of callback which can be used to iterate all Constraints in a Space.

spaceEachConstraint Source #

Arguments

:: Space

space

-> SpaceConstraintIteratorFunc

func

-> Ptr ()

data

-> IO () 

Call func for each constraint in the space also passing along your data pointer.

Simulating the Space

spaceStep :: Space -> Double -> IO () Source #

Update the space for the given time step. Using a fixed time step is highly recommended. Doing so can greatly increase the quality of the simulation. The easiest way to do constant timesteps is to simple step forward by 1/60th of a second (or whatever your target framerate is) for each frame regardless of how long it took to render. This works fine for many games, but a better way to do it is to separate your physics timestep and rendering.

Notes

  • When removing objects from the space, make sure you remove any other objects that reference it. For instance, when you remove a body, remove the joints and shapes attached to it.
  • Using more iterations or smaller time steps will increase the physics quality, but also increase the CPU usage.

Chipmunk Constraints

data Constraint Source #

A constraint is something that describes how two bodies interact with each other. (how they constrain each other) Constraints can be simple joints that allow bodies to pivot around each other like the bones in your body, or they can be more abstract like the gear joint or motors.

Instances
Eq Constraint Source # 
Instance details

Defined in Chiphunk.Low.Types

Ord Constraint Source # 
Instance details

Defined in Chiphunk.Low.Types

Generic Constraint Source # 
Instance details

Defined in Chiphunk.Low.Types

Associated Types

type Rep Constraint :: Type -> Type #

Storable Constraint Source # 
Instance details

Defined in Chiphunk.Low.Types

Hashable Constraint Source # 
Instance details

Defined in Chiphunk.Low.Types

type Rep Constraint Source # 
Instance details

Defined in Chiphunk.Low.Types

type Rep Constraint = D1 (MetaData "Constraint" "Chiphunk.Low.Types" "chiphunk-0.1.1.0-I8qACn0ilueBvyWZpW4e9s" True) (C1 (MetaCons "Constraint" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ptr Constraint))))

What constraints are and what they are not

Constraints in Chipmunk are all velocity based constraints. This means that they act primarily by synchronizing the velocity of two bodies. A pivot joint holds two anchor points on two separate bodies together by defining equations that say that the velocity of the anchor points must be the same and calculating impulses to apply to the bodies to try and keep it that way. A constraint takes a velocity as it’s primary input and produces a velocity change as its output. Some constraints, (joints in particular) apply velocity changes to correct differences in positions. More about this in the next section.

A spring connected between two bodies is not a constraint. It’s very constraint-like as it creates forces that affect the velocities of the two bodies, but a spring takes distances as input and produces forces as its output. If a spring is not a constraint, then why do I have two varieties of spring constraints you ask? The reason is because they are damped springs. The damping associated with the spring is a true constraint that creates velocity changes based on the relative velocities of the two bodies it links. As it is convenient to put a damper and a spring together most of the time, I figured I might as well just apply the spring force as part of the constraint instead of having a damper constraint and having the user calculate and apply their own spring forces separately.

Properties

constraintBodyA :: Constraint -> GettableStateVar Body Source #

The first body constraint is attached to

constraintBodyB :: Constraint -> GettableStateVar Body Source #

The second body constraint is attached to

constraintMaxForce :: Constraint -> StateVar Double Source #

The maximum force that the constraint can use to act on the two bodies. Defaults to INFINITY.

constraintErrorBias :: Constraint -> StateVar Double Source #

The percentage of joint error that remains unfixed after a second. This works exactly the same as the collision bias property of a space, but applies to fixing error (stretching) of joints instead of overlapping collisions.

constraintMaxBias :: Constraint -> StateVar Double Source #

Get the maximum speed at which the constraint can apply error correction. Defaults to INFINITY.

constraintSpace :: Constraint -> GettableStateVar Space Source #

The Space that constraint has been added to.

constraintCollideBodies :: Constraint -> StateVar Bool Source #

Constraints can be used for filtering collisions too. When two bodies collide, Chipmunk ignores the collisions if this property is set to False on any constraint that connects the two bodies. Defaults to True.

This can be used to create a chain that self collides, but adjacent links in the chain do not collide.

constraintUserData :: Constraint -> StateVar DataPtr Source #

A user definable data pointer. Use this pointer to get a reference to the game object that owns this constraint from callbacks.

constraintImpulse :: Constraint -> GettableStateVar Double Source #

The most recent impulse that constraint applied. To convert this to a force, divide by the timestep passed to spaceStep. You can use this to implement breakable joints to check if the force they attempted to apply exceeded a certain threshold.

Error correction by Feedback

Joints in Chipmunk are not perfect. A pin joint can’t maintain the exact correct distance between its anchor points, nor can a pivot joint hold its anchor points completely together. Instead, they are designed to deal with this by correcting themselves over time. Since Chipmunk 5, you have a fair amount of extra control over how joints correct themselves and can even use this ability to create physical effects that allow you to use joints in unique ways:

  • Servo motors – Ex: open/close doors or rotate things without going over a maximum force.
  • Winches – Pull one object towards another at a constant speed without going over a maximum force.
  • Mouse manipulation – Interact with objects smoothly given coarse/shaky mouse input.

There are three properties of Constraint structs that control the error correction, maxForce, maxBias, and biasCoef. maxForce is pretty self explanatory, a joint or constraint will not be able to use more than this amount of force in order to function. If it needs more force to be able to hold itself together, it will fall apart. maxBias is the maximum speed at which error correction can be applied. If you change a property on a joint so that the joint will have to correct itself, it normally does so very quickly. By setting a maxSpeed you can make the joint work like a servo, correcting itself at a constant rate over a longer period of time. Lastly, biasCoef is the percentage of error corrected every step before clamping to a maximum speed. You can use this to make joints correct themselves smoothly instead of at a constant speed, but is probably the least useful of the three properties by far.

Constraints and Collision Shapes

Neither constraints or collision shapes have any knowledge of the other. When connecting joints to a body the anchor points don’t need to be inside of any shapes attached to the body and it often makes sense that they shouldn’t. Also, adding a constraint between two bodies doesn’t prevent their collision shapes from colliding. In fact, this is the primary reason that the collision group property exists.

Video Tour of Current Joint Types

Shared Memory Management Functions

constraintFree :: Constraint -> IO () Source #

Free function is shared by all joint types. Allocation functions are specific to each joint type.

Constraint Types

Pin Joints

pinJointNew Source #

Arguments

:: Body

First body to connect

-> Body

Second body to connect

-> Vect

First anchor

-> Vect

Second anchor

-> IO Constraint 

Connect two bodies via anchor points on those bodies. The distance between the two anchor points is measured when the joint is created. If you want to set a specific distance, use the setter function to override it.

Properties

pinJointAnchorA :: Constraint -> StateVar Vect Source #

Anchor on first body.

pinJointAnchorB :: Constraint -> StateVar Vect Source #

Anchor on second body.

pinJointDist :: Constraint -> StateVar Double Source #

Desired distance the joint will try to enforce.

Slide Joints

slideJointNew Source #

Arguments

:: Body

First body to connect

-> Body

Second body to connect

-> Vect

First anchor

-> Vect

Second anchor

-> Double

Minimum allowed distance

-> Double

Maximum allowed distance

-> IO Constraint 

Connect two bodies via anchor points forcing distance to remain in range.

Properties

slideJointAnchorA :: Constraint -> StateVar Vect Source #

Anchor on first body.

slideJointAnchorB :: Constraint -> StateVar Vect Source #

Anchor on second body.

slideJointMin :: Constraint -> StateVar Double Source #

The minimum distance the joint will try to enforce.

slideJointMax :: Constraint -> StateVar Double Source #

The maximum distance the joint will try to enforce.

Pivot Joints

(Note for bindings: So each instance of pivot joint can be replaced with pin joint with dist of 0?)

pivotJointNew Source #

Arguments

:: Body

First body to connect

-> Body

Second body to connect

-> Vect

Point in the world coordinates of the pivot

-> IO Constraint 

Because the pivot location is given in world coordinates, you must have the bodies moved into the correct positions already.

pivotJointNew2 Source #

Arguments

:: Body

First body to connect

-> Body

Second body to connect

-> Vect

Anchor on first body

-> Vect

Anchor on second body

-> IO Constraint 

Alternatively you can specify the joint based on a pair of anchor points, but make sure you have the bodies in the right place as the joint will fix itself as soon as you start simulating the space.

Properties

pivotJointAnchorA :: Constraint -> StateVar Vect Source #

Anchor on first body.

pivotJointAnchorB :: Constraint -> StateVar Vect Source #

Anchor on second body.

Groove Joint

grooveJointNew Source #

Arguments

:: Body

First body to connect

-> Body

Second body to connect

-> Vect

First endpoint of groove (on first body)

-> Vect

Second endpoint of groove (on first body)

-> Vect

Anchor (on second body)

-> IO Constraint 

Pivot is attached to groove on first body and to anchor on the second. All coordinates are body local.

Properties

grooveJointGrooveA :: Constraint -> StateVar Vect Source #

First endpoint of groove (on first body).

grooveJointGrooveB :: Constraint -> StateVar Vect Source #

Second endpoint of groove (on first body).

grooveJointAnchorB :: Constraint -> StateVar Vect Source #

Anchor on second body.

Damped Spring

dampedSpringNew Source #

Arguments

:: Body

First body to connect

-> Body

Second body to connect

-> Vect

First anchor

-> Vect

Second anchor

-> Double

Distance the spring wants to be

-> Double

Spring constant (Young's modulus)

-> Double

How soft to make damping of the spring

-> IO Constraint 

Defined much like a slide joint.

Properties

dampedSpringAnchorA :: Constraint -> StateVar Vect Source #

Anchor on first body.

dampedSpringAnchorB :: Constraint -> StateVar Vect Source #

Anchor on second body.

dampedSpringRestLength :: Constraint -> StateVar Double Source #

Desired distance the spring will try to enforce.

Damped Rotary Spring

Like a damped spring, but works in an angular fashion.

dampedRotarySpringNew Source #

Arguments

:: Body

First body to connect

-> Body

Second body to connect

-> Double

Relative angle in radians that the bodies want to have

-> Double

Spring constant (stiffness)

-> Double

Spring damping

-> IO Constraint 

Create new damped rotary spring constraint

Properties

dampedRotarySpringRestAngle :: Constraint -> StateVar Double Source #

Set desired angle in radians the spring will try to enforce.

Rotary Limit Joint

Constrains the relative rotations of two bodies. It is implemented so that it’s possible to for the range to be greater than a full revolution.

rotaryLimitJointNew Source #

Arguments

:: Body

First body to connect

-> Body

Second body to connect

-> Double

Minimum angle in radians the joint will enforce

-> Double

Maximum angle in radians the joint will enforce

-> IO Constraint 

Create new rotation limiting joint

Properties

rotaryLimitJointMin :: Constraint -> StateVar Double Source #

Minimum angle in radians the joint will try to enforce.

rotaryLimitJointMax :: Constraint -> StateVar Double Source #

Maximum angle in radians the joint will try to enforce.

Ratchet Joint

Works like a socket wrench.

ratchetJointNew Source #

Arguments

:: Body

First body to connect

-> Body

Second body to connect

-> Double

The initial offset to use when deciding where the ratchet angles are.

-> Double

The distance between “clicks”

-> IO Constraint 

Allocate and initialize a ratchet joint.

Properties

ratchetJointAngle :: Constraint -> StateVar Double Source #

The angle of the current ratchet tooth.

ratchetJointPhase :: Constraint -> StateVar Double Source #

The phase offset of the ratchet.

ratchetJointRatchet :: Constraint -> StateVar Double Source #

The angular distance of each ratchet.

Gear Joint

Keeps the angular velocity ratio of a pair of bodies constant.

gearJointNew Source #

Arguments

:: Body

First body to connect

-> Body

Second body to connect

-> Double

The initial angular offset of the two bodies.

-> Double

Ratio measures in absolute terms

-> IO Constraint 

Allocate and initialize a gear joint.

Properties

gearJointPhase :: Constraint -> StateVar Double Source #

Phase offset of the ratchet.

gearJointRatio :: Constraint -> StateVar Double Source #

Ratio of the ratchet

Simple Motor

Keeps the relative angular velocity of a pair of bodies constant. You will usually want to set an force (torque) maximum for motors as otherwise they will be able to apply a nearly infinite torque to keep the bodies moving.

simpleMotorNew Source #

Arguments

:: Body

First body to connect

-> Body

Second body to connect

-> Double

The desired relative angular velocity.

-> IO Constraint 

Allocate and initialize a simple motor.

Properties

simpleMotorRate :: Constraint -> StateVar Double Source #

Ratio of angular velocities.

Notes

  • You can add multiple joints between two bodies, but make sure that they don’t fight. Doing so can cause the bodies jitter or spin violently.

Overview of Collision Detection in Chipmunk

In order to make collision detection in Chipmunk as fast as possible, the process is broken down into several stages. While I’ve tried to keep it conceptually simple, the implementation can be a bit daunting. Fortunately as a user of the library, you don’t need to understand everything about how it works. Though if you are trying to squeeze every bit of performance out of Chipmunk, understanding this section can be helpful.

Spatial Indexing

A for loop that checks every object against every other object in the scene would be very slow. So the first stage of the collision detection, commonly called the broadphase, uses a high level spatial algorithm to decide which pairs of objects to check for collisions. Currently Chipmunk supports two spatial indexes, an axis-aligned bounding box tree and a spatial hash. These spatial indexes are able to quickly identify which pairs of shapes are near each other and should be checked for a collision.

Fast Collision Filtering

After the spatial index figures out which pairs of shapes are likely to be near each other, it passes each pair back to the space using a callback to perform some additional filtering on the pairs. Before doing anything else, Chipmunk performs a few quick tests to check if shapes should collide.

  • Bounding Box Test: The shapes are not colliding if their bounding boxes are not overlapping. Objects like diagonal line segments can trigger a lot of false positives here, but it’s unlikely to be something you should worry about.
  • Category Mask Test: The categories of each shape are bitwise ANDed against the category mask of the other shape. If either result is 0, the shapes do not collide.
  • Group Test: Shapes shouldn’t collide with other shapes in the same non-zero group.

Constraint Based Filtering

After fast collision filtering, Chipmunk checks the list of joints on one of the bodies to see if it has a constraint that attaches it to the other body. If that constraint’s collideBodies property is false, the collision will be ignored. This check is often very fast since most scenes don’t contain a lot of constraints.

Primitive Shape to Shape Collision Detection

The most expensive test is to actually check for overlap based on their geometry. Circle to circle and circle to line collisions are very fast. Segment to segment and poly to poly collisions are handled using the GJK/EPA algorithms, and get more expensive as the number of vertexes increases. Simpler shapes make for faster collisions, and often more important, fewer collision points for the solver to run. Chipmunk uses a small dispatch table to figure out which function to use to check if the shapes overlap.

Without going into too much detail, the GJK algorithm checks the distance between two objects, and the EPA algorithm checks how much they are overlapping. If you give you segment and poly shapes a small radius when creating them, the EPA algorithm can usually be skipped, speeding up the collision detection considerably. The radius should be at least as big as the amount of allowed collision slop.

Collision Handler Filtering

After checking if two shapes overlap Chipmunk will look to see if you have defined a collision handler for the collision types of the shapes. This is vital to process collisions events for the gameplay, but also gives you a very flexible way to filter out collisions. The return value of the begin and preSolve callbacks determines whether or not the colliding pair of shapes is discarded or not. Returning true will keep the pair, false will discard it. Rejecting a collision from a begin callback is permanent, rejecting it from the preSolve only applies to the step it occured in. If you don’t define a handler for the given collision types, Chipmunk will call the space’s default handler, which by default is defined to simply accept all collisions.

Wildcard collisions can also return a value, but they are handled in a more complicated way. When you create a collision handler between two specific collision types, it’s your responsibility to decide when to call the wildcard handlers and what to do with their return values. Otherwise, the default is to call the wildcard handler for the first type, then the second type, and use a logical AND of their return values as filtering value. See DefaultBegin() in cpSpace.c for more information.

While using callbacks to filter collisions is the most flexible way, keep in mind that by the time your callback is called all of the most expensive collision detection has already been done. For simulations with a lot of colliding objects each frame, the time spent finding collisions is small compared to the time spent solving the physics for them so it may not be a big deal. Fast collision filtering should be preferred if possible.

Collision Callbacks

A physics library without any events or feedback would not be very useful for games. How would you know when the player bumped into an enemy so that you could take some health points away? How would you know how hard the car hit something so you don’t play a loud crash noise when a pebble hits it? What if you need to decide if a collision should be ignored based on specific conditions, like implementing one way platforms? Chipmunk has a number of powerful callback systems that you can use to solve these problems.

Collision Handlers

Collision handler function types. While all of them take an arbiter, space, and a user data pointer, only the begin and preSolve callbacks return a value. See above for more information.

type CollisionCallback ret = Arbiter -> Space -> DataPtr -> IO ret Source #

Collision callback

type CollisionType = WordPtr Source #

Collision type

data CollisionHandler Source #

This collision handler processes collisions between objects of type typeA and typeB. Fill the desired collision callback functions- they are documented above. A user definable context pointer userData is included for your convenience. This pointer is provided as an argument in each callback function.

A collision handler is a set of 4 function callbacks for the different collision events that Chipmunk recognizes.

Constructors

CollisionHandler 

Fields

  • chTypeA :: !CollisionType

    typeA

  • chTypeB :: !CollisionType

    typeB

  • chBeginFunc :: !(FunPtr (CollisionCallback CPBool))

    Two shapes just started touching for the first time this step. Return true from the callback to process the collision normally or false to cause Chipmunk to ignore the collision entirely. If you return false, the preSolve and postSolve callbacks will never be run, but you will still recieve a separate event when the shapes stop overlapping.

  • chPreSolveFunc :: !(FunPtr (CollisionCallback CPBool))

    Two shapes are touching during this step. Return false from the callback to make Chipmunk ignore the collision this step or true to process it normally. Additionally, you may override collision values using arbiterFriction, arbiterRestitution or arbiterSurfaceVelocity to provide custom friction, elasticity, or surface velocity values. See Arbiter for more info.

  • chPostSolveFunc :: !(FunPtr (CollisionCallback ()))

    Two shapes are touching and their collision response has been processed. You can retrieve the collision impulse or kinetic energy at this time if you want to use it to calculate sound volumes or damage amounts. See Arbiter for more info.

  • chSeparateFunc :: !(FunPtr (CollisionCallback ()))

    Two shapes have just stopped touching for the first time this step. To ensure that begin/separate are always called in balanced pairs, it will also be called when removing a shape while its in contact with something or when deallocating the space.

  • cpUserData :: !DataPtr

    userData

type CollisionHandlerPtr = Ptr CollisionHandler Source #

Pointer to collision handler

spaceAddCollisionHandler Source #

Add a CollisionHandler for specific collision type pair or return the existing handler for the type pair. Whenever shapes with collision types (cpShape.collision_type) a and b collide, this handler will be used to process the collision events. When a new collision handler is created, the callbacks will all be set to builtin callbacks that perform the default behavior (call the wildcard handlers, and accept all collisions).

spaceAddWildcardHandler Source #

Arguments

:: Space 
-> CollisionType

type

-> IO CollisionHandlerPtr 

Add a wildcard collision handler for given collision type. This handler will be used any time an object with this type collides with another object, regardless of its type. A good example is a projectile that should be destroyed the first time it hits anything. There may be a specific collision handler and two wildcard handlers. It’s up to the specific handler to decide if and when to call the wildcard handlers and what to do with their return values. (See arbiterCallWildcard* below) When a new wildcard handler is created, the callbacks will all be set to builtin callbacks that perform the default behavior. (accept all collisions in begin and preSolve, or do nothing for postSolve and separate.

spaceAddDefaultCollisionHandler :: Space -> IO CollisionHandlerPtr Source #

Return a reference to the default collision handler or that is used to process all collisions that don’t have a more specific handler. The default behavior for each of the callbacks is to call the wildcard handlers, ANDing their return values together if applicable.

modifyCollisionHandler :: CollisionHandlerPtr -> (CollisionHandler -> IO CollisionHandler) -> IO () Source #

Use this helper function to modify collision handler.

spaceAddCollisionHandler s t1 t2 >>= flip modifyColliionHandler (ch -> pure ch {chSeparateFunc = separateCollback})

mkCallback :: CollisionCallback () -> IO (FunPtr (CollisionCallback ())) Source #

Make callback. Need to free afterwards.

mkCallbackB :: CollisionCallback Bool -> IO (FunPtr (CollisionCallback CPBool)) Source #

Make callback. Need to free afterwards.

Post-Step Callbacks

Post-step callbacks are the one place where you can break the rules about adding or removing objects from within a callback. In fact, their primary function is to help you safely remove objects from the space that you wanted to disable or destroy in a collision or query callback.

Post step callbacks are registered as a function and a pointer that is used as a key. You can only register one postStep callback per key. This prevents you from accidentally removing an object more than once. For instance, say that you get a collision callback between a bullet and object A. You want to destroy both the bullet and object A, so you register a postStep callback to safely remove them from your game. Then you get a second collision callback between the bullet and object B. You register a postStep callback to remove object B, and a second postStep callback to remove the bullet. Because you can only register one callback per key, the postStep callback for the bullet will only be called once and you can’t accidentally try to remove it twice.

type PostStepFunc Source #

Arguments

 = Space

space

-> Ptr ()

obj

-> Ptr ()

data

-> IO () 

Function type used for postStep callbacks. space is the space the callback was registered on, obj is the pointer value you supplied as the key, and data is a user definable pointer you can use to pass in as a context value.

spaceAddPostStepCallback Source #

Arguments

:: Space

space

-> PostStepFunc

func

-> Ptr ()

key

-> Ptr ()

data

-> IO Bool 

Add func to be called before spaceStep returns. key and data will be passed to your function. Only the first callback registered for any unique value of key will be recorded.

It returns True if the callback is scheduled and False when the key has already been used.

The behavior of adding a postStep callback from outside of a collision handler or query callback is undefined.

Examples

See the callback examples for more information.

Chipmunk Collision Pairs

data Arbiter Source #

Chipmunk’s Arbiter struct encapsulates a pair of colliding shapes and all of the data about their collision. Arbiter is created when a collision starts, and persist until those shapes are no longer colliding.

Why are they called arbiters? The short answer is that I kept using the word “arbitrates” to describe the way that collisions were resolved and then I saw that Box2D actually called them arbiters way back in 2006 when I was looking at its solver. An arbiter is like a judge, a person that has authority to settle disputes between two people. It was a fun, fitting name and was shorter to type than CollisionPair which I had been using. It was originally meant to be a private internal structure only, but evolved to be useful from callbacks.

Instances
Eq Arbiter Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

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

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

Ord Arbiter Source # 
Instance details

Defined in Chiphunk.Low.Types

Generic Arbiter Source # 
Instance details

Defined in Chiphunk.Low.Types

Associated Types

type Rep Arbiter :: Type -> Type #

Methods

from :: Arbiter -> Rep Arbiter x #

to :: Rep Arbiter x -> Arbiter #

Storable Arbiter Source # 
Instance details

Defined in Chiphunk.Low.Types

Hashable Arbiter Source # 
Instance details

Defined in Chiphunk.Low.Types

Methods

hashWithSalt :: Int -> Arbiter -> Int #

hash :: Arbiter -> Int #

type Rep Arbiter Source # 
Instance details

Defined in Chiphunk.Low.Types

type Rep Arbiter = D1 (MetaData "Arbiter" "Chiphunk.Low.Types" "chiphunk-0.1.1.0-I8qACn0ilueBvyWZpW4e9s" True) (C1 (MetaCons "Arbiter" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ptr Arbiter))))

Memory Management

You will never need to create or free an arbiter. More importantly, because they are entirely managed by the space you should never store a reference to an arbiter as you don’t know when they will be freed or reused. Use them within the callback where they are given to you and then forget about them or copy out the information you need.

Properties

arbiterRestitution :: Arbiter -> StateVar Double Source #

The calculated elasticity for this collision pair. Setting the value in a preSolve() callback will override the value calculated by the space. The default calculation multiplies the elasticity of the two shapes together.

arbiterFriction :: Arbiter -> StateVar Double Source #

The calculated friction for this collision pair. Setting the value in a preSolve() callback will override the value calculated by the space. The default calculation multiplies the friction of the two shapes together.

arbiterSurfaceVelocity :: Arbiter -> StateVar Vect Source #

The calculated surface velocity for this collision pair. Setting the value in a preSolve() callback will override the value calculated by the space. The default calculation subtracts the surface velocity of the second shape from the first and then projects that onto the tangent of the collision. This is so that only friction is affected by default calculation.

Using a custom calculation, you can make something that responds like a pinball bumper, or where the surface velocity is dependent on the location of the contact point.

arbiterUserData :: Arbiter -> StateVar DataPtr Source #

A user definable context pointer. The value will persist until just after the separate callback is called for the pair.

Note: If you need to clean up this pointer, you should implement the separate callback to do it. Also be careful when destroying the space as there may be active collisions still. In order to trigger the separate callbacks and clean up your data, you’ll need to remove all the shapes from the space before disposing of it. This is something I’d suggest doing anyway. See ChipmunkDemo.c:ChipmunkDemoFreeSpaceChildren() for an example of how to do it easily.

Collision Point(s)

arbiterCount :: Arbiter -> GettableStateVar Int Source #

The number of contacts tracked by this arbiter. For the forseeable future, the maximum number of contacts will be two.

arbiterNormal :: Arbiter -> GettableStateVar Vect Source #

Collision normal in a specific point tracked by this collision.

arbiterPointA :: Arbiter -> Int -> GettableStateVar Vect Source #

Collision point of a specific point on first body.

arbiterPointB :: Arbiter -> Int -> GettableStateVar Vect Source #

Collision point of a specific point on second body.

arbiterDepth :: Arbiter -> Int -> GettableStateVar Double Source #

Penetration depth of a collision point.

Other

arbiterIsFirstContact :: Arbiter -> IO Bool Source #

Returns true if this is the first step the two shapes started touching. This can be useful for sound effects for instance. If its the first frame for a certain collision, check the energy of the collision in a postStep callbock and use that to determine the volume of a sound effect to play.

arbiterIsRemoval :: Arbiter -> IO Bool Source #

Returns True during a separate callback if the callback was invoked due to an object removal.

Bodies and shapes

arbiterShapes :: Arbiter -> GettableStateVar (Shape, Shape) Source #

The colliding shapes in the order that they were defined in the collision handler associated with this arbiter. If you defined the handler as cpSpaceAddCollisionHandler(space, 1, 2, ...), you you will find that a->collision_type == 1 and b->collision_type == 2.

arbiterBodies :: Arbiter -> GettableStateVar (Body, Body) Source #

The colliding bodies in the order that they were defined in the collision handler associated with this arbiter. If you defined the handler as cpSpaceAddCollisionHandler(space, 1, 2, ...), you you will find that a->collision_type == 1 and b->collision_type == 2.

Running wildcard handlers

These functions invoke the wildcard handlers for a given collision. For custom collision handlers between specific types or overriding the default handler, you must decide how to invoke the wildcard handlers since it may be important to call the wildcards first, last, or possibly skip them entirely. For the begin and preSolve callbacks, you also need to decide what to do with their return values since they may not agree with each other or the specific handler they were called from. Every collision handler is defined for two types, the “A” variants of these functions call the wildcard handler for the first type, and the “B” variants call the handler for the second type.

arbiterCallWildcardBeginA :: Arbiter -> Space -> IO Bool Source #

Run begin wildcard callback for first body.

arbiterCallWildcardBeginB :: Arbiter -> Space -> IO Bool Source #

Run begin wildcard callback for second body.

arbiterCallWildcardPreSolveA :: Arbiter -> Space -> IO Bool Source #

Run preSolve wildcard callback for first body.

arbiterCallWildcardPreSolveB :: Arbiter -> Space -> IO Bool Source #

Run preSolve wildcard callback for second body.

arbiterCallWildcardPostSolveA :: Arbiter -> Space -> IO () Source #

Run postSolve wildcard callback for first body.

arbiterCallWildcardPostSolveB :: Arbiter -> Space -> IO () Source #

Run postSolve wildcard callback for second body.

arbiterCallWildcardSeparateA :: Arbiter -> Space -> IO () Source #

Run separate wildcard callback for first body.

arbiterCallWildcardSeparateB :: Arbiter -> Space -> IO () Source #

Run separate wildcard callback for second body.

Misc

type DataPtr = Ptr () Source #

Pointer to user data.

data Transform Source #

Type used for 2×3 affine transforms in Chipmunk.

Constructors

Transform 

Fields

Re-exports

nullPtr :: Ptr a #

The constant nullPtr contains a distinguished value of Ptr that is not associated with a valid memory location.

class HasGetter t a | t -> a where #

This is the class of all readable state variables.

Methods

get :: MonadIO m => t -> m a #

Instances
HasGetter (IO a) a 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => IO a -> m a #

Storable a => HasGetter (Ptr a) a 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => Ptr a -> m a #

HasGetter (StateVar a) a 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => StateVar a -> m a #

Storable a => HasGetter (ForeignPtr a) a 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => ForeignPtr a -> m a #

HasGetter (STM a) a 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => STM a -> m a #

HasGetter (TVar a) a 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => TVar a -> m a #

HasGetter (IORef a) a 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => IORef a -> m a #

class HasSetter t a | t -> a where #

This is the class of all writable state variables.

Methods

($=) :: MonadIO m => t -> a -> m () infixr 2 #

Write a new value into a state variable.

Instances
Storable a => HasSetter (Ptr a) a 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => Ptr a -> a -> m () #

HasSetter (StateVar a) a 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => StateVar a -> a -> m () #

HasSetter (SettableStateVar a) a 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => SettableStateVar a -> a -> m () #

Storable a => HasSetter (ForeignPtr a) a 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => ForeignPtr a -> a -> m () #

HasSetter (TVar a) a 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => TVar a -> a -> m () #

HasSetter (IORef a) a 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => IORef a -> a -> m () #