-- GENERATED by C->Haskell Compiler, version 0.28.3 Switcheroo, 25 November 2017 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/Chiphunk/Low/Constraint.chs" #-}
-- | Description: Dealing with joints/constraints
-- Module defines utilities for operations with constraints.
module Chiphunk.Low.Constraint
  ( Constraint
  , constraintBodyA
  , constraintBodyB
  , constraintMaxForce
  , constraintErrorBias
  , constraintMaxBias
  , constraintSpace
  , constraintCollideBodies
  , constraintUserData
  , constraintImpulse
  , constraintFree
  , pinJointNew
  , pinJointAnchorA
  , pinJointAnchorB
  , pinJointDist
  , slideJointNew
  , slideJointAnchorA
  , slideJointAnchorB
  , slideJointMin
  , slideJointMax
  , pivotJointNew
  , pivotJointNew2
  , pivotJointAnchorA
  , pivotJointAnchorB
  , grooveJointNew
  , grooveJointGrooveA
  , grooveJointGrooveB
  , grooveJointAnchorB
  , dampedSpringNew
  , dampedSpringAnchorA
  , dampedSpringAnchorB
  , dampedSpringRestLength
  , dampedSpringStiffness
  , dampedSpringDamping
  , dampedRotarySpringNew
  , dampedRotarySpringRestAngle
  , dampedRotarySpringStiffness
  , dampedRotarySpringDamping
  , rotaryLimitJointNew
  , rotaryLimitJointMin
  , rotaryLimitJointMax
  , ratchetJointNew
  , ratchetJointAngle
  , ratchetJointPhase
  , ratchetJointRatchet
  , gearJointNew
  , gearJointPhase
  , gearJointRatio

  , simpleMotorNew
  , simpleMotorRate
  ) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Marshal.Utils as C2HSImp



import Data.StateVar
import Foreign

import Chiphunk.Low.Types
{-# LINE 60 "src/Chiphunk/Low/Constraint.chs" #-}





cpConstraintGetBodyA :: (Constraint) -> IO ((Body))
cpConstraintGetBodyA a1 =
  let {a1' = id a1} in
  cpConstraintGetBodyA'_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 65 "src/Chiphunk/Low/Constraint.chs" #-}


-- | The first body constraint is attached to
constraintBodyA :: Constraint -> GettableStateVar Body
constraintBodyA = makeGettableStateVar . cpConstraintGetBodyA

cpConstraintGetBodyB :: (Constraint) -> IO ((Body))
cpConstraintGetBodyB a1 =
  let {a1' = id a1} in
  cpConstraintGetBodyB'_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 71 "src/Chiphunk/Low/Constraint.chs" #-}


-- | The second body constraint is attached to
constraintBodyB :: Constraint -> GettableStateVar Body
constraintBodyB = makeGettableStateVar . cpConstraintGetBodyB

cpConstraintGetMaxForce :: (Constraint) -> IO ((Double))
cpConstraintGetMaxForce a1 =
  let {a1' = id a1} in
  cpConstraintGetMaxForce'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 77 "src/Chiphunk/Low/Constraint.chs" #-}


cpConstraintSetMaxForce :: (Constraint) -> (Double) -> IO ()
cpConstraintSetMaxForce a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpConstraintSetMaxForce'_ a1' a2' >>
  return ()

{-# LINE 79 "src/Chiphunk/Low/Constraint.chs" #-}


-- | The maximum force that the constraint can use to act on the two bodies.
-- Defaults to INFINITY.
constraintMaxForce :: Constraint -> StateVar Double
constraintMaxForce = mkStateVar cpConstraintGetMaxForce cpConstraintSetMaxForce

cpConstraintGetErrorBias :: (Constraint) -> IO ((Double))
cpConstraintGetErrorBias a1 =
  let {a1' = id a1} in
  cpConstraintGetErrorBias'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 86 "src/Chiphunk/Low/Constraint.chs" #-}


cpConstraintSetErrorBias :: (Constraint) -> (Double) -> IO ()
cpConstraintSetErrorBias a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpConstraintSetErrorBias'_ a1' a2' >>
  return ()

{-# LINE 88 "src/Chiphunk/Low/Constraint.chs" #-}


-- | 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.
constraintErrorBias :: Constraint -> StateVar Double
constraintErrorBias = mkStateVar cpConstraintGetErrorBias cpConstraintSetErrorBias

cpConstraintGetMaxBias :: (Constraint) -> IO ((Double))
cpConstraintGetMaxBias a1 =
  let {a1' = id a1} in
  cpConstraintGetMaxBias'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 96 "src/Chiphunk/Low/Constraint.chs" #-}


cpConstraintSetMaxBias :: (Constraint) -> (Double) -> IO ()
cpConstraintSetMaxBias a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpConstraintSetMaxBias'_ a1' a2' >>
  return ()

{-# LINE 98 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Get the maximum speed at which the constraint can apply error correction.
-- Defaults to INFINITY.
constraintMaxBias :: Constraint -> StateVar Double
constraintMaxBias = mkStateVar cpConstraintGetMaxBias cpConstraintSetMaxBias

cpConstraintGetSpace :: (Constraint) -> IO ((Space))
cpConstraintGetSpace a1 =
  let {a1' = id a1} in
  cpConstraintGetSpace'_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 105 "src/Chiphunk/Low/Constraint.chs" #-}


-- | The 'Space' that constraint has been added to.
constraintSpace :: Constraint -> GettableStateVar Space
constraintSpace = makeGettableStateVar . cpConstraintGetSpace

cpConstraintGetCollideBodies :: (Constraint) -> IO ((Bool))
cpConstraintGetCollideBodies a1 =
  let {a1' = id a1} in
  cpConstraintGetCollideBodies'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 111 "src/Chiphunk/Low/Constraint.chs" #-}


cpConstraintSetCollideBodies :: (Constraint) -> (Bool) -> IO ()
cpConstraintSetCollideBodies a1 a2 =
  let {a1' = id a1} in
  let {a2' = C2HSImp.fromBool a2} in
  cpConstraintSetCollideBodies'_ a1' a2' >>
  return ()

{-# LINE 113 "src/Chiphunk/Low/Constraint.chs" #-}


-- | 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.
constraintCollideBodies :: Constraint -> StateVar Bool
constraintCollideBodies = mkStateVar cpConstraintGetCollideBodies cpConstraintSetCollideBodies

cpConstraintGetUserData :: (Constraint) -> IO ((DataPtr))
cpConstraintGetUserData a1 =
  let {a1' = id a1} in
  cpConstraintGetUserData'_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 125 "src/Chiphunk/Low/Constraint.chs" #-}


cpConstraintSetUserData :: (Constraint) -> (DataPtr) -> IO ()
cpConstraintSetUserData a1 a2 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  cpConstraintSetUserData'_ a1' a2' >>
  return ()

{-# LINE 127 "src/Chiphunk/Low/Constraint.chs" #-}


-- | A user definable data pointer.
-- Use this pointer to get a reference to the game object that owns this constraint
-- from callbacks.
constraintUserData :: Constraint -> StateVar DataPtr
constraintUserData = mkStateVar cpConstraintGetUserData cpConstraintSetUserData

cpConstraintGetImpulse :: (Constraint) -> IO ((Double))
cpConstraintGetImpulse a1 =
  let {a1' = id a1} in
  cpConstraintGetImpulse'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 135 "src/Chiphunk/Low/Constraint.chs" #-}


-- | 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.
constraintImpulse :: Constraint -> GettableStateVar Double
constraintImpulse = makeGettableStateVar . cpConstraintGetImpulse

-- | Free function is shared by all joint types. Allocation functions are specific to each joint type.
constraintFree :: (Constraint) -> IO ()
constraintFree a1 =
  let {a1' = id a1} in
  constraintFree'_ a1' >>
  return ()

{-# LINE 145 "src/Chiphunk/Low/Constraint.chs" #-}

-- no "unsafe" qualifier because I think it may trigger separte callbacks

-- | 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.
pinJointNew :: (Body) -- ^ First body to connect
 -> (Body) -- ^ Second body to connect
 -> (Vect) -- ^ First anchor
 -> (Vect) -- ^ Second anchor
 -> IO ((Constraint))
pinJointNew a1 a2 a3 a4 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  with a3 $ \a3' ->
  with a4 $ \a4' ->
  pinJointNew'_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 155 "src/Chiphunk/Low/Constraint.chs" #-}


w_cpPinJointGetAnchorA :: (Constraint) -> IO ((Vect))
w_cpPinJointGetAnchorA a1 =
  let {a1' = id a1} in
  alloca $ \a2' ->
  w_cpPinJointGetAnchorA'_ a1' a2' >>
  peek  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 157 "src/Chiphunk/Low/Constraint.chs" #-}


cpPinJointSetAnchorA :: (Constraint) -> (Vect) -> IO ()
cpPinJointSetAnchorA a1 a2 =
  let {a1' = id a1} in
  with a2 $ \a2' ->
  cpPinJointSetAnchorA'_ a1' a2' >>
  return ()

{-# LINE 159 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Anchor on first body.
pinJointAnchorA :: Constraint -> StateVar Vect
pinJointAnchorA = mkStateVar w_cpPinJointGetAnchorA cpPinJointSetAnchorA

w_cpPinJointGetAnchorB :: (Constraint) -> IO ((Vect))
w_cpPinJointGetAnchorB a1 =
  let {a1' = id a1} in
  alloca $ \a2' ->
  w_cpPinJointGetAnchorB'_ a1' a2' >>
  peek  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 165 "src/Chiphunk/Low/Constraint.chs" #-}


cpPinJointSetAnchorB :: (Constraint) -> (Vect) -> IO ()
cpPinJointSetAnchorB a1 a2 =
  let {a1' = id a1} in
  with a2 $ \a2' ->
  cpPinJointSetAnchorB'_ a1' a2' >>
  return ()

{-# LINE 167 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Anchor on second body.
pinJointAnchorB :: Constraint -> StateVar Vect
pinJointAnchorB = mkStateVar w_cpPinJointGetAnchorB cpPinJointSetAnchorB

cpPinJointGetDist :: (Constraint) -> IO ((Double))
cpPinJointGetDist a1 =
  let {a1' = id a1} in
  cpPinJointGetDist'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 173 "src/Chiphunk/Low/Constraint.chs" #-}


cpPinJointSetDist :: (Constraint) -> (Double) -> IO ()
cpPinJointSetDist a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpPinJointSetDist'_ a1' a2' >>
  return ()

{-# LINE 175 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Desired distance the joint will try to enforce.
pinJointDist :: Constraint -> StateVar Double
pinJointDist = mkStateVar cpPinJointGetDist cpPinJointSetDist

-- | Connect two bodies via anchor points forcing distance to remain in range.
slideJointNew :: (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))
slideJointNew a1 a2 a3 a4 a5 a6 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  with a3 $ \a3' ->
  with a4 $ \a4' ->
  let {a5' = realToFrac a5} in
  let {a6' = realToFrac a6} in
  slideJointNew'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 189 "src/Chiphunk/Low/Constraint.chs" #-}


w_cpSlideJointGetAnchorA :: (Constraint) -> IO ((Vect))
w_cpSlideJointGetAnchorA a1 =
  let {a1' = id a1} in
  alloca $ \a2' ->
  w_cpSlideJointGetAnchorA'_ a1' a2' >>
  peek  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 191 "src/Chiphunk/Low/Constraint.chs" #-}


cpSlideJointSetAnchorA :: (Constraint) -> (Vect) -> IO ()
cpSlideJointSetAnchorA a1 a2 =
  let {a1' = id a1} in
  with a2 $ \a2' ->
  cpSlideJointSetAnchorA'_ a1' a2' >>
  return ()

{-# LINE 193 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Anchor on first body.
slideJointAnchorA :: Constraint -> StateVar Vect
slideJointAnchorA = mkStateVar w_cpSlideJointGetAnchorA cpSlideJointSetAnchorA

w_cpSlideJointGetAnchorB :: (Constraint) -> IO ((Vect))
w_cpSlideJointGetAnchorB a1 =
  let {a1' = id a1} in
  alloca $ \a2' ->
  w_cpSlideJointGetAnchorB'_ a1' a2' >>
  peek  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 199 "src/Chiphunk/Low/Constraint.chs" #-}


cpSlideJointSetAnchorB :: (Constraint) -> (Vect) -> IO ()
cpSlideJointSetAnchorB a1 a2 =
  let {a1' = id a1} in
  with a2 $ \a2' ->
  cpSlideJointSetAnchorB'_ a1' a2' >>
  return ()

{-# LINE 201 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Anchor on second body.
slideJointAnchorB :: Constraint -> StateVar Vect
slideJointAnchorB = mkStateVar w_cpSlideJointGetAnchorB cpSlideJointSetAnchorB

cpSlideJointGetMin :: (Constraint) -> IO ((Double))
cpSlideJointGetMin a1 =
  let {a1' = id a1} in
  cpSlideJointGetMin'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 207 "src/Chiphunk/Low/Constraint.chs" #-}


cpSlideJointSetMin :: (Constraint) -> (Double) -> IO ()
cpSlideJointSetMin a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpSlideJointSetMin'_ a1' a2' >>
  return ()

{-# LINE 209 "src/Chiphunk/Low/Constraint.chs" #-}


-- | The minimum distance the joint will try to enforce.
slideJointMin :: Constraint -> StateVar Double
slideJointMin = mkStateVar cpSlideJointGetMin cpSlideJointSetMin

cpSlideJointGetMax :: (Constraint) -> IO ((Double))
cpSlideJointGetMax a1 =
  let {a1' = id a1} in
  cpSlideJointGetMax'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 215 "src/Chiphunk/Low/Constraint.chs" #-}


cpSlideJointSetMax :: (Constraint) -> (Double) -> IO ()
cpSlideJointSetMax a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpSlideJointSetMax'_ a1' a2' >>
  return ()

{-# LINE 217 "src/Chiphunk/Low/Constraint.chs" #-}


-- | The maximum distance the joint will try to enforce.
slideJointMax :: Constraint -> StateVar Double
slideJointMax = mkStateVar cpSlideJointGetMax cpSlideJointSetMax

-- | Because the pivot location is given in world coordinates,
-- you must have the bodies moved into the correct positions already.
pivotJointNew :: (Body) -- ^ First body to connect
 -> (Body) -- ^ Second body to connect
 -> (Vect) -- ^ Point in the world coordinates of the pivot
 -> IO ((Constraint))
pivotJointNew a1 a2 a3 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  with a3 $ \a3' ->
  pivotJointNew'_ a1' a2' a3' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 229 "src/Chiphunk/Low/Constraint.chs" #-}


-- | 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.
pivotJointNew2 :: (Body) -- ^ First body to connect
 -> (Body) -- ^ Second body to connect
 -> (Vect) -- ^ Anchor on first body
 -> (Vect) -- ^ Anchor on second body
 -> IO ((Constraint))
pivotJointNew2 a1 a2 a3 a4 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  with a3 $ \a3' ->
  with a4 $ \a4' ->
  pivotJointNew2'_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 239 "src/Chiphunk/Low/Constraint.chs" #-}


w_cpPivotJointGetAnchorA :: (Constraint) -> IO ((Vect))
w_cpPivotJointGetAnchorA a1 =
  let {a1' = id a1} in
  alloca $ \a2' ->
  w_cpPivotJointGetAnchorA'_ a1' a2' >>
  peek  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 241 "src/Chiphunk/Low/Constraint.chs" #-}


cpPivotJointSetAnchorA :: (Constraint) -> (Vect) -> IO ()
cpPivotJointSetAnchorA a1 a2 =
  let {a1' = id a1} in
  with a2 $ \a2' ->
  cpPivotJointSetAnchorA'_ a1' a2' >>
  return ()

{-# LINE 243 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Anchor on first body.
pivotJointAnchorA :: Constraint -> StateVar Vect
pivotJointAnchorA = mkStateVar w_cpPivotJointGetAnchorA cpPivotJointSetAnchorA

w_cpPivotJointGetAnchorB :: (Constraint) -> IO ((Vect))
w_cpPivotJointGetAnchorB a1 =
  let {a1' = id a1} in
  alloca $ \a2' ->
  w_cpPivotJointGetAnchorB'_ a1' a2' >>
  peek  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 249 "src/Chiphunk/Low/Constraint.chs" #-}


cpPivotJointSetAnchorB :: (Constraint) -> (Vect) -> IO ()
cpPivotJointSetAnchorB a1 a2 =
  let {a1' = id a1} in
  with a2 $ \a2' ->
  cpPivotJointSetAnchorB'_ a1' a2' >>
  return ()

{-# LINE 251 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Anchor on second body.
pivotJointAnchorB :: Constraint -> StateVar Vect
pivotJointAnchorB = mkStateVar w_cpPivotJointGetAnchorB cpPivotJointSetAnchorB

-- | Pivot is attached to groove on first body and to anchor on the second. All coordinates are body local.
grooveJointNew :: (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))
grooveJointNew a1 a2 a3 a4 a5 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  with a3 $ \a3' ->
  with a4 $ \a4' ->
  with a5 $ \a5' ->
  grooveJointNew'_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 264 "src/Chiphunk/Low/Constraint.chs" #-}


w_cpGrooveJointGetGrooveA :: (Constraint) -> IO ((Vect))
w_cpGrooveJointGetGrooveA a1 =
  let {a1' = id a1} in
  alloca $ \a2' ->
  w_cpGrooveJointGetGrooveA'_ a1' a2' >>
  peek  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 266 "src/Chiphunk/Low/Constraint.chs" #-}


cpGrooveJointSetGrooveA :: (Constraint) -> (Vect) -> IO ()
cpGrooveJointSetGrooveA a1 a2 =
  let {a1' = id a1} in
  with a2 $ \a2' ->
  cpGrooveJointSetGrooveA'_ a1' a2' >>
  return ()

{-# LINE 268 "src/Chiphunk/Low/Constraint.chs" #-}


-- | First endpoint of groove (on first body).
grooveJointGrooveA :: Constraint -> StateVar Vect
grooveJointGrooveA = mkStateVar w_cpGrooveJointGetGrooveA cpGrooveJointSetGrooveA

w_cpGrooveJointGetGrooveB :: (Constraint) -> IO ((Vect))
w_cpGrooveJointGetGrooveB a1 =
  let {a1' = id a1} in
  alloca $ \a2' ->
  w_cpGrooveJointGetGrooveB'_ a1' a2' >>
  peek  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 274 "src/Chiphunk/Low/Constraint.chs" #-}


cpGrooveJointSetGrooveB :: (Constraint) -> (Vect) -> IO ()
cpGrooveJointSetGrooveB a1 a2 =
  let {a1' = id a1} in
  with a2 $ \a2' ->
  cpGrooveJointSetGrooveB'_ a1' a2' >>
  return ()

{-# LINE 276 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Second endpoint of groove (on first body).
grooveJointGrooveB :: Constraint -> StateVar Vect
grooveJointGrooveB = mkStateVar w_cpGrooveJointGetGrooveB cpGrooveJointSetGrooveB

w_cpGrooveJointGetAnchorB :: (Constraint) -> IO ((Vect))
w_cpGrooveJointGetAnchorB a1 =
  let {a1' = id a1} in
  alloca $ \a2' ->
  w_cpGrooveJointGetAnchorB'_ a1' a2' >>
  peek  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 282 "src/Chiphunk/Low/Constraint.chs" #-}


cpGrooveJointSetAnchorB :: (Constraint) -> (Vect) -> IO ()
cpGrooveJointSetAnchorB a1 a2 =
  let {a1' = id a1} in
  with a2 $ \a2' ->
  cpGrooveJointSetAnchorB'_ a1' a2' >>
  return ()

{-# LINE 284 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Anchor on second body.
grooveJointAnchorB :: Constraint -> StateVar Vect
grooveJointAnchorB = mkStateVar w_cpGrooveJointGetAnchorB cpGrooveJointSetAnchorB

-- | Defined much like a slide joint.
dampedSpringNew :: (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 (<http://en.wikipedia.org/wiki/Young%27s_modulus Young's modulus>)
 -> (Double) -- ^ How soft to make damping of the spring
 -> IO ((Constraint))
dampedSpringNew a1 a2 a3 a4 a5 a6 a7 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  with a3 $ \a3' ->
  with a4 $ \a4' ->
  let {a5' = realToFrac a5} in
  let {a6' = realToFrac a6} in
  let {a7' = realToFrac a7} in
  dampedSpringNew'_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 299 "src/Chiphunk/Low/Constraint.chs" #-}


w_cpDampedSpringGetAnchorA :: (Constraint) -> IO ((Vect))
w_cpDampedSpringGetAnchorA a1 =
  let {a1' = id a1} in
  alloca $ \a2' ->
  w_cpDampedSpringGetAnchorA'_ a1' a2' >>
  peek  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 301 "src/Chiphunk/Low/Constraint.chs" #-}


cpDampedSpringSetAnchorA :: (Constraint) -> (Vect) -> IO ()
cpDampedSpringSetAnchorA a1 a2 =
  let {a1' = id a1} in
  with a2 $ \a2' ->
  cpDampedSpringSetAnchorA'_ a1' a2' >>
  return ()

{-# LINE 303 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Anchor on first body.
dampedSpringAnchorA :: Constraint -> StateVar Vect
dampedSpringAnchorA = mkStateVar w_cpDampedSpringGetAnchorA cpDampedSpringSetAnchorA

w_cpDampedSpringGetAnchorB :: (Constraint) -> IO ((Vect))
w_cpDampedSpringGetAnchorB a1 =
  let {a1' = id a1} in
  alloca $ \a2' ->
  w_cpDampedSpringGetAnchorB'_ a1' a2' >>
  peek  a2'>>= \a2'' ->
  return (a2'')

{-# LINE 309 "src/Chiphunk/Low/Constraint.chs" #-}


cpDampedSpringSetAnchorB :: (Constraint) -> (Vect) -> IO ()
cpDampedSpringSetAnchorB a1 a2 =
  let {a1' = id a1} in
  with a2 $ \a2' ->
  cpDampedSpringSetAnchorB'_ a1' a2' >>
  return ()

{-# LINE 311 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Anchor on second body.
dampedSpringAnchorB :: Constraint -> StateVar Vect
dampedSpringAnchorB = mkStateVar w_cpDampedSpringGetAnchorB cpDampedSpringSetAnchorB

cpDampedSpringGetRestLength :: (Constraint) -> IO ((Double))
cpDampedSpringGetRestLength a1 =
  let {a1' = id a1} in
  cpDampedSpringGetRestLength'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 317 "src/Chiphunk/Low/Constraint.chs" #-}


cpDampedSpringSetRestLength :: (Constraint) -> (Double) -> IO ()
cpDampedSpringSetRestLength a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpDampedSpringSetRestLength'_ a1' a2' >>
  return ()

{-# LINE 319 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Desired distance the spring will try to enforce.
dampedSpringRestLength :: Constraint -> StateVar Double
dampedSpringRestLength = mkStateVar cpDampedSpringGetRestLength cpDampedSpringSetRestLength

cpDampedSpringGetStiffness :: (Constraint) -> IO ((Double))
cpDampedSpringGetStiffness a1 =
  let {a1' = id a1} in
  cpDampedSpringGetStiffness'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 325 "src/Chiphunk/Low/Constraint.chs" #-}


cpDampedSpringSetStiffness :: (Constraint) -> (Double) -> IO ()
cpDampedSpringSetStiffness a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpDampedSpringSetStiffness'_ a1' a2' >>
  return ()

{-# LINE 327 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Spring stiffness
dampedSpringStiffness :: Constraint -> StateVar Double
dampedSpringStiffness = mkStateVar cpDampedSpringGetStiffness cpDampedSpringSetStiffness

cpDampedSpringGetDamping :: (Constraint) -> IO ((Double))
cpDampedSpringGetDamping a1 =
  let {a1' = id a1} in
  cpDampedSpringGetDamping'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 333 "src/Chiphunk/Low/Constraint.chs" #-}


cpDampedSpringSetDamping :: (Constraint) -> (Double) -> IO ()
cpDampedSpringSetDamping a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpDampedSpringSetDamping'_ a1' a2' >>
  return ()

{-# LINE 335 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Spring damping
dampedSpringDamping :: Constraint -> StateVar Double
dampedSpringDamping = mkStateVar cpDampedSpringGetDamping cpDampedSpringSetDamping

-- | Create new damped rotary spring constraint
dampedRotarySpringNew :: (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))
dampedRotarySpringNew a1 a2 a3 a4 a5 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  let {a3' = realToFrac a3} in
  let {a4' = realToFrac a4} in
  let {a5' = realToFrac a5} in
  dampedRotarySpringNew'_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 348 "src/Chiphunk/Low/Constraint.chs" #-}


cpDampedRotarySpringGetRestAngle :: (Constraint) -> IO ((Double))
cpDampedRotarySpringGetRestAngle a1 =
  let {a1' = id a1} in
  cpDampedRotarySpringGetRestAngle'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 350 "src/Chiphunk/Low/Constraint.chs" #-}


cpDampedRotarySpringSetRestAngle :: (Constraint) -> (Double) -> IO ()
cpDampedRotarySpringSetRestAngle a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpDampedRotarySpringSetRestAngle'_ a1' a2' >>
  return ()

{-# LINE 352 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Set desired angle in radians the spring will try to enforce.
dampedRotarySpringRestAngle :: Constraint -> StateVar Double
dampedRotarySpringRestAngle = mkStateVar cpDampedRotarySpringGetRestAngle cpDampedRotarySpringSetRestAngle

cpDampedRotarySpringGetStiffness :: (Constraint) -> IO ((Double))
cpDampedRotarySpringGetStiffness a1 =
  let {a1' = id a1} in
  cpDampedRotarySpringGetStiffness'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 358 "src/Chiphunk/Low/Constraint.chs" #-}


cpDampedRotarySpringSetStiffness :: (Constraint) -> (Double) -> IO ()
cpDampedRotarySpringSetStiffness a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpDampedRotarySpringSetStiffness'_ a1' a2' >>
  return ()

{-# LINE 360 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Spring stiffness.
dampedRotarySpringStiffness :: Constraint -> StateVar Double
dampedRotarySpringStiffness = mkStateVar cpDampedRotarySpringGetStiffness cpDampedRotarySpringSetStiffness

cpDampedRotarySpringGetDamping :: (Constraint) -> IO ((Double))
cpDampedRotarySpringGetDamping a1 =
  let {a1' = id a1} in
  cpDampedRotarySpringGetDamping'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 366 "src/Chiphunk/Low/Constraint.chs" #-}


cpDampedRotarySpringSetDamping :: (Constraint) -> (Double) -> IO ()
cpDampedRotarySpringSetDamping a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpDampedRotarySpringSetDamping'_ a1' a2' >>
  return ()

{-# LINE 368 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Spring damping.
dampedRotarySpringDamping :: Constraint -> StateVar Double
dampedRotarySpringDamping = mkStateVar cpDampedRotarySpringGetDamping cpDampedRotarySpringSetDamping

-- | Create new rotation limiting joint
rotaryLimitJointNew :: (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))
rotaryLimitJointNew a1 a2 a3 a4 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  let {a3' = realToFrac a3} in
  let {a4' = realToFrac a4} in
  rotaryLimitJointNew'_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 380 "src/Chiphunk/Low/Constraint.chs" #-}


cpRotaryLimitJointGetMin :: (Constraint) -> IO ((Double))
cpRotaryLimitJointGetMin a1 =
  let {a1' = id a1} in
  cpRotaryLimitJointGetMin'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 382 "src/Chiphunk/Low/Constraint.chs" #-}


cpRotaryLimitJointSetMin :: (Constraint) -> (Double) -> IO ()
cpRotaryLimitJointSetMin a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpRotaryLimitJointSetMin'_ a1' a2' >>
  return ()

{-# LINE 384 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Minimum angle in radians the joint will try to enforce.
rotaryLimitJointMin :: Constraint -> StateVar Double
rotaryLimitJointMin = mkStateVar cpRotaryLimitJointGetMin cpRotaryLimitJointSetMin

cpRotaryLimitJointGetMax :: (Constraint) -> IO ((Double))
cpRotaryLimitJointGetMax a1 =
  let {a1' = id a1} in
  cpRotaryLimitJointGetMax'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 390 "src/Chiphunk/Low/Constraint.chs" #-}


cpRotaryLimitJointSetMax :: (Constraint) -> (Double) -> IO ()
cpRotaryLimitJointSetMax a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpRotaryLimitJointSetMax'_ a1' a2' >>
  return ()

{-# LINE 392 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Maximum angle in radians the joint will try to enforce.
rotaryLimitJointMax :: Constraint -> StateVar Double
rotaryLimitJointMax = mkStateVar cpRotaryLimitJointGetMax cpRotaryLimitJointSetMax

-- | Allocate and initialize a ratchet joint.
ratchetJointNew :: (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))
ratchetJointNew a1 a2 a3 a4 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  let {a3' = realToFrac a3} in
  let {a4' = realToFrac a4} in
  ratchetJointNew'_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 404 "src/Chiphunk/Low/Constraint.chs" #-}


cpRatchetJointGetAngle :: (Constraint) -> IO ((Double))
cpRatchetJointGetAngle a1 =
  let {a1' = id a1} in
  cpRatchetJointGetAngle'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 406 "src/Chiphunk/Low/Constraint.chs" #-}


cpRatchetJointSetAngle :: (Constraint) -> (Double) -> IO ()
cpRatchetJointSetAngle a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpRatchetJointSetAngle'_ a1' a2' >>
  return ()

{-# LINE 408 "src/Chiphunk/Low/Constraint.chs" #-}


-- | The angle of the current ratchet tooth.
ratchetJointAngle :: Constraint -> StateVar Double
ratchetJointAngle = mkStateVar cpRatchetJointGetAngle cpRatchetJointSetAngle

cpRatchetJointGetPhase :: (Constraint) -> IO ((Double))
cpRatchetJointGetPhase a1 =
  let {a1' = id a1} in
  cpRatchetJointGetPhase'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 414 "src/Chiphunk/Low/Constraint.chs" #-}


cpRatchetJointSetPhase :: (Constraint) -> (Double) -> IO ()
cpRatchetJointSetPhase a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpRatchetJointSetPhase'_ a1' a2' >>
  return ()

{-# LINE 416 "src/Chiphunk/Low/Constraint.chs" #-}


-- | The phase offset of the ratchet.
ratchetJointPhase :: Constraint -> StateVar Double
ratchetJointPhase = mkStateVar cpRatchetJointGetPhase cpRatchetJointSetPhase

cpRatchetJointGetRatchet :: (Constraint) -> IO ((Double))
cpRatchetJointGetRatchet a1 =
  let {a1' = id a1} in
  cpRatchetJointGetRatchet'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 422 "src/Chiphunk/Low/Constraint.chs" #-}


cpRatchetJointSetRatchet :: (Constraint) -> (Double) -> IO ()
cpRatchetJointSetRatchet a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpRatchetJointSetRatchet'_ a1' a2' >>
  return ()

{-# LINE 424 "src/Chiphunk/Low/Constraint.chs" #-}


-- | The angular distance of each ratchet.
ratchetJointRatchet :: Constraint -> StateVar Double
ratchetJointRatchet = mkStateVar cpRatchetJointGetRatchet cpRatchetJointSetRatchet

-- | Allocate and initialize a gear joint.
gearJointNew :: (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))
gearJointNew a1 a2 a3 a4 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  let {a3' = realToFrac a3} in
  let {a4' = realToFrac a4} in
  gearJointNew'_ a1' a2' a3' a4' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 436 "src/Chiphunk/Low/Constraint.chs" #-}


cpGearJointGetPhase :: (Constraint) -> IO ((Double))
cpGearJointGetPhase a1 =
  let {a1' = id a1} in
  cpGearJointGetPhase'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 438 "src/Chiphunk/Low/Constraint.chs" #-}


cpGearJointSetPhase :: (Constraint) -> (Double) -> IO ()
cpGearJointSetPhase a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpGearJointSetPhase'_ a1' a2' >>
  return ()

{-# LINE 440 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Phase offset of the ratchet.
gearJointPhase :: Constraint -> StateVar Double
gearJointPhase = mkStateVar cpGearJointGetPhase cpGearJointSetPhase

cpGearJointGetRatio :: (Constraint) -> IO ((Double))
cpGearJointGetRatio a1 =
  let {a1' = id a1} in
  cpGearJointGetRatio'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 446 "src/Chiphunk/Low/Constraint.chs" #-}


cpGearJointSetRatio :: (Constraint) -> (Double) -> IO ()
cpGearJointSetRatio a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpGearJointSetRatio'_ a1' a2' >>
  return ()

{-# LINE 448 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Ratio of the ratchet
gearJointRatio :: Constraint -> StateVar Double
gearJointRatio = mkStateVar cpGearJointGetRatio cpGearJointSetRatio

-- | Allocate and initialize a simple motor.
simpleMotorNew :: (Body) -- ^ First body to connect
 -> (Body) -- ^ Second body to connect
 -> (Double) -- ^ The desired relative angular velocity.
 -> IO ((Constraint))
simpleMotorNew a1 a2 a3 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  let {a3' = realToFrac a3} in
  simpleMotorNew'_ a1' a2' a3' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 459 "src/Chiphunk/Low/Constraint.chs" #-}


cpSimpleMotorGetRate :: (Constraint) -> IO ((Double))
cpSimpleMotorGetRate a1 =
  let {a1' = id a1} in
  cpSimpleMotorGetRate'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 461 "src/Chiphunk/Low/Constraint.chs" #-}


cpSimpleMotorSetRate :: (Constraint) -> (Double) -> IO ()
cpSimpleMotorSetRate a1 a2 =
  let {a1' = id a1} in
  let {a2' = realToFrac a2} in
  cpSimpleMotorSetRate'_ a1' a2' >>
  return ()

{-# LINE 463 "src/Chiphunk/Low/Constraint.chs" #-}


-- | Ratio of angular velocities.
simpleMotorRate :: Constraint -> StateVar Double
simpleMotorRate = mkStateVar cpSimpleMotorGetRate cpSimpleMotorSetRate

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintGetBodyA"
  cpConstraintGetBodyA'_ :: ((Constraint) -> (IO (Body)))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintGetBodyB"
  cpConstraintGetBodyB'_ :: ((Constraint) -> (IO (Body)))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintGetMaxForce"
  cpConstraintGetMaxForce'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintSetMaxForce"
  cpConstraintSetMaxForce'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintGetErrorBias"
  cpConstraintGetErrorBias'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintSetErrorBias"
  cpConstraintSetErrorBias'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintGetMaxBias"
  cpConstraintGetMaxBias'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintSetMaxBias"
  cpConstraintSetMaxBias'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintGetSpace"
  cpConstraintGetSpace'_ :: ((Constraint) -> (IO (Space)))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintGetCollideBodies"
  cpConstraintGetCollideBodies'_ :: ((Constraint) -> (IO C2HSImp.CUChar))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintSetCollideBodies"
  cpConstraintSetCollideBodies'_ :: ((Constraint) -> (C2HSImp.CUChar -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintGetUserData"
  cpConstraintGetUserData'_ :: ((Constraint) -> (IO (DataPtr)))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintSetUserData"
  cpConstraintSetUserData'_ :: ((Constraint) -> ((DataPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpConstraintGetImpulse"
  cpConstraintGetImpulse'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall safe "Chiphunk/Low/Constraint.chs.h cpConstraintFree"
  constraintFree'_ :: ((Constraint) -> (IO ()))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpPinJointNew"
  pinJointNew'_ :: ((Body) -> ((Body) -> ((VectPtr) -> ((VectPtr) -> (IO (Constraint))))))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h w_cpPinJointGetAnchorA"
  w_cpPinJointGetAnchorA'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpPinJointSetAnchorA"
  cpPinJointSetAnchorA'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h w_cpPinJointGetAnchorB"
  w_cpPinJointGetAnchorB'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpPinJointSetAnchorB"
  cpPinJointSetAnchorB'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpPinJointGetDist"
  cpPinJointGetDist'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpPinJointSetDist"
  cpPinJointSetDist'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpSlideJointNew"
  slideJointNew'_ :: ((Body) -> ((Body) -> ((VectPtr) -> ((VectPtr) -> (C2HSImp.CDouble -> (C2HSImp.CDouble -> (IO (Constraint))))))))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h w_cpSlideJointGetAnchorA"
  w_cpSlideJointGetAnchorA'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpSlideJointSetAnchorA"
  cpSlideJointSetAnchorA'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h w_cpSlideJointGetAnchorB"
  w_cpSlideJointGetAnchorB'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpSlideJointSetAnchorB"
  cpSlideJointSetAnchorB'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpSlideJointGetMin"
  cpSlideJointGetMin'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpSlideJointSetMin"
  cpSlideJointSetMin'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpSlideJointGetMax"
  cpSlideJointGetMax'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpSlideJointSetMax"
  cpSlideJointSetMax'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpPivotJointNew"
  pivotJointNew'_ :: ((Body) -> ((Body) -> ((VectPtr) -> (IO (Constraint)))))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpPivotJointNew2"
  pivotJointNew2'_ :: ((Body) -> ((Body) -> ((VectPtr) -> ((VectPtr) -> (IO (Constraint))))))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h w_cpPivotJointGetAnchorA"
  w_cpPivotJointGetAnchorA'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpPivotJointSetAnchorA"
  cpPivotJointSetAnchorA'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h w_cpPivotJointGetAnchorB"
  w_cpPivotJointGetAnchorB'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpPivotJointSetAnchorB"
  cpPivotJointSetAnchorB'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpGrooveJointNew"
  grooveJointNew'_ :: ((Body) -> ((Body) -> ((VectPtr) -> ((VectPtr) -> ((VectPtr) -> (IO (Constraint)))))))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h w_cpGrooveJointGetGrooveA"
  w_cpGrooveJointGetGrooveA'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpGrooveJointSetGrooveA"
  cpGrooveJointSetGrooveA'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h w_cpGrooveJointGetGrooveB"
  w_cpGrooveJointGetGrooveB'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpGrooveJointSetGrooveB"
  cpGrooveJointSetGrooveB'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h w_cpGrooveJointGetAnchorB"
  w_cpGrooveJointGetAnchorB'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpGrooveJointSetAnchorB"
  cpGrooveJointSetAnchorB'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpDampedSpringNew"
  dampedSpringNew'_ :: ((Body) -> ((Body) -> ((VectPtr) -> ((VectPtr) -> (C2HSImp.CDouble -> (C2HSImp.CDouble -> (C2HSImp.CDouble -> (IO (Constraint)))))))))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h w_cpDampedSpringGetAnchorA"
  w_cpDampedSpringGetAnchorA'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpDampedSpringSetAnchorA"
  cpDampedSpringSetAnchorA'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h w_cpDampedSpringGetAnchorB"
  w_cpDampedSpringGetAnchorB'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h __c2hs_wrapped__cpDampedSpringSetAnchorB"
  cpDampedSpringSetAnchorB'_ :: ((Constraint) -> ((VectPtr) -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpDampedSpringGetRestLength"
  cpDampedSpringGetRestLength'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpDampedSpringSetRestLength"
  cpDampedSpringSetRestLength'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpDampedSpringGetStiffness"
  cpDampedSpringGetStiffness'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpDampedSpringSetStiffness"
  cpDampedSpringSetStiffness'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpDampedSpringGetDamping"
  cpDampedSpringGetDamping'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpDampedSpringSetDamping"
  cpDampedSpringSetDamping'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpDampedRotarySpringNew"
  dampedRotarySpringNew'_ :: ((Body) -> ((Body) -> (C2HSImp.CDouble -> (C2HSImp.CDouble -> (C2HSImp.CDouble -> (IO (Constraint)))))))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpDampedRotarySpringGetRestAngle"
  cpDampedRotarySpringGetRestAngle'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpDampedRotarySpringSetRestAngle"
  cpDampedRotarySpringSetRestAngle'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpDampedRotarySpringGetStiffness"
  cpDampedRotarySpringGetStiffness'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpDampedRotarySpringSetStiffness"
  cpDampedRotarySpringSetStiffness'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpDampedRotarySpringGetDamping"
  cpDampedRotarySpringGetDamping'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpDampedRotarySpringSetDamping"
  cpDampedRotarySpringSetDamping'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpRotaryLimitJointNew"
  rotaryLimitJointNew'_ :: ((Body) -> ((Body) -> (C2HSImp.CDouble -> (C2HSImp.CDouble -> (IO (Constraint))))))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpRotaryLimitJointGetMin"
  cpRotaryLimitJointGetMin'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpRotaryLimitJointSetMin"
  cpRotaryLimitJointSetMin'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpRotaryLimitJointGetMax"
  cpRotaryLimitJointGetMax'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpRotaryLimitJointSetMax"
  cpRotaryLimitJointSetMax'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpRatchetJointNew"
  ratchetJointNew'_ :: ((Body) -> ((Body) -> (C2HSImp.CDouble -> (C2HSImp.CDouble -> (IO (Constraint))))))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpRatchetJointGetAngle"
  cpRatchetJointGetAngle'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpRatchetJointSetAngle"
  cpRatchetJointSetAngle'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpRatchetJointGetPhase"
  cpRatchetJointGetPhase'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpRatchetJointSetPhase"
  cpRatchetJointSetPhase'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpRatchetJointGetRatchet"
  cpRatchetJointGetRatchet'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpRatchetJointSetRatchet"
  cpRatchetJointSetRatchet'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpGearJointNew"
  gearJointNew'_ :: ((Body) -> ((Body) -> (C2HSImp.CDouble -> (C2HSImp.CDouble -> (IO (Constraint))))))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpGearJointGetPhase"
  cpGearJointGetPhase'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpGearJointSetPhase"
  cpGearJointSetPhase'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpGearJointGetRatio"
  cpGearJointGetRatio'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpGearJointSetRatio"
  cpGearJointSetRatio'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpSimpleMotorNew"
  simpleMotorNew'_ :: ((Body) -> ((Body) -> (C2HSImp.CDouble -> (IO (Constraint)))))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpSimpleMotorGetRate"
  cpSimpleMotorGetRate'_ :: ((Constraint) -> (IO C2HSImp.CDouble))

foreign import ccall unsafe "Chiphunk/Low/Constraint.chs.h cpSimpleMotorSetRate"
  cpSimpleMotorSetRate'_ :: ((Constraint) -> (C2HSImp.CDouble -> (IO ())))