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


{-# LINE 1 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}
{-#LANGUAGE ForeignFunctionInterface#-}

module Physics.Bullet.Raw.BulletDynamics.ConstraintSolver (
module Physics.Bullet.Raw.BulletDynamics.ConstraintSolver
) where
import qualified Foreign.C.String as C2HSImp
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Marshal.Utils as C2HSImp
import qualified Foreign.Ptr as C2HSImp


import Control.Monad
import Foreign.Marshal.Alloc
import Foreign.ForeignPtr.Unsafe
import Foreign.Ptr
import Physics.Bullet.Raw.C2HS
import Physics.Bullet.Raw.Types
import Physics.Bullet.Raw.Class
-- * btAngularLimit
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#359>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit :: IO ((BtAngularLimit))
btAngularLimit =
  btAngularLimit'_ >>= \res ->
  mkBtAngularLimit res >>= \res' ->
  return (res')

{-# LINE 17 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btAngularLimit_free :: ( BtAngularLimitClass bc ) => (bc) -> IO ()
btAngularLimit_free a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_free'_ a1' >>
  return ()

{-# LINE 18 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#398>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_getCorrection :: ( BtAngularLimitClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btAngularLimit_getCorrection a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_getCorrection'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 23 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#373>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_set :: ( BtAngularLimitClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ low
 -> (Float) -- ^ high
 -> (Float) -- ^ _softness
 -> (Float) -- ^ _biasFactor
 -> (Float) -- ^ _relaxationFactor
 -> IO ()
btAngularLimit_set a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  btAngularLimit_set'_ a1' a2' a3' a4' a5' a6' >>
  return ()

{-# LINE 33 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#426>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_getError :: ( BtAngularLimitClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btAngularLimit_getError a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_getError'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 38 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#416>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_isLimit :: ( BtAngularLimitClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btAngularLimit_isLimit a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_isLimit'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 43 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#404>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_getSign :: ( BtAngularLimitClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btAngularLimit_getSign a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_getSign'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 48 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#386>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_getBiasFactor :: ( BtAngularLimitClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btAngularLimit_getBiasFactor a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_getBiasFactor'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 53 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#380>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_getSoftness :: ( BtAngularLimitClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btAngularLimit_getSoftness a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_getSoftness'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 58 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#430>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_getHigh :: ( BtAngularLimitClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btAngularLimit_getHigh a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_getHigh'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 63 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#410>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_getHalfRange :: ( BtAngularLimitClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btAngularLimit_getHalfRange a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_getHalfRange'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 68 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#428>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_getLow :: ( BtAngularLimitClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btAngularLimit_getLow a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_getLow'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 73 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#392>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_getRelaxationFactor :: ( BtAngularLimitClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btAngularLimit_getRelaxationFactor a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_getRelaxationFactor'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 78 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#346>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_center_set :: ( BtAngularLimitClass bc ) => (bc) -> (Float) -> IO ()
btAngularLimit_m_center_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btAngularLimit_m_center_set'_ a1' a2' >>
  return ()

{-# LINE 82 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#346>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_center_get :: ( BtAngularLimitClass bc ) => (bc) -> IO ((Float))
btAngularLimit_m_center_get a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_m_center_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 86 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#347>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_halfRange_set :: ( BtAngularLimitClass bc ) => (bc) -> (Float) -> IO ()
btAngularLimit_m_halfRange_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btAngularLimit_m_halfRange_set'_ a1' a2' >>
  return ()

{-# LINE 90 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#347>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_halfRange_get :: ( BtAngularLimitClass bc ) => (bc) -> IO ((Float))
btAngularLimit_m_halfRange_get a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_m_halfRange_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 94 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#348>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_softness_set :: ( BtAngularLimitClass bc ) => (bc) -> (Float) -> IO ()
btAngularLimit_m_softness_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btAngularLimit_m_softness_set'_ a1' a2' >>
  return ()

{-# LINE 98 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#348>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_softness_get :: ( BtAngularLimitClass bc ) => (bc) -> IO ((Float))
btAngularLimit_m_softness_get a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_m_softness_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 102 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#349>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_biasFactor_set :: ( BtAngularLimitClass bc ) => (bc) -> (Float) -> IO ()
btAngularLimit_m_biasFactor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btAngularLimit_m_biasFactor_set'_ a1' a2' >>
  return ()

{-# LINE 106 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#349>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_biasFactor_get :: ( BtAngularLimitClass bc ) => (bc) -> IO ((Float))
btAngularLimit_m_biasFactor_get a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_m_biasFactor_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 110 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#350>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_relaxationFactor_set :: ( BtAngularLimitClass bc ) => (bc) -> (Float) -> IO ()
btAngularLimit_m_relaxationFactor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btAngularLimit_m_relaxationFactor_set'_ a1' a2' >>
  return ()

{-# LINE 114 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#350>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_relaxationFactor_get :: ( BtAngularLimitClass bc ) => (bc) -> IO ((Float))
btAngularLimit_m_relaxationFactor_get a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_m_relaxationFactor_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 118 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#351>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_correction_set :: ( BtAngularLimitClass bc ) => (bc) -> (Float) -> IO ()
btAngularLimit_m_correction_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btAngularLimit_m_correction_set'_ a1' a2' >>
  return ()

{-# LINE 122 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#351>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_correction_get :: ( BtAngularLimitClass bc ) => (bc) -> IO ((Float))
btAngularLimit_m_correction_get a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_m_correction_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 126 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#352>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_sign_set :: ( BtAngularLimitClass bc ) => (bc) -> (Float) -> IO ()
btAngularLimit_m_sign_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btAngularLimit_m_sign_set'_ a1' a2' >>
  return ()

{-# LINE 130 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#352>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_sign_get :: ( BtAngularLimitClass bc ) => (bc) -> IO ((Float))
btAngularLimit_m_sign_get a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_m_sign_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 134 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#355>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_solveLimit_set :: ( BtAngularLimitClass bc ) => (bc) -> (Bool) -> IO ()
btAngularLimit_m_solveLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btAngularLimit_m_solveLimit_set'_ a1' a2' >>
  return ()

{-# LINE 138 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#355>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btAngularLimit_m_solveLimit_get :: ( BtAngularLimitClass bc ) => (bc) -> IO ((Bool))
btAngularLimit_m_solveLimit_get a1 =
  withBt a1 $ \a1' -> 
  btAngularLimit_m_solveLimit_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 142 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btConeTwistConstraint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#129>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint0 :: ( BtRigidBodyClass p0 , BtRigidBodyClass p1 ) => (p0) -> (p1) -> (Transform) -> (Transform) -> IO ((BtConeTwistConstraint))
btConeTwistConstraint0 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  btConeTwistConstraint0'_ a1' a2' a3' a4' >>= \res ->
  mkBtConeTwistConstraint res >>= \res' ->
  return (res')

{-# LINE 147 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#131>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint1 :: ( BtRigidBodyClass p0 ) => (p0) -> (Transform) -> IO ((BtConeTwistConstraint))
btConeTwistConstraint1 a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btConeTwistConstraint1'_ a1' a2' >>= \res ->
  mkBtConeTwistConstraint res >>= \res' ->
  return (res')

{-# LINE 151 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btConeTwistConstraint_free :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ()
btConeTwistConstraint_free a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_free'_ a1' >>
  return ()

{-# LINE 152 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#152>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getRigidBodyB :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btConeTwistConstraint_getRigidBodyB a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_getRigidBodyB'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 157 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#133>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_buildJacobian :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btConeTwistConstraint_buildJacobian a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_buildJacobian'_ a1' >>
  return ()

{-# LINE 162 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getRigidBodyA :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btConeTwistConstraint_getRigidBodyA a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_getRigidBodyA'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 167 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#124>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_adjustSwingAxisToUseEllipseNormal :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ vSwingAxis
 -> IO ((Vec3))
btConeTwistConstraint_adjustSwingAxisToUseEllipseNormal a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btConeTwistConstraint_adjustSwingAxisToUseEllipseNormal'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 173 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#124>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_adjustSwingAxisToUseEllipseNormal' :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btConeTwistConstraint_adjustSwingAxisToUseEllipseNormal' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btConeTwistConstraint_adjustSwingAxisToUseEllipseNormal''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 179 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_isPastSwingLimit :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btConeTwistConstraint_isPastSwingLimit a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_isPastSwingLimit'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 184 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#274>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getFrameOffsetA :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btConeTwistConstraint_getFrameOffsetA a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btConeTwistConstraint_getFrameOffsetA'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 190 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#279>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getFrameOffsetB :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btConeTwistConstraint_getFrameOffsetB a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btConeTwistConstraint_getFrameOffsetB'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 196 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getInfo2NonVirtual :: ( BtConeTwistConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> (Mat3) -- ^ invInertiaWorldA
 -> (Mat3) -- ^ invInertiaWorldB
 -> IO ((Transform), (Transform), (Mat3), (Mat3))
btConeTwistConstraint_getInfo2NonVirtual a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  withMat3 a5 $ \a5' -> 
  withMat3 a6 $ \a6' -> 
  btConeTwistConstraint_getInfo2NonVirtual'_ a1' a2' a3' a4' a5' a6' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekMat3  a5'>>= \a5'' -> 
  peekMat3  a6'>>= \a6'' -> 
  return (a3'', a4'', a5'', a6'')

{-# LINE 206 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getInfo2NonVirtual' :: ( BtConeTwistConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ((Transform), (Transform), (Mat3), (Mat3))
btConeTwistConstraint_getInfo2NonVirtual' a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaTransform $ \a3' -> 
  allocaTransform $ \a4' -> 
  allocaMat3 $ \a5' -> 
  allocaMat3 $ \a6' -> 
  btConeTwistConstraint_getInfo2NonVirtual''_ a1' a2' a3' a4' a5' a6' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekMat3  a5'>>= \a5'' -> 
  peekMat3  a6'>>= \a6'' -> 
  return (a3'', a4'', a5'', a6'')

{-# LINE 216 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getSwingSpan1 :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btConeTwistConstraint_getSwingSpan1 a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_getSwingSpan1'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 221 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_calcAngleInfo2 :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> (Mat3) -- ^ invInertiaWorldA
 -> (Mat3) -- ^ invInertiaWorldB
 -> IO ((Transform), (Transform), (Mat3), (Mat3))
btConeTwistConstraint_calcAngleInfo2 a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withMat3 a4 $ \a4' -> 
  withMat3 a5 $ \a5' -> 
  btConeTwistConstraint_calcAngleInfo2'_ a1' a2' a3' a4' a5' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  peekMat3  a4'>>= \a4'' -> 
  peekMat3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')

{-# LINE 230 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_calcAngleInfo2' :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform), (Transform), (Mat3), (Mat3))
btConeTwistConstraint_calcAngleInfo2' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  allocaMat3 $ \a4' -> 
  allocaMat3 $ \a5' -> 
  btConeTwistConstraint_calcAngleInfo2''_ a1' a2' a3' a4' a5' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  peekMat3  a4'>>= \a4'' -> 
  peekMat3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')

{-# LINE 239 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#286>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getParam :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ num
 -> (Int) -- ^ axis
 -> IO ((Float))
btConeTwistConstraint_getParam a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btConeTwistConstraint_getParam'_ a1' a2' a3' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 246 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#248>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setDamping :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ damping
 -> IO ()
btConeTwistConstraint_setDamping a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_setDamping'_ a1' a2' >>
  return ()

{-# LINE 252 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#135>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getInfo1 :: ( BtConeTwistConstraintClass bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btConeTwistConstraint_getInfo1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btConeTwistConstraint_getInfo1'_ a1' a2' >>
  return ()

{-# LINE 258 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#139>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getInfo2 :: ( BtConeTwistConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btConeTwistConstraint_getInfo2 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btConeTwistConstraint_getInfo2'_ a1' a2' >>
  return ()

{-# LINE 264 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setParam :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ num
 -> (Float) -- ^ value
 -> (Int) -- ^ axis
 -> IO ()
btConeTwistConstraint_setParam a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = fromIntegral a4} in 
  btConeTwistConstraint_setParam'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 272 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#318>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_calculateSerializeBufferSize :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btConeTwistConstraint_calculateSerializeBufferSize a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_calculateSerializeBufferSize'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 277 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#116>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_init :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btConeTwistConstraint_init a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_init'_ a1' >>
  return ()

{-# LINE 282 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#242>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getTwistAngle :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btConeTwistConstraint_getTwistAngle a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_getTwistAngle'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 287 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#252>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setMaxMotorImpulseNormalized :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ maxMotorImpulse
 -> IO ()
btConeTwistConstraint_setMaxMotorImpulseNormalized a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_setMaxMotorImpulseNormalized'_ a1' a2' >>
  return ()

{-# LINE 293 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#212>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getSolveTwistLimit :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btConeTwistConstraint_getSolveTwistLimit a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_getSolveTwistLimit'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 298 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#250>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_enableMotor :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ b
 -> IO ()
btConeTwistConstraint_enableMotor a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btConeTwistConstraint_enableMotor'_ a1' a2' >>
  return ()

{-# LINE 304 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#210>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getBFrame :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btConeTwistConstraint_getBFrame a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btConeTwistConstraint_getBFrame'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 310 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#137>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getInfo1NonVirtual :: ( BtConeTwistConstraintClass bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btConeTwistConstraint_getInfo1NonVirtual a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btConeTwistConstraint_getInfo1NonVirtual'_ a1' a2' >>
  return ()

{-# LINE 316 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#326>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_serialize :: ( BtConeTwistConstraintClass bc , BtSerializerClass p1 ) => (bc) -- ^ 
 -> (VoidPtr) -- ^ dataBuffer
 -> (p1) -- ^ serializer
 -> IO ((String))
btConeTwistConstraint_serialize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btConeTwistConstraint_serialize'_ a1' a2' a3' >>= \res ->
  C2HSImp.peekCString res >>= \res' ->
  return (res')

{-# LINE 323 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#254>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getFixThresh :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btConeTwistConstraint_getFixThresh a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_getFixThresh'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 328 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getSolveSwingLimit :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btConeTwistConstraint_getSolveSwingLimit a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_getSolveSwingLimit'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 333 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#234>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getSwingSpan2 :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btConeTwistConstraint_getSwingSpan2 a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_getSwingSpan2'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 338 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#157>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setAngularOnly :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ angularOnly
 -> IO ()
btConeTwistConstraint_setAngularOnly a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btConeTwistConstraint_setAngularOnly'_ a1' a2' >>
  return ()

{-# LINE 344 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#272>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setFrames :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Transform) -- ^ frameA
 -> (Transform) -- ^ frameB
 -> IO ((Transform), (Transform))
btConeTwistConstraint_setFrames a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  btConeTwistConstraint_setFrames'_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 351 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#272>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setFrames' :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform), (Transform))
btConeTwistConstraint_setFrames' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  btConeTwistConstraint_setFrames''_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 358 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#162>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setLimit :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ limitIndex
 -> (Float) -- ^ limitValue
 -> IO ()
btConeTwistConstraint_setLimit a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  btConeTwistConstraint_setLimit'_ a1' a2' a3' >>
  return ()

{-# LINE 365 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#162>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setLimit0 :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ limitIndex
 -> (Float) -- ^ limitValue
 -> IO ()
btConeTwistConstraint_setLimit0 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  btConeTwistConstraint_setLimit0'_ a1' a2' a3' >>
  return ()

{-# LINE 372 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#198>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setLimit1 :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ _swingSpan1
 -> (Float) -- ^ _swingSpan2
 -> (Float) -- ^ _twistSpan
 -> (Float) -- ^ _softness
 -> (Float) -- ^ _biasFactor
 -> (Float) -- ^ _relaxationFactor
 -> IO ()
btConeTwistConstraint_setLimit1 a1 a2 a3 a4 a5 a6 a7 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  let {a7' = realToFrac a7} in 
  btConeTwistConstraint_setLimit1'_ a1' a2' a3' a4' a5' a6' a7' >>
  return ()

{-# LINE 383 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#222>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getTwistLimitSign :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btConeTwistConstraint_getTwistLimitSign a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_getTwistLimitSign'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 388 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#251>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setMaxMotorImpulse :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ maxMotorImpulse
 -> IO ()
btConeTwistConstraint_setMaxMotorImpulse a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_setMaxMotorImpulse'_ a1' a2' >>
  return ()

{-# LINE 394 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_calcAngleInfo :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btConeTwistConstraint_calcAngleInfo a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_calcAngleInfo'_ a1' >>
  return ()

{-# LINE 399 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#261>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setMotorTarget :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (UnitQuaternion) -- ^ q
 -> IO ((UnitQuaternion))
btConeTwistConstraint_setMotorTarget a1 a2 =
  withBt a1 $ \a1' -> 
  withUnitQuaternion a2 $ \a2' -> 
  btConeTwistConstraint_setMotorTarget'_ a1' a2' >>
  peekUnitQuaternion  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 405 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#261>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setMotorTarget' :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((UnitQuaternion))
btConeTwistConstraint_setMotorTarget' a1 =
  withBt a1 $ \a1' -> 
  allocaUnitQuaternion $ \a2' -> 
  btConeTwistConstraint_setMotorTarget''_ a1' a2' >>
  peekUnitQuaternion  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 411 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#255>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setFixThresh :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ fixThresh
 -> IO ()
btConeTwistConstraint_setFixThresh a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_setFixThresh'_ a1' a2' >>
  return ()

{-# LINE 417 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#264>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setMotorTargetInConstraintSpace :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (UnitQuaternion) -- ^ q
 -> IO ((UnitQuaternion))
btConeTwistConstraint_setMotorTargetInConstraintSpace a1 a2 =
  withBt a1 $ \a1' -> 
  withUnitQuaternion a2 $ \a2' -> 
  btConeTwistConstraint_setMotorTargetInConstraintSpace'_ a1' a2' >>
  peekUnitQuaternion  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 423 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#264>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_setMotorTargetInConstraintSpace' :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((UnitQuaternion))
btConeTwistConstraint_setMotorTargetInConstraintSpace' a1 =
  withBt a1 $ \a1' -> 
  allocaUnitQuaternion $ \a2' -> 
  btConeTwistConstraint_setMotorTargetInConstraintSpace''_ a1' a2' >>
  peekUnitQuaternion  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 429 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#143>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_solveConstraintObsolete :: ( BtConeTwistConstraintClass bc , BtRigidBodyClass p0 , BtRigidBodyClass p1 ) => (bc) -- ^ 
 -> (p0) -- ^ bodyA
 -> (p1) -- ^ bodyB
 -> (Float) -- ^ timeStep
 -> IO ()
btConeTwistConstraint_solveConstraintObsolete a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  btConeTwistConstraint_solveConstraintObsolete'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 437 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#266>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_GetPointForAngle :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ fAngleInRadians
 -> (Float) -- ^ fLength
 -> IO ((Vec3))
btConeTwistConstraint_GetPointForAngle a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  allocaVec3 $ \a4' -> 
  btConeTwistConstraint_GetPointForAngle'_ a1' a2' a3' a4' >>
  peekVec3  a4'>>= \a4'' -> 
  return (a4'')

{-# LINE 445 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#145>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_updateRHS :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ timeStep
 -> IO ()
btConeTwistConstraint_updateRHS a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_updateRHS'_ a1' a2' >>
  return ()

{-# LINE 451 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#238>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getTwistSpan :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btConeTwistConstraint_getTwistSpan a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_getTwistSpan'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 456 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#209>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_getAFrame :: ( BtConeTwistConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btConeTwistConstraint_getAFrame a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btConeTwistConstraint_getAFrame'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 462 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#60>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_rbAFrame_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Transform) -> IO ()
btConeTwistConstraint_m_rbAFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btConeTwistConstraint_m_rbAFrame_set'_ a1' a2' >>
  return ()

{-# LINE 466 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#60>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_rbAFrame_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Transform))
btConeTwistConstraint_m_rbAFrame_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btConeTwistConstraint_m_rbAFrame_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 470 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_rbBFrame_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Transform) -> IO ()
btConeTwistConstraint_m_rbBFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btConeTwistConstraint_m_rbBFrame_set'_ a1' a2' >>
  return ()

{-# LINE 474 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_rbBFrame_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Transform))
btConeTwistConstraint_m_rbBFrame_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btConeTwistConstraint_m_rbBFrame_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 478 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#63>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_limitSoftness_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_limitSoftness_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_limitSoftness_set'_ a1' a2' >>
  return ()

{-# LINE 482 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#63>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_limitSoftness_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_limitSoftness_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_limitSoftness_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 486 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#64>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_biasFactor_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_biasFactor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_biasFactor_set'_ a1' a2' >>
  return ()

{-# LINE 490 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#64>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_biasFactor_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_biasFactor_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_biasFactor_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 494 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#65>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_relaxationFactor_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_relaxationFactor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_relaxationFactor_set'_ a1' a2' >>
  return ()

{-# LINE 498 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#65>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_relaxationFactor_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_relaxationFactor_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_relaxationFactor_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 502 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#67>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_damping_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_damping_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_damping_set'_ a1' a2' >>
  return ()

{-# LINE 506 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#67>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_damping_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_damping_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_damping_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 510 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#69>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_swingSpan1_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_swingSpan1_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_swingSpan1_set'_ a1' a2' >>
  return ()

{-# LINE 514 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#69>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_swingSpan1_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_swingSpan1_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_swingSpan1_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 518 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#70>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_swingSpan2_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_swingSpan2_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_swingSpan2_set'_ a1' a2' >>
  return ()

{-# LINE 522 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#70>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_swingSpan2_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_swingSpan2_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_swingSpan2_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 526 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#71>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistSpan_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_twistSpan_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_twistSpan_set'_ a1' a2' >>
  return ()

{-# LINE 530 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#71>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistSpan_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_twistSpan_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_twistSpan_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 534 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#73>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_fixThresh_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_fixThresh_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_fixThresh_set'_ a1' a2' >>
  return ()

{-# LINE 538 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#73>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_fixThresh_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_fixThresh_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_fixThresh_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 542 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#75>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_swingAxis_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btConeTwistConstraint_m_swingAxis_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btConeTwistConstraint_m_swingAxis_set'_ a1' a2' >>
  return ()

{-# LINE 546 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#75>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_swingAxis_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Vec3))
btConeTwistConstraint_m_swingAxis_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btConeTwistConstraint_m_swingAxis_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 550 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#76>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistAxis_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btConeTwistConstraint_m_twistAxis_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btConeTwistConstraint_m_twistAxis_set'_ a1' a2' >>
  return ()

{-# LINE 554 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#76>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistAxis_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Vec3))
btConeTwistConstraint_m_twistAxis_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btConeTwistConstraint_m_twistAxis_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 558 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#78>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_kSwing_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_kSwing_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_kSwing_set'_ a1' a2' >>
  return ()

{-# LINE 562 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#78>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_kSwing_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_kSwing_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_kSwing_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 566 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#79>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_kTwist_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_kTwist_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_kTwist_set'_ a1' a2' >>
  return ()

{-# LINE 570 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#79>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_kTwist_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_kTwist_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_kTwist_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 574 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistLimitSign_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_twistLimitSign_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_twistLimitSign_set'_ a1' a2' >>
  return ()

{-# LINE 578 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistLimitSign_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_twistLimitSign_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_twistLimitSign_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 582 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_swingCorrection_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_swingCorrection_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_swingCorrection_set'_ a1' a2' >>
  return ()

{-# LINE 586 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_swingCorrection_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_swingCorrection_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_swingCorrection_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 590 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistCorrection_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_twistCorrection_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_twistCorrection_set'_ a1' a2' >>
  return ()

{-# LINE 594 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistCorrection_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_twistCorrection_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_twistCorrection_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 598 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#85>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistAngle_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_twistAngle_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_twistAngle_set'_ a1' a2' >>
  return ()

{-# LINE 602 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#85>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistAngle_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_twistAngle_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_twistAngle_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 606 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#87>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_accSwingLimitImpulse_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_accSwingLimitImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_accSwingLimitImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 610 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#87>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_accSwingLimitImpulse_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_accSwingLimitImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_accSwingLimitImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 614 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_accTwistLimitImpulse_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_accTwistLimitImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_accTwistLimitImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 618 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_accTwistLimitImpulse_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_accTwistLimitImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_accTwistLimitImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 622 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#90>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_angularOnly_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btConeTwistConstraint_m_angularOnly_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btConeTwistConstraint_m_angularOnly_set'_ a1' a2' >>
  return ()

{-# LINE 626 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#90>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_angularOnly_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Bool))
btConeTwistConstraint_m_angularOnly_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_angularOnly_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 630 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#91>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_solveTwistLimit_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btConeTwistConstraint_m_solveTwistLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btConeTwistConstraint_m_solveTwistLimit_set'_ a1' a2' >>
  return ()

{-# LINE 634 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#91>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_solveTwistLimit_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Bool))
btConeTwistConstraint_m_solveTwistLimit_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_solveTwistLimit_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 638 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_solveSwingLimit_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btConeTwistConstraint_m_solveSwingLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btConeTwistConstraint_m_solveSwingLimit_set'_ a1' a2' >>
  return ()

{-# LINE 642 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_solveSwingLimit_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Bool))
btConeTwistConstraint_m_solveSwingLimit_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_solveSwingLimit_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 646 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#94>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_useSolveConstraintObsolete_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btConeTwistConstraint_m_useSolveConstraintObsolete_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btConeTwistConstraint_m_useSolveConstraintObsolete_set'_ a1' a2' >>
  return ()

{-# LINE 650 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#94>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_useSolveConstraintObsolete_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Bool))
btConeTwistConstraint_m_useSolveConstraintObsolete_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_useSolveConstraintObsolete_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 654 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_swingLimitRatio_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_swingLimitRatio_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_swingLimitRatio_set'_ a1' a2' >>
  return ()

{-# LINE 658 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_swingLimitRatio_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_swingLimitRatio_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_swingLimitRatio_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 662 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#98>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistLimitRatio_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_twistLimitRatio_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_twistLimitRatio_set'_ a1' a2' >>
  return ()

{-# LINE 666 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#98>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistLimitRatio_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_twistLimitRatio_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_twistLimitRatio_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 670 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#99>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistAxisA_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btConeTwistConstraint_m_twistAxisA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btConeTwistConstraint_m_twistAxisA_set'_ a1' a2' >>
  return ()

{-# LINE 674 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#99>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_twistAxisA_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Vec3))
btConeTwistConstraint_m_twistAxisA_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btConeTwistConstraint_m_twistAxisA_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 678 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#102>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_bMotorEnabled_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btConeTwistConstraint_m_bMotorEnabled_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btConeTwistConstraint_m_bMotorEnabled_set'_ a1' a2' >>
  return ()

{-# LINE 682 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#102>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_bMotorEnabled_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Bool))
btConeTwistConstraint_m_bMotorEnabled_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_bMotorEnabled_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 686 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#103>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_bNormalizedMotorStrength_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btConeTwistConstraint_m_bNormalizedMotorStrength_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btConeTwistConstraint_m_bNormalizedMotorStrength_set'_ a1' a2' >>
  return ()

{-# LINE 690 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#103>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_bNormalizedMotorStrength_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Bool))
btConeTwistConstraint_m_bNormalizedMotorStrength_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_bNormalizedMotorStrength_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 694 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#104>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_qTarget_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (UnitQuaternion) -> IO ()
btConeTwistConstraint_m_qTarget_set a1 a2 =
  withBt a1 $ \a1' -> 
  withUnitQuaternion a2 $ \a2' -> 
  btConeTwistConstraint_m_qTarget_set'_ a1' a2' >>
  return ()

{-# LINE 698 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#104>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_qTarget_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((UnitQuaternion))
btConeTwistConstraint_m_qTarget_get a1 =
  withBt a1 $ \a1' -> 
  allocaUnitQuaternion $ \a2' -> 
  btConeTwistConstraint_m_qTarget_get'_ a1' a2' >>
  peekUnitQuaternion  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 702 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#105>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_maxMotorImpulse_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_maxMotorImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_maxMotorImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 706 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#105>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_maxMotorImpulse_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_maxMotorImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_maxMotorImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 710 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#106>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_accMotorImpulse_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btConeTwistConstraint_m_accMotorImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btConeTwistConstraint_m_accMotorImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 714 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#106>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_accMotorImpulse_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Vec3))
btConeTwistConstraint_m_accMotorImpulse_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btConeTwistConstraint_m_accMotorImpulse_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 718 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#109>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_flags_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Int) -> IO ()
btConeTwistConstraint_m_flags_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btConeTwistConstraint_m_flags_set'_ a1' a2' >>
  return ()

{-# LINE 722 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#109>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_flags_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Int))
btConeTwistConstraint_m_flags_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_flags_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 726 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#110>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_linCFM_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_linCFM_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_linCFM_set'_ a1' a2' >>
  return ()

{-# LINE 730 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#110>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_linCFM_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_linCFM_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_linCFM_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 734 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_linERP_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_linERP_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_linERP_set'_ a1' a2' >>
  return ()

{-# LINE 738 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_linERP_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_linERP_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_linERP_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 742 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#112>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_angCFM_set :: ( BtConeTwistConstraintClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraint_m_angCFM_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraint_m_angCFM_set'_ a1' a2' >>
  return ()

{-# LINE 746 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#112>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraint_m_angCFM_get :: ( BtConeTwistConstraintClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraint_m_angCFM_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraint_m_angCFM_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 750 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btConeTwistConstraintData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#297>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData :: IO ((BtConeTwistConstraintData))
btConeTwistConstraintData =
  btConeTwistConstraintData'_ >>= \res ->
  mkBtConeTwistConstraintData res >>= \res' ->
  return (res')

{-# LINE 755 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btConeTwistConstraintData_free :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> IO ()
btConeTwistConstraintData_free a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraintData_free'_ a1' >>
  return ()

{-# LINE 756 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#298>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_typeConstraintData_set :: ( BtConeTwistConstraintDataClass bc , BtTypedConstraintDataClass a ) => (bc) -> (a) -> IO ()
btConeTwistConstraintData_m_typeConstraintData_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btConeTwistConstraintData_m_typeConstraintData_set'_ a1' a2' >>
  return ()

{-# LINE 760 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#298>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_typeConstraintData_get :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> IO ((BtTypedConstraintData))
btConeTwistConstraintData_m_typeConstraintData_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraintData_m_typeConstraintData_get'_ a1' >>= \res ->
  mkBtTypedConstraintData res >>= \res' ->
  return (res')

{-# LINE 764 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#299>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_rbAFrame_set :: ( BtConeTwistConstraintDataClass bc , BtTransformFloatDataClass a ) => (bc) -> (a) -> IO ()
btConeTwistConstraintData_m_rbAFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btConeTwistConstraintData_m_rbAFrame_set'_ a1' a2' >>
  return ()

{-# LINE 768 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#299>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_rbAFrame_get :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> IO ((BtTransformFloatData))
btConeTwistConstraintData_m_rbAFrame_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraintData_m_rbAFrame_get'_ a1' >>= \res ->
  mkBtTransformFloatData res >>= \res' ->
  return (res')

{-# LINE 772 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#300>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_rbBFrame_set :: ( BtConeTwistConstraintDataClass bc , BtTransformFloatDataClass a ) => (bc) -> (a) -> IO ()
btConeTwistConstraintData_m_rbBFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btConeTwistConstraintData_m_rbBFrame_set'_ a1' a2' >>
  return ()

{-# LINE 776 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#300>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_rbBFrame_get :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> IO ((BtTransformFloatData))
btConeTwistConstraintData_m_rbBFrame_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraintData_m_rbBFrame_get'_ a1' >>= \res ->
  mkBtTransformFloatData res >>= \res' ->
  return (res')

{-# LINE 780 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#303>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_swingSpan1_set :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraintData_m_swingSpan1_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraintData_m_swingSpan1_set'_ a1' a2' >>
  return ()

{-# LINE 784 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#303>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_swingSpan1_get :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraintData_m_swingSpan1_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraintData_m_swingSpan1_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 788 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#304>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_swingSpan2_set :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraintData_m_swingSpan2_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraintData_m_swingSpan2_set'_ a1' a2' >>
  return ()

{-# LINE 792 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#304>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_swingSpan2_get :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraintData_m_swingSpan2_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraintData_m_swingSpan2_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 796 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#305>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_twistSpan_set :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraintData_m_twistSpan_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraintData_m_twistSpan_set'_ a1' a2' >>
  return ()

{-# LINE 800 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#305>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_twistSpan_get :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraintData_m_twistSpan_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraintData_m_twistSpan_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 804 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#306>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_limitSoftness_set :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraintData_m_limitSoftness_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraintData_m_limitSoftness_set'_ a1' a2' >>
  return ()

{-# LINE 808 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#306>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_limitSoftness_get :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraintData_m_limitSoftness_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraintData_m_limitSoftness_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 812 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#307>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_biasFactor_set :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraintData_m_biasFactor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraintData_m_biasFactor_set'_ a1' a2' >>
  return ()

{-# LINE 816 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#307>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_biasFactor_get :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraintData_m_biasFactor_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraintData_m_biasFactor_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 820 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#308>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_relaxationFactor_set :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraintData_m_relaxationFactor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraintData_m_relaxationFactor_set'_ a1' a2' >>
  return ()

{-# LINE 824 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#308>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_relaxationFactor_get :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraintData_m_relaxationFactor_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraintData_m_relaxationFactor_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 828 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#310>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_damping_set :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> (Float) -> IO ()
btConeTwistConstraintData_m_damping_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConeTwistConstraintData_m_damping_set'_ a1' a2' >>
  return ()

{-# LINE 832 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.h?r=2223#310>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConeTwistConstraint.cpp?r=2223>
-}
btConeTwistConstraintData_m_damping_get :: ( BtConeTwistConstraintDataClass bc ) => (bc) -> IO ((Float))
btConeTwistConstraintData_m_damping_get a1 =
  withBt a1 $ \a1' -> 
  btConeTwistConstraintData_m_damping_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 836 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btConstraintInfo1
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#95>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo1 :: IO ((BtTypedConstraint_btConstraintInfo1))
btTypedConstraint_btConstraintInfo1 =
  btTypedConstraint_btConstraintInfo1'_ >>= \res ->
  mkBtTypedConstraint_btConstraintInfo1 res >>= \res' ->
  return (res')

{-# LINE 841 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btTypedConstraint_btConstraintInfo1_free :: ( BtTypedConstraint_btConstraintInfo1Class bc ) => (bc) -> IO ()
btTypedConstraint_btConstraintInfo1_free a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_btConstraintInfo1_free'_ a1' >>
  return ()

{-# LINE 842 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo1_m_numConstraintRows_set :: ( BtTypedConstraint_btConstraintInfo1Class bc ) => (bc) -> (Int) -> IO ()
btTypedConstraint_btConstraintInfo1_m_numConstraintRows_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTypedConstraint_btConstraintInfo1_m_numConstraintRows_set'_ a1' a2' >>
  return ()

{-# LINE 846 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo1_m_numConstraintRows_get :: ( BtTypedConstraint_btConstraintInfo1Class bc ) => (bc) -> IO ((Int))
btTypedConstraint_btConstraintInfo1_m_numConstraintRows_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_btConstraintInfo1_m_numConstraintRows_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 850 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo1_nub_set :: ( BtTypedConstraint_btConstraintInfo1Class bc ) => (bc) -> (Int) -> IO ()
btTypedConstraint_btConstraintInfo1_nub_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTypedConstraint_btConstraintInfo1_nub_set'_ a1' a2' >>
  return ()

{-# LINE 854 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo1_nub_get :: ( BtTypedConstraint_btConstraintInfo1Class bc ) => (bc) -> IO ((Int))
btTypedConstraint_btConstraintInfo1_nub_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_btConstraintInfo1_nub_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 858 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btConstraintInfo2
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#99>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo2 :: IO ((BtTypedConstraint_btConstraintInfo2))
btTypedConstraint_btConstraintInfo2 =
  btTypedConstraint_btConstraintInfo2'_ >>= \res ->
  mkBtTypedConstraint_btConstraintInfo2 res >>= \res' ->
  return (res')

{-# LINE 863 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btTypedConstraint_btConstraintInfo2_free :: ( BtTypedConstraint_btConstraintInfo2Class bc ) => (bc) -> IO ()
btTypedConstraint_btConstraintInfo2_free a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_btConstraintInfo2_free'_ a1' >>
  return ()

{-# LINE 864 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#102>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo2_erp_set :: ( BtTypedConstraint_btConstraintInfo2Class bc ) => (bc) -> (Float) -> IO ()
btTypedConstraint_btConstraintInfo2_erp_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTypedConstraint_btConstraintInfo2_erp_set'_ a1' a2' >>
  return ()

{-# LINE 868 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#102>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo2_erp_get :: ( BtTypedConstraint_btConstraintInfo2Class bc ) => (bc) -> IO ((Float))
btTypedConstraint_btConstraintInfo2_erp_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_btConstraintInfo2_erp_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 872 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#102>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo2_fps_set :: ( BtTypedConstraint_btConstraintInfo2Class bc ) => (bc) -> (Float) -> IO ()
btTypedConstraint_btConstraintInfo2_fps_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTypedConstraint_btConstraintInfo2_fps_set'_ a1' a2' >>
  return ()

{-# LINE 876 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#102>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo2_fps_get :: ( BtTypedConstraint_btConstraintInfo2Class bc ) => (bc) -> IO ((Float))
btTypedConstraint_btConstraintInfo2_fps_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_btConstraintInfo2_fps_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 880 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#130>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo2_m_damping_set :: ( BtTypedConstraint_btConstraintInfo2Class bc ) => (bc) -> (Float) -> IO ()
btTypedConstraint_btConstraintInfo2_m_damping_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTypedConstraint_btConstraintInfo2_m_damping_set'_ a1' a2' >>
  return ()

{-# LINE 884 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#130>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo2_m_damping_get :: ( BtTypedConstraint_btConstraintInfo2Class bc ) => (bc) -> IO ((Float))
btTypedConstraint_btConstraintInfo2_m_damping_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_btConstraintInfo2_m_damping_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 888 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#127>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo2_m_numIterations_set :: ( BtTypedConstraint_btConstraintInfo2Class bc ) => (bc) -> (Int) -> IO ()
btTypedConstraint_btConstraintInfo2_m_numIterations_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTypedConstraint_btConstraintInfo2_m_numIterations_set'_ a1' a2' >>
  return ()

{-# LINE 892 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#127>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo2_m_numIterations_get :: ( BtTypedConstraint_btConstraintInfo2Class bc ) => (bc) -> IO ((Int))
btTypedConstraint_btConstraintInfo2_m_numIterations_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_btConstraintInfo2_m_numIterations_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 896 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo2_rowskip_set :: ( BtTypedConstraint_btConstraintInfo2Class bc ) => (bc) -> (Int) -> IO ()
btTypedConstraint_btConstraintInfo2_rowskip_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTypedConstraint_btConstraintInfo2_rowskip_set'_ a1' a2' >>
  return ()

{-# LINE 900 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_btConstraintInfo2_rowskip_get :: ( BtTypedConstraint_btConstraintInfo2Class bc ) => (bc) -> IO ((Int))
btTypedConstraint_btConstraintInfo2_rowskip_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_btConstraintInfo2_rowskip_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 904 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btConstraintSetting
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#36>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btConstraintSetting :: IO ((BtConstraintSetting))
btConstraintSetting =
  btConstraintSetting'_ >>= \res ->
  mkBtConstraintSetting res >>= \res' ->
  return (res')

{-# LINE 909 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btConstraintSetting_free :: ( BtConstraintSettingClass bc ) => (bc) -> IO ()
btConstraintSetting_free a1 =
  withBt a1 $ \a1' -> 
  btConstraintSetting_free'_ a1' >>
  return ()

{-# LINE 910 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btConstraintSetting_m_tau_set :: ( BtConstraintSettingClass bc ) => (bc) -> (Float) -> IO ()
btConstraintSetting_m_tau_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConstraintSetting_m_tau_set'_ a1' a2' >>
  return ()

{-# LINE 914 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btConstraintSetting_m_tau_get :: ( BtConstraintSettingClass bc ) => (bc) -> IO ((Float))
btConstraintSetting_m_tau_get a1 =
  withBt a1 $ \a1' -> 
  btConstraintSetting_m_tau_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 918 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#43>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btConstraintSetting_m_damping_set :: ( BtConstraintSettingClass bc ) => (bc) -> (Float) -> IO ()
btConstraintSetting_m_damping_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConstraintSetting_m_damping_set'_ a1' a2' >>
  return ()

{-# LINE 922 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#43>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btConstraintSetting_m_damping_get :: ( BtConstraintSettingClass bc ) => (bc) -> IO ((Float))
btConstraintSetting_m_damping_get a1 =
  withBt a1 $ \a1' -> 
  btConstraintSetting_m_damping_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 926 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#44>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btConstraintSetting_m_impulseClamp_set :: ( BtConstraintSettingClass bc ) => (bc) -> (Float) -> IO ()
btConstraintSetting_m_impulseClamp_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConstraintSetting_m_impulseClamp_set'_ a1' a2' >>
  return ()

{-# LINE 930 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#44>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btConstraintSetting_m_impulseClamp_get :: ( BtConstraintSettingClass bc ) => (bc) -> IO ((Float))
btConstraintSetting_m_impulseClamp_get a1 =
  withBt a1 $ \a1' -> 
  btConstraintSetting_m_impulseClamp_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 934 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btConstraintSolver
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConstraintSolver.h?r=2223#46>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConstraintSolver.cpp?r=2223>
-}
btConstraintSolver_reset :: ( BtConstraintSolverClass bc ) => (bc) -- ^ 
 -> IO ()
btConstraintSolver_reset a1 =
  withBt a1 $ \a1' -> 
  btConstraintSolver_reset'_ a1' >>
  return ()

{-# LINE 940 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConstraintSolver.h?r=2223#43>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConstraintSolver.cpp?r=2223>
-}
btConstraintSolver_allSolved :: ( BtConstraintSolverClass bc , BtContactSolverInfoClass p0 , BtIDebugDrawClass p1 , BtStackAllocClass p2 ) => (bc) -- ^ 
 -> (p0) -- ^ arg0
 -> (p1) -- ^ arg1
 -> (p2) -- ^ arg2
 -> IO ()
btConstraintSolver_allSolved a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btConstraintSolver_allSolved'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 948 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConstraintSolver.h?r=2223#38>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btConstraintSolver.cpp?r=2223>
-}
btConstraintSolver_prepareSolve :: ( BtConstraintSolverClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ arg0
 -> (Int) -- ^ arg1
 -> IO ()
btConstraintSolver_prepareSolve a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btConstraintSolver_prepareSolve'_ a1' a2' a3' >>
  return ()

{-# LINE 955 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btContactConstraint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.cpp?r=2223>
-}
btContactConstraint_getInfo1 :: ( BtContactConstraintClass bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btContactConstraint_getInfo1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btContactConstraint_getInfo1'_ a1' a2' >>
  return ()

{-# LINE 962 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.h?r=2223#36>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.cpp?r=2223>
-}
btContactConstraint_setContactManifold :: ( BtContactConstraintClass bc , BtPersistentManifoldClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ contactManifold
 -> IO ()
btContactConstraint_setContactManifold a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btContactConstraint_setContactManifold'_ a1' a2' >>
  return ()

{-# LINE 968 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.h?r=2223#55>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.cpp?r=2223>
-}
btContactConstraint_buildJacobian :: ( BtContactConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btContactConstraint_buildJacobian a1 =
  withBt a1 $ \a1' -> 
  btContactConstraint_buildJacobian'_ a1' >>
  return ()

{-# LINE 973 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.cpp?r=2223>
-}
btContactConstraint_getInfo2 :: ( BtContactConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btContactConstraint_getInfo2 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btContactConstraint_getInfo2'_ a1' a2' >>
  return ()

{-# LINE 979 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.h?r=2223#38>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.cpp?r=2223>
-}
btContactConstraint_getContactManifold :: ( BtContactConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtPersistentManifold))
btContactConstraint_getContactManifold a1 =
  withBt a1 $ \a1' -> 
  btContactConstraint_getContactManifold'_ a1' >>= \res ->
  mkBtPersistentManifold res >>= \res' ->
  return (res')

{-# LINE 984 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.h?r=2223#38>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.cpp?r=2223>
-}
btContactConstraint_getContactManifold0 :: ( BtContactConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtPersistentManifold))
btContactConstraint_getContactManifold0 a1 =
  withBt a1 $ \a1' -> 
  btContactConstraint_getContactManifold0'_ a1' >>= \res ->
  mkBtPersistentManifold res >>= \res' ->
  return (res')

{-# LINE 989 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.h?r=2223#43>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.cpp?r=2223>
-}
btContactConstraint_getContactManifold1 :: ( BtContactConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtPersistentManifold))
btContactConstraint_getContactManifold1 a1 =
  withBt a1 $ \a1' -> 
  btContactConstraint_getContactManifold1'_ a1' >>= \res ->
  mkBtPersistentManifold res >>= \res' ->
  return (res')

{-# LINE 994 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.h?r=2223#29>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.cpp?r=2223>
-}
btContactConstraint_m_contactManifold_set :: ( BtContactConstraintClass bc , BtPersistentManifoldClass a ) => (bc) -> (a) -> IO ()
btContactConstraint_m_contactManifold_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btContactConstraint_m_contactManifold_set'_ a1' a2' >>
  return ()

{-# LINE 998 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.h?r=2223#29>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactConstraint.cpp?r=2223>
-}
btContactConstraint_m_contactManifold_get :: ( BtContactConstraintClass bc ) => (bc) -> IO ((BtPersistentManifold))
btContactConstraint_m_contactManifold_get a1 =
  withBt a1 $ \a1' -> 
  btContactConstraint_m_contactManifold_get'_ a1' >>= \res ->
  mkBtPersistentManifold res >>= \res' ->
  return (res')

{-# LINE 1002 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btContactSolverInfo
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#65>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfo :: IO ((BtContactSolverInfo))
btContactSolverInfo =
  btContactSolverInfo'_ >>= \res ->
  mkBtContactSolverInfo res >>= \res' ->
  return (res')

{-# LINE 1007 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btContactSolverInfo_free :: ( BtContactSolverInfoClass bc ) => (bc) -> IO ()
btContactSolverInfo_free a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfo_free'_ a1' >>
  return ()

{-# LINE 1008 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btContactSolverInfoData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#34>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData :: IO ((BtContactSolverInfoData))
btContactSolverInfoData =
  btContactSolverInfoData'_ >>= \res ->
  mkBtContactSolverInfoData res >>= \res' ->
  return (res')

{-# LINE 1013 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btContactSolverInfoData_free :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ()
btContactSolverInfoData_free a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_free'_ a1' >>
  return ()

{-# LINE 1014 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#37>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_tau_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Float) -> IO ()
btContactSolverInfoData_m_tau_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btContactSolverInfoData_m_tau_set'_ a1' a2' >>
  return ()

{-# LINE 1018 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#37>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_tau_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Float))
btContactSolverInfoData_m_tau_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_tau_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1022 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#38>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_damping_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Float) -> IO ()
btContactSolverInfoData_m_damping_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btContactSolverInfoData_m_damping_set'_ a1' a2' >>
  return ()

{-# LINE 1026 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#38>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_damping_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Float))
btContactSolverInfoData_m_damping_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_damping_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1030 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#39>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_friction_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Float) -> IO ()
btContactSolverInfoData_m_friction_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btContactSolverInfoData_m_friction_set'_ a1' a2' >>
  return ()

{-# LINE 1034 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#39>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_friction_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Float))
btContactSolverInfoData_m_friction_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_friction_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1038 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#40>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_timeStep_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Float) -> IO ()
btContactSolverInfoData_m_timeStep_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btContactSolverInfoData_m_timeStep_set'_ a1' a2' >>
  return ()

{-# LINE 1042 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#40>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_timeStep_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Float))
btContactSolverInfoData_m_timeStep_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_timeStep_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1046 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#41>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_restitution_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Float) -> IO ()
btContactSolverInfoData_m_restitution_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btContactSolverInfoData_m_restitution_set'_ a1' a2' >>
  return ()

{-# LINE 1050 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#41>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_restitution_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Float))
btContactSolverInfoData_m_restitution_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_restitution_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1054 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_numIterations_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Int) -> IO ()
btContactSolverInfoData_m_numIterations_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btContactSolverInfoData_m_numIterations_set'_ a1' a2' >>
  return ()

{-# LINE 1058 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_numIterations_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Int))
btContactSolverInfoData_m_numIterations_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_numIterations_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1062 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#43>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_maxErrorReduction_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Float) -> IO ()
btContactSolverInfoData_m_maxErrorReduction_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btContactSolverInfoData_m_maxErrorReduction_set'_ a1' a2' >>
  return ()

{-# LINE 1066 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#43>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_maxErrorReduction_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Float))
btContactSolverInfoData_m_maxErrorReduction_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_maxErrorReduction_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1070 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#44>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_sor_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Float) -> IO ()
btContactSolverInfoData_m_sor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btContactSolverInfoData_m_sor_set'_ a1' a2' >>
  return ()

{-# LINE 1074 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#44>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_sor_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Float))
btContactSolverInfoData_m_sor_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_sor_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1078 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#45>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_erp_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Float) -> IO ()
btContactSolverInfoData_m_erp_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btContactSolverInfoData_m_erp_set'_ a1' a2' >>
  return ()

{-# LINE 1082 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#45>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_erp_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Float))
btContactSolverInfoData_m_erp_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_erp_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1086 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#46>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_erp2_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Float) -> IO ()
btContactSolverInfoData_m_erp2_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btContactSolverInfoData_m_erp2_set'_ a1' a2' >>
  return ()

{-# LINE 1090 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#46>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_erp2_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Float))
btContactSolverInfoData_m_erp2_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_erp2_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1094 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#47>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_globalCfm_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Float) -> IO ()
btContactSolverInfoData_m_globalCfm_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btContactSolverInfoData_m_globalCfm_set'_ a1' a2' >>
  return ()

{-# LINE 1098 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#47>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_globalCfm_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Float))
btContactSolverInfoData_m_globalCfm_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_globalCfm_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1102 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_splitImpulse_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Int) -> IO ()
btContactSolverInfoData_m_splitImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btContactSolverInfoData_m_splitImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 1106 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_splitImpulse_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Int))
btContactSolverInfoData_m_splitImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_splitImpulse_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1110 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#49>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_splitImpulsePenetrationThreshold_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Float) -> IO ()
btContactSolverInfoData_m_splitImpulsePenetrationThreshold_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btContactSolverInfoData_m_splitImpulsePenetrationThreshold_set'_ a1' a2' >>
  return ()

{-# LINE 1114 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#49>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_splitImpulsePenetrationThreshold_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Float))
btContactSolverInfoData_m_splitImpulsePenetrationThreshold_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_splitImpulsePenetrationThreshold_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1118 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_linearSlop_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Float) -> IO ()
btContactSolverInfoData_m_linearSlop_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btContactSolverInfoData_m_linearSlop_set'_ a1' a2' >>
  return ()

{-# LINE 1122 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_linearSlop_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Float))
btContactSolverInfoData_m_linearSlop_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_linearSlop_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1126 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_warmstartingFactor_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Float) -> IO ()
btContactSolverInfoData_m_warmstartingFactor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btContactSolverInfoData_m_warmstartingFactor_set'_ a1' a2' >>
  return ()

{-# LINE 1130 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_warmstartingFactor_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Float))
btContactSolverInfoData_m_warmstartingFactor_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_warmstartingFactor_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1134 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#53>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_solverMode_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Int) -> IO ()
btContactSolverInfoData_m_solverMode_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btContactSolverInfoData_m_solverMode_set'_ a1' a2' >>
  return ()

{-# LINE 1138 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#53>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_solverMode_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Int))
btContactSolverInfoData_m_solverMode_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_solverMode_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1142 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_restingContactRestitutionThreshold_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Int) -> IO ()
btContactSolverInfoData_m_restingContactRestitutionThreshold_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btContactSolverInfoData_m_restingContactRestitutionThreshold_set'_ a1' a2' >>
  return ()

{-# LINE 1146 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_restingContactRestitutionThreshold_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Int))
btContactSolverInfoData_m_restingContactRestitutionThreshold_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_restingContactRestitutionThreshold_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1150 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#55>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_minimumSolverBatchSize_set :: ( BtContactSolverInfoDataClass bc ) => (bc) -> (Int) -> IO ()
btContactSolverInfoData_m_minimumSolverBatchSize_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btContactSolverInfoData_m_minimumSolverBatchSize_set'_ a1' a2' >>
  return ()

{-# LINE 1154 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.h?r=2223#55>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btContactSolverInfo.cpp?r=2223>
-}
btContactSolverInfoData_m_minimumSolverBatchSize_get :: ( BtContactSolverInfoDataClass bc ) => (bc) -> IO ((Int))
btContactSolverInfoData_m_minimumSolverBatchSize_get a1 =
  withBt a1 $ \a1' -> 
  btContactSolverInfoData_m_minimumSolverBatchSize_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1158 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btGeneric6DofConstraint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#352>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint0 :: ( BtRigidBodyClass p0 , BtRigidBodyClass p1 ) => (p0) -> (p1) -> (Transform) -> (Transform) -> (Bool) -> IO ((BtGeneric6DofConstraint))
btGeneric6DofConstraint0 a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  let {a5' = C2HSImp.fromBool a5} in 
  btGeneric6DofConstraint0'_ a1' a2' a3' a4' a5' >>= \res ->
  mkBtGeneric6DofConstraint res >>= \res' ->
  return (res')

{-# LINE 1163 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#353>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint1 :: ( BtRigidBodyClass p0 ) => (p0) -> (Transform) -> (Bool) -> IO ((BtGeneric6DofConstraint))
btGeneric6DofConstraint1 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  let {a3' = C2HSImp.fromBool a3} in 
  btGeneric6DofConstraint1'_ a1' a2' a3' >>= \res ->
  mkBtGeneric6DofConstraint res >>= \res' ->
  return (res')

{-# LINE 1167 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btGeneric6DofConstraint_free :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ()
btGeneric6DofConstraint_free a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_free'_ a1' >>
  return ()

{-# LINE 1168 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#405>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_buildJacobian :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btGeneric6DofConstraint_buildJacobian a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_buildJacobian'_ a1' >>
  return ()

{-# LINE 1173 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#547>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setParam :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ num
 -> (Float) -- ^ value
 -> (Int) -- ^ axis
 -> IO ()
btGeneric6DofConstraint_setParam a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = fromIntegral a4} in 
  btGeneric6DofConstraint_setParam'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 1181 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#409>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getInfo1NonVirtual :: ( BtGeneric6DofConstraintClass bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btGeneric6DofConstraint_getInfo1NonVirtual a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofConstraint_getInfo1NonVirtual'_ a1' a2' >>
  return ()

{-# LINE 1187 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#382>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getFrameOffsetA :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btGeneric6DofConstraint_getFrameOffsetA a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btGeneric6DofConstraint_getFrameOffsetA'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1193 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#382>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getFrameOffsetA0 :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btGeneric6DofConstraint_getFrameOffsetA0 a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btGeneric6DofConstraint_getFrameOffsetA0'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1199 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#393>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getFrameOffsetA1 :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btGeneric6DofConstraint_getFrameOffsetA1 a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btGeneric6DofConstraint_getFrameOffsetA1'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1205 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#434>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getRelativePivotPosition :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ axis_index
 -> IO ((Float))
btGeneric6DofConstraint_getRelativePivotPosition a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGeneric6DofConstraint_getRelativePivotPosition'_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1211 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#343>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_calculateAngleInfo :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btGeneric6DofConstraint_calculateAngleInfo a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_calculateAngleInfo'_ a1' >>
  return ()

{-# LINE 1216 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#413>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getInfo2NonVirtual :: ( BtGeneric6DofConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> (Vec3) -- ^ linVelA
 -> (Vec3) -- ^ linVelB
 -> (Vec3) -- ^ angVelA
 -> (Vec3) -- ^ angVelB
 -> IO ((Transform), (Transform), (Vec3), (Vec3), (Vec3), (Vec3))
btGeneric6DofConstraint_getInfo2NonVirtual a1 a2 a3 a4 a5 a6 a7 a8 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  withVec3 a7 $ \a7' -> 
  withVec3 a8 $ \a8' -> 
  btGeneric6DofConstraint_getInfo2NonVirtual'_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  return (a3'', a4'', a5'', a6'', a7'', a8'')

{-# LINE 1228 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#413>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getInfo2NonVirtual' :: ( BtGeneric6DofConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ((Transform), (Transform), (Vec3), (Vec3), (Vec3), (Vec3))
btGeneric6DofConstraint_getInfo2NonVirtual' a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaTransform $ \a3' -> 
  allocaTransform $ \a4' -> 
  allocaVec3 $ \a5' -> 
  allocaVec3 $ \a6' -> 
  allocaVec3 $ \a7' -> 
  allocaVec3 $ \a8' -> 
  btGeneric6DofConstraint_getInfo2NonVirtual''_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  return (a3'', a4'', a5'', a6'', a7'', a8'')

{-# LINE 1240 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#329>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setAngularLimits :: ( BtGeneric6DofConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> (Int) -- ^ row_offset
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> (Vec3) -- ^ linVelA
 -> (Vec3) -- ^ linVelB
 -> (Vec3) -- ^ angVelA
 -> (Vec3) -- ^ angVelB
 -> IO ((Int), (Transform), (Transform), (Vec3), (Vec3), (Vec3), (Vec3))
btGeneric6DofConstraint_setAngularLimits a1 a2 a3 a4 a5 a6 a7 a8 a9 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  withTransform a4 $ \a4' -> 
  withTransform a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  withVec3 a7 $ \a7' -> 
  withVec3 a8 $ \a8' -> 
  withVec3 a9 $ \a9' -> 
  btGeneric6DofConstraint_setAngularLimits'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  let {res' = fromIntegral res} in
  peekTransform  a4'>>= \a4'' -> 
  peekTransform  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  peekVec3  a9'>>= \a9'' -> 
  return (res', a4'', a5'', a6'', a7'', a8'', a9'')

{-# LINE 1253 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#329>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setAngularLimits' :: ( BtGeneric6DofConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> (Int) -- ^ row_offset
 -> IO ((Int), (Transform), (Transform), (Vec3), (Vec3), (Vec3), (Vec3))
btGeneric6DofConstraint_setAngularLimits' a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  allocaTransform $ \a4' -> 
  allocaTransform $ \a5' -> 
  allocaVec3 $ \a6' -> 
  allocaVec3 $ \a7' -> 
  allocaVec3 $ \a8' -> 
  allocaVec3 $ \a9' -> 
  btGeneric6DofConstraint_setAngularLimits''_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  let {res' = fromIntegral res} in
  peekTransform  a4'>>= \a4'' -> 
  peekTransform  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  peekVec3  a9'>>= \a9'' -> 
  return (res', a4'', a5'', a6'', a7'', a8'', a9'')

{-# LINE 1266 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#549>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getParam :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ num
 -> (Int) -- ^ axis
 -> IO ((Float))
btGeneric6DofConstraint_getParam a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btGeneric6DofConstraint_getParam'_ a1' a2' a3' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1273 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#407>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getInfo1 :: ( BtGeneric6DofConstraintClass bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btGeneric6DofConstraint_getInfo1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofConstraint_getInfo1'_ a1' a2' >>
  return ()

{-# LINE 1279 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#411>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getInfo2 :: ( BtGeneric6DofConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btGeneric6DofConstraint_getInfo2 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofConstraint_getInfo2'_ a1' a2' >>
  return ()

{-# LINE 1285 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#535>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_calcAnchorPos :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btGeneric6DofConstraint_calcAnchorPos a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_calcAnchorPos'_ a1' >>
  return ()

{-# LINE 1290 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#471>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getAngularLowerLimit :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ angularLower
 -> IO ((Vec3))
btGeneric6DofConstraint_getAngularLowerLimit a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGeneric6DofConstraint_getAngularLowerLimit'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1296 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#471>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getAngularLowerLimit' :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btGeneric6DofConstraint_getAngularLowerLimit' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGeneric6DofConstraint_getAngularLowerLimit''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1302 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#579>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_calculateSerializeBufferSize :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btGeneric6DofConstraint_calculateSerializeBufferSize a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_calculateSerializeBufferSize'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1307 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#422>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getAxis :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ axis_index
 -> IO ((Vec3))
btGeneric6DofConstraint_getAxis a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaVec3 $ \a3' -> 
  btGeneric6DofConstraint_getAxis'_ a1' a2' a3' >>
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')

{-# LINE 1314 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#460>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getLinearUpperLimit :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ linearUpper
 -> IO ((Vec3))
btGeneric6DofConstraint_getLinearUpperLimit a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGeneric6DofConstraint_getLinearUpperLimit'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1320 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#460>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getLinearUpperLimit' :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btGeneric6DofConstraint_getLinearUpperLimit' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGeneric6DofConstraint_getLinearUpperLimit''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1326 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#543>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setUseFrameOffset :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ frameOffsetOnOff
 -> IO ()
btGeneric6DofConstraint_setUseFrameOffset a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btGeneric6DofConstraint_setUseFrameOffset'_ a1' a2' >>
  return ()

{-# LINE 1332 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#525>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_isLimited :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ limitIndex
 -> IO ((Bool))
btGeneric6DofConstraint_isLimited a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGeneric6DofConstraint_isLimited'_ a1' a2' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1338 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#490>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getRotationalLimitMotor :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ index
 -> IO ((BtRotationalLimitMotor))
btGeneric6DofConstraint_getRotationalLimitMotor a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGeneric6DofConstraint_getRotationalLimitMotor'_ a1' a2' >>= \res ->
  mkBtRotationalLimitMotor res >>= \res' ->
  return (res')

{-# LINE 1344 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#337>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_buildAngularJacobian :: ( BtGeneric6DofConstraintClass bc , BtJacobianEntryClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ jacAngular
 -> (Vec3) -- ^ jointAxisW
 -> IO ((Vec3))
btGeneric6DofConstraint_buildAngularJacobian a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btGeneric6DofConstraint_buildAngularJacobian'_ a1' a2' a3' >>
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')

{-# LINE 1351 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#337>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_buildAngularJacobian' :: ( BtGeneric6DofConstraintClass bc , BtJacobianEntryClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ jacAngular
 -> IO ((Vec3))
btGeneric6DofConstraint_buildAngularJacobian' a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btGeneric6DofConstraint_buildAngularJacobian''_ a1' a2' a3' >>
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')

{-# LINE 1358 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#387>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getFrameOffsetB :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btGeneric6DofConstraint_getFrameOffsetB a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btGeneric6DofConstraint_getFrameOffsetB'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1364 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#387>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getFrameOffsetB0 :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btGeneric6DofConstraint_getFrameOffsetB0 a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btGeneric6DofConstraint_getFrameOffsetB0'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1370 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#398>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getFrameOffsetB1 :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btGeneric6DofConstraint_getFrameOffsetB1 a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btGeneric6DofConstraint_getFrameOffsetB1'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1376 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#445>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setLinearLowerLimit :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ linearLower
 -> IO ((Vec3))
btGeneric6DofConstraint_setLinearLowerLimit a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGeneric6DofConstraint_setLinearLowerLimit'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1382 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#445>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setLinearLowerLimit' :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btGeneric6DofConstraint_setLinearLowerLimit' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGeneric6DofConstraint_setLinearLowerLimit''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1388 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#450>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getLinearLowerLimit :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ linearLower
 -> IO ((Vec3))
btGeneric6DofConstraint_getLinearLowerLimit a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGeneric6DofConstraint_getLinearLowerLimit'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1394 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#450>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getLinearLowerLimit' :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btGeneric6DofConstraint_getLinearLowerLimit' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGeneric6DofConstraint_getLinearLowerLimit''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1400 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#335>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_buildLinearJacobian :: ( BtGeneric6DofConstraintClass bc , BtJacobianEntryClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ jacLinear
 -> (Vec3) -- ^ normalWorld
 -> (Vec3) -- ^ pivotAInW
 -> (Vec3) -- ^ pivotBInW
 -> IO ((Vec3), (Vec3), (Vec3))
btGeneric6DofConstraint_buildLinearJacobian a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btGeneric6DofConstraint_buildLinearJacobian'_ a1' a2' a3' a4' a5' >>
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a3'', a4'', a5'')

{-# LINE 1409 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#335>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_buildLinearJacobian' :: ( BtGeneric6DofConstraintClass bc , BtJacobianEntryClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ jacLinear
 -> IO ((Vec3), (Vec3), (Vec3))
btGeneric6DofConstraint_buildLinearJacobian' a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  btGeneric6DofConstraint_buildLinearJacobian''_ a1' a2' a3' a4' a5' >>
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a3'', a4'', a5'')

{-# LINE 1418 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#542>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getUseFrameOffset :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btGeneric6DofConstraint_getUseFrameOffset a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_getUseFrameOffset'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1423 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#377>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getCalculatedTransformB :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btGeneric6DofConstraint_getCalculatedTransformB a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btGeneric6DofConstraint_getCalculatedTransformB'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1429 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#360>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_calculateTransforms :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> IO ((Transform), (Transform))
btGeneric6DofConstraint_calculateTransforms a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  btGeneric6DofConstraint_calculateTransforms'_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 1436 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#360>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_calculateTransforms' :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform), (Transform))
btGeneric6DofConstraint_calculateTransforms' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  btGeneric6DofConstraint_calculateTransforms''_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 1443 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#360>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_calculateTransforms0 :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> IO ((Transform), (Transform))
btGeneric6DofConstraint_calculateTransforms0 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  btGeneric6DofConstraint_calculateTransforms0'_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 1450 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#360>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_calculateTransforms0' :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform), (Transform))
btGeneric6DofConstraint_calculateTransforms0' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  btGeneric6DofConstraint_calculateTransforms0''_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 1457 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#362>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_calculateTransforms1 :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btGeneric6DofConstraint_calculateTransforms1 a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_calculateTransforms1'_ a1' >>
  return ()

{-# LINE 1462 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#539>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_get_limit_motor_info2 :: ( BtGeneric6DofConstraintClass bc , BtRotationalLimitMotorClass p0 , BtTypedConstraint_btConstraintInfo2Class p7 ) => (bc) -- ^ 
 -> (p0) -- ^ limot
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> (Vec3) -- ^ linVelA
 -> (Vec3) -- ^ linVelB
 -> (Vec3) -- ^ angVelA
 -> (Vec3) -- ^ angVelB
 -> (p7) -- ^ info
 -> (Int) -- ^ row
 -> (Vec3) -- ^ ax1
 -> (Int) -- ^ rotational
 -> (Int) -- ^ rotAllowed
 -> IO ((Int), (Transform), (Transform), (Vec3), (Vec3), (Vec3), (Vec3), (Vec3))
btGeneric6DofConstraint_get_limit_motor_info2 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  withVec3 a7 $ \a7' -> 
  withVec3 a8 $ \a8' -> 
  withBt a9 $ \a9' -> 
  let {a10' = fromIntegral a10} in 
  withVec3 a11 $ \a11' -> 
  let {a12' = fromIntegral a12} in 
  let {a13' = fromIntegral a13} in 
  btGeneric6DofConstraint_get_limit_motor_info2'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' a13' >>= \res ->
  let {res' = fromIntegral res} in
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  peekVec3  a11'>>= \a11'' -> 
  return (res', a3'', a4'', a5'', a6'', a7'', a8'', a11'')

{-# LINE 1479 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#539>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_get_limit_motor_info2' :: ( BtGeneric6DofConstraintClass bc , BtRotationalLimitMotorClass p0 , BtTypedConstraint_btConstraintInfo2Class p7 ) => (bc) -- ^ 
 -> (p0) -- ^ limot
 -> (p7) -- ^ info
 -> (Int) -- ^ row
 -> (Int) -- ^ rotational
 -> (Int) -- ^ rotAllowed
 -> IO ((Int), (Transform), (Transform), (Vec3), (Vec3), (Vec3), (Vec3), (Vec3))
btGeneric6DofConstraint_get_limit_motor_info2' a1 a2 a9 a10 a12 a13 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaTransform $ \a3' -> 
  allocaTransform $ \a4' -> 
  allocaVec3 $ \a5' -> 
  allocaVec3 $ \a6' -> 
  allocaVec3 $ \a7' -> 
  allocaVec3 $ \a8' -> 
  withBt a9 $ \a9' -> 
  let {a10' = fromIntegral a10} in 
  allocaVec3 $ \a11' -> 
  let {a12' = fromIntegral a12} in 
  let {a13' = fromIntegral a13} in 
  btGeneric6DofConstraint_get_limit_motor_info2''_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' a13' >>= \res ->
  let {res' = fromIntegral res} in
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  peekVec3  a11'>>= \a11'' -> 
  return (res', a3'', a4'', a5'', a6'', a7'', a8'', a11'')

{-# LINE 1496 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#368>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getCalculatedTransformA :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btGeneric6DofConstraint_getCalculatedTransformA a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btGeneric6DofConstraint_getCalculatedTransformA'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1502 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#585>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_serialize :: ( BtGeneric6DofConstraintClass bc , BtSerializerClass p1 ) => (bc) -- ^ 
 -> (VoidPtr) -- ^ dataBuffer
 -> (p1) -- ^ serializer
 -> IO ((String))
btGeneric6DofConstraint_serialize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGeneric6DofConstraint_serialize'_ a1' a2' a3' >>= \res ->
  C2HSImp.peekCString res >>= \res' ->
  return (res')

{-# LINE 1509 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#502>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setLimit :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ axis
 -> (Float) -- ^ lo
 -> (Float) -- ^ hi
 -> IO ()
btGeneric6DofConstraint_setLimit a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  btGeneric6DofConstraint_setLimit'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 1517 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#496>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getTranslationalLimitMotor :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtTranslationalLimitMotor))
btGeneric6DofConstraint_getTranslationalLimitMotor a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_getTranslationalLimitMotor'_ a1' >>= \res ->
  mkBtTranslationalLimitMotor res >>= \res' ->
  return (res')

{-# LINE 1522 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#331>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setLinearLimits :: ( BtGeneric6DofConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> (Int) -- ^ row
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> (Vec3) -- ^ linVelA
 -> (Vec3) -- ^ linVelB
 -> (Vec3) -- ^ angVelA
 -> (Vec3) -- ^ angVelB
 -> IO ((Int), (Transform), (Transform), (Vec3), (Vec3), (Vec3), (Vec3))
btGeneric6DofConstraint_setLinearLimits a1 a2 a3 a4 a5 a6 a7 a8 a9 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  withTransform a4 $ \a4' -> 
  withTransform a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  withVec3 a7 $ \a7' -> 
  withVec3 a8 $ \a8' -> 
  withVec3 a9 $ \a9' -> 
  btGeneric6DofConstraint_setLinearLimits'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  let {res' = fromIntegral res} in
  peekTransform  a4'>>= \a4'' -> 
  peekTransform  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  peekVec3  a9'>>= \a9'' -> 
  return (res', a4'', a5'', a6'', a7'', a8'', a9'')

{-# LINE 1535 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#331>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setLinearLimits' :: ( BtGeneric6DofConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> (Int) -- ^ row
 -> IO ((Int), (Transform), (Transform), (Vec3), (Vec3), (Vec3), (Vec3))
btGeneric6DofConstraint_setLinearLimits' a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  allocaTransform $ \a4' -> 
  allocaTransform $ \a5' -> 
  allocaVec3 $ \a6' -> 
  allocaVec3 $ \a7' -> 
  allocaVec3 $ \a8' -> 
  allocaVec3 $ \a9' -> 
  btGeneric6DofConstraint_setLinearLimits''_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  let {res' = fromIntegral res} in
  peekTransform  a4'>>= \a4'' -> 
  peekTransform  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  peekVec3  a9'>>= \a9'' -> 
  return (res', a4'', a5'', a6'', a7'', a8'', a9'')

{-# LINE 1548 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#428>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getAngle :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ axis_index
 -> IO ((Float))
btGeneric6DofConstraint_getAngle a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGeneric6DofConstraint_getAngle'_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1554 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#416>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_updateRHS :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ timeStep
 -> IO ()
btGeneric6DofConstraint_updateRHS a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btGeneric6DofConstraint_updateRHS'_ a1' a2' >>
  return ()

{-# LINE 1560 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#483>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getAngularUpperLimit :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ angularUpper
 -> IO ((Vec3))
btGeneric6DofConstraint_getAngularUpperLimit a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGeneric6DofConstraint_getAngularUpperLimit'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1566 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#483>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_getAngularUpperLimit' :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btGeneric6DofConstraint_getAngularUpperLimit' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGeneric6DofConstraint_getAngularUpperLimit''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1572 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#465>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setAngularLowerLimit :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ angularLower
 -> IO ((Vec3))
btGeneric6DofConstraint_setAngularLowerLimit a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGeneric6DofConstraint_setAngularLowerLimit'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1578 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#465>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setAngularLowerLimit' :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btGeneric6DofConstraint_setAngularLowerLimit' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGeneric6DofConstraint_setAngularLowerLimit''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1584 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#340>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_calculateLinearInfo :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btGeneric6DofConstraint_calculateLinearInfo a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_calculateLinearInfo'_ a1' >>
  return ()

{-# LINE 1589 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#436>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setFrames :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Transform) -- ^ frameA
 -> (Transform) -- ^ frameB
 -> IO ((Transform), (Transform))
btGeneric6DofConstraint_setFrames a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  btGeneric6DofConstraint_setFrames'_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 1596 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#436>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setFrames' :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform), (Transform))
btGeneric6DofConstraint_setFrames' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  btGeneric6DofConstraint_setFrames''_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 1603 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#455>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setLinearUpperLimit :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ linearUpper
 -> IO ((Vec3))
btGeneric6DofConstraint_setLinearUpperLimit a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGeneric6DofConstraint_setLinearUpperLimit'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1609 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#455>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setLinearUpperLimit' :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btGeneric6DofConstraint_setLinearUpperLimit' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGeneric6DofConstraint_setLinearUpperLimit''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1615 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#477>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setAngularUpperLimit :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ angularUpper
 -> IO ((Vec3))
btGeneric6DofConstraint_setAngularUpperLimit a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGeneric6DofConstraint_setAngularUpperLimit'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1621 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#477>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setAngularUpperLimit' :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btGeneric6DofConstraint_setAngularUpperLimit' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGeneric6DofConstraint_setAngularUpperLimit''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1627 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#551>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setAxis :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ axis1
 -> (Vec3) -- ^ axis2
 -> IO ((Vec3), (Vec3))
btGeneric6DofConstraint_setAxis a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btGeneric6DofConstraint_setAxis'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 1634 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#551>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_setAxis' :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3), (Vec3))
btGeneric6DofConstraint_setAxis' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btGeneric6DofConstraint_setAxis''_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 1641 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#443>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_testAngularLimitMotor :: ( BtGeneric6DofConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ axis_index
 -> IO ((Bool))
btGeneric6DofConstraint_testAngularLimitMotor a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGeneric6DofConstraint_testAngularLimitMotor'_ a1' a2' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1647 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#277>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_frameInA_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Transform) -> IO ()
btGeneric6DofConstraint_m_frameInA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btGeneric6DofConstraint_m_frameInA_set'_ a1' a2' >>
  return ()

{-# LINE 1651 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#277>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_frameInA_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Transform))
btGeneric6DofConstraint_m_frameInA_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btGeneric6DofConstraint_m_frameInA_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1655 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#278>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_frameInB_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Transform) -> IO ()
btGeneric6DofConstraint_m_frameInB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btGeneric6DofConstraint_m_frameInB_set'_ a1' a2' >>
  return ()

{-# LINE 1659 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#278>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_frameInB_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Transform))
btGeneric6DofConstraint_m_frameInB_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btGeneric6DofConstraint_m_frameInB_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1663 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#289>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_linearLimits_set :: ( BtGeneric6DofConstraintClass bc , BtTranslationalLimitMotorClass a ) => (bc) -> (a) -> IO ()
btGeneric6DofConstraint_m_linearLimits_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofConstraint_m_linearLimits_set'_ a1' a2' >>
  return ()

{-# LINE 1667 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#289>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_linearLimits_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((BtTranslationalLimitMotor))
btGeneric6DofConstraint_m_linearLimits_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_m_linearLimits_get'_ a1' >>= \res ->
  mkBtTranslationalLimitMotor res >>= \res' ->
  return (res')

{-# LINE 1671 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#302>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_timeStep_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Float) -> IO ()
btGeneric6DofConstraint_m_timeStep_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btGeneric6DofConstraint_m_timeStep_set'_ a1' a2' >>
  return ()

{-# LINE 1675 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#302>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_timeStep_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Float))
btGeneric6DofConstraint_m_timeStep_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_m_timeStep_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1679 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#303>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_calculatedTransformA_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Transform) -> IO ()
btGeneric6DofConstraint_m_calculatedTransformA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btGeneric6DofConstraint_m_calculatedTransformA_set'_ a1' a2' >>
  return ()

{-# LINE 1683 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#303>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_calculatedTransformA_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Transform))
btGeneric6DofConstraint_m_calculatedTransformA_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btGeneric6DofConstraint_m_calculatedTransformA_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1687 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#304>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_calculatedTransformB_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Transform) -> IO ()
btGeneric6DofConstraint_m_calculatedTransformB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btGeneric6DofConstraint_m_calculatedTransformB_set'_ a1' a2' >>
  return ()

{-# LINE 1691 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#304>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_calculatedTransformB_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Transform))
btGeneric6DofConstraint_m_calculatedTransformB_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btGeneric6DofConstraint_m_calculatedTransformB_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1695 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#305>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_calculatedAxisAngleDiff_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btGeneric6DofConstraint_m_calculatedAxisAngleDiff_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGeneric6DofConstraint_m_calculatedAxisAngleDiff_set'_ a1' a2' >>
  return ()

{-# LINE 1699 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#305>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_calculatedAxisAngleDiff_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Vec3))
btGeneric6DofConstraint_m_calculatedAxisAngleDiff_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGeneric6DofConstraint_m_calculatedAxisAngleDiff_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1703 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#307>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_calculatedLinearDiff_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btGeneric6DofConstraint_m_calculatedLinearDiff_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGeneric6DofConstraint_m_calculatedLinearDiff_set'_ a1' a2' >>
  return ()

{-# LINE 1707 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#307>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_calculatedLinearDiff_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Vec3))
btGeneric6DofConstraint_m_calculatedLinearDiff_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGeneric6DofConstraint_m_calculatedLinearDiff_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1711 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#308>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_factA_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Float) -> IO ()
btGeneric6DofConstraint_m_factA_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btGeneric6DofConstraint_m_factA_set'_ a1' a2' >>
  return ()

{-# LINE 1715 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#308>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_factA_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Float))
btGeneric6DofConstraint_m_factA_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_m_factA_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1719 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#309>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_factB_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Float) -> IO ()
btGeneric6DofConstraint_m_factB_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btGeneric6DofConstraint_m_factB_set'_ a1' a2' >>
  return ()

{-# LINE 1723 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#309>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_factB_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Float))
btGeneric6DofConstraint_m_factB_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_m_factB_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1727 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#310>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_hasStaticBody_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btGeneric6DofConstraint_m_hasStaticBody_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btGeneric6DofConstraint_m_hasStaticBody_set'_ a1' a2' >>
  return ()

{-# LINE 1731 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#310>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_hasStaticBody_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Bool))
btGeneric6DofConstraint_m_hasStaticBody_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_m_hasStaticBody_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1735 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#312>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_AnchorPos_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btGeneric6DofConstraint_m_AnchorPos_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGeneric6DofConstraint_m_AnchorPos_set'_ a1' a2' >>
  return ()

{-# LINE 1739 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#312>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_AnchorPos_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Vec3))
btGeneric6DofConstraint_m_AnchorPos_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGeneric6DofConstraint_m_AnchorPos_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1743 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#314>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_useLinearReferenceFrameA_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btGeneric6DofConstraint_m_useLinearReferenceFrameA_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btGeneric6DofConstraint_m_useLinearReferenceFrameA_set'_ a1' a2' >>
  return ()

{-# LINE 1747 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#314>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_useLinearReferenceFrameA_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Bool))
btGeneric6DofConstraint_m_useLinearReferenceFrameA_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_m_useLinearReferenceFrameA_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1751 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#315>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_useOffsetForConstraintFrame_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btGeneric6DofConstraint_m_useOffsetForConstraintFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btGeneric6DofConstraint_m_useOffsetForConstraintFrame_set'_ a1' a2' >>
  return ()

{-# LINE 1755 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#315>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_useOffsetForConstraintFrame_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Bool))
btGeneric6DofConstraint_m_useOffsetForConstraintFrame_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_m_useOffsetForConstraintFrame_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1759 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#317>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_flags_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Int) -> IO ()
btGeneric6DofConstraint_m_flags_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGeneric6DofConstraint_m_flags_set'_ a1' a2' >>
  return ()

{-# LINE 1763 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#317>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_flags_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Int))
btGeneric6DofConstraint_m_flags_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_m_flags_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1767 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#350>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_useSolveConstraintObsolete_set :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btGeneric6DofConstraint_m_useSolveConstraintObsolete_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btGeneric6DofConstraint_m_useSolveConstraintObsolete_set'_ a1' a2' >>
  return ()

{-# LINE 1771 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#350>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraint_m_useSolveConstraintObsolete_get :: ( BtGeneric6DofConstraintClass bc ) => (bc) -> IO ((Bool))
btGeneric6DofConstraint_m_useSolveConstraintObsolete_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraint_m_useSolveConstraintObsolete_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1775 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btGeneric6DofConstraintData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#564>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData :: IO ((BtGeneric6DofConstraintData))
btGeneric6DofConstraintData =
  btGeneric6DofConstraintData'_ >>= \res ->
  mkBtGeneric6DofConstraintData res >>= \res' ->
  return (res')

{-# LINE 1780 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btGeneric6DofConstraintData_free :: ( BtGeneric6DofConstraintDataClass bc ) => (bc) -> IO ()
btGeneric6DofConstraintData_free a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraintData_free'_ a1' >>
  return ()

{-# LINE 1781 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#565>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_typeConstraintData_set :: ( BtGeneric6DofConstraintDataClass bc , BtTypedConstraintDataClass a ) => (bc) -> (a) -> IO ()
btGeneric6DofConstraintData_m_typeConstraintData_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofConstraintData_m_typeConstraintData_set'_ a1' a2' >>
  return ()

{-# LINE 1785 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#565>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_typeConstraintData_get :: ( BtGeneric6DofConstraintDataClass bc ) => (bc) -> IO ((BtTypedConstraintData))
btGeneric6DofConstraintData_m_typeConstraintData_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraintData_m_typeConstraintData_get'_ a1' >>= \res ->
  mkBtTypedConstraintData res >>= \res' ->
  return (res')

{-# LINE 1789 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#566>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_rbAFrame_set :: ( BtGeneric6DofConstraintDataClass bc , BtTransformFloatDataClass a ) => (bc) -> (a) -> IO ()
btGeneric6DofConstraintData_m_rbAFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofConstraintData_m_rbAFrame_set'_ a1' a2' >>
  return ()

{-# LINE 1793 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#566>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_rbAFrame_get :: ( BtGeneric6DofConstraintDataClass bc ) => (bc) -> IO ((BtTransformFloatData))
btGeneric6DofConstraintData_m_rbAFrame_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraintData_m_rbAFrame_get'_ a1' >>= \res ->
  mkBtTransformFloatData res >>= \res' ->
  return (res')

{-# LINE 1797 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#567>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_rbBFrame_set :: ( BtGeneric6DofConstraintDataClass bc , BtTransformFloatDataClass a ) => (bc) -> (a) -> IO ()
btGeneric6DofConstraintData_m_rbBFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofConstraintData_m_rbBFrame_set'_ a1' a2' >>
  return ()

{-# LINE 1801 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#567>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_rbBFrame_get :: ( BtGeneric6DofConstraintDataClass bc ) => (bc) -> IO ((BtTransformFloatData))
btGeneric6DofConstraintData_m_rbBFrame_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraintData_m_rbBFrame_get'_ a1' >>= \res ->
  mkBtTransformFloatData res >>= \res' ->
  return (res')

{-# LINE 1805 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#569>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_linearUpperLimit_set :: ( BtGeneric6DofConstraintDataClass bc , BtVector3FloatDataClass a ) => (bc) -> (a) -> IO ()
btGeneric6DofConstraintData_m_linearUpperLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofConstraintData_m_linearUpperLimit_set'_ a1' a2' >>
  return ()

{-# LINE 1809 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#569>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_linearUpperLimit_get :: ( BtGeneric6DofConstraintDataClass bc ) => (bc) -> IO ((BtVector3FloatData))
btGeneric6DofConstraintData_m_linearUpperLimit_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraintData_m_linearUpperLimit_get'_ a1' >>= \res ->
  mkBtVector3FloatData res >>= \res' ->
  return (res')

{-# LINE 1813 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#570>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_linearLowerLimit_set :: ( BtGeneric6DofConstraintDataClass bc , BtVector3FloatDataClass a ) => (bc) -> (a) -> IO ()
btGeneric6DofConstraintData_m_linearLowerLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofConstraintData_m_linearLowerLimit_set'_ a1' a2' >>
  return ()

{-# LINE 1817 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#570>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_linearLowerLimit_get :: ( BtGeneric6DofConstraintDataClass bc ) => (bc) -> IO ((BtVector3FloatData))
btGeneric6DofConstraintData_m_linearLowerLimit_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraintData_m_linearLowerLimit_get'_ a1' >>= \res ->
  mkBtVector3FloatData res >>= \res' ->
  return (res')

{-# LINE 1821 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#572>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_angularUpperLimit_set :: ( BtGeneric6DofConstraintDataClass bc , BtVector3FloatDataClass a ) => (bc) -> (a) -> IO ()
btGeneric6DofConstraintData_m_angularUpperLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofConstraintData_m_angularUpperLimit_set'_ a1' a2' >>
  return ()

{-# LINE 1825 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#572>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_angularUpperLimit_get :: ( BtGeneric6DofConstraintDataClass bc ) => (bc) -> IO ((BtVector3FloatData))
btGeneric6DofConstraintData_m_angularUpperLimit_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraintData_m_angularUpperLimit_get'_ a1' >>= \res ->
  mkBtVector3FloatData res >>= \res' ->
  return (res')

{-# LINE 1829 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#573>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_angularLowerLimit_set :: ( BtGeneric6DofConstraintDataClass bc , BtVector3FloatDataClass a ) => (bc) -> (a) -> IO ()
btGeneric6DofConstraintData_m_angularLowerLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofConstraintData_m_angularLowerLimit_set'_ a1' a2' >>
  return ()

{-# LINE 1833 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#573>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_angularLowerLimit_get :: ( BtGeneric6DofConstraintDataClass bc ) => (bc) -> IO ((BtVector3FloatData))
btGeneric6DofConstraintData_m_angularLowerLimit_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraintData_m_angularLowerLimit_get'_ a1' >>= \res ->
  mkBtVector3FloatData res >>= \res' ->
  return (res')

{-# LINE 1837 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#575>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_useLinearReferenceFrameA_set :: ( BtGeneric6DofConstraintDataClass bc ) => (bc) -> (Int) -> IO ()
btGeneric6DofConstraintData_m_useLinearReferenceFrameA_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGeneric6DofConstraintData_m_useLinearReferenceFrameA_set'_ a1' a2' >>
  return ()

{-# LINE 1841 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#575>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_useLinearReferenceFrameA_get :: ( BtGeneric6DofConstraintDataClass bc ) => (bc) -> IO ((Int))
btGeneric6DofConstraintData_m_useLinearReferenceFrameA_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraintData_m_useLinearReferenceFrameA_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1845 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#576>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_useOffsetForConstraintFrame_set :: ( BtGeneric6DofConstraintDataClass bc ) => (bc) -> (Int) -> IO ()
btGeneric6DofConstraintData_m_useOffsetForConstraintFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGeneric6DofConstraintData_m_useOffsetForConstraintFrame_set'_ a1' a2' >>
  return ()

{-# LINE 1849 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#576>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btGeneric6DofConstraintData_m_useOffsetForConstraintFrame_get :: ( BtGeneric6DofConstraintDataClass bc ) => (bc) -> IO ((Int))
btGeneric6DofConstraintData_m_useOffsetForConstraintFrame_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofConstraintData_m_useOffsetForConstraintFrame_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1853 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btGeneric6DofSpringConstraint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#44>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint :: ( BtRigidBodyClass p0 , BtRigidBodyClass p1 ) => (p0) -> (p1) -> (Transform) -> (Transform) -> (Bool) -> IO ((BtGeneric6DofSpringConstraint))
btGeneric6DofSpringConstraint a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  let {a5' = C2HSImp.fromBool a5} in 
  btGeneric6DofSpringConstraint'_ a1' a2' a3' a4' a5' >>= \res ->
  mkBtGeneric6DofSpringConstraint res >>= \res' ->
  return (res')

{-# LINE 1858 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btGeneric6DofSpringConstraint_free :: ( BtGeneric6DofSpringConstraintClass bc ) => (bc) -> IO ()
btGeneric6DofSpringConstraint_free a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofSpringConstraint_free'_ a1' >>
  return ()

{-# LINE 1859 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#74>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint_calculateSerializeBufferSize :: ( BtGeneric6DofSpringConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btGeneric6DofSpringConstraint_calculateSerializeBufferSize a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofSpringConstraint_calculateSerializeBufferSize'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1864 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint_setEquilibriumPoint :: ( BtGeneric6DofSpringConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btGeneric6DofSpringConstraint_setEquilibriumPoint a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofSpringConstraint_setEquilibriumPoint'_ a1' >>
  return ()

{-# LINE 1869 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint_setEquilibriumPoint0 :: ( BtGeneric6DofSpringConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btGeneric6DofSpringConstraint_setEquilibriumPoint0 a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofSpringConstraint_setEquilibriumPoint0'_ a1' >>
  return ()

{-# LINE 1874 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#49>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint_setEquilibriumPoint1 :: ( BtGeneric6DofSpringConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ index
 -> IO ()
btGeneric6DofSpringConstraint_setEquilibriumPoint1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGeneric6DofSpringConstraint_setEquilibriumPoint1'_ a1' a2' >>
  return ()

{-# LINE 1880 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint_setEquilibriumPoint2 :: ( BtGeneric6DofSpringConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ index
 -> (Float) -- ^ val
 -> IO ()
btGeneric6DofSpringConstraint_setEquilibriumPoint2 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  btGeneric6DofSpringConstraint_setEquilibriumPoint2'_ a1' a2' a3' >>
  return ()

{-# LINE 1887 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint_serialize :: ( BtGeneric6DofSpringConstraintClass bc , BtSerializerClass p1 ) => (bc) -- ^ 
 -> (VoidPtr) -- ^ dataBuffer
 -> (p1) -- ^ serializer
 -> IO ((String))
btGeneric6DofSpringConstraint_serialize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGeneric6DofSpringConstraint_serialize'_ a1' a2' a3' >>= \res ->
  C2HSImp.peekCString res >>= \res' ->
  return (res')

{-# LINE 1894 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#45>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint_enableSpring :: ( BtGeneric6DofSpringConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ index
 -> (Bool) -- ^ onOff
 -> IO ()
btGeneric6DofSpringConstraint_enableSpring a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = C2HSImp.fromBool a3} in 
  btGeneric6DofSpringConstraint_enableSpring'_ a1' a2' a3' >>
  return ()

{-# LINE 1901 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#46>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint_setStiffness :: ( BtGeneric6DofSpringConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ index
 -> (Float) -- ^ stiffness
 -> IO ()
btGeneric6DofSpringConstraint_setStiffness a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  btGeneric6DofSpringConstraint_setStiffness'_ a1' a2' a3' >>
  return ()

{-# LINE 1908 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#47>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint_setDamping :: ( BtGeneric6DofSpringConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ index
 -> (Float) -- ^ damping
 -> IO ()
btGeneric6DofSpringConstraint_setDamping a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  btGeneric6DofSpringConstraint_setDamping'_ a1' a2' a3' >>
  return ()

{-# LINE 1915 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint_getInfo2 :: ( BtGeneric6DofSpringConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btGeneric6DofSpringConstraint_getInfo2 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofSpringConstraint_getInfo2'_ a1' a2' >>
  return ()

{-# LINE 1921 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint_internalUpdateSprings :: ( BtGeneric6DofSpringConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btGeneric6DofSpringConstraint_internalUpdateSprings a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofSpringConstraint_internalUpdateSprings'_ a1' a2' >>
  return ()

{-# LINE 1927 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint_setAxis :: ( BtGeneric6DofSpringConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ axis1
 -> (Vec3) -- ^ axis2
 -> IO ((Vec3), (Vec3))
btGeneric6DofSpringConstraint_setAxis a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btGeneric6DofSpringConstraint_setAxis'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 1934 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraint_setAxis' :: ( BtGeneric6DofSpringConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3), (Vec3))
btGeneric6DofSpringConstraint_setAxis' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btGeneric6DofSpringConstraint_setAxis''_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 1941 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btGeneric6DofSpringConstraintData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#65>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraintData :: IO ((BtGeneric6DofSpringConstraintData))
btGeneric6DofSpringConstraintData =
  btGeneric6DofSpringConstraintData'_ >>= \res ->
  mkBtGeneric6DofSpringConstraintData res >>= \res' ->
  return (res')

{-# LINE 1946 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btGeneric6DofSpringConstraintData_free :: ( BtGeneric6DofSpringConstraintDataClass bc ) => (bc) -> IO ()
btGeneric6DofSpringConstraintData_free a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofSpringConstraintData_free'_ a1' >>
  return ()

{-# LINE 1947 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraintData_m_6dofData_set :: ( BtGeneric6DofSpringConstraintDataClass bc , BtGeneric6DofConstraintDataClass a ) => (bc) -> (a) -> IO ()
btGeneric6DofSpringConstraintData_m_6dofData_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeneric6DofSpringConstraintData_m_6dofData_set'_ a1' a2' >>
  return ()

{-# LINE 1951 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofSpringConstraint.cpp?r=2223>
-}
btGeneric6DofSpringConstraintData_m_6dofData_get :: ( BtGeneric6DofSpringConstraintDataClass bc ) => (bc) -> IO ((BtGeneric6DofConstraintData))
btGeneric6DofSpringConstraintData_m_6dofData_get a1 =
  withBt a1 $ \a1' -> 
  btGeneric6DofSpringConstraintData_m_6dofData_get'_ a1' >>= \res ->
  mkBtGeneric6DofConstraintData res >>= \res' ->
  return (res')

{-# LINE 1955 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btHinge2Constraint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint :: ( BtRigidBodyClass p0 , BtRigidBodyClass p1 ) => (p0) -> (p1) -> (Vec3) -> (Vec3) -> (Vec3) -> IO ((BtHinge2Constraint))
btHinge2Constraint a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btHinge2Constraint'_ a1' a2' a3' a4' a5' >>= \res ->
  mkBtHinge2Constraint res >>= \res' ->
  return (res')

{-# LINE 1960 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btHinge2Constraint_free :: ( BtHinge2ConstraintClass bc ) => (bc) -> IO ()
btHinge2Constraint_free a1 =
  withBt a1 $ \a1' -> 
  btHinge2Constraint_free'_ a1' >>
  return ()

{-# LINE 1961 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_setLowerLimit :: ( BtHinge2ConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ ang1min
 -> IO ()
btHinge2Constraint_setLowerLimit a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHinge2Constraint_setLowerLimit'_ a1' a2' >>
  return ()

{-# LINE 1967 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#45>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_getAnchor2 :: ( BtHinge2ConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btHinge2Constraint_getAnchor2 a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btHinge2Constraint_getAnchor2'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1973 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#46>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_getAxis1 :: ( BtHinge2ConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btHinge2Constraint_getAxis1 a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btHinge2Constraint_getAxis1'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1979 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#44>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_getAnchor :: ( BtHinge2ConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btHinge2Constraint_getAnchor a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btHinge2Constraint_getAnchor'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1985 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#47>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_getAxis2 :: ( BtHinge2ConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btHinge2Constraint_getAxis2 a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btHinge2Constraint_getAxis2'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1991 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_setUpperLimit :: ( BtHinge2ConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ ang1max
 -> IO ()
btHinge2Constraint_setUpperLimit a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHinge2Constraint_setUpperLimit'_ a1' a2' >>
  return ()

{-# LINE 1997 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#49>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_getAngle2 :: ( BtHinge2ConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btHinge2Constraint_getAngle2 a1 =
  withBt a1 $ \a1' -> 
  btHinge2Constraint_getAngle2'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2002 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_getAngle1 :: ( BtHinge2ConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btHinge2Constraint_getAngle1 a1 =
  withBt a1 $ \a1' -> 
  btHinge2Constraint_getAngle1'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2007 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#35>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_m_anchor_set :: ( BtHinge2ConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btHinge2Constraint_m_anchor_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btHinge2Constraint_m_anchor_set'_ a1' a2' >>
  return ()

{-# LINE 2011 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#35>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_m_anchor_get :: ( BtHinge2ConstraintClass bc ) => (bc) -> IO ((Vec3))
btHinge2Constraint_m_anchor_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btHinge2Constraint_m_anchor_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2015 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#36>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_m_axis1_set :: ( BtHinge2ConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btHinge2Constraint_m_axis1_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btHinge2Constraint_m_axis1_set'_ a1' a2' >>
  return ()

{-# LINE 2019 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#36>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_m_axis1_get :: ( BtHinge2ConstraintClass bc ) => (bc) -> IO ((Vec3))
btHinge2Constraint_m_axis1_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btHinge2Constraint_m_axis1_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2023 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#37>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_m_axis2_set :: ( BtHinge2ConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btHinge2Constraint_m_axis2_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btHinge2Constraint_m_axis2_set'_ a1' a2' >>
  return ()

{-# LINE 2027 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.h?r=2223#37>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHinge2Constraint.cpp?r=2223>
-}
btHinge2Constraint_m_axis2_get :: ( BtHinge2ConstraintClass bc ) => (bc) -> IO ((Vec3))
btHinge2Constraint_m_axis2_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btHinge2Constraint_m_axis2_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2031 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btHingeConstraint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#103>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint0 :: ( BtRigidBodyClass p0 , BtRigidBodyClass p1 ) => (p0) -> (p1) -> (Vec3) -> (Vec3) -> (Vec3) -> (Vec3) -> (Bool) -> IO ((BtHingeConstraint))
btHingeConstraint0 a1 a2 a3 a4 a5 a6 a7 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  let {a7' = C2HSImp.fromBool a7} in 
  btHingeConstraint0'_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
  mkBtHingeConstraint res >>= \res' ->
  return (res')

{-# LINE 2036 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#105>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint1 :: ( BtRigidBodyClass p0 ) => (p0) -> (Vec3) -> (Vec3) -> (Bool) -> IO ((BtHingeConstraint))
btHingeConstraint1 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  let {a4' = C2HSImp.fromBool a4} in 
  btHingeConstraint1'_ a1' a2' a3' a4' >>= \res ->
  mkBtHingeConstraint res >>= \res' ->
  return (res')

{-# LINE 2040 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#107>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint2 :: ( BtRigidBodyClass p0 , BtRigidBodyClass p1 ) => (p0) -> (p1) -> (Transform) -> (Transform) -> (Bool) -> IO ((BtHingeConstraint))
btHingeConstraint2 a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  let {a5' = C2HSImp.fromBool a5} in 
  btHingeConstraint2'_ a1' a2' a3' a4' a5' >>= \res ->
  mkBtHingeConstraint res >>= \res' ->
  return (res')

{-# LINE 2044 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#109>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint3 :: ( BtRigidBodyClass p0 ) => (p0) -> (Transform) -> (Bool) -> IO ((BtHingeConstraint))
btHingeConstraint3 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  let {a3' = C2HSImp.fromBool a3} in 
  btHingeConstraint3'_ a1' a2' a3' >>= \res ->
  mkBtHingeConstraint res >>= \res' ->
  return (res')

{-# LINE 2048 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btHingeConstraint_free :: ( BtHingeConstraintClass bc ) => (bc) -> IO ()
btHingeConstraint_free a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_free'_ a1' >>
  return ()

{-# LINE 2049 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#132>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getRigidBodyB :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btHingeConstraint_getRigidBodyB a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getRigidBodyB'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 2054 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#132>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getRigidBodyB0 :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btHingeConstraint_getRigidBodyB0 a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getRigidBodyB0'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 2059 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#142>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getRigidBodyB1 :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btHingeConstraint_getRigidBodyB1 a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getRigidBodyB1'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 2064 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#120>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getInfo2NonVirtual :: ( BtHingeConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> (Vec3) -- ^ angVelA
 -> (Vec3) -- ^ angVelB
 -> IO ((Transform), (Transform), (Vec3), (Vec3))
btHingeConstraint_getInfo2NonVirtual a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  btHingeConstraint_getInfo2NonVirtual'_ a1' a2' a3' a4' a5' a6' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a3'', a4'', a5'', a6'')

{-# LINE 2074 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#120>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getInfo2NonVirtual' :: ( BtHingeConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ((Transform), (Transform), (Vec3), (Vec3))
btHingeConstraint_getInfo2NonVirtual' a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaTransform $ \a3' -> 
  allocaTransform $ \a4' -> 
  allocaVec3 $ \a5' -> 
  allocaVec3 $ \a6' -> 
  btHingeConstraint_getInfo2NonVirtual''_ a1' a2' a3' a4' a5' a6' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a3'', a4'', a5'', a6'')

{-# LINE 2084 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#128>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getRigidBodyA :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btHingeConstraint_getRigidBodyA a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getRigidBodyA'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 2089 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#128>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getRigidBodyA0 :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btHingeConstraint_getRigidBodyA0 a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getRigidBodyA0'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 2094 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#137>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getRigidBodyA1 :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btHingeConstraint_getRigidBodyA1 a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getRigidBodyA1'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 2099 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#276>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getMotorTargetVelosity :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btHingeConstraint_getMotorTargetVelosity a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getMotorTargetVelosity'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2104 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getFrameOffsetA :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btHingeConstraint_getFrameOffsetA a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btHingeConstraint_getFrameOffsetA'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2110 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#152>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getFrameOffsetB :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btHingeConstraint_getFrameOffsetB a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btHingeConstraint_getFrameOffsetB'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2116 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#112>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_buildJacobian :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btHingeConstraint_buildJacobian a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_buildJacobian'_ a1' >>
  return ()

{-# LINE 2121 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#175>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setMaxMotorImpulse :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ maxMotorImpulse
 -> IO ()
btHingeConstraint_setMaxMotorImpulse a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraint_setMaxMotorImpulse'_ a1' a2' >>
  return ()

{-# LINE 2127 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#237>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getHingeAngle :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btHingeConstraint_getHingeAngle a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getHingeAngle'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2132 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#237>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getHingeAngle0 :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btHingeConstraint_getHingeAngle0 a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getHingeAngle0'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2137 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#239>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getHingeAngle1 :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> IO ((Float), (Transform), (Transform))
btHingeConstraint_getHingeAngle1 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  btHingeConstraint_getHingeAngle1'_ a1' a2' a3' >>= \res ->
  let {res' = realToFrac res} in
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (res', a2'', a3'')

{-# LINE 2144 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#239>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getHingeAngle1' :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float), (Transform), (Transform))
btHingeConstraint_getHingeAngle1' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  btHingeConstraint_getHingeAngle1''_ a1' a2' a3' >>= \res ->
  let {res' = realToFrac res} in
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (res', a2'', a3'')

{-# LINE 2151 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#241>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_testLimit :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> IO ((Transform), (Transform))
btHingeConstraint_testLimit a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  btHingeConstraint_testLimit'_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 2158 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#241>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_testLimit' :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform), (Transform))
btHingeConstraint_testLimit' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  btHingeConstraint_testLimit''_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 2165 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#114>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getInfo1 :: ( BtHingeConstraintClass bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btHingeConstraint_getInfo1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHingeConstraint_getInfo1'_ a1' a2' >>
  return ()

{-# LINE 2171 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#122>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getInfo2Internal :: ( BtHingeConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> (Vec3) -- ^ angVelA
 -> (Vec3) -- ^ angVelB
 -> IO ((Transform), (Transform), (Vec3), (Vec3))
btHingeConstraint_getInfo2Internal a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  btHingeConstraint_getInfo2Internal'_ a1' a2' a3' a4' a5' a6' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a3'', a4'', a5'', a6'')

{-# LINE 2181 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#122>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getInfo2Internal' :: ( BtHingeConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ((Transform), (Transform), (Vec3), (Vec3))
btHingeConstraint_getInfo2Internal' a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaTransform $ \a3' -> 
  allocaTransform $ \a4' -> 
  allocaVec3 $ \a5' -> 
  allocaVec3 $ \a6' -> 
  btHingeConstraint_getInfo2Internal''_ a1' a2' a3' a4' a5' a6' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a3'', a4'', a5'', a6'')

{-# LINE 2191 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#118>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getInfo2 :: ( BtHingeConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btHingeConstraint_getInfo2 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHingeConstraint_getInfo2'_ a1' a2' >>
  return ()

{-# LINE 2197 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getUpperLimit :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btHingeConstraint_getUpperLimit a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getUpperLimit'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2202 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#164>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_enableAngularMotor :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ enableMotor
 -> (Float) -- ^ targetVelocity
 -> (Float) -- ^ maxMotorImpulse
 -> IO ()
btHingeConstraint_enableAngularMotor a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  btHingeConstraint_enableAngularMotor'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 2210 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#259>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getLimitSign :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btHingeConstraint_getLimitSign a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getLimitSign'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2215 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#345>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_calculateSerializeBufferSize :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btHingeConstraint_calculateSerializeBufferSize a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_calculateSerializeBufferSize'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 2220 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#280>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getMaxMotorImpulse :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btHingeConstraint_getMaxMotorImpulse a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getMaxMotorImpulse'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2225 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#218>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getLowerLimit :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btHingeConstraint_getLowerLimit a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getLowerLimit'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2230 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#291>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setParam :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ num
 -> (Float) -- ^ value
 -> (Int) -- ^ axis
 -> IO ()
btHingeConstraint_setParam a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = fromIntegral a4} in 
  btHingeConstraint_setParam'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 2238 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#286>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setUseFrameOffset :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ frameOffsetOnOff
 -> IO ()
btHingeConstraint_setUseFrameOffset a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btHingeConstraint_setUseFrameOffset'_ a1' a2' >>
  return ()

{-# LINE 2244 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#272>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getEnableAngularMotor :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btHingeConstraint_getEnableAngularMotor a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getEnableAngularMotor'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 2249 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#174>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_enableMotor :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ enableMotor
 -> IO ()
btHingeConstraint_enableMotor a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btHingeConstraint_enableMotor'_ a1' a2' >>
  return ()

{-# LINE 2255 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#245>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getBFrame :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btHingeConstraint_getBFrame a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btHingeConstraint_getBFrame'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2261 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#245>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getBFrame0 :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btHingeConstraint_getBFrame0 a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btHingeConstraint_getBFrame0'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2267 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#248>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getBFrame1 :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btHingeConstraint_getBFrame1 a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btHingeConstraint_getBFrame1'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2273 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#116>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getInfo1NonVirtual :: ( BtHingeConstraintClass bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btHingeConstraint_getInfo1NonVirtual a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHingeConstraint_getInfo1NonVirtual'_ a1' a2' >>
  return ()

{-# LINE 2279 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#123>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getInfo2InternalUsingFrameOffset :: ( BtHingeConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> (Vec3) -- ^ angVelA
 -> (Vec3) -- ^ angVelB
 -> IO ((Transform), (Transform), (Vec3), (Vec3))
btHingeConstraint_getInfo2InternalUsingFrameOffset a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  btHingeConstraint_getInfo2InternalUsingFrameOffset'_ a1' a2' a3' a4' a5' a6' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a3'', a4'', a5'', a6'')

{-# LINE 2289 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#123>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getInfo2InternalUsingFrameOffset' :: ( BtHingeConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ((Transform), (Transform), (Vec3), (Vec3))
btHingeConstraint_getInfo2InternalUsingFrameOffset' a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaTransform $ \a3' -> 
  allocaTransform $ \a4' -> 
  allocaVec3 $ \a5' -> 
  allocaVec3 $ \a6' -> 
  btHingeConstraint_getInfo2InternalUsingFrameOffset''_ a1' a2' a3' a4' a5' a6' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a3'', a4'', a5'', a6'')

{-# LINE 2299 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#351>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_serialize :: ( BtHingeConstraintClass bc , BtSerializerClass p1 ) => (bc) -- ^ 
 -> (VoidPtr) -- ^ dataBuffer
 -> (p1) -- ^ serializer
 -> IO ((String))
btHingeConstraint_serialize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btHingeConstraint_serialize'_ a1' a2' a3' >>= \res ->
  C2HSImp.peekCString res >>= \res' ->
  return (res')

{-# LINE 2306 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#285>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getUseFrameOffset :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btHingeConstraint_getUseFrameOffset a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getUseFrameOffset'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 2311 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#159>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setAngularOnly :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ angularOnly
 -> IO ()
btHingeConstraint_setAngularOnly a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btHingeConstraint_setAngularOnly'_ a1' a2' >>
  return ()

{-# LINE 2317 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#293>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getParam :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ num
 -> (Int) -- ^ axis
 -> IO ((Float))
btHingeConstraint_getParam a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btHingeConstraint_getParam'_ a1' a2' a3' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2324 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setLimit :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ low
 -> (Float) -- ^ high
 -> (Float) -- ^ _softness
 -> (Float) -- ^ _biasFactor
 -> (Float) -- ^ _relaxationFactor
 -> IO ()
btHingeConstraint_setLimit a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  btHingeConstraint_setLimit'_ a1' a2' a3' a4' a5' a6' >>
  return ()

{-# LINE 2334 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#250>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getSolveLimit :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btHingeConstraint_getSolveLimit a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getSolveLimit'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 2339 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#126>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_updateRHS :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ timeStep
 -> IO ()
btHingeConstraint_updateRHS a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraint_updateRHS'_ a1' a2' >>
  return ()

{-# LINE 2345 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#176>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setMotorTarget :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (UnitQuaternion) -- ^ qAinB
 -> (Float) -- ^ dt
 -> IO ((UnitQuaternion))
btHingeConstraint_setMotorTarget a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withUnitQuaternion a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btHingeConstraint_setMotorTarget'_ a1' a2' a3' >>
  peekUnitQuaternion  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2352 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#176>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setMotorTarget' :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> IO ((UnitQuaternion))
btHingeConstraint_setMotorTarget' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaUnitQuaternion $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btHingeConstraint_setMotorTarget''_ a1' a2' a3' >>
  peekUnitQuaternion  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2359 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#176>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setMotorTarget0 :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (UnitQuaternion) -- ^ qAinB
 -> (Float) -- ^ dt
 -> IO ((UnitQuaternion))
btHingeConstraint_setMotorTarget0 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withUnitQuaternion a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btHingeConstraint_setMotorTarget0'_ a1' a2' a3' >>
  peekUnitQuaternion  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2366 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#176>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setMotorTarget0' :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> IO ((UnitQuaternion))
btHingeConstraint_setMotorTarget0' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaUnitQuaternion $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btHingeConstraint_setMotorTarget0''_ a1' a2' a3' >>
  peekUnitQuaternion  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2373 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#177>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setMotorTarget1 :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ targetAngle
 -> (Float) -- ^ dt
 -> IO ()
btHingeConstraint_setMotorTarget1 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btHingeConstraint_setMotorTarget1'_ a1' a2' a3' >>
  return ()

{-# LINE 2380 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#268>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getAngularOnly :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btHingeConstraint_getAngularOnly a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_getAngularOnly'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 2385 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#157>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setFrames :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Transform) -- ^ frameA
 -> (Transform) -- ^ frameB
 -> IO ((Transform), (Transform))
btHingeConstraint_setFrames a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  btHingeConstraint_setFrames'_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 2392 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#157>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setFrames' :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform), (Transform))
btHingeConstraint_setFrames' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  btHingeConstraint_setFrames''_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 2399 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#193>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setAxis :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ axisInA
 -> IO ((Vec3))
btHingeConstraint_setAxis a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btHingeConstraint_setAxis'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2405 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#193>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_setAxis' :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btHingeConstraint_setAxis' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btHingeConstraint_setAxis''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2411 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#244>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getAFrame :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btHingeConstraint_getAFrame a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btHingeConstraint_getAFrame'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2417 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#244>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getAFrame0 :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btHingeConstraint_getAFrame0 a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btHingeConstraint_getAFrame0'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2423 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#247>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_getAFrame1 :: ( BtHingeConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btHingeConstraint_getAFrame1 a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btHingeConstraint_getAFrame1'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2429 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#58>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_rbAFrame_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Transform) -> IO ()
btHingeConstraint_m_rbAFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btHingeConstraint_m_rbAFrame_set'_ a1' a2' >>
  return ()

{-# LINE 2433 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#58>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_rbAFrame_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Transform))
btHingeConstraint_m_rbAFrame_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btHingeConstraint_m_rbAFrame_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2437 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#59>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_rbBFrame_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Transform) -> IO ()
btHingeConstraint_m_rbBFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btHingeConstraint_m_rbBFrame_set'_ a1' a2' >>
  return ()

{-# LINE 2441 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#59>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_rbBFrame_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Transform))
btHingeConstraint_m_rbBFrame_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btHingeConstraint_m_rbBFrame_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2445 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_motorTargetVelocity_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraint_m_motorTargetVelocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraint_m_motorTargetVelocity_set'_ a1' a2' >>
  return ()

{-# LINE 2449 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_motorTargetVelocity_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Float))
btHingeConstraint_m_motorTargetVelocity_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_motorTargetVelocity_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2453 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_maxMotorImpulse_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraint_m_maxMotorImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraint_m_maxMotorImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 2457 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_maxMotorImpulse_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Float))
btHingeConstraint_m_maxMotorImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_maxMotorImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2461 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_limit_set :: ( BtHingeConstraintClass bc , BtAngularLimitClass a ) => (bc) -> (a) -> IO ()
btHingeConstraint_m_limit_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHingeConstraint_m_limit_set'_ a1' a2' >>
  return ()

{-# LINE 2465 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_limit_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((BtAngularLimit))
btHingeConstraint_m_limit_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_limit_get'_ a1' >>= \res ->
  mkBtAngularLimit res >>= \res' ->
  return (res')

{-# LINE 2469 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_kHinge_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraint_m_kHinge_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraint_m_kHinge_set'_ a1' a2' >>
  return ()

{-# LINE 2473 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_kHinge_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Float))
btHingeConstraint_m_kHinge_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_kHinge_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2477 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_accLimitImpulse_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraint_m_accLimitImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraint_m_accLimitImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 2481 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_accLimitImpulse_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Float))
btHingeConstraint_m_accLimitImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_accLimitImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2485 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#84>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_hingeAngle_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraint_m_hingeAngle_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraint_m_hingeAngle_set'_ a1' a2' >>
  return ()

{-# LINE 2489 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#84>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_hingeAngle_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Float))
btHingeConstraint_m_hingeAngle_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_hingeAngle_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2493 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#85>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_referenceSign_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraint_m_referenceSign_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraint_m_referenceSign_set'_ a1' a2' >>
  return ()

{-# LINE 2497 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#85>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_referenceSign_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Float))
btHingeConstraint_m_referenceSign_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_referenceSign_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2501 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#87>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_angularOnly_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btHingeConstraint_m_angularOnly_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btHingeConstraint_m_angularOnly_set'_ a1' a2' >>
  return ()

{-# LINE 2505 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#87>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_angularOnly_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Bool))
btHingeConstraint_m_angularOnly_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_angularOnly_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 2509 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_enableAngularMotor_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btHingeConstraint_m_enableAngularMotor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btHingeConstraint_m_enableAngularMotor_set'_ a1' a2' >>
  return ()

{-# LINE 2513 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_enableAngularMotor_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Bool))
btHingeConstraint_m_enableAngularMotor_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_enableAngularMotor_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 2517 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_useSolveConstraintObsolete_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btHingeConstraint_m_useSolveConstraintObsolete_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btHingeConstraint_m_useSolveConstraintObsolete_set'_ a1' a2' >>
  return ()

{-# LINE 2521 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_useSolveConstraintObsolete_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Bool))
btHingeConstraint_m_useSolveConstraintObsolete_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_useSolveConstraintObsolete_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 2525 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#90>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_useOffsetForConstraintFrame_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btHingeConstraint_m_useOffsetForConstraintFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btHingeConstraint_m_useOffsetForConstraintFrame_set'_ a1' a2' >>
  return ()

{-# LINE 2529 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#90>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_useOffsetForConstraintFrame_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Bool))
btHingeConstraint_m_useOffsetForConstraintFrame_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_useOffsetForConstraintFrame_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 2533 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#91>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_useReferenceFrameA_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btHingeConstraint_m_useReferenceFrameA_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btHingeConstraint_m_useReferenceFrameA_set'_ a1' a2' >>
  return ()

{-# LINE 2537 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#91>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_useReferenceFrameA_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Bool))
btHingeConstraint_m_useReferenceFrameA_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_useReferenceFrameA_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 2541 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#93>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_accMotorImpulse_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraint_m_accMotorImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraint_m_accMotorImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 2545 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#93>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_accMotorImpulse_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Float))
btHingeConstraint_m_accMotorImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_accMotorImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2549 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#95>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_flags_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Int) -> IO ()
btHingeConstraint_m_flags_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHingeConstraint_m_flags_set'_ a1' a2' >>
  return ()

{-# LINE 2553 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#95>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_flags_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Int))
btHingeConstraint_m_flags_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_flags_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 2557 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_normalCFM_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraint_m_normalCFM_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraint_m_normalCFM_set'_ a1' a2' >>
  return ()

{-# LINE 2561 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_normalCFM_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Float))
btHingeConstraint_m_normalCFM_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_normalCFM_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2565 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_stopCFM_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraint_m_stopCFM_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraint_m_stopCFM_set'_ a1' a2' >>
  return ()

{-# LINE 2569 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_stopCFM_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Float))
btHingeConstraint_m_stopCFM_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_stopCFM_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2573 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#98>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_stopERP_set :: ( BtHingeConstraintClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraint_m_stopERP_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraint_m_stopERP_set'_ a1' a2' >>
  return ()

{-# LINE 2577 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#98>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraint_m_stopERP_get :: ( BtHingeConstraintClass bc ) => (bc) -> IO ((Float))
btHingeConstraint_m_stopERP_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraint_m_stopERP_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2581 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btHingeConstraintDoubleData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#305>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData :: IO ((BtHingeConstraintDoubleData))
btHingeConstraintDoubleData =
  btHingeConstraintDoubleData'_ >>= \res ->
  mkBtHingeConstraintDoubleData res >>= \res' ->
  return (res')

{-# LINE 2586 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btHingeConstraintDoubleData_free :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ()
btHingeConstraintDoubleData_free a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_free'_ a1' >>
  return ()

{-# LINE 2587 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#306>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_typeConstraintData_set :: ( BtHingeConstraintDoubleDataClass bc , BtTypedConstraintDataClass a ) => (bc) -> (a) -> IO ()
btHingeConstraintDoubleData_m_typeConstraintData_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHingeConstraintDoubleData_m_typeConstraintData_set'_ a1' a2' >>
  return ()

{-# LINE 2591 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#306>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_typeConstraintData_get :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ((BtTypedConstraintData))
btHingeConstraintDoubleData_m_typeConstraintData_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_m_typeConstraintData_get'_ a1' >>= \res ->
  mkBtTypedConstraintData res >>= \res' ->
  return (res')

{-# LINE 2595 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#307>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_rbAFrame_set :: ( BtHingeConstraintDoubleDataClass bc , BtTransformDoubleDataClass a ) => (bc) -> (a) -> IO ()
btHingeConstraintDoubleData_m_rbAFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHingeConstraintDoubleData_m_rbAFrame_set'_ a1' a2' >>
  return ()

{-# LINE 2599 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#307>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_rbAFrame_get :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ((BtTransformDoubleData))
btHingeConstraintDoubleData_m_rbAFrame_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_m_rbAFrame_get'_ a1' >>= \res ->
  mkBtTransformDoubleData res >>= \res' ->
  return (res')

{-# LINE 2603 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#308>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_rbBFrame_set :: ( BtHingeConstraintDoubleDataClass bc , BtTransformDoubleDataClass a ) => (bc) -> (a) -> IO ()
btHingeConstraintDoubleData_m_rbBFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHingeConstraintDoubleData_m_rbBFrame_set'_ a1' a2' >>
  return ()

{-# LINE 2607 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#308>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_rbBFrame_get :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ((BtTransformDoubleData))
btHingeConstraintDoubleData_m_rbBFrame_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_m_rbBFrame_get'_ a1' >>= \res ->
  mkBtTransformDoubleData res >>= \res' ->
  return (res')

{-# LINE 2611 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#309>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_useReferenceFrameA_set :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> (Int) -> IO ()
btHingeConstraintDoubleData_m_useReferenceFrameA_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHingeConstraintDoubleData_m_useReferenceFrameA_set'_ a1' a2' >>
  return ()

{-# LINE 2615 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#309>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_useReferenceFrameA_get :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ((Int))
btHingeConstraintDoubleData_m_useReferenceFrameA_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_m_useReferenceFrameA_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 2619 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#310>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_angularOnly_set :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> (Int) -> IO ()
btHingeConstraintDoubleData_m_angularOnly_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHingeConstraintDoubleData_m_angularOnly_set'_ a1' a2' >>
  return ()

{-# LINE 2623 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#310>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_angularOnly_get :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ((Int))
btHingeConstraintDoubleData_m_angularOnly_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_m_angularOnly_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 2627 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#311>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_enableAngularMotor_set :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> (Int) -> IO ()
btHingeConstraintDoubleData_m_enableAngularMotor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHingeConstraintDoubleData_m_enableAngularMotor_set'_ a1' a2' >>
  return ()

{-# LINE 2631 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#311>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_enableAngularMotor_get :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ((Int))
btHingeConstraintDoubleData_m_enableAngularMotor_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_m_enableAngularMotor_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 2635 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#312>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_motorTargetVelocity_set :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintDoubleData_m_motorTargetVelocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintDoubleData_m_motorTargetVelocity_set'_ a1' a2' >>
  return ()

{-# LINE 2639 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#312>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_motorTargetVelocity_get :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintDoubleData_m_motorTargetVelocity_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_m_motorTargetVelocity_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2643 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#313>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_maxMotorImpulse_set :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintDoubleData_m_maxMotorImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintDoubleData_m_maxMotorImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 2647 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#313>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_maxMotorImpulse_get :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintDoubleData_m_maxMotorImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_m_maxMotorImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2651 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#315>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_lowerLimit_set :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintDoubleData_m_lowerLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintDoubleData_m_lowerLimit_set'_ a1' a2' >>
  return ()

{-# LINE 2655 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#315>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_lowerLimit_get :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintDoubleData_m_lowerLimit_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_m_lowerLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2659 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#316>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_upperLimit_set :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintDoubleData_m_upperLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintDoubleData_m_upperLimit_set'_ a1' a2' >>
  return ()

{-# LINE 2663 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#316>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_upperLimit_get :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintDoubleData_m_upperLimit_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_m_upperLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2667 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#317>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_limitSoftness_set :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintDoubleData_m_limitSoftness_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintDoubleData_m_limitSoftness_set'_ a1' a2' >>
  return ()

{-# LINE 2671 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#317>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_limitSoftness_get :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintDoubleData_m_limitSoftness_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_m_limitSoftness_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2675 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#318>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_biasFactor_set :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintDoubleData_m_biasFactor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintDoubleData_m_biasFactor_set'_ a1' a2' >>
  return ()

{-# LINE 2679 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#318>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_biasFactor_get :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintDoubleData_m_biasFactor_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_m_biasFactor_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2683 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#319>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_relaxationFactor_set :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintDoubleData_m_relaxationFactor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintDoubleData_m_relaxationFactor_set'_ a1' a2' >>
  return ()

{-# LINE 2687 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#319>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintDoubleData_m_relaxationFactor_get :: ( BtHingeConstraintDoubleDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintDoubleData_m_relaxationFactor_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintDoubleData_m_relaxationFactor_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2691 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btHingeConstraintFloatData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#324>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData :: IO ((BtHingeConstraintFloatData))
btHingeConstraintFloatData =
  btHingeConstraintFloatData'_ >>= \res ->
  mkBtHingeConstraintFloatData res >>= \res' ->
  return (res')

{-# LINE 2696 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btHingeConstraintFloatData_free :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ()
btHingeConstraintFloatData_free a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_free'_ a1' >>
  return ()

{-# LINE 2697 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#325>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_typeConstraintData_set :: ( BtHingeConstraintFloatDataClass bc , BtTypedConstraintDataClass a ) => (bc) -> (a) -> IO ()
btHingeConstraintFloatData_m_typeConstraintData_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHingeConstraintFloatData_m_typeConstraintData_set'_ a1' a2' >>
  return ()

{-# LINE 2701 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#325>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_typeConstraintData_get :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ((BtTypedConstraintData))
btHingeConstraintFloatData_m_typeConstraintData_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_m_typeConstraintData_get'_ a1' >>= \res ->
  mkBtTypedConstraintData res >>= \res' ->
  return (res')

{-# LINE 2705 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#326>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_rbAFrame_set :: ( BtHingeConstraintFloatDataClass bc , BtTransformFloatDataClass a ) => (bc) -> (a) -> IO ()
btHingeConstraintFloatData_m_rbAFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHingeConstraintFloatData_m_rbAFrame_set'_ a1' a2' >>
  return ()

{-# LINE 2709 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#326>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_rbAFrame_get :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ((BtTransformFloatData))
btHingeConstraintFloatData_m_rbAFrame_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_m_rbAFrame_get'_ a1' >>= \res ->
  mkBtTransformFloatData res >>= \res' ->
  return (res')

{-# LINE 2713 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#327>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_rbBFrame_set :: ( BtHingeConstraintFloatDataClass bc , BtTransformFloatDataClass a ) => (bc) -> (a) -> IO ()
btHingeConstraintFloatData_m_rbBFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHingeConstraintFloatData_m_rbBFrame_set'_ a1' a2' >>
  return ()

{-# LINE 2717 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#327>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_rbBFrame_get :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ((BtTransformFloatData))
btHingeConstraintFloatData_m_rbBFrame_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_m_rbBFrame_get'_ a1' >>= \res ->
  mkBtTransformFloatData res >>= \res' ->
  return (res')

{-# LINE 2721 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#328>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_useReferenceFrameA_set :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> (Int) -> IO ()
btHingeConstraintFloatData_m_useReferenceFrameA_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHingeConstraintFloatData_m_useReferenceFrameA_set'_ a1' a2' >>
  return ()

{-# LINE 2725 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#328>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_useReferenceFrameA_get :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ((Int))
btHingeConstraintFloatData_m_useReferenceFrameA_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_m_useReferenceFrameA_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 2729 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#329>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_angularOnly_set :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> (Int) -> IO ()
btHingeConstraintFloatData_m_angularOnly_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHingeConstraintFloatData_m_angularOnly_set'_ a1' a2' >>
  return ()

{-# LINE 2733 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#329>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_angularOnly_get :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ((Int))
btHingeConstraintFloatData_m_angularOnly_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_m_angularOnly_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 2737 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#331>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_enableAngularMotor_set :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> (Int) -> IO ()
btHingeConstraintFloatData_m_enableAngularMotor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHingeConstraintFloatData_m_enableAngularMotor_set'_ a1' a2' >>
  return ()

{-# LINE 2741 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#331>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_enableAngularMotor_get :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ((Int))
btHingeConstraintFloatData_m_enableAngularMotor_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_m_enableAngularMotor_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 2745 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#332>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_motorTargetVelocity_set :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintFloatData_m_motorTargetVelocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintFloatData_m_motorTargetVelocity_set'_ a1' a2' >>
  return ()

{-# LINE 2749 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#332>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_motorTargetVelocity_get :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintFloatData_m_motorTargetVelocity_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_m_motorTargetVelocity_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2753 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#333>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_maxMotorImpulse_set :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintFloatData_m_maxMotorImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintFloatData_m_maxMotorImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 2757 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#333>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_maxMotorImpulse_get :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintFloatData_m_maxMotorImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_m_maxMotorImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2761 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#335>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_lowerLimit_set :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintFloatData_m_lowerLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintFloatData_m_lowerLimit_set'_ a1' a2' >>
  return ()

{-# LINE 2765 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#335>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_lowerLimit_get :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintFloatData_m_lowerLimit_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_m_lowerLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2769 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#336>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_upperLimit_set :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintFloatData_m_upperLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintFloatData_m_upperLimit_set'_ a1' a2' >>
  return ()

{-# LINE 2773 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#336>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_upperLimit_get :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintFloatData_m_upperLimit_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_m_upperLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2777 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#337>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_limitSoftness_set :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintFloatData_m_limitSoftness_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintFloatData_m_limitSoftness_set'_ a1' a2' >>
  return ()

{-# LINE 2781 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#337>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_limitSoftness_get :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintFloatData_m_limitSoftness_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_m_limitSoftness_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2785 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#338>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_biasFactor_set :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintFloatData_m_biasFactor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintFloatData_m_biasFactor_set'_ a1' a2' >>
  return ()

{-# LINE 2789 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#338>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_biasFactor_get :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintFloatData_m_biasFactor_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_m_biasFactor_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2793 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#339>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_relaxationFactor_set :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> (Float) -> IO ()
btHingeConstraintFloatData_m_relaxationFactor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btHingeConstraintFloatData_m_relaxationFactor_set'_ a1' a2' >>
  return ()

{-# LINE 2797 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.h?r=2223#339>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btHingeConstraint.cpp?r=2223>
-}
btHingeConstraintFloatData_m_relaxationFactor_get :: ( BtHingeConstraintFloatDataClass bc ) => (bc) -> IO ((Float))
btHingeConstraintFloatData_m_relaxationFactor_get a1 =
  withBt a1 $ \a1' -> 
  btHingeConstraintFloatData_m_relaxationFactor_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2801 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btJacobianEntry
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#34>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry0 :: IO ((BtJacobianEntry))
btJacobianEntry0 =
  btJacobianEntry0'_ >>= \res ->
  mkBtJacobianEntry res >>= \res' ->
  return (res')

{-# LINE 2806 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry2 :: (Vec3) -> (Mat3) -> (Mat3) -> (Vec3) -> (Vec3) -> IO ((BtJacobianEntry))
btJacobianEntry2 a1 a2 a3 a4 a5 =
  withVec3 a1 $ \a1' -> 
  withMat3 a2 $ \a2' -> 
  withMat3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btJacobianEntry2'_ a1' a2' a3' a4' a5' >>= \res ->
  mkBtJacobianEntry res >>= \res' ->
  return (res')

{-# LINE 2810 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#77>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry3 :: (Vec3) -> (Vec3) -> (Vec3) -> (Vec3) -> IO ((BtJacobianEntry))
btJacobianEntry3 a1 a2 a3 a4 =
  withVec3 a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btJacobianEntry3'_ a1' a2' a3' a4' >>= \res ->
  mkBtJacobianEntry res >>= \res' ->
  return (res')

{-# LINE 2814 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btJacobianEntry_free :: ( BtJacobianEntryClass bc ) => (bc) -> IO ()
btJacobianEntry_free a1 =
  withBt a1 $ \a1' -> 
  btJacobianEntry_free'_ a1' >>
  return ()

{-# LINE 2815 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#107>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_getDiagonal :: ( BtJacobianEntryClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btJacobianEntry_getDiagonal a1 =
  withBt a1 $ \a1' -> 
  btJacobianEntry_getDiagonal'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2820 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#133>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_getRelativeVelocity :: ( BtJacobianEntryClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ linvelA
 -> (Vec3) -- ^ angvelA
 -> (Vec3) -- ^ linvelB
 -> (Vec3) -- ^ angvelB
 -> IO ((Float), (Vec3), (Vec3), (Vec3), (Vec3))
btJacobianEntry_getRelativeVelocity a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btJacobianEntry_getRelativeVelocity'_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = realToFrac res} in
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (res', a2'', a3'', a4'', a5'')

{-# LINE 2829 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#133>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_getRelativeVelocity' :: ( BtJacobianEntryClass bc ) => (bc) -- ^ 
 -> IO ((Float), (Vec3), (Vec3), (Vec3), (Vec3))
btJacobianEntry_getRelativeVelocity' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  btJacobianEntry_getRelativeVelocity''_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = realToFrac res} in
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (res', a2'', a3'', a4'', a5'')

{-# LINE 2838 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#149>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_m_0MinvJt_set :: ( BtJacobianEntryClass bc ) => (bc) -> (Vec3) -> IO ()
btJacobianEntry_m_0MinvJt_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btJacobianEntry_m_0MinvJt_set'_ a1' a2' >>
  return ()

{-# LINE 2842 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#149>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_m_0MinvJt_get :: ( BtJacobianEntryClass bc ) => (bc) -> IO ((Vec3))
btJacobianEntry_m_0MinvJt_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btJacobianEntry_m_0MinvJt_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2846 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#150>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_m_1MinvJt_set :: ( BtJacobianEntryClass bc ) => (bc) -> (Vec3) -> IO ()
btJacobianEntry_m_1MinvJt_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btJacobianEntry_m_1MinvJt_set'_ a1' a2' >>
  return ()

{-# LINE 2850 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#150>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_m_1MinvJt_get :: ( BtJacobianEntryClass bc ) => (bc) -> IO ((Vec3))
btJacobianEntry_m_1MinvJt_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btJacobianEntry_m_1MinvJt_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2854 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#152>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_m_Adiag_set :: ( BtJacobianEntryClass bc ) => (bc) -> (Float) -> IO ()
btJacobianEntry_m_Adiag_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btJacobianEntry_m_Adiag_set'_ a1' a2' >>
  return ()

{-# LINE 2858 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#152>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_m_Adiag_get :: ( BtJacobianEntryClass bc ) => (bc) -> IO ((Float))
btJacobianEntry_m_Adiag_get a1 =
  withBt a1 $ \a1' -> 
  btJacobianEntry_m_Adiag_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2862 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_m_aJ_set :: ( BtJacobianEntryClass bc ) => (bc) -> (Vec3) -> IO ()
btJacobianEntry_m_aJ_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btJacobianEntry_m_aJ_set'_ a1' a2' >>
  return ()

{-# LINE 2866 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_m_aJ_get :: ( BtJacobianEntryClass bc ) => (bc) -> IO ((Vec3))
btJacobianEntry_m_aJ_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btJacobianEntry_m_aJ_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2870 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_m_bJ_set :: ( BtJacobianEntryClass bc ) => (bc) -> (Vec3) -> IO ()
btJacobianEntry_m_bJ_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btJacobianEntry_m_bJ_set'_ a1' a2' >>
  return ()

{-# LINE 2874 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_m_bJ_get :: ( BtJacobianEntryClass bc ) => (bc) -> IO ((Vec3))
btJacobianEntry_m_bJ_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btJacobianEntry_m_bJ_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2878 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#146>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_m_linearJointAxis_set :: ( BtJacobianEntryClass bc ) => (bc) -> (Vec3) -> IO ()
btJacobianEntry_m_linearJointAxis_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btJacobianEntry_m_linearJointAxis_set'_ a1' a2' >>
  return ()

{-# LINE 2882 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.h?r=2223#146>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btJacobianEntry.cpp?r=2223>
-}
btJacobianEntry_m_linearJointAxis_get :: ( BtJacobianEntryClass bc ) => (bc) -> IO ((Vec3))
btJacobianEntry_m_linearJointAxis_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btJacobianEntry_m_linearJointAxis_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2886 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btPoint2PointConstraint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#75>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint0 :: ( BtRigidBodyClass p0 , BtRigidBodyClass p1 ) => (p0) -> (p1) -> (Vec3) -> (Vec3) -> IO ((BtPoint2PointConstraint))
btPoint2PointConstraint0 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btPoint2PointConstraint0'_ a1' a2' a3' a4' >>= \res ->
  mkBtPoint2PointConstraint res >>= \res' ->
  return (res')

{-# LINE 2891 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#77>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint1 :: ( BtRigidBodyClass p0 ) => (p0) -> (Vec3) -> IO ((BtPoint2PointConstraint))
btPoint2PointConstraint1 a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btPoint2PointConstraint1'_ a1' a2' >>= \res ->
  mkBtPoint2PointConstraint res >>= \res' ->
  return (res')

{-# LINE 2895 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btPoint2PointConstraint_free :: ( BtPoint2PointConstraintClass bc ) => (bc) -> IO ()
btPoint2PointConstraint_free a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraint_free'_ a1' >>
  return ()

{-# LINE 2896 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#84>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_getInfo1NonVirtual :: ( BtPoint2PointConstraintClass bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btPoint2PointConstraint_getInfo1NonVirtual a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btPoint2PointConstraint_getInfo1NonVirtual'_ a1' a2' >>
  return ()

{-# LINE 2902 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_getInfo2NonVirtual :: ( BtPoint2PointConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> (Transform) -- ^ body0_trans
 -> (Transform) -- ^ body1_trans
 -> IO ((Transform), (Transform))
btPoint2PointConstraint_getInfo2NonVirtual a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  btPoint2PointConstraint_getInfo2NonVirtual'_ a1' a2' a3' a4' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  return (a3'', a4'')

{-# LINE 2910 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_getInfo2NonVirtual' :: ( BtPoint2PointConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ((Transform), (Transform))
btPoint2PointConstraint_getInfo2NonVirtual' a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaTransform $ \a3' -> 
  allocaTransform $ \a4' -> 
  btPoint2PointConstraint_getInfo2NonVirtual''_ a1' a2' a3' a4' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  return (a3'', a4'')

{-# LINE 2918 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#114>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_setParam :: ( BtPoint2PointConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ num
 -> (Float) -- ^ value
 -> (Int) -- ^ axis
 -> IO ()
btPoint2PointConstraint_setParam a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = fromIntegral a4} in 
  btPoint2PointConstraint_setParam'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 2926 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#102>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_getPivotInA :: ( BtPoint2PointConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btPoint2PointConstraint_getPivotInA a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btPoint2PointConstraint_getPivotInA'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2932 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#107>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_getPivotInB :: ( BtPoint2PointConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btPoint2PointConstraint_getPivotInB a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btPoint2PointConstraint_getPivotInB'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2938 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#90>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_updateRHS :: ( BtPoint2PointConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ timeStep
 -> IO ()
btPoint2PointConstraint_updateRHS a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btPoint2PointConstraint_updateRHS'_ a1' a2' >>
  return ()

{-# LINE 2944 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#150>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_serialize :: ( BtPoint2PointConstraintClass bc , BtSerializerClass p1 ) => (bc) -- ^ 
 -> (VoidPtr) -- ^ dataBuffer
 -> (p1) -- ^ serializer
 -> IO ((String))
btPoint2PointConstraint_serialize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btPoint2PointConstraint_serialize'_ a1' a2' a3' >>= \res ->
  C2HSImp.peekCString res >>= \res' ->
  return (res')

{-# LINE 2951 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_buildJacobian :: ( BtPoint2PointConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btPoint2PointConstraint_buildJacobian a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraint_buildJacobian'_ a1' >>
  return ()

{-# LINE 2956 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#143>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_calculateSerializeBufferSize :: ( BtPoint2PointConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btPoint2PointConstraint_calculateSerializeBufferSize a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraint_calculateSerializeBufferSize'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 2961 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#116>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_getParam :: ( BtPoint2PointConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ num
 -> (Int) -- ^ axis
 -> IO ((Float))
btPoint2PointConstraint_getParam a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btPoint2PointConstraint_getParam'_ a1' a2' a3' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2968 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_getInfo1 :: ( BtPoint2PointConstraintClass bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btPoint2PointConstraint_getInfo1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btPoint2PointConstraint_getInfo1'_ a1' a2' >>
  return ()

{-# LINE 2974 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#86>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_getInfo2 :: ( BtPoint2PointConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btPoint2PointConstraint_getInfo2 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btPoint2PointConstraint_getInfo2'_ a1' a2' >>
  return ()

{-# LINE 2980 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_setPivotA :: ( BtPoint2PointConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ pivotA
 -> IO ((Vec3))
btPoint2PointConstraint_setPivotA a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btPoint2PointConstraint_setPivotA'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2986 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_setPivotA' :: ( BtPoint2PointConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btPoint2PointConstraint_setPivotA' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btPoint2PointConstraint_setPivotA''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2992 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_setPivotB :: ( BtPoint2PointConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ pivotB
 -> IO ((Vec3))
btPoint2PointConstraint_setPivotB a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btPoint2PointConstraint_setPivotB'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2998 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_setPivotB' :: ( BtPoint2PointConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btPoint2PointConstraint_setPivotB' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btPoint2PointConstraint_setPivotB''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3004 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_pivotInA_set :: ( BtPoint2PointConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btPoint2PointConstraint_m_pivotInA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btPoint2PointConstraint_m_pivotInA_set'_ a1' a2' >>
  return ()

{-# LINE 3008 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_pivotInA_get :: ( BtPoint2PointConstraintClass bc ) => (bc) -> IO ((Vec3))
btPoint2PointConstraint_m_pivotInA_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btPoint2PointConstraint_m_pivotInA_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3012 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_pivotInB_set :: ( BtPoint2PointConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btPoint2PointConstraint_m_pivotInB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btPoint2PointConstraint_m_pivotInB_set'_ a1' a2' >>
  return ()

{-# LINE 3016 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_pivotInB_get :: ( BtPoint2PointConstraintClass bc ) => (bc) -> IO ((Vec3))
btPoint2PointConstraint_m_pivotInB_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btPoint2PointConstraint_m_pivotInB_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3020 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#64>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_flags_set :: ( BtPoint2PointConstraintClass bc ) => (bc) -> (Int) -> IO ()
btPoint2PointConstraint_m_flags_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btPoint2PointConstraint_m_flags_set'_ a1' a2' >>
  return ()

{-# LINE 3024 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#64>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_flags_get :: ( BtPoint2PointConstraintClass bc ) => (bc) -> IO ((Int))
btPoint2PointConstraint_m_flags_get a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraint_m_flags_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3028 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#65>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_erp_set :: ( BtPoint2PointConstraintClass bc ) => (bc) -> (Float) -> IO ()
btPoint2PointConstraint_m_erp_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btPoint2PointConstraint_m_erp_set'_ a1' a2' >>
  return ()

{-# LINE 3032 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#65>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_erp_get :: ( BtPoint2PointConstraintClass bc ) => (bc) -> IO ((Float))
btPoint2PointConstraint_m_erp_get a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraint_m_erp_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3036 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_cfm_set :: ( BtPoint2PointConstraintClass bc ) => (bc) -> (Float) -> IO ()
btPoint2PointConstraint_m_cfm_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btPoint2PointConstraint_m_cfm_set'_ a1' a2' >>
  return ()

{-# LINE 3040 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_cfm_get :: ( BtPoint2PointConstraintClass bc ) => (bc) -> IO ((Float))
btPoint2PointConstraint_m_cfm_get a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraint_m_cfm_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3044 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#71>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_useSolveConstraintObsolete_set :: ( BtPoint2PointConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btPoint2PointConstraint_m_useSolveConstraintObsolete_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btPoint2PointConstraint_m_useSolveConstraintObsolete_set'_ a1' a2' >>
  return ()

{-# LINE 3048 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#71>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_useSolveConstraintObsolete_get :: ( BtPoint2PointConstraintClass bc ) => (bc) -> IO ((Bool))
btPoint2PointConstraint_m_useSolveConstraintObsolete_get a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraint_m_useSolveConstraintObsolete_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 3052 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#73>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_setting_set :: ( BtPoint2PointConstraintClass bc , BtConstraintSettingClass a ) => (bc) -> (a) -> IO ()
btPoint2PointConstraint_m_setting_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btPoint2PointConstraint_m_setting_set'_ a1' a2' >>
  return ()

{-# LINE 3056 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#73>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraint_m_setting_get :: ( BtPoint2PointConstraintClass bc ) => (bc) -> IO ((BtConstraintSetting))
btPoint2PointConstraint_m_setting_get a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraint_m_setting_get'_ a1' >>= \res ->
  mkBtConstraintSetting res >>= \res' ->
  return (res')

{-# LINE 3060 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btPoint2PointConstraintDoubleData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintDoubleData :: IO ((BtPoint2PointConstraintDoubleData))
btPoint2PointConstraintDoubleData =
  btPoint2PointConstraintDoubleData'_ >>= \res ->
  mkBtPoint2PointConstraintDoubleData res >>= \res' ->
  return (res')

{-# LINE 3065 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btPoint2PointConstraintDoubleData_free :: ( BtPoint2PointConstraintDoubleDataClass bc ) => (bc) -> IO ()
btPoint2PointConstraintDoubleData_free a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraintDoubleData_free'_ a1' >>
  return ()

{-# LINE 3066 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#137>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintDoubleData_m_typeConstraintData_set :: ( BtPoint2PointConstraintDoubleDataClass bc , BtTypedConstraintDataClass a ) => (bc) -> (a) -> IO ()
btPoint2PointConstraintDoubleData_m_typeConstraintData_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btPoint2PointConstraintDoubleData_m_typeConstraintData_set'_ a1' a2' >>
  return ()

{-# LINE 3070 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#137>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintDoubleData_m_typeConstraintData_get :: ( BtPoint2PointConstraintDoubleDataClass bc ) => (bc) -> IO ((BtTypedConstraintData))
btPoint2PointConstraintDoubleData_m_typeConstraintData_get a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraintDoubleData_m_typeConstraintData_get'_ a1' >>= \res ->
  mkBtTypedConstraintData res >>= \res' ->
  return (res')

{-# LINE 3074 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#138>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintDoubleData_m_pivotInA_set :: ( BtPoint2PointConstraintDoubleDataClass bc , BtVector3DoubleDataClass a ) => (bc) -> (a) -> IO ()
btPoint2PointConstraintDoubleData_m_pivotInA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btPoint2PointConstraintDoubleData_m_pivotInA_set'_ a1' a2' >>
  return ()

{-# LINE 3078 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#138>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintDoubleData_m_pivotInA_get :: ( BtPoint2PointConstraintDoubleDataClass bc ) => (bc) -> IO ((BtVector3DoubleData))
btPoint2PointConstraintDoubleData_m_pivotInA_get a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraintDoubleData_m_pivotInA_get'_ a1' >>= \res ->
  mkBtVector3DoubleData res >>= \res' ->
  return (res')

{-# LINE 3082 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#139>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintDoubleData_m_pivotInB_set :: ( BtPoint2PointConstraintDoubleDataClass bc , BtVector3DoubleDataClass a ) => (bc) -> (a) -> IO ()
btPoint2PointConstraintDoubleData_m_pivotInB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btPoint2PointConstraintDoubleData_m_pivotInB_set'_ a1' a2' >>
  return ()

{-# LINE 3086 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#139>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintDoubleData_m_pivotInB_get :: ( BtPoint2PointConstraintDoubleDataClass bc ) => (bc) -> IO ((BtVector3DoubleData))
btPoint2PointConstraintDoubleData_m_pivotInB_get a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraintDoubleData_m_pivotInB_get'_ a1' >>= \res ->
  mkBtVector3DoubleData res >>= \res' ->
  return (res')

{-# LINE 3090 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btPoint2PointConstraintFloatData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#128>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintFloatData :: IO ((BtPoint2PointConstraintFloatData))
btPoint2PointConstraintFloatData =
  btPoint2PointConstraintFloatData'_ >>= \res ->
  mkBtPoint2PointConstraintFloatData res >>= \res' ->
  return (res')

{-# LINE 3095 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btPoint2PointConstraintFloatData_free :: ( BtPoint2PointConstraintFloatDataClass bc ) => (bc) -> IO ()
btPoint2PointConstraintFloatData_free a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraintFloatData_free'_ a1' >>
  return ()

{-# LINE 3096 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#129>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintFloatData_m_typeConstraintData_set :: ( BtPoint2PointConstraintFloatDataClass bc , BtTypedConstraintDataClass a ) => (bc) -> (a) -> IO ()
btPoint2PointConstraintFloatData_m_typeConstraintData_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btPoint2PointConstraintFloatData_m_typeConstraintData_set'_ a1' a2' >>
  return ()

{-# LINE 3100 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#129>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintFloatData_m_typeConstraintData_get :: ( BtPoint2PointConstraintFloatDataClass bc ) => (bc) -> IO ((BtTypedConstraintData))
btPoint2PointConstraintFloatData_m_typeConstraintData_get a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraintFloatData_m_typeConstraintData_get'_ a1' >>= \res ->
  mkBtTypedConstraintData res >>= \res' ->
  return (res')

{-# LINE 3104 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#130>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintFloatData_m_pivotInA_set :: ( BtPoint2PointConstraintFloatDataClass bc , BtVector3FloatDataClass a ) => (bc) -> (a) -> IO ()
btPoint2PointConstraintFloatData_m_pivotInA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btPoint2PointConstraintFloatData_m_pivotInA_set'_ a1' a2' >>
  return ()

{-# LINE 3108 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#130>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintFloatData_m_pivotInA_get :: ( BtPoint2PointConstraintFloatDataClass bc ) => (bc) -> IO ((BtVector3FloatData))
btPoint2PointConstraintFloatData_m_pivotInA_get a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraintFloatData_m_pivotInA_get'_ a1' >>= \res ->
  mkBtVector3FloatData res >>= \res' ->
  return (res')

{-# LINE 3112 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#131>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintFloatData_m_pivotInB_set :: ( BtPoint2PointConstraintFloatDataClass bc , BtVector3FloatDataClass a ) => (bc) -> (a) -> IO ()
btPoint2PointConstraintFloatData_m_pivotInB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btPoint2PointConstraintFloatData_m_pivotInB_set'_ a1' a2' >>
  return ()

{-# LINE 3116 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.h?r=2223#131>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btPoint2PointConstraint.cpp?r=2223>
-}
btPoint2PointConstraintFloatData_m_pivotInB_get :: ( BtPoint2PointConstraintFloatDataClass bc ) => (bc) -> IO ((BtVector3FloatData))
btPoint2PointConstraintFloatData_m_pivotInB_get a1 =
  withBt a1 $ \a1' -> 
  btPoint2PointConstraintFloatData_m_pivotInB_get'_ a1' >>= \res ->
  mkBtVector3FloatData res >>= \res' ->
  return (res')

{-# LINE 3120 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btRotationalLimitMotor
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor :: IO ((BtRotationalLimitMotor))
btRotationalLimitMotor =
  btRotationalLimitMotor'_ >>= \res ->
  mkBtRotationalLimitMotor res >>= \res' ->
  return (res')

{-# LINE 3125 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btRotationalLimitMotor_free :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ()
btRotationalLimitMotor_free a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_free'_ a1' >>
  return ()

{-# LINE 3126 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#123>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_testLimitValue :: ( BtRotationalLimitMotorClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ test_value
 -> IO ((Int))
btRotationalLimitMotor_testLimitValue a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_testLimitValue'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3132 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#126>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_solveAngularLimits :: ( BtRotationalLimitMotorClass bc , BtRigidBodyClass p3 , BtRigidBodyClass p4 ) => (bc) -- ^ 
 -> (Float) -- ^ timeStep
 -> (Vec3) -- ^ axis
 -> (Float) -- ^ jacDiagABInv
 -> (p3) -- ^ body0
 -> (p4) -- ^ body1
 -> IO ((Float), (Vec3))
btRotationalLimitMotor_solveAngularLimits a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  withVec3 a3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  withBt a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  btRotationalLimitMotor_solveAngularLimits'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  let {res' = realToFrac res} in
  peekVec3  a3'>>= \a3'' -> 
  return (res', a3'')

{-# LINE 3142 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#126>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_solveAngularLimits' :: ( BtRotationalLimitMotorClass bc , BtRigidBodyClass p3 , BtRigidBodyClass p4 ) => (bc) -- ^ 
 -> (Float) -- ^ timeStep
 -> (Float) -- ^ jacDiagABInv
 -> (p3) -- ^ body0
 -> (p4) -- ^ body1
 -> IO ((Float), (Vec3))
btRotationalLimitMotor_solveAngularLimits' a1 a2 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  allocaVec3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  withBt a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  btRotationalLimitMotor_solveAngularLimits''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  let {res' = realToFrac res} in
  peekVec3  a3'>>= \a3'' -> 
  return (res', a3'')

{-# LINE 3152 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_needApplyTorques :: ( BtRotationalLimitMotorClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btRotationalLimitMotor_needApplyTorques a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_needApplyTorques'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 3157 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#106>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_isLimited :: ( BtRotationalLimitMotorClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btRotationalLimitMotor_isLimited a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_isLimited'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 3162 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#65>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_accumulatedImpulse_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_accumulatedImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_accumulatedImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 3166 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#65>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_accumulatedImpulse_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_accumulatedImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_accumulatedImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3170 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#55>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_bounce_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_bounce_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_bounce_set'_ a1' a2' >>
  return ()

{-# LINE 3174 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#55>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_bounce_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_bounce_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_bounce_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3178 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#64>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_currentLimit_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Int) -> IO ()
btRotationalLimitMotor_m_currentLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btRotationalLimitMotor_m_currentLimit_set'_ a1' a2' >>
  return ()

{-# LINE 3182 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#64>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_currentLimit_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Int))
btRotationalLimitMotor_m_currentLimit_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_currentLimit_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3186 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_currentLimitError_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_currentLimitError_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_currentLimitError_set'_ a1' a2' >>
  return ()

{-# LINE 3190 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_currentLimitError_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_currentLimitError_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_currentLimitError_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3194 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#63>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_currentPosition_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_currentPosition_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_currentPosition_set'_ a1' a2' >>
  return ()

{-# LINE 3198 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#63>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_currentPosition_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_currentPosition_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_currentPosition_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3202 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_damping_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_damping_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_damping_set'_ a1' a2' >>
  return ()

{-# LINE 3206 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_damping_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_damping_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_damping_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3210 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#56>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_enableMotor_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Bool) -> IO ()
btRotationalLimitMotor_m_enableMotor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btRotationalLimitMotor_m_enableMotor_set'_ a1' a2' >>
  return ()

{-# LINE 3214 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#56>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_enableMotor_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Bool))
btRotationalLimitMotor_m_enableMotor_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_enableMotor_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 3218 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#46>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_hiLimit_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_hiLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_hiLimit_set'_ a1' a2' >>
  return ()

{-# LINE 3222 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#46>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_hiLimit_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_hiLimit_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_hiLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3226 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_limitSoftness_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_limitSoftness_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_limitSoftness_set'_ a1' a2' >>
  return ()

{-# LINE 3230 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_limitSoftness_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_limitSoftness_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_limitSoftness_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3234 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#45>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_loLimit_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_loLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_loLimit_set'_ a1' a2' >>
  return ()

{-# LINE 3238 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#45>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_loLimit_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_loLimit_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_loLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3242 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#49>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_maxLimitForce_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_maxLimitForce_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_maxLimitForce_set'_ a1' a2' >>
  return ()

{-# LINE 3246 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#49>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_maxLimitForce_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_maxLimitForce_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_maxLimitForce_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3250 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_maxMotorForce_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_maxMotorForce_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_maxMotorForce_set'_ a1' a2' >>
  return ()

{-# LINE 3254 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_maxMotorForce_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_maxMotorForce_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_maxMotorForce_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3258 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_normalCFM_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_normalCFM_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_normalCFM_set'_ a1' a2' >>
  return ()

{-# LINE 3262 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_normalCFM_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_normalCFM_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_normalCFM_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3266 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_stopCFM_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_stopCFM_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_stopCFM_set'_ a1' a2' >>
  return ()

{-# LINE 3270 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_stopCFM_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_stopCFM_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_stopCFM_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3274 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#53>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_stopERP_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_stopERP_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_stopERP_set'_ a1' a2' >>
  return ()

{-# LINE 3278 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#53>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_stopERP_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_stopERP_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_stopERP_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3282 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#47>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_targetVelocity_set :: ( BtRotationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btRotationalLimitMotor_m_targetVelocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btRotationalLimitMotor_m_targetVelocity_set'_ a1' a2' >>
  return ()

{-# LINE 3286 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#47>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btRotationalLimitMotor_m_targetVelocity_get :: ( BtRotationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btRotationalLimitMotor_m_targetVelocity_get a1 =
  withBt a1 $ \a1' -> 
  btRotationalLimitMotor_m_targetVelocity_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3290 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btSequentialImpulseConstraintSolver
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver :: IO ((BtSequentialImpulseConstraintSolver))
btSequentialImpulseConstraintSolver =
  btSequentialImpulseConstraintSolver'_ >>= \res ->
  mkBtSequentialImpulseConstraintSolver res >>= \res' ->
  return (res')

{-# LINE 3295 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btSequentialImpulseConstraintSolver_free :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -> IO ()
btSequentialImpulseConstraintSolver_free a1 =
  withBt a1 $ \a1' -> 
  btSequentialImpulseConstraintSolver_free'_ a1' >>
  return ()

{-# LINE 3296 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#59>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_convertContact :: ( BtSequentialImpulseConstraintSolverClass bc , BtPersistentManifoldClass p0 , BtContactSolverInfoClass p1 ) => (bc) -- ^ 
 -> (p0) -- ^ manifold
 -> (p1) -- ^ infoGlobal
 -> IO ()
btSequentialImpulseConstraintSolver_convertContact a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btSequentialImpulseConstraintSolver_convertContact'_ a1' a2' a3' >>
  return ()

{-# LINE 3303 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_setRandSeed :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -- ^ 
 -> (Word64) -- ^ seed
 -> IO ()
btSequentialImpulseConstraintSolver_setRandSeed a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSequentialImpulseConstraintSolver_setRandSeed'_ a1' a2' >>
  return ()

{-# LINE 3309 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#84>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_getFixedBody :: ( ) => IO ((BtRigidBody))
btSequentialImpulseConstraintSolver_getFixedBody =
  btSequentialImpulseConstraintSolver_getFixedBody'_ >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 3313 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_resolveSingleConstraintRowLowerLimitSIMD :: ( BtSequentialImpulseConstraintSolverClass bc , BtRigidBodyClass p0 , BtRigidBodyClass p1 , BtSolverConstraintClass p2 ) => (bc) -- ^ 
 -> (p0) -- ^ body1
 -> (p1) -- ^ body2
 -> (p2) -- ^ contactConstraint
 -> IO ()
btSequentialImpulseConstraintSolver_resolveSingleConstraintRowLowerLimitSIMD a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSequentialImpulseConstraintSolver_resolveSingleConstraintRowLowerLimitSIMD'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 3321 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#107>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_btRand2 :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -- ^ 
 -> IO ((Word64))
btSequentialImpulseConstraintSolver_btRand2 a1 =
  withBt a1 $ \a1' -> 
  btSequentialImpulseConstraintSolver_btRand2'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3326 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_setFrictionConstraintImpulse :: ( BtSequentialImpulseConstraintSolverClass bc , BtSolverConstraintClass p0 , BtRigidBodyClass p1 , BtRigidBodyClass p2 , BtManifoldPointClass p3 , BtContactSolverInfoClass p4 ) => (bc) -- ^ 
 -> (p0) -- ^ solverConstraint
 -> (p1) -- ^ rb0
 -> (p2) -- ^ rb1
 -> (p3) -- ^ cp
 -> (p4) -- ^ infoGlobal
 -> IO ()
btSequentialImpulseConstraintSolver_setFrictionConstraintImpulse a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  btSequentialImpulseConstraintSolver_setFrictionConstraintImpulse'_ a1' a2' a3' a4' a5' a6' >>
  return ()

{-# LINE 3336 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#73>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_getOrInitSolverBody :: ( BtSequentialImpulseConstraintSolverClass bc , BtCollisionObjectClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ body
 -> IO ((Int))
btSequentialImpulseConstraintSolver_getOrInitSolverBody a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSequentialImpulseConstraintSolver_getOrInitSolverBody'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3342 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#77>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_resolveSingleConstraintRowGenericSIMD :: ( BtSequentialImpulseConstraintSolverClass bc , BtRigidBodyClass p0 , BtRigidBodyClass p1 , BtSolverConstraintClass p2 ) => (bc) -- ^ 
 -> (p0) -- ^ body1
 -> (p1) -- ^ body2
 -> (p2) -- ^ contactConstraint
 -> IO ()
btSequentialImpulseConstraintSolver_resolveSingleConstraintRowGenericSIMD a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSequentialImpulseConstraintSolver_resolveSingleConstraintRowGenericSIMD'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 3350 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#109>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_btRandInt2 :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ n
 -> IO ((Int))
btSequentialImpulseConstraintSolver_btRandInt2 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSequentialImpulseConstraintSolver_btRandInt2'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3356 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#79>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_resolveSingleConstraintRowLowerLimit :: ( BtSequentialImpulseConstraintSolverClass bc , BtRigidBodyClass p0 , BtRigidBodyClass p1 , BtSolverConstraintClass p2 ) => (bc) -- ^ 
 -> (p0) -- ^ body1
 -> (p1) -- ^ body2
 -> (p2) -- ^ contactConstraint
 -> IO ()
btSequentialImpulseConstraintSolver_resolveSingleConstraintRowLowerLimit a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSequentialImpulseConstraintSolver_resolveSingleConstraintRowLowerLimit'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 3364 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#105>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_reset :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -- ^ 
 -> IO ()
btSequentialImpulseConstraintSolver_reset a1 =
  withBt a1 $ \a1' -> 
  btSequentialImpulseConstraintSolver_reset'_ a1' >>
  return ()

{-# LINE 3369 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#70>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_resolveSplitPenetrationImpulseCacheFriendly :: ( BtSequentialImpulseConstraintSolverClass bc , BtRigidBodyClass p0 , BtRigidBodyClass p1 , BtSolverConstraintClass p2 ) => (bc) -- ^ 
 -> (p0) -- ^ body1
 -> (p1) -- ^ body2
 -> (p2) -- ^ contactConstraint
 -> IO ()
btSequentialImpulseConstraintSolver_resolveSplitPenetrationImpulseCacheFriendly a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSequentialImpulseConstraintSolver_resolveSplitPenetrationImpulseCacheFriendly'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 3377 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_setupFrictionConstraint :: ( BtSequentialImpulseConstraintSolverClass bc , BtSolverConstraintClass p0 , BtRigidBodyClass p2 , BtRigidBodyClass p3 , BtManifoldPointClass p4 , BtCollisionObjectClass p7 , BtCollisionObjectClass p8 ) => (bc) -- ^ 
 -> (p0) -- ^ solverConstraint
 -> (Vec3) -- ^ normalAxis
 -> (p2) -- ^ solverBodyA
 -> (p3) -- ^ solverBodyIdB
 -> (p4) -- ^ cp
 -> (Vec3) -- ^ rel_pos1
 -> (Vec3) -- ^ rel_pos2
 -> (p7) -- ^ colObj0
 -> (p8) -- ^ colObj1
 -> (Float) -- ^ relaxation
 -> (Float) -- ^ desiredVelocity
 -> (Float) -- ^ cfmSlip
 -> IO ((Vec3), (Vec3), (Vec3))
btSequentialImpulseConstraintSolver_setupFrictionConstraint a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  withVec3 a7 $ \a7' -> 
  withVec3 a8 $ \a8' -> 
  withBt a9 $ \a9' -> 
  withBt a10 $ \a10' -> 
  let {a11' = realToFrac a11} in 
  let {a12' = realToFrac a12} in 
  let {a13' = realToFrac a13} in 
  btSequentialImpulseConstraintSolver_setupFrictionConstraint'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' a13' >>
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  return (a3'', a7'', a8'')

{-# LINE 3394 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_setupFrictionConstraint' :: ( BtSequentialImpulseConstraintSolverClass bc , BtSolverConstraintClass p0 , BtRigidBodyClass p2 , BtRigidBodyClass p3 , BtManifoldPointClass p4 , BtCollisionObjectClass p7 , BtCollisionObjectClass p8 ) => (bc) -- ^ 
 -> (p0) -- ^ solverConstraint
 -> (p2) -- ^ solverBodyA
 -> (p3) -- ^ solverBodyIdB
 -> (p4) -- ^ cp
 -> (p7) -- ^ colObj0
 -> (p8) -- ^ colObj1
 -> (Float) -- ^ relaxation
 -> (Float) -- ^ desiredVelocity
 -> (Float) -- ^ cfmSlip
 -> IO ((Vec3), (Vec3), (Vec3))
btSequentialImpulseConstraintSolver_setupFrictionConstraint' a1 a2 a4 a5 a6 a9 a10 a11 a12 a13 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  allocaVec3 $ \a7' -> 
  allocaVec3 $ \a8' -> 
  withBt a9 $ \a9' -> 
  withBt a10 $ \a10' -> 
  let {a11' = realToFrac a11} in 
  let {a12' = realToFrac a12} in 
  let {a13' = realToFrac a13} in 
  btSequentialImpulseConstraintSolver_setupFrictionConstraint''_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' a13' >>
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  return (a3'', a7'', a8'')

{-# LINE 3411 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#115>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_getRandSeed :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -- ^ 
 -> IO ((Word64))
btSequentialImpulseConstraintSolver_getRandSeed a1 =
  withBt a1 $ \a1' -> 
  btSequentialImpulseConstraintSolver_getRandSeed'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3416 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#44>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_addFrictionConstraint :: ( BtSequentialImpulseConstraintSolverClass bc , BtRigidBodyClass p1 , BtRigidBodyClass p2 , BtManifoldPointClass p4 , BtCollisionObjectClass p7 , BtCollisionObjectClass p8 ) => (bc) -- ^ 
 -> (Vec3) -- ^ normalAxis
 -> (p1) -- ^ solverBodyA
 -> (p2) -- ^ solverBodyB
 -> (Int) -- ^ frictionIndex
 -> (p4) -- ^ cp
 -> (Vec3) -- ^ rel_pos1
 -> (Vec3) -- ^ rel_pos2
 -> (p7) -- ^ colObj0
 -> (p8) -- ^ colObj1
 -> (Float) -- ^ relaxation
 -> (Float) -- ^ desiredVelocity
 -> (Float) -- ^ cfmSlip
 -> IO ((BtSolverConstraint), (Vec3), (Vec3), (Vec3))
btSequentialImpulseConstraintSolver_addFrictionConstraint a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  let {a5' = fromIntegral a5} in 
  withBt a6 $ \a6' -> 
  withVec3 a7 $ \a7' -> 
  withVec3 a8 $ \a8' -> 
  withBt a9 $ \a9' -> 
  withBt a10 $ \a10' -> 
  let {a11' = realToFrac a11} in 
  let {a12' = realToFrac a12} in 
  let {a13' = realToFrac a13} in 
  btSequentialImpulseConstraintSolver_addFrictionConstraint'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' a13' >>= \res ->
  mkBtSolverConstraint res >>= \res' ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  return (res', a2'', a7'', a8'')

{-# LINE 3433 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#44>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_addFrictionConstraint' :: ( BtSequentialImpulseConstraintSolverClass bc , BtRigidBodyClass p1 , BtRigidBodyClass p2 , BtManifoldPointClass p4 , BtCollisionObjectClass p7 , BtCollisionObjectClass p8 ) => (bc) -- ^ 
 -> (p1) -- ^ solverBodyA
 -> (p2) -- ^ solverBodyB
 -> (Int) -- ^ frictionIndex
 -> (p4) -- ^ cp
 -> (p7) -- ^ colObj0
 -> (p8) -- ^ colObj1
 -> (Float) -- ^ relaxation
 -> (Float) -- ^ desiredVelocity
 -> (Float) -- ^ cfmSlip
 -> IO ((BtSolverConstraint), (Vec3), (Vec3), (Vec3))
btSequentialImpulseConstraintSolver_addFrictionConstraint' a1 a3 a4 a5 a6 a9 a10 a11 a12 a13 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  let {a5' = fromIntegral a5} in 
  withBt a6 $ \a6' -> 
  allocaVec3 $ \a7' -> 
  allocaVec3 $ \a8' -> 
  withBt a9 $ \a9' -> 
  withBt a10 $ \a10' -> 
  let {a11' = realToFrac a11} in 
  let {a12' = realToFrac a12} in 
  let {a13' = realToFrac a13} in 
  btSequentialImpulseConstraintSolver_addFrictionConstraint''_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' a12' a13' >>= \res ->
  mkBtSolverConstraint res >>= \res' ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  return (res', a2'', a7'', a8'')

{-# LINE 3450 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_restitutionCurve :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ rel_vel
 -> (Float) -- ^ restitution
 -> IO ((Float))
btSequentialImpulseConstraintSolver_restitutionCurve a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btSequentialImpulseConstraintSolver_restitutionCurve'_ a1' a2' a3' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3457 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#75>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_resolveSingleConstraintRowGeneric :: ( BtSequentialImpulseConstraintSolverClass bc , BtRigidBodyClass p0 , BtRigidBodyClass p1 , BtSolverConstraintClass p2 ) => (bc) -- ^ 
 -> (p0) -- ^ body1
 -> (p1) -- ^ body2
 -> (p2) -- ^ contactConstraint
 -> IO ()
btSequentialImpulseConstraintSolver_resolveSingleConstraintRowGeneric a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSequentialImpulseConstraintSolver_resolveSingleConstraintRowGeneric'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 3465 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#65>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_resolveSplitPenetrationSIMD :: ( BtSequentialImpulseConstraintSolverClass bc , BtRigidBodyClass p0 , BtRigidBodyClass p1 , BtSolverConstraintClass p2 ) => (bc) -- ^ 
 -> (p0) -- ^ body1
 -> (p1) -- ^ body2
 -> (p2) -- ^ contactConstraint
 -> IO ()
btSequentialImpulseConstraintSolver_resolveSplitPenetrationSIMD a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSequentialImpulseConstraintSolver_resolveSplitPenetrationSIMD'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 3473 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#32>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_tmpSolverContactConstraintPool_set :: ( BtSequentialImpulseConstraintSolverClass bc , BtAlignedObjectArray_btSolverConstraint_Class a ) => (bc) -> (a) -> IO ()
btSequentialImpulseConstraintSolver_m_tmpSolverContactConstraintPool_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSequentialImpulseConstraintSolver_m_tmpSolverContactConstraintPool_set'_ a1' a2' >>
  return ()

{-# LINE 3477 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#32>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_tmpSolverContactConstraintPool_get :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSolverConstraint_))
btSequentialImpulseConstraintSolver_m_tmpSolverContactConstraintPool_get a1 =
  withBt a1 $ \a1' -> 
  btSequentialImpulseConstraintSolver_m_tmpSolverContactConstraintPool_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSolverConstraint_ res >>= \res' ->
  return (res')

{-# LINE 3481 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#33>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_tmpSolverNonContactConstraintPool_set :: ( BtSequentialImpulseConstraintSolverClass bc , BtAlignedObjectArray_btSolverConstraint_Class a ) => (bc) -> (a) -> IO ()
btSequentialImpulseConstraintSolver_m_tmpSolverNonContactConstraintPool_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSequentialImpulseConstraintSolver_m_tmpSolverNonContactConstraintPool_set'_ a1' a2' >>
  return ()

{-# LINE 3485 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#33>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_tmpSolverNonContactConstraintPool_get :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSolverConstraint_))
btSequentialImpulseConstraintSolver_m_tmpSolverNonContactConstraintPool_get a1 =
  withBt a1 $ \a1' -> 
  btSequentialImpulseConstraintSolver_m_tmpSolverNonContactConstraintPool_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSolverConstraint_ res >>= \res' ->
  return (res')

{-# LINE 3489 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#34>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_tmpSolverContactFrictionConstraintPool_set :: ( BtSequentialImpulseConstraintSolverClass bc , BtAlignedObjectArray_btSolverConstraint_Class a ) => (bc) -> (a) -> IO ()
btSequentialImpulseConstraintSolver_m_tmpSolverContactFrictionConstraintPool_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSequentialImpulseConstraintSolver_m_tmpSolverContactFrictionConstraintPool_set'_ a1' a2' >>
  return ()

{-# LINE 3493 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#34>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_tmpSolverContactFrictionConstraintPool_get :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSolverConstraint_))
btSequentialImpulseConstraintSolver_m_tmpSolverContactFrictionConstraintPool_get a1 =
  withBt a1 $ \a1' -> 
  btSequentialImpulseConstraintSolver_m_tmpSolverContactFrictionConstraintPool_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSolverConstraint_ res >>= \res' ->
  return (res')

{-# LINE 3497 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#35>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_orderTmpConstraintPool_set :: ( BtSequentialImpulseConstraintSolverClass bc , BtAlignedObjectArray_int_Class a ) => (bc) -> (a) -> IO ()
btSequentialImpulseConstraintSolver_m_orderTmpConstraintPool_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSequentialImpulseConstraintSolver_m_orderTmpConstraintPool_set'_ a1' a2' >>
  return ()

{-# LINE 3501 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#35>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_orderTmpConstraintPool_get :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -> IO ((BtAlignedObjectArray_int_))
btSequentialImpulseConstraintSolver_m_orderTmpConstraintPool_get a1 =
  withBt a1 $ \a1' -> 
  btSequentialImpulseConstraintSolver_m_orderTmpConstraintPool_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')

{-# LINE 3505 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#36>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_orderFrictionConstraintPool_set :: ( BtSequentialImpulseConstraintSolverClass bc , BtAlignedObjectArray_int_Class a ) => (bc) -> (a) -> IO ()
btSequentialImpulseConstraintSolver_m_orderFrictionConstraintPool_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSequentialImpulseConstraintSolver_m_orderFrictionConstraintPool_set'_ a1' a2' >>
  return ()

{-# LINE 3509 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#36>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_orderFrictionConstraintPool_get :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -> IO ((BtAlignedObjectArray_int_))
btSequentialImpulseConstraintSolver_m_orderFrictionConstraintPool_get a1 =
  withBt a1 $ \a1' -> 
  btSequentialImpulseConstraintSolver_m_orderFrictionConstraintPool_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')

{-# LINE 3513 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#37>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_tmpConstraintSizesPool_set :: ( BtSequentialImpulseConstraintSolverClass bc , BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class a ) => (bc) -> (a) -> IO ()
btSequentialImpulseConstraintSolver_m_tmpConstraintSizesPool_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSequentialImpulseConstraintSolver_m_tmpConstraintSizesPool_set'_ a1' a2' >>
  return ()

{-# LINE 3517 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#37>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_tmpConstraintSizesPool_get :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_))
btSequentialImpulseConstraintSolver_m_tmpConstraintSizesPool_get a1 =
  withBt a1 $ \a1' -> 
  btSequentialImpulseConstraintSolver_m_tmpConstraintSizesPool_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_ res >>= \res' ->
  return (res')

{-# LINE 3521 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_btSeed2_set :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -> (Word64) -> IO ()
btSequentialImpulseConstraintSolver_m_btSeed2_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSequentialImpulseConstraintSolver_m_btSeed2_set'_ a1' a2' >>
  return ()

{-# LINE 3525 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSequentialImpulseConstraintSolver.cpp?r=2223>
-}
btSequentialImpulseConstraintSolver_m_btSeed2_get :: ( BtSequentialImpulseConstraintSolverClass bc ) => (bc) -> IO ((Word64))
btSequentialImpulseConstraintSolver_m_btSeed2_get a1 =
  withBt a1 $ \a1' -> 
  btSequentialImpulseConstraintSolver_m_btSeed2_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3529 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btSliderConstraint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#159>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint0 :: ( BtRigidBodyClass p0 , BtRigidBodyClass p1 ) => (p0) -> (p1) -> (Transform) -> (Transform) -> (Bool) -> IO ((BtSliderConstraint))
btSliderConstraint0 a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  let {a5' = C2HSImp.fromBool a5} in 
  btSliderConstraint0'_ a1' a2' a3' a4' a5' >>= \res ->
  mkBtSliderConstraint res >>= \res' ->
  return (res')

{-# LINE 3534 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#160>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint1 :: ( BtRigidBodyClass p0 ) => (p0) -> (Transform) -> (Bool) -> IO ((BtSliderConstraint))
btSliderConstraint1 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  let {a3' = C2HSImp.fromBool a3} in 
  btSliderConstraint1'_ a1' a2' a3' >>= \res ->
  mkBtSliderConstraint res >>= \res' ->
  return (res')

{-# LINE 3538 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btSliderConstraint_free :: ( BtSliderConstraintClass bc ) => (bc) -> IO ()
btSliderConstraint_free a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_free'_ a1' >>
  return ()

{-# LINE 3539 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#175>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getRigidBodyB :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btSliderConstraint_getRigidBodyB a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getRigidBodyB'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 3544 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#174>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getRigidBodyA :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btSliderConstraint_getRigidBodyA a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getRigidBodyA'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 3549 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#249>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getAngDepth :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getAngDepth a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getAngDepth'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3554 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#236>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getTargetAngMotorVelocity :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getTargetAngMotorVelocity a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getTargetAngMotorVelocity'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3559 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#241>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getAngularPos :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getAngularPos a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getAngularPos'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3564 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#219>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setRestitutionLimAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ restitutionLimAng
 -> IO ()
btSliderConstraint_setRestitutionLimAng a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setRestitutionLimAng'_ a1' a2' >>
  return ()

{-# LINE 3570 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#274>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getParam :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ num
 -> (Int) -- ^ axis
 -> IO ((Float))
btSliderConstraint_getParam a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btSliderConstraint_getParam'_ a1' a2' a3' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3577 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#164>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getInfo1 :: ( BtSliderConstraintClass bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btSliderConstraint_getInfo1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSliderConstraint_getInfo1'_ a1' a2' >>
  return ()

{-# LINE 3583 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#168>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getInfo2 :: ( BtSliderConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btSliderConstraint_getInfo2 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSliderConstraint_getInfo2'_ a1' a2' >>
  return ()

{-# LINE 3589 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getPoweredLinMotor :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btSliderConstraint_getPoweredLinMotor a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getPoweredLinMotor'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 3594 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#259>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setUseFrameOffset :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ frameOffsetOnOff
 -> IO ()
btSliderConstraint_setUseFrameOffset a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSliderConstraint_setUseFrameOffset'_ a1' a2' >>
  return ()

{-# LINE 3600 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#215>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setSoftnessLimLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ softnessLimLin
 -> IO ()
btSliderConstraint_setSoftnessLimLin a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setSoftnessLimLin'_ a1' a2' >>
  return ()

{-# LINE 3606 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#255>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getAncorInA :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSliderConstraint_getAncorInA a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSliderConstraint_getAncorInA'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3612 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#256>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getAncorInB :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSliderConstraint_getAncorInB a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSliderConstraint_getAncorInB'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3618 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#214>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setDampingDirAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dampingDirAng
 -> IO ()
btSliderConstraint_setDampingDirAng a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setDampingDirAng'_ a1' a2' >>
  return ()

{-# LINE 3624 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getSolveLinLimit :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btSliderConstraint_getSolveLinLimit a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getSolveLinLimit'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 3629 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#258>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getUseFrameOffset :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btSliderConstraint_getUseFrameOffset a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getUseFrameOffset'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 3634 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#238>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getMaxAngMotorForce :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getMaxAngMotorForce a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getMaxAngMotorForce'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3639 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#213>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setRestitutionDirAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ restitutionDirAng
 -> IO ()
btSliderConstraint_setRestitutionDirAng a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setRestitutionDirAng'_ a1' a2' >>
  return ()

{-# LINE 3645 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#232>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getMaxLinMotorForce :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getMaxLinMotorForce a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getMaxLinMotorForce'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3650 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#223>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setDampingOrthoLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dampingOrthoLin
 -> IO ()
btSliderConstraint_setDampingOrthoLin a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setDampingOrthoLin'_ a1' a2' >>
  return ()

{-# LINE 3656 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#248>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getSolveAngLimit :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btSliderConstraint_getSolveAngLimit a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getSolveAngLimit'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 3661 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#233>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setPoweredAngMotor :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ onOff
 -> IO ()
btSliderConstraint_setPoweredAngMotor a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSliderConstraint_setPoweredAngMotor'_ a1' a2' >>
  return ()

{-# LINE 3667 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#240>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getLinearPos :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getLinearPos a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getLinearPos'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3672 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#177>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getCalculatedTransformB :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btSliderConstraint_getCalculatedTransformB a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSliderConstraint_getCalculatedTransformB'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3678 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#176>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getCalculatedTransformA :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btSliderConstraint_getCalculatedTransformA a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSliderConstraint_getCalculatedTransformA'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3684 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#253>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_testAngLimits :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btSliderConstraint_testAngLimits a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_testAngLimits'_ a1' >>
  return ()

{-# LINE 3689 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#211>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setDampingDirLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dampingDirLin
 -> IO ()
btSliderConstraint_setDampingDirLin a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setDampingDirLin'_ a1' a2' >>
  return ()

{-# LINE 3695 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#188>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getUpperAngLimit :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getUpperAngLimit a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getUpperAngLimit'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3700 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setUpperAngLimit :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ upperLimit
 -> IO ()
btSliderConstraint_setUpperAngLimit a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setUpperAngLimit'_ a1' a2' >>
  return ()

{-# LINE 3706 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#201>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getRestitutionLimAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getRestitutionLimAng a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getRestitutionLimAng'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3711 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#203>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getSoftnessOrthoLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getSoftnessOrthoLin a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getSoftnessOrthoLin'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3716 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#183>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setLowerLinLimit :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ lowerLimit
 -> IO ()
btSliderConstraint_setLowerLinLimit a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setLowerLinLimit'_ a1' a2' >>
  return ()

{-# LINE 3722 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#192>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getRestitutionDirLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getRestitutionDirLin a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getRestitutionDirLin'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3727 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#166>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getInfo1NonVirtual :: ( BtSliderConstraintClass bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btSliderConstraint_getInfo1NonVirtual a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSliderConstraint_getInfo1NonVirtual'_ a1' a2' >>
  return ()

{-# LINE 3733 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#216>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setRestitutionLimLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ restitutionLimLin
 -> IO ()
btSliderConstraint_setRestitutionLimLin a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setRestitutionLimLin'_ a1' a2' >>
  return ()

{-# LINE 3739 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#229>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setTargetLinMotorVelocity :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ targetLinMotorVelocity
 -> IO ()
btSliderConstraint_setTargetLinMotorVelocity a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setTargetLinMotorVelocity'_ a1' a2' >>
  return ()

{-# LINE 3745 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#184>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getUpperLinLimit :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getUpperLinLimit a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getUpperLinLimit'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3750 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#231>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setMaxLinMotorForce :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ maxLinMotorForce
 -> IO ()
btSliderConstraint_setMaxLinMotorForce a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setMaxLinMotorForce'_ a1' a2' >>
  return ()

{-# LINE 3756 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#186>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getLowerAngLimit :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getLowerAngLimit a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getLowerAngLimit'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3761 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#209>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setSoftnessDirLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ softnessDirLin
 -> IO ()
btSliderConstraint_setSoftnessDirLin a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setSoftnessDirLin'_ a1' a2' >>
  return ()

{-# LINE 3767 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#156>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_initParams :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btSliderConstraint_initParams a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_initParams'_ a1' >>
  return ()

{-# LINE 3772 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#170>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getInfo2NonVirtual :: ( BtSliderConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> (Vec3) -- ^ linVelA
 -> (Vec3) -- ^ linVelB
 -> (Float) -- ^ rbAinvMass
 -> (Float) -- ^ rbBinvMass
 -> IO ((Transform), (Transform), (Vec3), (Vec3))
btSliderConstraint_getInfo2NonVirtual a1 a2 a3 a4 a5 a6 a7 a8 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  let {a7' = realToFrac a7} in 
  let {a8' = realToFrac a8} in 
  btSliderConstraint_getInfo2NonVirtual'_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a3'', a4'', a5'', a6'')

{-# LINE 3784 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#170>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getInfo2NonVirtual' :: ( BtSliderConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> (Float) -- ^ rbAinvMass
 -> (Float) -- ^ rbBinvMass
 -> IO ((Transform), (Transform), (Vec3), (Vec3))
btSliderConstraint_getInfo2NonVirtual' a1 a2 a7 a8 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaTransform $ \a3' -> 
  allocaTransform $ \a4' -> 
  allocaVec3 $ \a5' -> 
  allocaVec3 $ \a6' -> 
  let {a7' = realToFrac a7} in 
  let {a8' = realToFrac a8} in 
  btSliderConstraint_getInfo2NonVirtual''_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  peekTransform  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a3'', a4'', a5'', a6'')

{-# LINE 3796 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#178>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getFrameOffsetA :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btSliderConstraint_getFrameOffsetA a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSliderConstraint_getFrameOffsetA'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3802 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#178>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getFrameOffsetA0 :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btSliderConstraint_getFrameOffsetA0 a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSliderConstraint_getFrameOffsetA0'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3808 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getFrameOffsetA1 :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btSliderConstraint_getFrameOffsetA1 a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSliderConstraint_getFrameOffsetA1'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3814 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#179>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getFrameOffsetB :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btSliderConstraint_getFrameOffsetB a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSliderConstraint_getFrameOffsetB'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3820 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#179>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getFrameOffsetB0 :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btSliderConstraint_getFrameOffsetB0 a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSliderConstraint_getFrameOffsetB0'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3826 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#181>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getFrameOffsetB1 :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btSliderConstraint_getFrameOffsetB1 a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSliderConstraint_getFrameOffsetB1'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3832 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#196>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getDampingDirAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getDampingDirAng a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getDampingDirAng'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3837 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#198>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getRestitutionLimLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getRestitutionLimLin a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getRestitutionLimLin'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3842 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#206>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getSoftnessOrthoAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getSoftnessOrthoAng a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getSoftnessOrthoAng'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3847 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#221>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setSoftnessOrthoLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ softnessOrthoLin
 -> IO ()
btSliderConstraint_setSoftnessOrthoLin a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setSoftnessOrthoLin'_ a1' a2' >>
  return ()

{-# LINE 3853 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#218>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setSoftnessLimAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ softnessLimAng
 -> IO ()
btSliderConstraint_setSoftnessLimAng a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setSoftnessLimAng'_ a1' a2' >>
  return ()

{-# LINE 3859 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#193>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getDampingDirLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getDampingDirLin a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getDampingDirLin'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3864 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#197>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getSoftnessLimLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getSoftnessLimLin a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getSoftnessLimLin'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3869 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setPoweredLinMotor :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ onOff
 -> IO ()
btSliderConstraint_setPoweredLinMotor a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSliderConstraint_setPoweredLinMotor'_ a1' a2' >>
  return ()

{-# LINE 3875 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#251>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_calculateTransforms :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Transform) -- ^ transA
 -> (Transform) -- ^ transB
 -> IO ((Transform), (Transform))
btSliderConstraint_calculateTransforms a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  btSliderConstraint_calculateTransforms'_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 3882 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#251>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_calculateTransforms' :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform), (Transform))
btSliderConstraint_calculateTransforms' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  btSliderConstraint_calculateTransforms''_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 3889 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#247>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getLinDepth :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getLinDepth a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getLinDepth'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3894 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#309>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_serialize :: ( BtSliderConstraintClass bc , BtSerializerClass p1 ) => (bc) -- ^ 
 -> (VoidPtr) -- ^ dataBuffer
 -> (p1) -- ^ serializer
 -> IO ((String))
btSliderConstraint_serialize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btSliderConstraint_serialize'_ a1' a2' a3' >>= \res ->
  C2HSImp.peekCString res >>= \res' ->
  return (res')

{-# LINE 3901 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#199>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getDampingLimLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getDampingLimLin a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getDampingLimLin'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3906 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#195>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getRestitutionDirAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getRestitutionDirAng a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getRestitutionDirAng'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3911 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#272>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setParam :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ num
 -> (Float) -- ^ value
 -> (Int) -- ^ axis
 -> IO ()
btSliderConstraint_setParam a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = fromIntegral a4} in 
  btSliderConstraint_setParam'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 3919 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#202>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getDampingLimAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getDampingLimAng a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getDampingLimAng'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3924 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#222>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setRestitutionOrthoLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ restitutionOrthoLin
 -> IO ()
btSliderConstraint_setRestitutionOrthoLin a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setRestitutionOrthoLin'_ a1' a2' >>
  return ()

{-# LINE 3930 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#210>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setRestitutionDirLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ restitutionDirLin
 -> IO ()
btSliderConstraint_setRestitutionDirLin a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setRestitutionDirLin'_ a1' a2' >>
  return ()

{-# LINE 3936 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#220>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setDampingLimAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dampingLimAng
 -> IO ()
btSliderConstraint_setDampingLimAng a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setDampingLimAng'_ a1' a2' >>
  return ()

{-# LINE 3942 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#212>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setSoftnessDirAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ softnessDirAng
 -> IO ()
btSliderConstraint_setSoftnessDirAng a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setSoftnessDirAng'_ a1' a2' >>
  return ()

{-# LINE 3948 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#185>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setUpperLinLimit :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ upperLimit
 -> IO ()
btSliderConstraint_setUpperLinLimit a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setUpperLinLimit'_ a1' a2' >>
  return ()

{-# LINE 3954 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#303>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_calculateSerializeBufferSize :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btSliderConstraint_calculateSerializeBufferSize a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_calculateSerializeBufferSize'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3959 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#235>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setTargetAngMotorVelocity :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ targetAngMotorVelocity
 -> IO ()
btSliderConstraint_setTargetAngMotorVelocity a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setTargetAngMotorVelocity'_ a1' a2' >>
  return ()

{-# LINE 3965 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#194>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getSoftnessDirAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getSoftnessDirAng a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getSoftnessDirAng'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3970 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#237>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setMaxAngMotorForce :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ maxAngMotorForce
 -> IO ()
btSliderConstraint_setMaxAngMotorForce a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setMaxAngMotorForce'_ a1' a2' >>
  return ()

{-# LINE 3976 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#187>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setLowerAngLimit :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ lowerLimit
 -> IO ()
btSliderConstraint_setLowerAngLimit a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setLowerAngLimit'_ a1' a2' >>
  return ()

{-# LINE 3982 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#234>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getPoweredAngMotor :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btSliderConstraint_getPoweredAngMotor a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getPoweredAngMotor'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 3987 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#208>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getDampingOrthoAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getDampingOrthoAng a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getDampingOrthoAng'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3992 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#204>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getRestitutionOrthoLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getRestitutionOrthoLin a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getRestitutionOrthoLin'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3997 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getTargetLinMotorVelocity :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getTargetLinMotorVelocity a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getTargetLinMotorVelocity'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4002 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#252>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_testLinLimits :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btSliderConstraint_testLinLimits a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_testLinLimits'_ a1' >>
  return ()

{-# LINE 4007 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#182>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getLowerLinLimit :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getLowerLinLimit a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getLowerLinLimit'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4012 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#226>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setDampingOrthoAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dampingOrthoAng
 -> IO ()
btSliderConstraint_setDampingOrthoAng a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setDampingOrthoAng'_ a1' a2' >>
  return ()

{-# LINE 4018 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setRestitutionOrthoAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ restitutionOrthoAng
 -> IO ()
btSliderConstraint_setRestitutionOrthoAng a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setRestitutionOrthoAng'_ a1' a2' >>
  return ()

{-# LINE 4024 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#207>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getRestitutionOrthoAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getRestitutionOrthoAng a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getRestitutionOrthoAng'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4029 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#205>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getDampingOrthoLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getDampingOrthoLin a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getDampingOrthoLin'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4034 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#200>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getSoftnessLimAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getSoftnessLimAng a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getSoftnessLimAng'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4039 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setSoftnessOrthoAng :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ softnessOrthoAng
 -> IO ()
btSliderConstraint_setSoftnessOrthoAng a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setSoftnessOrthoAng'_ a1' a2' >>
  return ()

{-# LINE 4045 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setDampingLimLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dampingLimLin
 -> IO ()
btSliderConstraint_setDampingLimLin a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_setDampingLimLin'_ a1' a2' >>
  return ()

{-# LINE 4051 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#261>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setFrames :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> (Transform) -- ^ frameA
 -> (Transform) -- ^ frameB
 -> IO ((Transform), (Transform))
btSliderConstraint_setFrames a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  btSliderConstraint_setFrames'_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 4058 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#261>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_setFrames' :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Transform), (Transform))
btSliderConstraint_setFrames' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  btSliderConstraint_setFrames''_ a1' a2' a3' >>
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 4065 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#191>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getSoftnessDirLin :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSliderConstraint_getSoftnessDirLin a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getSoftnessDirLin'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4070 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#190>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_getUseLinearReferenceFrameA :: ( BtSliderConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btSliderConstraint_getUseLinearReferenceFrameA a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_getUseLinearReferenceFrameA'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 4075 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#67>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_useSolveConstraintObsolete_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btSliderConstraint_m_useSolveConstraintObsolete_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSliderConstraint_m_useSolveConstraintObsolete_set'_ a1' a2' >>
  return ()

{-# LINE 4079 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#67>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_useSolveConstraintObsolete_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Bool))
btSliderConstraint_m_useSolveConstraintObsolete_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_useSolveConstraintObsolete_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 4083 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_useOffsetForConstraintFrame_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btSliderConstraint_m_useOffsetForConstraintFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSliderConstraint_m_useOffsetForConstraintFrame_set'_ a1' a2' >>
  return ()

{-# LINE 4087 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_useOffsetForConstraintFrame_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Bool))
btSliderConstraint_m_useOffsetForConstraintFrame_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_useOffsetForConstraintFrame_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 4091 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#69>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_frameInA_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Transform) -> IO ()
btSliderConstraint_m_frameInA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btSliderConstraint_m_frameInA_set'_ a1' a2' >>
  return ()

{-# LINE 4095 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#69>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_frameInA_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Transform))
btSliderConstraint_m_frameInA_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSliderConstraint_m_frameInA_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4099 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#70>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_frameInB_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Transform) -> IO ()
btSliderConstraint_m_frameInB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btSliderConstraint_m_frameInB_set'_ a1' a2' >>
  return ()

{-# LINE 4103 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#70>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_frameInB_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Transform))
btSliderConstraint_m_frameInB_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSliderConstraint_m_frameInB_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4107 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_useLinearReferenceFrameA_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btSliderConstraint_m_useLinearReferenceFrameA_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSliderConstraint_m_useLinearReferenceFrameA_set'_ a1' a2' >>
  return ()

{-# LINE 4111 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_useLinearReferenceFrameA_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Bool))
btSliderConstraint_m_useLinearReferenceFrameA_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_useLinearReferenceFrameA_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 4115 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#74>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_lowerLinLimit_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_lowerLinLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_lowerLinLimit_set'_ a1' a2' >>
  return ()

{-# LINE 4119 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#74>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_lowerLinLimit_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_lowerLinLimit_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_lowerLinLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4123 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#75>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_upperLinLimit_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_upperLinLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_upperLinLimit_set'_ a1' a2' >>
  return ()

{-# LINE 4127 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#75>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_upperLinLimit_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_upperLinLimit_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_upperLinLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4131 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#77>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_lowerAngLimit_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_lowerAngLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_lowerAngLimit_set'_ a1' a2' >>
  return ()

{-# LINE 4135 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#77>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_lowerAngLimit_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_lowerAngLimit_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_lowerAngLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4139 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#78>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_upperAngLimit_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_upperAngLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_upperAngLimit_set'_ a1' a2' >>
  return ()

{-# LINE 4143 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#78>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_upperAngLimit_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_upperAngLimit_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_upperAngLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4147 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#85>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_softnessDirLin_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_softnessDirLin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_softnessDirLin_set'_ a1' a2' >>
  return ()

{-# LINE 4151 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#85>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_softnessDirLin_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_softnessDirLin_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_softnessDirLin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4155 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#86>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_restitutionDirLin_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_restitutionDirLin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_restitutionDirLin_set'_ a1' a2' >>
  return ()

{-# LINE 4159 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#86>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_restitutionDirLin_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_restitutionDirLin_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_restitutionDirLin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4163 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#87>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_dampingDirLin_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_dampingDirLin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_dampingDirLin_set'_ a1' a2' >>
  return ()

{-# LINE 4167 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#87>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_dampingDirLin_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_dampingDirLin_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_dampingDirLin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4171 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_cfmDirLin_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_cfmDirLin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_cfmDirLin_set'_ a1' a2' >>
  return ()

{-# LINE 4175 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_cfmDirLin_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_cfmDirLin_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_cfmDirLin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4179 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#90>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_softnessDirAng_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_softnessDirAng_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_softnessDirAng_set'_ a1' a2' >>
  return ()

{-# LINE 4183 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#90>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_softnessDirAng_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_softnessDirAng_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_softnessDirAng_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4187 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#91>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_restitutionDirAng_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_restitutionDirAng_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_restitutionDirAng_set'_ a1' a2' >>
  return ()

{-# LINE 4191 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#91>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_restitutionDirAng_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_restitutionDirAng_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_restitutionDirAng_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4195 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_dampingDirAng_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_dampingDirAng_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_dampingDirAng_set'_ a1' a2' >>
  return ()

{-# LINE 4199 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_dampingDirAng_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_dampingDirAng_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_dampingDirAng_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4203 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#93>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_cfmDirAng_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_cfmDirAng_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_cfmDirAng_set'_ a1' a2' >>
  return ()

{-# LINE 4207 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#93>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_cfmDirAng_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_cfmDirAng_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_cfmDirAng_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4211 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#95>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_softnessLimLin_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_softnessLimLin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_softnessLimLin_set'_ a1' a2' >>
  return ()

{-# LINE 4215 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#95>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_softnessLimLin_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_softnessLimLin_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_softnessLimLin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4219 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_restitutionLimLin_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_restitutionLimLin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_restitutionLimLin_set'_ a1' a2' >>
  return ()

{-# LINE 4223 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_restitutionLimLin_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_restitutionLimLin_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_restitutionLimLin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4227 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_dampingLimLin_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_dampingLimLin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_dampingLimLin_set'_ a1' a2' >>
  return ()

{-# LINE 4231 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_dampingLimLin_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_dampingLimLin_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_dampingLimLin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4235 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#98>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_cfmLimLin_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_cfmLimLin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_cfmLimLin_set'_ a1' a2' >>
  return ()

{-# LINE 4239 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#98>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_cfmLimLin_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_cfmLimLin_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_cfmLimLin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4243 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#100>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_softnessLimAng_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_softnessLimAng_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_softnessLimAng_set'_ a1' a2' >>
  return ()

{-# LINE 4247 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#100>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_softnessLimAng_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_softnessLimAng_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_softnessLimAng_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4251 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#101>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_restitutionLimAng_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_restitutionLimAng_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_restitutionLimAng_set'_ a1' a2' >>
  return ()

{-# LINE 4255 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#101>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_restitutionLimAng_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_restitutionLimAng_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_restitutionLimAng_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4259 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#102>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_dampingLimAng_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_dampingLimAng_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_dampingLimAng_set'_ a1' a2' >>
  return ()

{-# LINE 4263 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#102>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_dampingLimAng_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_dampingLimAng_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_dampingLimAng_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4267 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#103>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_cfmLimAng_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_cfmLimAng_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_cfmLimAng_set'_ a1' a2' >>
  return ()

{-# LINE 4271 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#103>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_cfmLimAng_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_cfmLimAng_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_cfmLimAng_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4275 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#105>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_softnessOrthoLin_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_softnessOrthoLin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_softnessOrthoLin_set'_ a1' a2' >>
  return ()

{-# LINE 4279 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#105>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_softnessOrthoLin_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_softnessOrthoLin_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_softnessOrthoLin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4283 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#106>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_restitutionOrthoLin_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_restitutionOrthoLin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_restitutionOrthoLin_set'_ a1' a2' >>
  return ()

{-# LINE 4287 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#106>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_restitutionOrthoLin_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_restitutionOrthoLin_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_restitutionOrthoLin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4291 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#107>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_dampingOrthoLin_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_dampingOrthoLin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_dampingOrthoLin_set'_ a1' a2' >>
  return ()

{-# LINE 4295 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#107>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_dampingOrthoLin_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_dampingOrthoLin_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_dampingOrthoLin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4299 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#108>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_cfmOrthoLin_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_cfmOrthoLin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_cfmOrthoLin_set'_ a1' a2' >>
  return ()

{-# LINE 4303 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#108>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_cfmOrthoLin_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_cfmOrthoLin_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_cfmOrthoLin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4307 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#110>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_softnessOrthoAng_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_softnessOrthoAng_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_softnessOrthoAng_set'_ a1' a2' >>
  return ()

{-# LINE 4311 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#110>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_softnessOrthoAng_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_softnessOrthoAng_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_softnessOrthoAng_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4315 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_restitutionOrthoAng_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_restitutionOrthoAng_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_restitutionOrthoAng_set'_ a1' a2' >>
  return ()

{-# LINE 4319 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_restitutionOrthoAng_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_restitutionOrthoAng_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_restitutionOrthoAng_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4323 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#112>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_dampingOrthoAng_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_dampingOrthoAng_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_dampingOrthoAng_set'_ a1' a2' >>
  return ()

{-# LINE 4327 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#112>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_dampingOrthoAng_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_dampingOrthoAng_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_dampingOrthoAng_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4331 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_cfmOrthoAng_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_cfmOrthoAng_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_cfmOrthoAng_set'_ a1' a2' >>
  return ()

{-# LINE 4335 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_cfmOrthoAng_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_cfmOrthoAng_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_cfmOrthoAng_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4339 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#116>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_solveLinLim_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btSliderConstraint_m_solveLinLim_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSliderConstraint_m_solveLinLim_set'_ a1' a2' >>
  return ()

{-# LINE 4343 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#116>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_solveLinLim_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Bool))
btSliderConstraint_m_solveLinLim_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_solveLinLim_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 4347 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#117>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_solveAngLim_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btSliderConstraint_m_solveAngLim_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSliderConstraint_m_solveAngLim_set'_ a1' a2' >>
  return ()

{-# LINE 4351 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#117>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_solveAngLim_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Bool))
btSliderConstraint_m_solveAngLim_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_solveAngLim_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 4355 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#119>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_flags_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Int) -> IO ()
btSliderConstraint_m_flags_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSliderConstraint_m_flags_set'_ a1' a2' >>
  return ()

{-# LINE 4359 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#119>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_flags_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Int))
btSliderConstraint_m_flags_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_flags_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 4363 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#126>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_timeStep_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_timeStep_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_timeStep_set'_ a1' a2' >>
  return ()

{-# LINE 4367 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#126>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_timeStep_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_timeStep_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_timeStep_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4371 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#127>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_calculatedTransformA_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Transform) -> IO ()
btSliderConstraint_m_calculatedTransformA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btSliderConstraint_m_calculatedTransformA_set'_ a1' a2' >>
  return ()

{-# LINE 4375 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#127>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_calculatedTransformA_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Transform))
btSliderConstraint_m_calculatedTransformA_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSliderConstraint_m_calculatedTransformA_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4379 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#128>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_calculatedTransformB_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Transform) -> IO ()
btSliderConstraint_m_calculatedTransformB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btSliderConstraint_m_calculatedTransformB_set'_ a1' a2' >>
  return ()

{-# LINE 4383 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#128>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_calculatedTransformB_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Transform))
btSliderConstraint_m_calculatedTransformB_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSliderConstraint_m_calculatedTransformB_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4387 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#130>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_sliderAxis_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btSliderConstraint_m_sliderAxis_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSliderConstraint_m_sliderAxis_set'_ a1' a2' >>
  return ()

{-# LINE 4391 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#130>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_sliderAxis_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Vec3))
btSliderConstraint_m_sliderAxis_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSliderConstraint_m_sliderAxis_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4395 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#131>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_realPivotAInW_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btSliderConstraint_m_realPivotAInW_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSliderConstraint_m_realPivotAInW_set'_ a1' a2' >>
  return ()

{-# LINE 4399 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#131>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_realPivotAInW_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Vec3))
btSliderConstraint_m_realPivotAInW_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSliderConstraint_m_realPivotAInW_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4403 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#132>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_realPivotBInW_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btSliderConstraint_m_realPivotBInW_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSliderConstraint_m_realPivotBInW_set'_ a1' a2' >>
  return ()

{-# LINE 4407 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#132>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_realPivotBInW_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Vec3))
btSliderConstraint_m_realPivotBInW_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSliderConstraint_m_realPivotBInW_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4411 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#133>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_projPivotInW_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btSliderConstraint_m_projPivotInW_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSliderConstraint_m_projPivotInW_set'_ a1' a2' >>
  return ()

{-# LINE 4415 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#133>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_projPivotInW_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Vec3))
btSliderConstraint_m_projPivotInW_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSliderConstraint_m_projPivotInW_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4419 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#134>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_delta_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btSliderConstraint_m_delta_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSliderConstraint_m_delta_set'_ a1' a2' >>
  return ()

{-# LINE 4423 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#134>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_delta_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Vec3))
btSliderConstraint_m_delta_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSliderConstraint_m_delta_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4427 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#135>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_depth_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btSliderConstraint_m_depth_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSliderConstraint_m_depth_set'_ a1' a2' >>
  return ()

{-# LINE 4431 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#135>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_depth_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Vec3))
btSliderConstraint_m_depth_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSliderConstraint_m_depth_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4435 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_relPosA_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btSliderConstraint_m_relPosA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSliderConstraint_m_relPosA_set'_ a1' a2' >>
  return ()

{-# LINE 4439 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_relPosA_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Vec3))
btSliderConstraint_m_relPosA_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSliderConstraint_m_relPosA_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4443 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#137>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_relPosB_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btSliderConstraint_m_relPosB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSliderConstraint_m_relPosB_set'_ a1' a2' >>
  return ()

{-# LINE 4447 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#137>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_relPosB_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Vec3))
btSliderConstraint_m_relPosB_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSliderConstraint_m_relPosB_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4451 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#139>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_linPos_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_linPos_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_linPos_set'_ a1' a2' >>
  return ()

{-# LINE 4455 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#139>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_linPos_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_linPos_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_linPos_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4459 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#140>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_angPos_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_angPos_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_angPos_set'_ a1' a2' >>
  return ()

{-# LINE 4463 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#140>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_angPos_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_angPos_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_angPos_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4467 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#142>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_angDepth_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_angDepth_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_angDepth_set'_ a1' a2' >>
  return ()

{-# LINE 4471 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#142>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_angDepth_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_angDepth_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_angDepth_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4475 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#143>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_kAngle_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_kAngle_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_kAngle_set'_ a1' a2' >>
  return ()

{-# LINE 4479 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#143>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_kAngle_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_kAngle_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_kAngle_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4483 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#145>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_poweredLinMotor_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btSliderConstraint_m_poweredLinMotor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSliderConstraint_m_poweredLinMotor_set'_ a1' a2' >>
  return ()

{-# LINE 4487 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#145>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_poweredLinMotor_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Bool))
btSliderConstraint_m_poweredLinMotor_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_poweredLinMotor_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 4491 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#146>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_targetLinMotorVelocity_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_targetLinMotorVelocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_targetLinMotorVelocity_set'_ a1' a2' >>
  return ()

{-# LINE 4495 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#146>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_targetLinMotorVelocity_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_targetLinMotorVelocity_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_targetLinMotorVelocity_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4499 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_maxLinMotorForce_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_maxLinMotorForce_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_maxLinMotorForce_set'_ a1' a2' >>
  return ()

{-# LINE 4503 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_maxLinMotorForce_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_maxLinMotorForce_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_maxLinMotorForce_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4507 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_accumulatedLinMotorImpulse_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_accumulatedLinMotorImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_accumulatedLinMotorImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 4511 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_accumulatedLinMotorImpulse_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_accumulatedLinMotorImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_accumulatedLinMotorImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4515 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#150>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_poweredAngMotor_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btSliderConstraint_m_poweredAngMotor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSliderConstraint_m_poweredAngMotor_set'_ a1' a2' >>
  return ()

{-# LINE 4519 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#150>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_poweredAngMotor_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Bool))
btSliderConstraint_m_poweredAngMotor_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_poweredAngMotor_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 4523 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#151>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_targetAngMotorVelocity_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_targetAngMotorVelocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_targetAngMotorVelocity_set'_ a1' a2' >>
  return ()

{-# LINE 4527 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#151>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_targetAngMotorVelocity_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_targetAngMotorVelocity_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_targetAngMotorVelocity_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4531 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#152>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_maxAngMotorForce_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_maxAngMotorForce_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_maxAngMotorForce_set'_ a1' a2' >>
  return ()

{-# LINE 4535 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#152>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_maxAngMotorForce_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_maxAngMotorForce_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_maxAngMotorForce_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4539 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#153>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_accumulatedAngMotorImpulse_set :: ( BtSliderConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraint_m_accumulatedAngMotorImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraint_m_accumulatedAngMotorImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 4543 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#153>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraint_m_accumulatedAngMotorImpulse_get :: ( BtSliderConstraintClass bc ) => (bc) -> IO ((Float))
btSliderConstraint_m_accumulatedAngMotorImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraint_m_accumulatedAngMotorImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4547 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btSliderConstraintData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#286>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData :: IO ((BtSliderConstraintData))
btSliderConstraintData =
  btSliderConstraintData'_ >>= \res ->
  mkBtSliderConstraintData res >>= \res' ->
  return (res')

{-# LINE 4552 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btSliderConstraintData_free :: ( BtSliderConstraintDataClass bc ) => (bc) -> IO ()
btSliderConstraintData_free a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraintData_free'_ a1' >>
  return ()

{-# LINE 4553 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#287>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_typeConstraintData_set :: ( BtSliderConstraintDataClass bc , BtTypedConstraintDataClass a ) => (bc) -> (a) -> IO ()
btSliderConstraintData_m_typeConstraintData_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSliderConstraintData_m_typeConstraintData_set'_ a1' a2' >>
  return ()

{-# LINE 4557 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#287>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_typeConstraintData_get :: ( BtSliderConstraintDataClass bc ) => (bc) -> IO ((BtTypedConstraintData))
btSliderConstraintData_m_typeConstraintData_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraintData_m_typeConstraintData_get'_ a1' >>= \res ->
  mkBtTypedConstraintData res >>= \res' ->
  return (res')

{-# LINE 4561 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#288>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_rbAFrame_set :: ( BtSliderConstraintDataClass bc , BtTransformFloatDataClass a ) => (bc) -> (a) -> IO ()
btSliderConstraintData_m_rbAFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSliderConstraintData_m_rbAFrame_set'_ a1' a2' >>
  return ()

{-# LINE 4565 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#288>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_rbAFrame_get :: ( BtSliderConstraintDataClass bc ) => (bc) -> IO ((BtTransformFloatData))
btSliderConstraintData_m_rbAFrame_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraintData_m_rbAFrame_get'_ a1' >>= \res ->
  mkBtTransformFloatData res >>= \res' ->
  return (res')

{-# LINE 4569 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#289>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_rbBFrame_set :: ( BtSliderConstraintDataClass bc , BtTransformFloatDataClass a ) => (bc) -> (a) -> IO ()
btSliderConstraintData_m_rbBFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSliderConstraintData_m_rbBFrame_set'_ a1' a2' >>
  return ()

{-# LINE 4573 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#289>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_rbBFrame_get :: ( BtSliderConstraintDataClass bc ) => (bc) -> IO ((BtTransformFloatData))
btSliderConstraintData_m_rbBFrame_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraintData_m_rbBFrame_get'_ a1' >>= \res ->
  mkBtTransformFloatData res >>= \res' ->
  return (res')

{-# LINE 4577 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#291>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_linearUpperLimit_set :: ( BtSliderConstraintDataClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraintData_m_linearUpperLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraintData_m_linearUpperLimit_set'_ a1' a2' >>
  return ()

{-# LINE 4581 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#291>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_linearUpperLimit_get :: ( BtSliderConstraintDataClass bc ) => (bc) -> IO ((Float))
btSliderConstraintData_m_linearUpperLimit_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraintData_m_linearUpperLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4585 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#292>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_linearLowerLimit_set :: ( BtSliderConstraintDataClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraintData_m_linearLowerLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraintData_m_linearLowerLimit_set'_ a1' a2' >>
  return ()

{-# LINE 4589 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#292>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_linearLowerLimit_get :: ( BtSliderConstraintDataClass bc ) => (bc) -> IO ((Float))
btSliderConstraintData_m_linearLowerLimit_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraintData_m_linearLowerLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4593 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#294>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_angularUpperLimit_set :: ( BtSliderConstraintDataClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraintData_m_angularUpperLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraintData_m_angularUpperLimit_set'_ a1' a2' >>
  return ()

{-# LINE 4597 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#294>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_angularUpperLimit_get :: ( BtSliderConstraintDataClass bc ) => (bc) -> IO ((Float))
btSliderConstraintData_m_angularUpperLimit_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraintData_m_angularUpperLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4601 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#295>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_angularLowerLimit_set :: ( BtSliderConstraintDataClass bc ) => (bc) -> (Float) -> IO ()
btSliderConstraintData_m_angularLowerLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSliderConstraintData_m_angularLowerLimit_set'_ a1' a2' >>
  return ()

{-# LINE 4605 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#295>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_angularLowerLimit_get :: ( BtSliderConstraintDataClass bc ) => (bc) -> IO ((Float))
btSliderConstraintData_m_angularLowerLimit_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraintData_m_angularLowerLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4609 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#297>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_useLinearReferenceFrameA_set :: ( BtSliderConstraintDataClass bc ) => (bc) -> (Int) -> IO ()
btSliderConstraintData_m_useLinearReferenceFrameA_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSliderConstraintData_m_useLinearReferenceFrameA_set'_ a1' a2' >>
  return ()

{-# LINE 4613 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#297>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_useLinearReferenceFrameA_get :: ( BtSliderConstraintDataClass bc ) => (bc) -> IO ((Int))
btSliderConstraintData_m_useLinearReferenceFrameA_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraintData_m_useLinearReferenceFrameA_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 4617 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#298>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_useOffsetForConstraintFrame_set :: ( BtSliderConstraintDataClass bc ) => (bc) -> (Int) -> IO ()
btSliderConstraintData_m_useOffsetForConstraintFrame_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSliderConstraintData_m_useOffsetForConstraintFrame_set'_ a1' a2' >>
  return ()

{-# LINE 4621 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.h?r=2223#298>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSliderConstraint.cpp?r=2223>
-}
btSliderConstraintData_m_useOffsetForConstraintFrame_get :: ( BtSliderConstraintDataClass bc ) => (bc) -> IO ((Int))
btSliderConstraintData_m_useOffsetForConstraintFrame_get a1 =
  withBt a1 $ \a1' -> 
  btSliderConstraintData_m_useOffsetForConstraintFrame_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 4625 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btSolverBodyObsolete
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#109>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete :: IO ((BtSolverBodyObsolete))
btSolverBodyObsolete =
  btSolverBodyObsolete'_ >>= \res ->
  mkBtSolverBodyObsolete res >>= \res' ->
  return (res')

{-# LINE 4630 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btSolverBodyObsolete_free :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> IO ()
btSolverBodyObsolete_free a1 =
  withBt a1 $ \a1' -> 
  btSolverBodyObsolete_free'_ a1' >>
  return ()

{-# LINE 4631 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#128>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_getAngularVelocity :: ( BtSolverBodyObsoleteClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ angVel
 -> IO ((Vec3))
btSolverBodyObsolete_getAngularVelocity a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSolverBodyObsolete_getAngularVelocity'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4637 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#128>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_getAngularVelocity' :: ( BtSolverBodyObsoleteClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSolverBodyObsolete_getAngularVelocity' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSolverBodyObsolete_getAngularVelocity''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4643 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#156>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_writebackVelocity :: ( BtSolverBodyObsoleteClass bc ) => (bc) -- ^ 
 -> IO ()
btSolverBodyObsolete_writebackVelocity a1 =
  withBt a1 $ \a1' -> 
  btSolverBodyObsolete_writebackVelocity'_ a1' >>
  return ()

{-# LINE 4648 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#156>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_writebackVelocity0 :: ( BtSolverBodyObsoleteClass bc ) => (bc) -- ^ 
 -> IO ()
btSolverBodyObsolete_writebackVelocity0 a1 =
  withBt a1 $ \a1' -> 
  btSolverBodyObsolete_writebackVelocity0'_ a1' >>
  return ()

{-# LINE 4653 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#168>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_writebackVelocity1 :: ( BtSolverBodyObsoleteClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ timeStep
 -> IO ()
btSolverBodyObsolete_writebackVelocity1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSolverBodyObsolete_writebackVelocity1'_ a1' a2' >>
  return ()

{-# LINE 4659 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_internalApplyPushImpulse :: ( BtSolverBodyObsoleteClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ linearComponent
 -> (Vec3) -- ^ angularComponent
 -> (Float) -- ^ impulseMagnitude
 -> IO ((Vec3), (Vec3))
btSolverBodyObsolete_internalApplyPushImpulse a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  btSolverBodyObsolete_internalApplyPushImpulse'_ a1' a2' a3' a4' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 4667 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_internalApplyPushImpulse' :: ( BtSolverBodyObsoleteClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ impulseMagnitude
 -> IO ((Vec3), (Vec3))
btSolverBodyObsolete_internalApplyPushImpulse' a1 a4 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  btSolverBodyObsolete_internalApplyPushImpulse''_ a1' a2' a3' a4' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 4675 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#120>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_getVelocityInLocalPointObsolete :: ( BtSolverBodyObsoleteClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ rel_pos
 -> (Vec3) -- ^ velocity
 -> IO ((Vec3), (Vec3))
btSolverBodyObsolete_getVelocityInLocalPointObsolete a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btSolverBodyObsolete_getVelocityInLocalPointObsolete'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 4682 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#120>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_getVelocityInLocalPointObsolete' :: ( BtSolverBodyObsoleteClass bc ) => (bc) -- ^ 
 -> IO ((Vec3), (Vec3))
btSolverBodyObsolete_getVelocityInLocalPointObsolete' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btSolverBodyObsolete_getVelocityInLocalPointObsolete''_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 4689 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_deltaLinearVelocity_set :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> (Vec3) -> IO ()
btSolverBodyObsolete_m_deltaLinearVelocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSolverBodyObsolete_m_deltaLinearVelocity_set'_ a1' a2' >>
  return ()

{-# LINE 4693 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_deltaLinearVelocity_get :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> IO ((Vec3))
btSolverBodyObsolete_m_deltaLinearVelocity_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSolverBodyObsolete_m_deltaLinearVelocity_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4697 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#112>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_deltaAngularVelocity_set :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> (Vec3) -> IO ()
btSolverBodyObsolete_m_deltaAngularVelocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSolverBodyObsolete_m_deltaAngularVelocity_set'_ a1' a2' >>
  return ()

{-# LINE 4701 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#112>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_deltaAngularVelocity_get :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> IO ((Vec3))
btSolverBodyObsolete_m_deltaAngularVelocity_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSolverBodyObsolete_m_deltaAngularVelocity_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4705 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_angularFactor_set :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> (Vec3) -> IO ()
btSolverBodyObsolete_m_angularFactor_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSolverBodyObsolete_m_angularFactor_set'_ a1' a2' >>
  return ()

{-# LINE 4709 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_angularFactor_get :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> IO ((Vec3))
btSolverBodyObsolete_m_angularFactor_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSolverBodyObsolete_m_angularFactor_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4713 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#114>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_invMass_set :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> (Vec3) -> IO ()
btSolverBodyObsolete_m_invMass_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSolverBodyObsolete_m_invMass_set'_ a1' a2' >>
  return ()

{-# LINE 4717 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#114>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_invMass_get :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> IO ((Vec3))
btSolverBodyObsolete_m_invMass_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSolverBodyObsolete_m_invMass_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4721 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#115>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_originalBody_set :: ( BtSolverBodyObsoleteClass bc , BtRigidBodyClass a ) => (bc) -> (a) -> IO ()
btSolverBodyObsolete_m_originalBody_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSolverBodyObsolete_m_originalBody_set'_ a1' a2' >>
  return ()

{-# LINE 4725 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#115>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_originalBody_get :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> IO ((BtRigidBody))
btSolverBodyObsolete_m_originalBody_get a1 =
  withBt a1 $ \a1' -> 
  btSolverBodyObsolete_m_originalBody_get'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 4729 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#116>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_pushVelocity_set :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> (Vec3) -> IO ()
btSolverBodyObsolete_m_pushVelocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSolverBodyObsolete_m_pushVelocity_set'_ a1' a2' >>
  return ()

{-# LINE 4733 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#116>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_pushVelocity_get :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> IO ((Vec3))
btSolverBodyObsolete_m_pushVelocity_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSolverBodyObsolete_m_pushVelocity_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4737 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#117>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_turnVelocity_set :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> (Vec3) -> IO ()
btSolverBodyObsolete_m_turnVelocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSolverBodyObsolete_m_turnVelocity_set'_ a1' a2' >>
  return ()

{-# LINE 4741 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.h?r=2223#117>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverBody.cpp?r=2223>
-}
btSolverBodyObsolete_m_turnVelocity_get :: ( BtSolverBodyObsoleteClass bc ) => (bc) -> IO ((Vec3))
btSolverBodyObsolete_m_turnVelocity_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSolverBodyObsolete_m_turnVelocity_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4745 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btSolverConstraint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#30>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint :: IO ((BtSolverConstraint))
btSolverConstraint =
  btSolverConstraint'_ >>= \res ->
  mkBtSolverConstraint res >>= \res' ->
  return (res')

{-# LINE 4750 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btSolverConstraint_free :: ( BtSolverConstraintClass bc ) => (bc) -> IO ()
btSolverConstraint_free a1 =
  withBt a1 $ \a1' -> 
  btSolverConstraint_free'_ a1' >>
  return ()

{-# LINE 4751 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#39>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_angularComponentA_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btSolverConstraint_m_angularComponentA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSolverConstraint_m_angularComponentA_set'_ a1' a2' >>
  return ()

{-# LINE 4755 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#39>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_angularComponentA_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Vec3))
btSolverConstraint_m_angularComponentA_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSolverConstraint_m_angularComponentA_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4759 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#40>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_angularComponentB_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btSolverConstraint_m_angularComponentB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSolverConstraint_m_angularComponentB_set'_ a1' a2' >>
  return ()

{-# LINE 4763 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#40>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_angularComponentB_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Vec3))
btSolverConstraint_m_angularComponentB_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSolverConstraint_m_angularComponentB_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4767 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#43>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_appliedImpulse_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSolverConstraint_m_appliedImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSolverConstraint_m_appliedImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 4771 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#43>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_appliedImpulse_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Float))
btSolverConstraint_m_appliedImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btSolverConstraint_m_appliedImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4775 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_appliedPushImpulse_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSolverConstraint_m_appliedPushImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSolverConstraint_m_appliedPushImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 4779 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_appliedPushImpulse_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Float))
btSolverConstraint_m_appliedPushImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btSolverConstraint_m_appliedPushImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4783 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#77>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_cfm_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSolverConstraint_m_cfm_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSolverConstraint_m_cfm_set'_ a1' a2' >>
  return ()

{-# LINE 4787 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#77>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_cfm_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Float))
btSolverConstraint_m_cfm_get a1 =
  withBt a1 $ \a1' -> 
  btSolverConstraint_m_cfm_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4791 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#34>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_contactNormal_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btSolverConstraint_m_contactNormal_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSolverConstraint_m_contactNormal_set'_ a1' a2' >>
  return ()

{-# LINE 4795 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#34>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_contactNormal_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Vec3))
btSolverConstraint_m_contactNormal_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSolverConstraint_m_contactNormal_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4799 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#46>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_friction_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSolverConstraint_m_friction_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSolverConstraint_m_friction_set'_ a1' a2' >>
  return ()

{-# LINE 4803 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#46>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_friction_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Float))
btSolverConstraint_m_friction_get a1 =
  withBt a1 $ \a1' -> 
  btSolverConstraint_m_friction_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4807 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#47>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_jacDiagABInv_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSolverConstraint_m_jacDiagABInv_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSolverConstraint_m_jacDiagABInv_set'_ a1' a2' >>
  return ()

{-# LINE 4811 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#47>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_jacDiagABInv_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Float))
btSolverConstraint_m_jacDiagABInv_get a1 =
  withBt a1 $ \a1' -> 
  btSolverConstraint_m_jacDiagABInv_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4815 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#78>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_lowerLimit_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSolverConstraint_m_lowerLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSolverConstraint_m_lowerLimit_set'_ a1' a2' >>
  return ()

{-# LINE 4819 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#78>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_lowerLimit_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Float))
btSolverConstraint_m_lowerLimit_get a1 =
  withBt a1 $ \a1' -> 
  btSolverConstraint_m_lowerLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4823 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#33>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_relpos1CrossNormal_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btSolverConstraint_m_relpos1CrossNormal_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSolverConstraint_m_relpos1CrossNormal_set'_ a1' a2' >>
  return ()

{-# LINE 4827 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#33>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_relpos1CrossNormal_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Vec3))
btSolverConstraint_m_relpos1CrossNormal_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSolverConstraint_m_relpos1CrossNormal_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4831 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#36>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_relpos2CrossNormal_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btSolverConstraint_m_relpos2CrossNormal_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSolverConstraint_m_relpos2CrossNormal_set'_ a1' a2' >>
  return ()

{-# LINE 4835 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#36>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_relpos2CrossNormal_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Vec3))
btSolverConstraint_m_relpos2CrossNormal_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSolverConstraint_m_relpos2CrossNormal_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4839 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#76>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_rhs_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSolverConstraint_m_rhs_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSolverConstraint_m_rhs_set'_ a1' a2' >>
  return ()

{-# LINE 4843 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#76>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_rhs_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Float))
btSolverConstraint_m_rhs_get a1 =
  withBt a1 $ \a1' -> 
  btSolverConstraint_m_rhs_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4847 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_rhsPenetration_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSolverConstraint_m_rhsPenetration_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSolverConstraint_m_rhsPenetration_set'_ a1' a2' >>
  return ()

{-# LINE 4851 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_rhsPenetration_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Float))
btSolverConstraint_m_rhsPenetration_get a1 =
  withBt a1 $ \a1' -> 
  btSolverConstraint_m_rhsPenetration_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4855 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#79>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_upperLimit_set :: ( BtSolverConstraintClass bc ) => (bc) -> (Float) -> IO ()
btSolverConstraint_m_upperLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSolverConstraint_m_upperLimit_set'_ a1' a2' >>
  return ()

{-# LINE 4859 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.h?r=2223#79>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btSolverConstraint.cpp?r=2223>
-}
btSolverConstraint_m_upperLimit_get :: ( BtSolverConstraintClass bc ) => (bc) -> IO ((Float))
btSolverConstraint_m_upperLimit_get a1 =
  withBt a1 $ \a1' -> 
  btSolverConstraint_m_upperLimit_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4863 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btTranslationalLimitMotor
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#154>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor :: IO ((BtTranslationalLimitMotor))
btTranslationalLimitMotor =
  btTranslationalLimitMotor'_ >>= \res ->
  mkBtTranslationalLimitMotor res >>= \res' ->
  return (res')

{-# LINE 4868 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btTranslationalLimitMotor_free :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ()
btTranslationalLimitMotor_free a1 =
  withBt a1 $ \a1' -> 
  btTranslationalLimitMotor_free'_ a1' >>
  return ()

{-# LINE 4869 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#211>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_testLimitValue :: ( BtTranslationalLimitMotorClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ limitIndex
 -> (Float) -- ^ test_value
 -> IO ((Int))
btTranslationalLimitMotor_testLimitValue a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  btTranslationalLimitMotor_testLimitValue'_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 4876 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#206>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_needApplyForce :: ( BtTranslationalLimitMotorClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ limitIndex
 -> IO ((Bool))
btTranslationalLimitMotor_needApplyForce a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTranslationalLimitMotor_needApplyForce'_ a1' a2' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 4882 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#221>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_solveLinearAxis :: ( BtTranslationalLimitMotorClass bc , BtRigidBodyClass p2 , BtRigidBodyClass p4 ) => (bc) -- ^ 
 -> (Float) -- ^ timeStep
 -> (Float) -- ^ jacDiagABInv
 -> (p2) -- ^ body1
 -> (Vec3) -- ^ pointInA
 -> (p4) -- ^ body2
 -> (Vec3) -- ^ pointInB
 -> (Int) -- ^ limit_index
 -> (Vec3) -- ^ axis_normal_on_a
 -> (Vec3) -- ^ anchorPos
 -> IO ((Float), (Vec3), (Vec3), (Vec3), (Vec3))
btTranslationalLimitMotor_solveLinearAxis a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  withBt a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  withVec3 a7 $ \a7' -> 
  let {a8' = fromIntegral a8} in 
  withVec3 a9 $ \a9' -> 
  withVec3 a10 $ \a10' -> 
  btTranslationalLimitMotor_solveLinearAxis'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  let {res' = realToFrac res} in
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a9'>>= \a9'' -> 
  peekVec3  a10'>>= \a10'' -> 
  return (res', a5'', a7'', a9'', a10'')

{-# LINE 4896 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#221>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_solveLinearAxis' :: ( BtTranslationalLimitMotorClass bc , BtRigidBodyClass p2 , BtRigidBodyClass p4 ) => (bc) -- ^ 
 -> (Float) -- ^ timeStep
 -> (Float) -- ^ jacDiagABInv
 -> (p2) -- ^ body1
 -> (p4) -- ^ body2
 -> (Int) -- ^ limit_index
 -> IO ((Float), (Vec3), (Vec3), (Vec3), (Vec3))
btTranslationalLimitMotor_solveLinearAxis' a1 a2 a3 a4 a6 a8 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  withBt a4 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  withBt a6 $ \a6' -> 
  allocaVec3 $ \a7' -> 
  let {a8' = fromIntegral a8} in 
  allocaVec3 $ \a9' -> 
  allocaVec3 $ \a10' -> 
  btTranslationalLimitMotor_solveLinearAxis''_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
  let {res' = realToFrac res} in
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a9'>>= \a9'' -> 
  peekVec3  a10'>>= \a10'' -> 
  return (res', a5'', a7'', a9'', a10'')

{-# LINE 4910 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#202>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_isLimited :: ( BtTranslationalLimitMotorClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ limitIndex
 -> IO ((Bool))
btTranslationalLimitMotor_isLimited a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTranslationalLimitMotor_isLimited'_ a1' a2' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 4916 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#137>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_accumulatedImpulse_set :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> (Vec3) -> IO ()
btTranslationalLimitMotor_m_accumulatedImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btTranslationalLimitMotor_m_accumulatedImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 4920 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#137>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_accumulatedImpulse_get :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ((Vec3))
btTranslationalLimitMotor_m_accumulatedImpulse_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btTranslationalLimitMotor_m_accumulatedImpulse_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4924 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#150>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_currentLimitError_set :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> (Vec3) -> IO ()
btTranslationalLimitMotor_m_currentLimitError_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btTranslationalLimitMotor_m_currentLimitError_set'_ a1' a2' >>
  return ()

{-# LINE 4928 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#150>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_currentLimitError_get :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ((Vec3))
btTranslationalLimitMotor_m_currentLimitError_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btTranslationalLimitMotor_m_currentLimitError_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4932 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#151>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_currentLinearDiff_set :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> (Vec3) -> IO ()
btTranslationalLimitMotor_m_currentLinearDiff_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btTranslationalLimitMotor_m_currentLinearDiff_set'_ a1' a2' >>
  return ()

{-# LINE 4936 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#151>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_currentLinearDiff_get :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ((Vec3))
btTranslationalLimitMotor_m_currentLinearDiff_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btTranslationalLimitMotor_m_currentLinearDiff_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4940 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_damping_set :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btTranslationalLimitMotor_m_damping_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTranslationalLimitMotor_m_damping_set'_ a1' a2' >>
  return ()

{-# LINE 4944 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_damping_get :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btTranslationalLimitMotor_m_damping_get a1 =
  withBt a1 $ \a1' -> 
  btTranslationalLimitMotor_m_damping_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4948 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#140>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_limitSoftness_set :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btTranslationalLimitMotor_m_limitSoftness_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTranslationalLimitMotor_m_limitSoftness_set'_ a1' a2' >>
  return ()

{-# LINE 4952 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#140>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_limitSoftness_get :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btTranslationalLimitMotor_m_limitSoftness_get a1 =
  withBt a1 $ \a1' -> 
  btTranslationalLimitMotor_m_limitSoftness_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4956 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#135>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_lowerLimit_set :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> (Vec3) -> IO ()
btTranslationalLimitMotor_m_lowerLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btTranslationalLimitMotor_m_lowerLimit_set'_ a1' a2' >>
  return ()

{-# LINE 4960 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#135>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_lowerLimit_get :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ((Vec3))
btTranslationalLimitMotor_m_lowerLimit_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btTranslationalLimitMotor_m_lowerLimit_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4964 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#149>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_maxMotorForce_set :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> (Vec3) -> IO ()
btTranslationalLimitMotor_m_maxMotorForce_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btTranslationalLimitMotor_m_maxMotorForce_set'_ a1' a2' >>
  return ()

{-# LINE 4968 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#149>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_maxMotorForce_get :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ((Vec3))
btTranslationalLimitMotor_m_maxMotorForce_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btTranslationalLimitMotor_m_maxMotorForce_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4972 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#143>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_normalCFM_set :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> (Vec3) -> IO ()
btTranslationalLimitMotor_m_normalCFM_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btTranslationalLimitMotor_m_normalCFM_set'_ a1' a2' >>
  return ()

{-# LINE 4976 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#143>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_normalCFM_get :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ((Vec3))
btTranslationalLimitMotor_m_normalCFM_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btTranslationalLimitMotor_m_normalCFM_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4980 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#142>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_restitution_set :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> (Float) -> IO ()
btTranslationalLimitMotor_m_restitution_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTranslationalLimitMotor_m_restitution_set'_ a1' a2' >>
  return ()

{-# LINE 4984 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#142>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_restitution_get :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ((Float))
btTranslationalLimitMotor_m_restitution_get a1 =
  withBt a1 $ \a1' -> 
  btTranslationalLimitMotor_m_restitution_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 4988 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#145>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_stopCFM_set :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> (Vec3) -> IO ()
btTranslationalLimitMotor_m_stopCFM_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btTranslationalLimitMotor_m_stopCFM_set'_ a1' a2' >>
  return ()

{-# LINE 4992 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#145>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_stopCFM_get :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ((Vec3))
btTranslationalLimitMotor_m_stopCFM_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btTranslationalLimitMotor_m_stopCFM_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 4996 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#144>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_stopERP_set :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> (Vec3) -> IO ()
btTranslationalLimitMotor_m_stopERP_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btTranslationalLimitMotor_m_stopERP_set'_ a1' a2' >>
  return ()

{-# LINE 5000 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#144>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_stopERP_get :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ((Vec3))
btTranslationalLimitMotor_m_stopERP_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btTranslationalLimitMotor_m_stopERP_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 5004 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_targetVelocity_set :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> (Vec3) -> IO ()
btTranslationalLimitMotor_m_targetVelocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btTranslationalLimitMotor_m_targetVelocity_set'_ a1' a2' >>
  return ()

{-# LINE 5008 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_targetVelocity_get :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ((Vec3))
btTranslationalLimitMotor_m_targetVelocity_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btTranslationalLimitMotor_m_targetVelocity_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 5012 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_upperLimit_set :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> (Vec3) -> IO ()
btTranslationalLimitMotor_m_upperLimit_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btTranslationalLimitMotor_m_upperLimit_set'_ a1' a2' >>
  return ()

{-# LINE 5016 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btGeneric6DofConstraint.cpp?r=2223>
-}
btTranslationalLimitMotor_m_upperLimit_get :: ( BtTranslationalLimitMotorClass bc ) => (bc) -> IO ((Vec3))
btTranslationalLimitMotor_m_upperLimit_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btTranslationalLimitMotor_m_upperLimit_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 5020 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btTypedConstraint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#192>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getRigidBodyB :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btTypedConstraint_getRigidBodyB a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_getRigidBodyB'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 5026 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#192>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getRigidBodyB0 :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btTypedConstraint_getRigidBodyB0 a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_getRigidBodyB0'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 5031 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#201>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getRigidBodyB1 :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btTypedConstraint_getRigidBodyB1 a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_getRigidBodyB1'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 5036 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#134>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_buildJacobian :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ()
btTypedConstraint_buildJacobian a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_buildJacobian'_ a1' >>
  return ()

{-# LINE 5041 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#188>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getRigidBodyA :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btTypedConstraint_getRigidBodyA a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_getRigidBodyA'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 5046 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#188>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getRigidBodyA0 :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btTypedConstraint_getRigidBodyA0 a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_getRigidBodyA0'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 5051 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#197>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getRigidBodyA1 :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((BtRigidBody))
btTypedConstraint_getRigidBodyA1 a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_getRigidBodyA1'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 5056 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#285>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_serialize :: ( BtTypedConstraintClass bc , BtSerializerClass p1 ) => (bc) -- ^ 
 -> (VoidPtr) -- ^ dataBuffer
 -> (p1) -- ^ serializer
 -> IO ((String))
btTypedConstraint_serialize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btTypedConstraint_serialize'_ a1' a2' a3' >>= \res ->
  C2HSImp.peekCString res >>= \res' ->
  return (res')

{-# LINE 5063 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#248>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_enableFeedback :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ needsFeedback
 -> IO ()
btTypedConstraint_enableFeedback a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btTypedConstraint_enableFeedback'_ a1' a2' >>
  return ()

{-# LINE 5069 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#221>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getUserConstraintId :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btTypedConstraint_getUserConstraintId a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_getUserConstraintId'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 5074 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#277>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_setParam :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ num
 -> (Float) -- ^ value
 -> (Int) -- ^ axis
 -> IO ()
btTypedConstraint_setParam a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = fromIntegral a4} in 
  btTypedConstraint_setParam'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 5082 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#280>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getParam :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ num
 -> (Int) -- ^ axis
 -> IO ((Float))
btTypedConstraint_getParam a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btTypedConstraint_getParam'_ a1' a2' a3' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 5089 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#146>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getInfo1 :: ( BtTypedConstraintClass bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btTypedConstraint_getInfo1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btTypedConstraint_getInfo1'_ a1' a2' >>
  return ()

{-# LINE 5095 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#149>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getInfo2 :: ( BtTypedConstraintClass bc , BtTypedConstraint_btConstraintInfo2Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ info
 -> IO ()
btTypedConstraint_getInfo2 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btTypedConstraint_getInfo2'_ a1' a2' >>
  return ()

{-# LINE 5101 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#168>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_setBreakingImpulseThreshold :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ threshold
 -> IO ()
btTypedConstraint_setBreakingImpulseThreshold a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTypedConstraint_setBreakingImpulseThreshold'_ a1' a2' >>
  return ()

{-# LINE 5107 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#87>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getFixedBody :: ( ) => IO ((BtRigidBody))
btTypedConstraint_getFixedBody =
  btTypedConstraint_getFixedBody'_ >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 5111 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#335>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_calculateSerializeBufferSize :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btTypedConstraint_calculateSerializeBufferSize a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_calculateSerializeBufferSize'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 5116 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#173>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_isEnabled :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btTypedConstraint_isEnabled a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_isEnabled'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 5121 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#216>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_setUserConstraintId :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ uid
 -> IO ()
btTypedConstraint_setUserConstraintId a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTypedConstraint_setUserConstraintId'_ a1' a2' >>
  return ()

{-# LINE 5127 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#85>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getMotorFactor :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ pos
 -> (Float) -- ^ lowLim
 -> (Float) -- ^ uppLim
 -> (Float) -- ^ vel
 -> (Float) -- ^ timeFact
 -> IO ((Float))
btTypedConstraint_getMotorFactor a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  btTypedConstraint_getMotorFactor'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 5137 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getDbgDrawSize :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btTypedConstraint_getDbgDrawSize a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_getDbgDrawSize'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 5142 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#152>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_internalSetAppliedImpulse :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ appliedImpulse
 -> IO ()
btTypedConstraint_internalSetAppliedImpulse a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTypedConstraint_internalSetAppliedImpulse'_ a1' a2' >>
  return ()

{-# LINE 5148 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#241>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_needsFeedback :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Bool))
btTypedConstraint_needsFeedback a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_needsFeedback'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 5153 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#231>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getUserConstraintPtr :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((VoidPtr))
btTypedConstraint_getUserConstraintPtr a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_getUserConstraintPtr'_ a1' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')

{-# LINE 5158 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#178>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_setEnabled :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ enabled
 -> IO ()
btTypedConstraint_setEnabled a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btTypedConstraint_setEnabled'_ a1' a2' >>
  return ()

{-# LINE 5164 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#236>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getUid :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btTypedConstraint_getUid a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_getUid'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 5169 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#266>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_setDbgDrawSize :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dbgDrawSize
 -> IO ()
btTypedConstraint_setDbgDrawSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTypedConstraint_setDbgDrawSize'_ a1' a2' >>
  return ()

{-# LINE 5175 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#211>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_setUserConstraintType :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ userConstraintType
 -> IO ()
btTypedConstraint_setUserConstraintType a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTypedConstraint_setUserConstraintType'_ a1' a2' >>
  return ()

{-# LINE 5181 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#157>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_internalGetAppliedImpulse :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btTypedConstraint_internalGetAppliedImpulse a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_internalGetAppliedImpulse'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 5186 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#137>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_setupSolverConstraint :: ( BtTypedConstraintClass bc , BtAlignedObjectArray_btSolverConstraint_Class p0 ) => (bc) -- ^ 
 -> (p0) -- ^ ca
 -> (Int) -- ^ solverBodyA
 -> (Int) -- ^ solverBodyB
 -> (Float) -- ^ timeStep
 -> IO ()
btTypedConstraint_setupSolverConstraint a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = realToFrac a5} in 
  btTypedConstraint_setupSolverConstraint'_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 5195 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#163>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getBreakingImpulseThreshold :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btTypedConstraint_getBreakingImpulseThreshold a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_getBreakingImpulseThreshold'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 5200 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#206>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getUserConstraintType :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btTypedConstraint_getUserConstraintType a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_getUserConstraintType'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 5205 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#185>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_solveConstraintObsolete :: ( BtTypedConstraintClass bc , BtRigidBodyClass p0 , BtRigidBodyClass p1 ) => (bc) -- ^ 
 -> (p0) -- ^ arg0
 -> (p1) -- ^ arg1
 -> (Float) -- ^ arg2
 -> IO ()
btTypedConstraint_solveConstraintObsolete a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  btTypedConstraint_solveConstraintObsolete'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 5213 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#255>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_getAppliedImpulse :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btTypedConstraint_getAppliedImpulse a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_getAppliedImpulse'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 5218 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#226>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_setUserConstraintPtr :: ( BtTypedConstraintClass bc ) => (bc) -- ^ 
 -> (VoidPtr) -- ^ ptr
 -> IO ()
btTypedConstraint_setUserConstraintPtr a1 a2 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  btTypedConstraint_setUserConstraintPtr'_ a1' a2' >>
  return ()

{-# LINE 5224 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_appliedImpulse_set :: ( BtTypedConstraintClass bc ) => (bc) -> (Float) -> IO ()
btTypedConstraint_m_appliedImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTypedConstraint_m_appliedImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 5228 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_appliedImpulse_get :: ( BtTypedConstraintClass bc ) => (bc) -> IO ((Float))
btTypedConstraint_m_appliedImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_m_appliedImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 5232 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#65>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_breakingImpulseThreshold_set :: ( BtTypedConstraintClass bc ) => (bc) -> (Float) -> IO ()
btTypedConstraint_m_breakingImpulseThreshold_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTypedConstraint_m_breakingImpulseThreshold_set'_ a1' a2' >>
  return ()

{-# LINE 5236 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#65>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_breakingImpulseThreshold_get :: ( BtTypedConstraintClass bc ) => (bc) -> IO ((Float))
btTypedConstraint_m_breakingImpulseThreshold_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_m_breakingImpulseThreshold_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 5240 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_dbgDrawSize_set :: ( BtTypedConstraintClass bc ) => (bc) -> (Float) -> IO ()
btTypedConstraint_m_dbgDrawSize_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTypedConstraint_m_dbgDrawSize_set'_ a1' a2' >>
  return ()

{-# LINE 5244 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_dbgDrawSize_get :: ( BtTypedConstraintClass bc ) => (bc) -> IO ((Float))
btTypedConstraint_m_dbgDrawSize_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_m_dbgDrawSize_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 5248 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_isEnabled_set :: ( BtTypedConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btTypedConstraint_m_isEnabled_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btTypedConstraint_m_isEnabled_set'_ a1' a2' >>
  return ()

{-# LINE 5252 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_isEnabled_get :: ( BtTypedConstraintClass bc ) => (bc) -> IO ((Bool))
btTypedConstraint_m_isEnabled_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_m_isEnabled_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 5256 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#69>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_needsFeedback_set :: ( BtTypedConstraintClass bc ) => (bc) -> (Bool) -> IO ()
btTypedConstraint_m_needsFeedback_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btTypedConstraint_m_needsFeedback_set'_ a1' a2' >>
  return ()

{-# LINE 5260 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#69>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_needsFeedback_get :: ( BtTypedConstraintClass bc ) => (bc) -> IO ((Bool))
btTypedConstraint_m_needsFeedback_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_m_needsFeedback_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 5264 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#79>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_rbA_set :: ( BtTypedConstraintClass bc , BtRigidBodyClass a ) => (bc) -> (a) -> IO ()
btTypedConstraint_m_rbA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btTypedConstraint_m_rbA_set'_ a1' a2' >>
  return ()

{-# LINE 5268 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#79>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_rbA_get :: ( BtTypedConstraintClass bc ) => (bc) -> IO ((BtRigidBody))
btTypedConstraint_m_rbA_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_m_rbA_get'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 5272 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_rbB_set :: ( BtTypedConstraintClass bc , BtRigidBodyClass a ) => (bc) -> (a) -> IO ()
btTypedConstraint_m_rbB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btTypedConstraint_m_rbB_set'_ a1' a2' >>
  return ()

{-# LINE 5276 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_rbB_get :: ( BtTypedConstraintClass bc ) => (bc) -> IO ((BtRigidBody))
btTypedConstraint_m_rbB_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_m_rbB_get'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 5280 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_userConstraintType_set :: ( BtTypedConstraintClass bc ) => (bc) -> (Int) -> IO ()
btTypedConstraint_m_userConstraintType_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTypedConstraint_m_userConstraintType_set'_ a1' a2' >>
  return ()

{-# LINE 5284 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraint_m_userConstraintType_get :: ( BtTypedConstraintClass bc ) => (bc) -> IO ((Int))
btTypedConstraint_m_userConstraintType_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraint_m_userConstraintType_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 5288 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btTypedConstraintData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#317>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData :: IO ((BtTypedConstraintData))
btTypedConstraintData =
  btTypedConstraintData'_ >>= \res ->
  mkBtTypedConstraintData res >>= \res' ->
  return (res')

{-# LINE 5293 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btTypedConstraintData_free :: ( BtTypedConstraintDataClass bc ) => (bc) -> IO ()
btTypedConstraintData_free a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraintData_free'_ a1' >>
  return ()

{-# LINE 5294 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#327>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_appliedImpulse_set :: ( BtTypedConstraintDataClass bc ) => (bc) -> (Float) -> IO ()
btTypedConstraintData_m_appliedImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTypedConstraintData_m_appliedImpulse_set'_ a1' a2' >>
  return ()

{-# LINE 5298 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#327>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_appliedImpulse_get :: ( BtTypedConstraintDataClass bc ) => (bc) -> IO ((Float))
btTypedConstraintData_m_appliedImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraintData_m_appliedImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 5302 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#328>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_dbgDrawSize_set :: ( BtTypedConstraintDataClass bc ) => (bc) -> (Float) -> IO ()
btTypedConstraintData_m_dbgDrawSize_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btTypedConstraintData_m_dbgDrawSize_set'_ a1' a2' >>
  return ()

{-# LINE 5306 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#328>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_dbgDrawSize_get :: ( BtTypedConstraintDataClass bc ) => (bc) -> IO ((Float))
btTypedConstraintData_m_dbgDrawSize_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraintData_m_dbgDrawSize_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 5310 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#330>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_disableCollisionsBetweenLinkedBodies_set :: ( BtTypedConstraintDataClass bc ) => (bc) -> (Int) -> IO ()
btTypedConstraintData_m_disableCollisionsBetweenLinkedBodies_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTypedConstraintData_m_disableCollisionsBetweenLinkedBodies_set'_ a1' a2' >>
  return ()

{-# LINE 5314 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#330>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_disableCollisionsBetweenLinkedBodies_get :: ( BtTypedConstraintDataClass bc ) => (bc) -> IO ((Int))
btTypedConstraintData_m_disableCollisionsBetweenLinkedBodies_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraintData_m_disableCollisionsBetweenLinkedBodies_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 5318 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#320>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_name_set :: ( BtTypedConstraintDataClass bc ) => (bc) -> (String) -> IO ()
btTypedConstraintData_m_name_set a1 a2 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  btTypedConstraintData_m_name_set'_ a1' a2' >>
  return ()

{-# LINE 5322 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#320>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_name_get :: ( BtTypedConstraintDataClass bc ) => (bc) -> IO ((String))
btTypedConstraintData_m_name_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraintData_m_name_get'_ a1' >>= \res ->
  C2HSImp.peekCString res >>= \res' ->
  return (res')

{-# LINE 5326 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#325>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_needsFeedback_set :: ( BtTypedConstraintDataClass bc ) => (bc) -> (Int) -> IO ()
btTypedConstraintData_m_needsFeedback_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTypedConstraintData_m_needsFeedback_set'_ a1' a2' >>
  return ()

{-# LINE 5330 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#325>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_needsFeedback_get :: ( BtTypedConstraintDataClass bc ) => (bc) -> IO ((Int))
btTypedConstraintData_m_needsFeedback_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraintData_m_needsFeedback_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 5334 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#322>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_objectType_set :: ( BtTypedConstraintDataClass bc ) => (bc) -> (Int) -> IO ()
btTypedConstraintData_m_objectType_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTypedConstraintData_m_objectType_set'_ a1' a2' >>
  return ()

{-# LINE 5338 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#322>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_objectType_get :: ( BtTypedConstraintDataClass bc ) => (bc) -> IO ((Int))
btTypedConstraintData_m_objectType_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraintData_m_objectType_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 5342 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#318>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_rbA_set :: ( BtTypedConstraintDataClass bc , BtRigidBodyFloatDataClass a ) => (bc) -> (a) -> IO ()
btTypedConstraintData_m_rbA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btTypedConstraintData_m_rbA_set'_ a1' a2' >>
  return ()

{-# LINE 5346 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#318>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_rbA_get :: ( BtTypedConstraintDataClass bc ) => (bc) -> IO ((BtRigidBodyFloatData))
btTypedConstraintData_m_rbA_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraintData_m_rbA_get'_ a1' >>= \res ->
  mkBtRigidBodyFloatData res >>= \res' ->
  return (res')

{-# LINE 5350 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#319>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_rbB_set :: ( BtTypedConstraintDataClass bc , BtRigidBodyFloatDataClass a ) => (bc) -> (a) -> IO ()
btTypedConstraintData_m_rbB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btTypedConstraintData_m_rbB_set'_ a1' a2' >>
  return ()

{-# LINE 5354 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#319>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_rbB_get :: ( BtTypedConstraintDataClass bc ) => (bc) -> IO ((BtRigidBodyFloatData))
btTypedConstraintData_m_rbB_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraintData_m_rbB_get'_ a1' >>= \res ->
  mkBtRigidBodyFloatData res >>= \res' ->
  return (res')

{-# LINE 5358 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#324>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_userConstraintId_set :: ( BtTypedConstraintDataClass bc ) => (bc) -> (Int) -> IO ()
btTypedConstraintData_m_userConstraintId_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTypedConstraintData_m_userConstraintId_set'_ a1' a2' >>
  return ()

{-# LINE 5362 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#324>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_userConstraintId_get :: ( BtTypedConstraintDataClass bc ) => (bc) -> IO ((Int))
btTypedConstraintData_m_userConstraintId_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraintData_m_userConstraintId_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 5366 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#323>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_userConstraintType_set :: ( BtTypedConstraintDataClass bc ) => (bc) -> (Int) -> IO ()
btTypedConstraintData_m_userConstraintType_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTypedConstraintData_m_userConstraintType_set'_ a1' a2' >>
  return ()

{-# LINE 5370 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.h?r=2223#323>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btTypedConstraint.cpp?r=2223>
-}
btTypedConstraintData_m_userConstraintType_get :: ( BtTypedConstraintDataClass bc ) => (bc) -> IO ((Int))
btTypedConstraintData_m_userConstraintType_get a1 =
  withBt a1 $ \a1' -> 
  btTypedConstraintData_m_userConstraintType_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 5374 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

-- * btUniversalConstraint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#44>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint :: ( BtRigidBodyClass p0 , BtRigidBodyClass p1 ) => (p0) -> (p1) -> (Vec3) -> (Vec3) -> (Vec3) -> IO ((BtUniversalConstraint))
btUniversalConstraint a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btUniversalConstraint'_ a1' a2' a3' a4' a5' >>= \res ->
  mkBtUniversalConstraint res >>= \res' ->
  return (res')

{-# LINE 5379 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

btUniversalConstraint_free :: ( BtUniversalConstraintClass bc ) => (bc) -> IO ()
btUniversalConstraint_free a1 =
  withBt a1 $ \a1' -> 
  btUniversalConstraint_free'_ a1' >>
  return ()

{-# LINE 5380 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_setLowerLimit :: ( BtUniversalConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ ang1min
 -> (Float) -- ^ ang2min
 -> IO ()
btUniversalConstraint_setLowerLimit a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btUniversalConstraint_setLowerLimit'_ a1' a2' a3' >>
  return ()

{-# LINE 5387 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#47>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_getAnchor2 :: ( BtUniversalConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btUniversalConstraint_getAnchor2 a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btUniversalConstraint_getAnchor2'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 5393 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#56>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_setAxis :: ( BtUniversalConstraintClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ axis1
 -> (Vec3) -- ^ axis2
 -> IO ((Vec3), (Vec3))
btUniversalConstraint_setAxis a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btUniversalConstraint_setAxis'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 5400 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#56>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_setAxis' :: ( BtUniversalConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3), (Vec3))
btUniversalConstraint_setAxis' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btUniversalConstraint_setAxis''_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 5407 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_getAxis1 :: ( BtUniversalConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btUniversalConstraint_getAxis1 a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btUniversalConstraint_getAxis1'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 5413 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#46>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_getAnchor :: ( BtUniversalConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btUniversalConstraint_getAnchor a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btUniversalConstraint_getAnchor'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 5419 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#49>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_getAxis2 :: ( BtUniversalConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btUniversalConstraint_getAxis2 a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btUniversalConstraint_getAxis2'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 5425 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#53>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_setUpperLimit :: ( BtUniversalConstraintClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ ang1max
 -> (Float) -- ^ ang2max
 -> IO ()
btUniversalConstraint_setUpperLimit a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btUniversalConstraint_setUpperLimit'_ a1' a2' a3' >>
  return ()

{-# LINE 5432 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_getAngle2 :: ( BtUniversalConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btUniversalConstraint_getAngle2 a1 =
  withBt a1 $ \a1' -> 
  btUniversalConstraint_getAngle2'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 5437 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_getAngle1 :: ( BtUniversalConstraintClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btUniversalConstraint_getAngle1 a1 =
  withBt a1 $ \a1' -> 
  btUniversalConstraint_getAngle1'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 5442 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#37>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_m_anchor_set :: ( BtUniversalConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btUniversalConstraint_m_anchor_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btUniversalConstraint_m_anchor_set'_ a1' a2' >>
  return ()

{-# LINE 5446 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#37>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_m_anchor_get :: ( BtUniversalConstraintClass bc ) => (bc) -> IO ((Vec3))
btUniversalConstraint_m_anchor_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btUniversalConstraint_m_anchor_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 5450 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#38>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_m_axis1_set :: ( BtUniversalConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btUniversalConstraint_m_axis1_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btUniversalConstraint_m_axis1_set'_ a1' a2' >>
  return ()

{-# LINE 5454 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#38>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_m_axis1_get :: ( BtUniversalConstraintClass bc ) => (bc) -> IO ((Vec3))
btUniversalConstraint_m_axis1_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btUniversalConstraint_m_axis1_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 5458 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#39>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_m_axis2_set :: ( BtUniversalConstraintClass bc ) => (bc) -> (Vec3) -> IO ()
btUniversalConstraint_m_axis2_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btUniversalConstraint_m_axis2_set'_ a1' a2' >>
  return ()

{-# LINE 5462 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.h?r=2223#39>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletDynamics/ConstraintSolver/btUniversalConstraint.cpp?r=2223>
-}
btUniversalConstraint_m_axis2_get :: ( BtUniversalConstraintClass bc ) => (bc) -> IO ((Vec3))
btUniversalConstraint_m_axis2_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btUniversalConstraint_m_axis2_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 5466 "./Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs" #-}


foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_new"
  btAngularLimit'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_free"
  btAngularLimit_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_getCorrection"
  btAngularLimit_getCorrection'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_set"
  btAngularLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_getError"
  btAngularLimit_getError'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_isLimit"
  btAngularLimit_isLimit'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_getSign"
  btAngularLimit_getSign'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_getBiasFactor"
  btAngularLimit_getBiasFactor'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_getSoftness"
  btAngularLimit_getSoftness'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_getHigh"
  btAngularLimit_getHigh'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_getHalfRange"
  btAngularLimit_getHalfRange'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_getLow"
  btAngularLimit_getLow'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_getRelaxationFactor"
  btAngularLimit_getRelaxationFactor'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_center_set"
  btAngularLimit_m_center_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_center_get"
  btAngularLimit_m_center_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_halfRange_set"
  btAngularLimit_m_halfRange_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_halfRange_get"
  btAngularLimit_m_halfRange_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_softness_set"
  btAngularLimit_m_softness_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_softness_get"
  btAngularLimit_m_softness_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_biasFactor_set"
  btAngularLimit_m_biasFactor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_biasFactor_get"
  btAngularLimit_m_biasFactor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_relaxationFactor_set"
  btAngularLimit_m_relaxationFactor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_relaxationFactor_get"
  btAngularLimit_m_relaxationFactor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_correction_set"
  btAngularLimit_m_correction_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_correction_get"
  btAngularLimit_m_correction_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_sign_set"
  btAngularLimit_m_sign_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_sign_get"
  btAngularLimit_m_sign_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_solveLimit_set"
  btAngularLimit_m_solveLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btAngularLimit_m_solveLimit_get"
  btAngularLimit_m_solveLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_new0"
  btConeTwistConstraint0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO (C2HSImp.Ptr ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_new1"
  btConeTwistConstraint1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO (C2HSImp.Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_free"
  btConeTwistConstraint_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getRigidBodyB"
  btConeTwistConstraint_getRigidBodyB'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_buildJacobian"
  btConeTwistConstraint_buildJacobian'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getRigidBodyA"
  btConeTwistConstraint_getRigidBodyA'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_adjustSwingAxisToUseEllipseNormal"
  btConeTwistConstraint_adjustSwingAxisToUseEllipseNormal'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_adjustSwingAxisToUseEllipseNormal"
  btConeTwistConstraint_adjustSwingAxisToUseEllipseNormal''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_isPastSwingLimit"
  btConeTwistConstraint_isPastSwingLimit'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getFrameOffsetA"
  btConeTwistConstraint_getFrameOffsetA'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getFrameOffsetB"
  btConeTwistConstraint_getFrameOffsetB'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getInfo2NonVirtual"
  btConeTwistConstraint_getInfo2NonVirtual'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getInfo2NonVirtual"
  btConeTwistConstraint_getInfo2NonVirtual''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getSwingSpan1"
  btConeTwistConstraint_getSwingSpan1'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_calcAngleInfo2"
  btConeTwistConstraint_calcAngleInfo2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_calcAngleInfo2"
  btConeTwistConstraint_calcAngleInfo2''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getParam"
  btConeTwistConstraint_getParam'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CFloat))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setDamping"
  btConeTwistConstraint_setDamping'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getInfo1"
  btConeTwistConstraint_getInfo1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getInfo2"
  btConeTwistConstraint_getInfo2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setParam"
  btConeTwistConstraint_setParam'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (C2HSImp.CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_calculateSerializeBufferSize"
  btConeTwistConstraint_calculateSerializeBufferSize'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_init"
  btConeTwistConstraint_init'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getTwistAngle"
  btConeTwistConstraint_getTwistAngle'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setMaxMotorImpulseNormalized"
  btConeTwistConstraint_setMaxMotorImpulseNormalized'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getSolveTwistLimit"
  btConeTwistConstraint_getSolveTwistLimit'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_enableMotor"
  btConeTwistConstraint_enableMotor'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getBFrame"
  btConeTwistConstraint_getBFrame'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getInfo1NonVirtual"
  btConeTwistConstraint_getInfo1NonVirtual'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_serialize"
  btConeTwistConstraint_serialize'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getFixThresh"
  btConeTwistConstraint_getFixThresh'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getSolveSwingLimit"
  btConeTwistConstraint_getSolveSwingLimit'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getSwingSpan2"
  btConeTwistConstraint_getSwingSpan2'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setAngularOnly"
  btConeTwistConstraint_setAngularOnly'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setFrames"
  btConeTwistConstraint_setFrames'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setFrames"
  btConeTwistConstraint_setFrames''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setLimit0"
  btConeTwistConstraint_setLimit'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setLimit0"
  btConeTwistConstraint_setLimit0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setLimit1"
  btConeTwistConstraint_setLimit1'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getTwistLimitSign"
  btConeTwistConstraint_getTwistLimitSign'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setMaxMotorImpulse"
  btConeTwistConstraint_setMaxMotorImpulse'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_calcAngleInfo"
  btConeTwistConstraint_calcAngleInfo'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setMotorTarget"
  btConeTwistConstraint_setMotorTarget'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setMotorTarget"
  btConeTwistConstraint_setMotorTarget''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setFixThresh"
  btConeTwistConstraint_setFixThresh'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setMotorTargetInConstraintSpace"
  btConeTwistConstraint_setMotorTargetInConstraintSpace'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_setMotorTargetInConstraintSpace"
  btConeTwistConstraint_setMotorTargetInConstraintSpace''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_solveConstraintObsolete"
  btConeTwistConstraint_solveConstraintObsolete'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_GetPointForAngle"
  btConeTwistConstraint_GetPointForAngle'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_updateRHS"
  btConeTwistConstraint_updateRHS'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getTwistSpan"
  btConeTwistConstraint_getTwistSpan'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_getAFrame"
  btConeTwistConstraint_getAFrame'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_rbAFrame_set"
  btConeTwistConstraint_m_rbAFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_rbAFrame_get"
  btConeTwistConstraint_m_rbAFrame_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_rbBFrame_set"
  btConeTwistConstraint_m_rbBFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_rbBFrame_get"
  btConeTwistConstraint_m_rbBFrame_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_limitSoftness_set"
  btConeTwistConstraint_m_limitSoftness_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_limitSoftness_get"
  btConeTwistConstraint_m_limitSoftness_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_biasFactor_set"
  btConeTwistConstraint_m_biasFactor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_biasFactor_get"
  btConeTwistConstraint_m_biasFactor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_relaxationFactor_set"
  btConeTwistConstraint_m_relaxationFactor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_relaxationFactor_get"
  btConeTwistConstraint_m_relaxationFactor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_damping_set"
  btConeTwistConstraint_m_damping_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_damping_get"
  btConeTwistConstraint_m_damping_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_swingSpan1_set"
  btConeTwistConstraint_m_swingSpan1_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_swingSpan1_get"
  btConeTwistConstraint_m_swingSpan1_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_swingSpan2_set"
  btConeTwistConstraint_m_swingSpan2_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_swingSpan2_get"
  btConeTwistConstraint_m_swingSpan2_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistSpan_set"
  btConeTwistConstraint_m_twistSpan_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistSpan_get"
  btConeTwistConstraint_m_twistSpan_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_fixThresh_set"
  btConeTwistConstraint_m_fixThresh_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_fixThresh_get"
  btConeTwistConstraint_m_fixThresh_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_swingAxis_set"
  btConeTwistConstraint_m_swingAxis_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_swingAxis_get"
  btConeTwistConstraint_m_swingAxis_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistAxis_set"
  btConeTwistConstraint_m_twistAxis_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistAxis_get"
  btConeTwistConstraint_m_twistAxis_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_kSwing_set"
  btConeTwistConstraint_m_kSwing_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_kSwing_get"
  btConeTwistConstraint_m_kSwing_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_kTwist_set"
  btConeTwistConstraint_m_kTwist_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_kTwist_get"
  btConeTwistConstraint_m_kTwist_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistLimitSign_set"
  btConeTwistConstraint_m_twistLimitSign_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistLimitSign_get"
  btConeTwistConstraint_m_twistLimitSign_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_swingCorrection_set"
  btConeTwistConstraint_m_swingCorrection_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_swingCorrection_get"
  btConeTwistConstraint_m_swingCorrection_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistCorrection_set"
  btConeTwistConstraint_m_twistCorrection_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistCorrection_get"
  btConeTwistConstraint_m_twistCorrection_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistAngle_set"
  btConeTwistConstraint_m_twistAngle_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistAngle_get"
  btConeTwistConstraint_m_twistAngle_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_accSwingLimitImpulse_set"
  btConeTwistConstraint_m_accSwingLimitImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_accSwingLimitImpulse_get"
  btConeTwistConstraint_m_accSwingLimitImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_accTwistLimitImpulse_set"
  btConeTwistConstraint_m_accTwistLimitImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_accTwistLimitImpulse_get"
  btConeTwistConstraint_m_accTwistLimitImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_angularOnly_set"
  btConeTwistConstraint_m_angularOnly_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_angularOnly_get"
  btConeTwistConstraint_m_angularOnly_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_solveTwistLimit_set"
  btConeTwistConstraint_m_solveTwistLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_solveTwistLimit_get"
  btConeTwistConstraint_m_solveTwistLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_solveSwingLimit_set"
  btConeTwistConstraint_m_solveSwingLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_solveSwingLimit_get"
  btConeTwistConstraint_m_solveSwingLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_useSolveConstraintObsolete_set"
  btConeTwistConstraint_m_useSolveConstraintObsolete_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_useSolveConstraintObsolete_get"
  btConeTwistConstraint_m_useSolveConstraintObsolete_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_swingLimitRatio_set"
  btConeTwistConstraint_m_swingLimitRatio_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_swingLimitRatio_get"
  btConeTwistConstraint_m_swingLimitRatio_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistLimitRatio_set"
  btConeTwistConstraint_m_twistLimitRatio_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistLimitRatio_get"
  btConeTwistConstraint_m_twistLimitRatio_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistAxisA_set"
  btConeTwistConstraint_m_twistAxisA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_twistAxisA_get"
  btConeTwistConstraint_m_twistAxisA_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_bMotorEnabled_set"
  btConeTwistConstraint_m_bMotorEnabled_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_bMotorEnabled_get"
  btConeTwistConstraint_m_bMotorEnabled_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_bNormalizedMotorStrength_set"
  btConeTwistConstraint_m_bNormalizedMotorStrength_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_bNormalizedMotorStrength_get"
  btConeTwistConstraint_m_bNormalizedMotorStrength_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_qTarget_set"
  btConeTwistConstraint_m_qTarget_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_qTarget_get"
  btConeTwistConstraint_m_qTarget_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_maxMotorImpulse_set"
  btConeTwistConstraint_m_maxMotorImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_maxMotorImpulse_get"
  btConeTwistConstraint_m_maxMotorImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_accMotorImpulse_set"
  btConeTwistConstraint_m_accMotorImpulse_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_accMotorImpulse_get"
  btConeTwistConstraint_m_accMotorImpulse_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_flags_set"
  btConeTwistConstraint_m_flags_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_flags_get"
  btConeTwistConstraint_m_flags_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_linCFM_set"
  btConeTwistConstraint_m_linCFM_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_linCFM_get"
  btConeTwistConstraint_m_linCFM_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_linERP_set"
  btConeTwistConstraint_m_linERP_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_linERP_get"
  btConeTwistConstraint_m_linERP_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_angCFM_set"
  btConeTwistConstraint_m_angCFM_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraint_m_angCFM_get"
  btConeTwistConstraint_m_angCFM_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_new"
  btConeTwistConstraintData'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_free"
  btConeTwistConstraintData_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_typeConstraintData_set"
  btConeTwistConstraintData_m_typeConstraintData_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_typeConstraintData_get"
  btConeTwistConstraintData_m_typeConstraintData_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_rbAFrame_set"
  btConeTwistConstraintData_m_rbAFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_rbAFrame_get"
  btConeTwistConstraintData_m_rbAFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_rbBFrame_set"
  btConeTwistConstraintData_m_rbBFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_rbBFrame_get"
  btConeTwistConstraintData_m_rbBFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_swingSpan1_set"
  btConeTwistConstraintData_m_swingSpan1_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_swingSpan1_get"
  btConeTwistConstraintData_m_swingSpan1_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_swingSpan2_set"
  btConeTwistConstraintData_m_swingSpan2_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_swingSpan2_get"
  btConeTwistConstraintData_m_swingSpan2_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_twistSpan_set"
  btConeTwistConstraintData_m_twistSpan_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_twistSpan_get"
  btConeTwistConstraintData_m_twistSpan_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_limitSoftness_set"
  btConeTwistConstraintData_m_limitSoftness_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_limitSoftness_get"
  btConeTwistConstraintData_m_limitSoftness_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_biasFactor_set"
  btConeTwistConstraintData_m_biasFactor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_biasFactor_get"
  btConeTwistConstraintData_m_biasFactor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_relaxationFactor_set"
  btConeTwistConstraintData_m_relaxationFactor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_relaxationFactor_get"
  btConeTwistConstraintData_m_relaxationFactor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_damping_set"
  btConeTwistConstraintData_m_damping_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConeTwistConstraintData_m_damping_get"
  btConeTwistConstraintData_m_damping_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo1_new"
  btTypedConstraint_btConstraintInfo1'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo1_free"
  btTypedConstraint_btConstraintInfo1_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo1_m_numConstraintRows_set"
  btTypedConstraint_btConstraintInfo1_m_numConstraintRows_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo1_m_numConstraintRows_get"
  btTypedConstraint_btConstraintInfo1_m_numConstraintRows_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo1_nub_set"
  btTypedConstraint_btConstraintInfo1_nub_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo1_nub_get"
  btTypedConstraint_btConstraintInfo1_nub_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo2_new"
  btTypedConstraint_btConstraintInfo2'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo2_free"
  btTypedConstraint_btConstraintInfo2_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo2_erp_set"
  btTypedConstraint_btConstraintInfo2_erp_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo2_erp_get"
  btTypedConstraint_btConstraintInfo2_erp_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo2_fps_set"
  btTypedConstraint_btConstraintInfo2_fps_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo2_fps_get"
  btTypedConstraint_btConstraintInfo2_fps_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo2_m_damping_set"
  btTypedConstraint_btConstraintInfo2_m_damping_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo2_m_damping_get"
  btTypedConstraint_btConstraintInfo2_m_damping_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo2_m_numIterations_set"
  btTypedConstraint_btConstraintInfo2_m_numIterations_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo2_m_numIterations_get"
  btTypedConstraint_btConstraintInfo2_m_numIterations_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo2_rowskip_set"
  btTypedConstraint_btConstraintInfo2_rowskip_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_btConstraintInfo2_rowskip_get"
  btTypedConstraint_btConstraintInfo2_rowskip_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConstraintSetting_new"
  btConstraintSetting'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConstraintSetting_free"
  btConstraintSetting_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConstraintSetting_m_tau_set"
  btConstraintSetting_m_tau_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConstraintSetting_m_tau_get"
  btConstraintSetting_m_tau_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConstraintSetting_m_damping_set"
  btConstraintSetting_m_damping_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConstraintSetting_m_damping_get"
  btConstraintSetting_m_damping_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConstraintSetting_m_impulseClamp_set"
  btConstraintSetting_m_impulseClamp_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConstraintSetting_m_impulseClamp_get"
  btConstraintSetting_m_impulseClamp_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConstraintSolver_reset"
  btConstraintSolver_reset'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConstraintSolver_allSolved"
  btConstraintSolver_allSolved'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btConstraintSolver_prepareSolve"
  btConstraintSolver_prepareSolve'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactConstraint_getInfo1"
  btContactConstraint_getInfo1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactConstraint_setContactManifold"
  btContactConstraint_setContactManifold'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactConstraint_buildJacobian"
  btContactConstraint_buildJacobian'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactConstraint_getInfo2"
  btContactConstraint_getInfo2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactConstraint_getContactManifold0"
  btContactConstraint_getContactManifold'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactConstraint_getContactManifold0"
  btContactConstraint_getContactManifold0'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactConstraint_getContactManifold1"
  btContactConstraint_getContactManifold1'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactConstraint_m_contactManifold_set"
  btContactConstraint_m_contactManifold_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactConstraint_m_contactManifold_get"
  btContactConstraint_m_contactManifold_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfo_new"
  btContactSolverInfo'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfo_free"
  btContactSolverInfo_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_new"
  btContactSolverInfoData'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_free"
  btContactSolverInfoData_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_tau_set"
  btContactSolverInfoData_m_tau_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_tau_get"
  btContactSolverInfoData_m_tau_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_damping_set"
  btContactSolverInfoData_m_damping_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_damping_get"
  btContactSolverInfoData_m_damping_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_friction_set"
  btContactSolverInfoData_m_friction_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_friction_get"
  btContactSolverInfoData_m_friction_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_timeStep_set"
  btContactSolverInfoData_m_timeStep_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_timeStep_get"
  btContactSolverInfoData_m_timeStep_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_restitution_set"
  btContactSolverInfoData_m_restitution_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_restitution_get"
  btContactSolverInfoData_m_restitution_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_numIterations_set"
  btContactSolverInfoData_m_numIterations_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_numIterations_get"
  btContactSolverInfoData_m_numIterations_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_maxErrorReduction_set"
  btContactSolverInfoData_m_maxErrorReduction_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_maxErrorReduction_get"
  btContactSolverInfoData_m_maxErrorReduction_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_sor_set"
  btContactSolverInfoData_m_sor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_sor_get"
  btContactSolverInfoData_m_sor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_erp_set"
  btContactSolverInfoData_m_erp_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_erp_get"
  btContactSolverInfoData_m_erp_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_erp2_set"
  btContactSolverInfoData_m_erp2_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_erp2_get"
  btContactSolverInfoData_m_erp2_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_globalCfm_set"
  btContactSolverInfoData_m_globalCfm_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_globalCfm_get"
  btContactSolverInfoData_m_globalCfm_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_splitImpulse_set"
  btContactSolverInfoData_m_splitImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_splitImpulse_get"
  btContactSolverInfoData_m_splitImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_splitImpulsePenetrationThreshold_set"
  btContactSolverInfoData_m_splitImpulsePenetrationThreshold_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_splitImpulsePenetrationThreshold_get"
  btContactSolverInfoData_m_splitImpulsePenetrationThreshold_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_linearSlop_set"
  btContactSolverInfoData_m_linearSlop_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_linearSlop_get"
  btContactSolverInfoData_m_linearSlop_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_warmstartingFactor_set"
  btContactSolverInfoData_m_warmstartingFactor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_warmstartingFactor_get"
  btContactSolverInfoData_m_warmstartingFactor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_solverMode_set"
  btContactSolverInfoData_m_solverMode_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_solverMode_get"
  btContactSolverInfoData_m_solverMode_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_restingContactRestitutionThreshold_set"
  btContactSolverInfoData_m_restingContactRestitutionThreshold_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_restingContactRestitutionThreshold_get"
  btContactSolverInfoData_m_restingContactRestitutionThreshold_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_minimumSolverBatchSize_set"
  btContactSolverInfoData_m_minimumSolverBatchSize_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btContactSolverInfoData_m_minimumSolverBatchSize_get"
  btContactSolverInfoData_m_minimumSolverBatchSize_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_new0"
  btGeneric6DofConstraint0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_new1"
  btGeneric6DofConstraint1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_free"
  btGeneric6DofConstraint_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_buildJacobian"
  btGeneric6DofConstraint_buildJacobian'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setParam"
  btGeneric6DofConstraint_setParam'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (C2HSImp.CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getInfo1NonVirtual"
  btGeneric6DofConstraint_getInfo1NonVirtual'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getFrameOffsetA0"
  btGeneric6DofConstraint_getFrameOffsetA'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getFrameOffsetA0"
  btGeneric6DofConstraint_getFrameOffsetA0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getFrameOffsetA1"
  btGeneric6DofConstraint_getFrameOffsetA1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getRelativePivotPosition"
  btGeneric6DofConstraint_getRelativePivotPosition'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CFloat)))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_calculateAngleInfo"
  btGeneric6DofConstraint_calculateAngleInfo'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getInfo2NonVirtual"
  btGeneric6DofConstraint_getInfo2NonVirtual'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getInfo2NonVirtual"
  btGeneric6DofConstraint_getInfo2NonVirtual''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setAngularLimits"
  btGeneric6DofConstraint_setAngularLimits'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CInt))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setAngularLimits"
  btGeneric6DofConstraint_setAngularLimits''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CInt))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getParam"
  btGeneric6DofConstraint_getParam'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CFloat))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getInfo1"
  btGeneric6DofConstraint_getInfo1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getInfo2"
  btGeneric6DofConstraint_getInfo2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_calcAnchorPos"
  btGeneric6DofConstraint_calcAnchorPos'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getAngularLowerLimit"
  btGeneric6DofConstraint_getAngularLowerLimit'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getAngularLowerLimit"
  btGeneric6DofConstraint_getAngularLowerLimit''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_calculateSerializeBufferSize"
  btGeneric6DofConstraint_calculateSerializeBufferSize'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getAxis"
  btGeneric6DofConstraint_getAxis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getLinearUpperLimit"
  btGeneric6DofConstraint_getLinearUpperLimit'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getLinearUpperLimit"
  btGeneric6DofConstraint_getLinearUpperLimit''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setUseFrameOffset"
  btGeneric6DofConstraint_setUseFrameOffset'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_isLimited"
  btGeneric6DofConstraint_isLimited'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getRotationalLimitMotor"
  btGeneric6DofConstraint_getRotationalLimitMotor'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_buildAngularJacobian"
  btGeneric6DofConstraint_buildAngularJacobian'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_buildAngularJacobian"
  btGeneric6DofConstraint_buildAngularJacobian''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getFrameOffsetB0"
  btGeneric6DofConstraint_getFrameOffsetB'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getFrameOffsetB0"
  btGeneric6DofConstraint_getFrameOffsetB0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getFrameOffsetB1"
  btGeneric6DofConstraint_getFrameOffsetB1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setLinearLowerLimit"
  btGeneric6DofConstraint_setLinearLowerLimit'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setLinearLowerLimit"
  btGeneric6DofConstraint_setLinearLowerLimit''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getLinearLowerLimit"
  btGeneric6DofConstraint_getLinearLowerLimit'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getLinearLowerLimit"
  btGeneric6DofConstraint_getLinearLowerLimit''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_buildLinearJacobian"
  btGeneric6DofConstraint_buildLinearJacobian'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_buildLinearJacobian"
  btGeneric6DofConstraint_buildLinearJacobian''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getUseFrameOffset"
  btGeneric6DofConstraint_getUseFrameOffset'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getCalculatedTransformB"
  btGeneric6DofConstraint_getCalculatedTransformB'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_calculateTransforms0"
  btGeneric6DofConstraint_calculateTransforms'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_calculateTransforms0"
  btGeneric6DofConstraint_calculateTransforms''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_calculateTransforms0"
  btGeneric6DofConstraint_calculateTransforms0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_calculateTransforms0"
  btGeneric6DofConstraint_calculateTransforms0''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_calculateTransforms1"
  btGeneric6DofConstraint_calculateTransforms1'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_get_limit_motor_info2"
  btGeneric6DofConstraint_get_limit_motor_info2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_get_limit_motor_info2"
  btGeneric6DofConstraint_get_limit_motor_info2''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getCalculatedTransformA"
  btGeneric6DofConstraint_getCalculatedTransformA'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_serialize"
  btGeneric6DofConstraint_serialize'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setLimit"
  btGeneric6DofConstraint_setLimit'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getTranslationalLimitMotor"
  btGeneric6DofConstraint_getTranslationalLimitMotor'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setLinearLimits"
  btGeneric6DofConstraint_setLinearLimits'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CInt))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setLinearLimits"
  btGeneric6DofConstraint_setLinearLimits''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CInt))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getAngle"
  btGeneric6DofConstraint_getAngle'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CFloat)))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_updateRHS"
  btGeneric6DofConstraint_updateRHS'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getAngularUpperLimit"
  btGeneric6DofConstraint_getAngularUpperLimit'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_getAngularUpperLimit"
  btGeneric6DofConstraint_getAngularUpperLimit''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setAngularLowerLimit"
  btGeneric6DofConstraint_setAngularLowerLimit'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setAngularLowerLimit"
  btGeneric6DofConstraint_setAngularLowerLimit''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_calculateLinearInfo"
  btGeneric6DofConstraint_calculateLinearInfo'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setFrames"
  btGeneric6DofConstraint_setFrames'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setFrames"
  btGeneric6DofConstraint_setFrames''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setLinearUpperLimit"
  btGeneric6DofConstraint_setLinearUpperLimit'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setLinearUpperLimit"
  btGeneric6DofConstraint_setLinearUpperLimit''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setAngularUpperLimit"
  btGeneric6DofConstraint_setAngularUpperLimit'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setAngularUpperLimit"
  btGeneric6DofConstraint_setAngularUpperLimit''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setAxis"
  btGeneric6DofConstraint_setAxis'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_setAxis"
  btGeneric6DofConstraint_setAxis''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_testAngularLimitMotor"
  btGeneric6DofConstraint_testAngularLimitMotor'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_frameInA_set"
  btGeneric6DofConstraint_m_frameInA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_frameInA_get"
  btGeneric6DofConstraint_m_frameInA_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_frameInB_set"
  btGeneric6DofConstraint_m_frameInB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_frameInB_get"
  btGeneric6DofConstraint_m_frameInB_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_linearLimits_set"
  btGeneric6DofConstraint_m_linearLimits_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_linearLimits_get"
  btGeneric6DofConstraint_m_linearLimits_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_timeStep_set"
  btGeneric6DofConstraint_m_timeStep_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_timeStep_get"
  btGeneric6DofConstraint_m_timeStep_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_calculatedTransformA_set"
  btGeneric6DofConstraint_m_calculatedTransformA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_calculatedTransformA_get"
  btGeneric6DofConstraint_m_calculatedTransformA_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_calculatedTransformB_set"
  btGeneric6DofConstraint_m_calculatedTransformB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_calculatedTransformB_get"
  btGeneric6DofConstraint_m_calculatedTransformB_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_calculatedAxisAngleDiff_set"
  btGeneric6DofConstraint_m_calculatedAxisAngleDiff_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_calculatedAxisAngleDiff_get"
  btGeneric6DofConstraint_m_calculatedAxisAngleDiff_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_calculatedLinearDiff_set"
  btGeneric6DofConstraint_m_calculatedLinearDiff_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_calculatedLinearDiff_get"
  btGeneric6DofConstraint_m_calculatedLinearDiff_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_factA_set"
  btGeneric6DofConstraint_m_factA_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_factA_get"
  btGeneric6DofConstraint_m_factA_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_factB_set"
  btGeneric6DofConstraint_m_factB_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_factB_get"
  btGeneric6DofConstraint_m_factB_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_hasStaticBody_set"
  btGeneric6DofConstraint_m_hasStaticBody_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_hasStaticBody_get"
  btGeneric6DofConstraint_m_hasStaticBody_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_AnchorPos_set"
  btGeneric6DofConstraint_m_AnchorPos_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_AnchorPos_get"
  btGeneric6DofConstraint_m_AnchorPos_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_useLinearReferenceFrameA_set"
  btGeneric6DofConstraint_m_useLinearReferenceFrameA_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_useLinearReferenceFrameA_get"
  btGeneric6DofConstraint_m_useLinearReferenceFrameA_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_useOffsetForConstraintFrame_set"
  btGeneric6DofConstraint_m_useOffsetForConstraintFrame_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_useOffsetForConstraintFrame_get"
  btGeneric6DofConstraint_m_useOffsetForConstraintFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_flags_set"
  btGeneric6DofConstraint_m_flags_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_flags_get"
  btGeneric6DofConstraint_m_flags_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_useSolveConstraintObsolete_set"
  btGeneric6DofConstraint_m_useSolveConstraintObsolete_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraint_m_useSolveConstraintObsolete_get"
  btGeneric6DofConstraint_m_useSolveConstraintObsolete_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_new"
  btGeneric6DofConstraintData'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_free"
  btGeneric6DofConstraintData_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_typeConstraintData_set"
  btGeneric6DofConstraintData_m_typeConstraintData_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_typeConstraintData_get"
  btGeneric6DofConstraintData_m_typeConstraintData_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_rbAFrame_set"
  btGeneric6DofConstraintData_m_rbAFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_rbAFrame_get"
  btGeneric6DofConstraintData_m_rbAFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_rbBFrame_set"
  btGeneric6DofConstraintData_m_rbBFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_rbBFrame_get"
  btGeneric6DofConstraintData_m_rbBFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_linearUpperLimit_set"
  btGeneric6DofConstraintData_m_linearUpperLimit_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_linearUpperLimit_get"
  btGeneric6DofConstraintData_m_linearUpperLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_linearLowerLimit_set"
  btGeneric6DofConstraintData_m_linearLowerLimit_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_linearLowerLimit_get"
  btGeneric6DofConstraintData_m_linearLowerLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_angularUpperLimit_set"
  btGeneric6DofConstraintData_m_angularUpperLimit_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_angularUpperLimit_get"
  btGeneric6DofConstraintData_m_angularUpperLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_angularLowerLimit_set"
  btGeneric6DofConstraintData_m_angularLowerLimit_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_angularLowerLimit_get"
  btGeneric6DofConstraintData_m_angularLowerLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_useLinearReferenceFrameA_set"
  btGeneric6DofConstraintData_m_useLinearReferenceFrameA_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_useLinearReferenceFrameA_get"
  btGeneric6DofConstraintData_m_useLinearReferenceFrameA_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_useOffsetForConstraintFrame_set"
  btGeneric6DofConstraintData_m_useOffsetForConstraintFrame_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofConstraintData_m_useOffsetForConstraintFrame_get"
  btGeneric6DofConstraintData_m_useOffsetForConstraintFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_new"
  btGeneric6DofSpringConstraint'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_free"
  btGeneric6DofSpringConstraint_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_calculateSerializeBufferSize"
  btGeneric6DofSpringConstraint_calculateSerializeBufferSize'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_setEquilibriumPoint0"
  btGeneric6DofSpringConstraint_setEquilibriumPoint'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_setEquilibriumPoint0"
  btGeneric6DofSpringConstraint_setEquilibriumPoint0'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_setEquilibriumPoint1"
  btGeneric6DofSpringConstraint_setEquilibriumPoint1'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_setEquilibriumPoint2"
  btGeneric6DofSpringConstraint_setEquilibriumPoint2'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_serialize"
  btGeneric6DofSpringConstraint_serialize'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_enableSpring"
  btGeneric6DofSpringConstraint_enableSpring'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_setStiffness"
  btGeneric6DofSpringConstraint_setStiffness'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_setDamping"
  btGeneric6DofSpringConstraint_setDamping'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_getInfo2"
  btGeneric6DofSpringConstraint_getInfo2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_internalUpdateSprings"
  btGeneric6DofSpringConstraint_internalUpdateSprings'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_setAxis"
  btGeneric6DofSpringConstraint_setAxis'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraint_setAxis"
  btGeneric6DofSpringConstraint_setAxis''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraintData_new"
  btGeneric6DofSpringConstraintData'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraintData_free"
  btGeneric6DofSpringConstraintData_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraintData_m_6dofData_set"
  btGeneric6DofSpringConstraintData_m_6dofData_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btGeneric6DofSpringConstraintData_m_6dofData_get"
  btGeneric6DofSpringConstraintData_m_6dofData_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_new"
  btHinge2Constraint'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO (C2HSImp.Ptr ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_free"
  btHinge2Constraint_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_setLowerLimit"
  btHinge2Constraint_setLowerLimit'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_getAnchor2"
  btHinge2Constraint_getAnchor2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_getAxis1"
  btHinge2Constraint_getAxis1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_getAnchor"
  btHinge2Constraint_getAnchor'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_getAxis2"
  btHinge2Constraint_getAxis2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_setUpperLimit"
  btHinge2Constraint_setUpperLimit'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_getAngle2"
  btHinge2Constraint_getAngle2'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_getAngle1"
  btHinge2Constraint_getAngle1'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_m_anchor_set"
  btHinge2Constraint_m_anchor_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_m_anchor_get"
  btHinge2Constraint_m_anchor_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_m_axis1_set"
  btHinge2Constraint_m_axis1_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_m_axis1_get"
  btHinge2Constraint_m_axis1_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_m_axis2_set"
  btHinge2Constraint_m_axis2_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHinge2Constraint_m_axis2_get"
  btHinge2Constraint_m_axis2_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_new0"
  btHingeConstraint0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_new1"
  btHingeConstraint1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_new2"
  btHingeConstraint2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_new3"
  btHingeConstraint3'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_free"
  btHingeConstraint_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getRigidBodyB0"
  btHingeConstraint_getRigidBodyB'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getRigidBodyB0"
  btHingeConstraint_getRigidBodyB0'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getRigidBodyB1"
  btHingeConstraint_getRigidBodyB1'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getInfo2NonVirtual"
  btHingeConstraint_getInfo2NonVirtual'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getInfo2NonVirtual"
  btHingeConstraint_getInfo2NonVirtual''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getRigidBodyA0"
  btHingeConstraint_getRigidBodyA'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getRigidBodyA0"
  btHingeConstraint_getRigidBodyA0'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getRigidBodyA1"
  btHingeConstraint_getRigidBodyA1'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getMotorTargetVelosity"
  btHingeConstraint_getMotorTargetVelosity'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getFrameOffsetA"
  btHingeConstraint_getFrameOffsetA'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getFrameOffsetB"
  btHingeConstraint_getFrameOffsetB'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_buildJacobian"
  btHingeConstraint_buildJacobian'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setMaxMotorImpulse"
  btHingeConstraint_setMaxMotorImpulse'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getHingeAngle0"
  btHingeConstraint_getHingeAngle'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getHingeAngle0"
  btHingeConstraint_getHingeAngle0'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getHingeAngle1"
  btHingeConstraint_getHingeAngle1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CFloat))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getHingeAngle1"
  btHingeConstraint_getHingeAngle1''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CFloat))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_testLimit"
  btHingeConstraint_testLimit'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_testLimit"
  btHingeConstraint_testLimit''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getInfo1"
  btHingeConstraint_getInfo1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getInfo2Internal"
  btHingeConstraint_getInfo2Internal'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getInfo2Internal"
  btHingeConstraint_getInfo2Internal''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getInfo2"
  btHingeConstraint_getInfo2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getUpperLimit"
  btHingeConstraint_getUpperLimit'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_enableAngularMotor"
  btHingeConstraint_enableAngularMotor'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getLimitSign"
  btHingeConstraint_getLimitSign'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_calculateSerializeBufferSize"
  btHingeConstraint_calculateSerializeBufferSize'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getMaxMotorImpulse"
  btHingeConstraint_getMaxMotorImpulse'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getLowerLimit"
  btHingeConstraint_getLowerLimit'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setParam"
  btHingeConstraint_setParam'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (C2HSImp.CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setUseFrameOffset"
  btHingeConstraint_setUseFrameOffset'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getEnableAngularMotor"
  btHingeConstraint_getEnableAngularMotor'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_enableMotor"
  btHingeConstraint_enableMotor'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getBFrame0"
  btHingeConstraint_getBFrame'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getBFrame0"
  btHingeConstraint_getBFrame0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getBFrame1"
  btHingeConstraint_getBFrame1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getInfo1NonVirtual"
  btHingeConstraint_getInfo1NonVirtual'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getInfo2InternalUsingFrameOffset"
  btHingeConstraint_getInfo2InternalUsingFrameOffset'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getInfo2InternalUsingFrameOffset"
  btHingeConstraint_getInfo2InternalUsingFrameOffset''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_serialize"
  btHingeConstraint_serialize'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getUseFrameOffset"
  btHingeConstraint_getUseFrameOffset'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setAngularOnly"
  btHingeConstraint_setAngularOnly'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getParam"
  btHingeConstraint_getParam'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CFloat))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setLimit"
  btHingeConstraint_setLimit'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getSolveLimit"
  btHingeConstraint_getSolveLimit'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_updateRHS"
  btHingeConstraint_updateRHS'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setMotorTarget0"
  btHingeConstraint_setMotorTarget'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setMotorTarget0"
  btHingeConstraint_setMotorTarget''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setMotorTarget0"
  btHingeConstraint_setMotorTarget0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setMotorTarget0"
  btHingeConstraint_setMotorTarget0''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setMotorTarget1"
  btHingeConstraint_setMotorTarget1'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getAngularOnly"
  btHingeConstraint_getAngularOnly'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setFrames"
  btHingeConstraint_setFrames'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setFrames"
  btHingeConstraint_setFrames''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setAxis"
  btHingeConstraint_setAxis'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_setAxis"
  btHingeConstraint_setAxis''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getAFrame0"
  btHingeConstraint_getAFrame'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getAFrame0"
  btHingeConstraint_getAFrame0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_getAFrame1"
  btHingeConstraint_getAFrame1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_rbAFrame_set"
  btHingeConstraint_m_rbAFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_rbAFrame_get"
  btHingeConstraint_m_rbAFrame_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_rbBFrame_set"
  btHingeConstraint_m_rbBFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_rbBFrame_get"
  btHingeConstraint_m_rbBFrame_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_motorTargetVelocity_set"
  btHingeConstraint_m_motorTargetVelocity_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_motorTargetVelocity_get"
  btHingeConstraint_m_motorTargetVelocity_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_maxMotorImpulse_set"
  btHingeConstraint_m_maxMotorImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_maxMotorImpulse_get"
  btHingeConstraint_m_maxMotorImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_limit_set"
  btHingeConstraint_m_limit_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_limit_get"
  btHingeConstraint_m_limit_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_kHinge_set"
  btHingeConstraint_m_kHinge_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_kHinge_get"
  btHingeConstraint_m_kHinge_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_accLimitImpulse_set"
  btHingeConstraint_m_accLimitImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_accLimitImpulse_get"
  btHingeConstraint_m_accLimitImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_hingeAngle_set"
  btHingeConstraint_m_hingeAngle_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_hingeAngle_get"
  btHingeConstraint_m_hingeAngle_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_referenceSign_set"
  btHingeConstraint_m_referenceSign_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_referenceSign_get"
  btHingeConstraint_m_referenceSign_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_angularOnly_set"
  btHingeConstraint_m_angularOnly_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_angularOnly_get"
  btHingeConstraint_m_angularOnly_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_enableAngularMotor_set"
  btHingeConstraint_m_enableAngularMotor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_enableAngularMotor_get"
  btHingeConstraint_m_enableAngularMotor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_useSolveConstraintObsolete_set"
  btHingeConstraint_m_useSolveConstraintObsolete_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_useSolveConstraintObsolete_get"
  btHingeConstraint_m_useSolveConstraintObsolete_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_useOffsetForConstraintFrame_set"
  btHingeConstraint_m_useOffsetForConstraintFrame_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_useOffsetForConstraintFrame_get"
  btHingeConstraint_m_useOffsetForConstraintFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_useReferenceFrameA_set"
  btHingeConstraint_m_useReferenceFrameA_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_useReferenceFrameA_get"
  btHingeConstraint_m_useReferenceFrameA_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_accMotorImpulse_set"
  btHingeConstraint_m_accMotorImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_accMotorImpulse_get"
  btHingeConstraint_m_accMotorImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_flags_set"
  btHingeConstraint_m_flags_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_flags_get"
  btHingeConstraint_m_flags_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_normalCFM_set"
  btHingeConstraint_m_normalCFM_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_normalCFM_get"
  btHingeConstraint_m_normalCFM_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_stopCFM_set"
  btHingeConstraint_m_stopCFM_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_stopCFM_get"
  btHingeConstraint_m_stopCFM_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_stopERP_set"
  btHingeConstraint_m_stopERP_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraint_m_stopERP_get"
  btHingeConstraint_m_stopERP_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_new"
  btHingeConstraintDoubleData'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_free"
  btHingeConstraintDoubleData_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_typeConstraintData_set"
  btHingeConstraintDoubleData_m_typeConstraintData_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_typeConstraintData_get"
  btHingeConstraintDoubleData_m_typeConstraintData_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_rbAFrame_set"
  btHingeConstraintDoubleData_m_rbAFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_rbAFrame_get"
  btHingeConstraintDoubleData_m_rbAFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_rbBFrame_set"
  btHingeConstraintDoubleData_m_rbBFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_rbBFrame_get"
  btHingeConstraintDoubleData_m_rbBFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_useReferenceFrameA_set"
  btHingeConstraintDoubleData_m_useReferenceFrameA_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_useReferenceFrameA_get"
  btHingeConstraintDoubleData_m_useReferenceFrameA_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_angularOnly_set"
  btHingeConstraintDoubleData_m_angularOnly_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_angularOnly_get"
  btHingeConstraintDoubleData_m_angularOnly_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_enableAngularMotor_set"
  btHingeConstraintDoubleData_m_enableAngularMotor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_enableAngularMotor_get"
  btHingeConstraintDoubleData_m_enableAngularMotor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_motorTargetVelocity_set"
  btHingeConstraintDoubleData_m_motorTargetVelocity_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_motorTargetVelocity_get"
  btHingeConstraintDoubleData_m_motorTargetVelocity_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_maxMotorImpulse_set"
  btHingeConstraintDoubleData_m_maxMotorImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_maxMotorImpulse_get"
  btHingeConstraintDoubleData_m_maxMotorImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_lowerLimit_set"
  btHingeConstraintDoubleData_m_lowerLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_lowerLimit_get"
  btHingeConstraintDoubleData_m_lowerLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_upperLimit_set"
  btHingeConstraintDoubleData_m_upperLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_upperLimit_get"
  btHingeConstraintDoubleData_m_upperLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_limitSoftness_set"
  btHingeConstraintDoubleData_m_limitSoftness_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_limitSoftness_get"
  btHingeConstraintDoubleData_m_limitSoftness_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_biasFactor_set"
  btHingeConstraintDoubleData_m_biasFactor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_biasFactor_get"
  btHingeConstraintDoubleData_m_biasFactor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_relaxationFactor_set"
  btHingeConstraintDoubleData_m_relaxationFactor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintDoubleData_m_relaxationFactor_get"
  btHingeConstraintDoubleData_m_relaxationFactor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_new"
  btHingeConstraintFloatData'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_free"
  btHingeConstraintFloatData_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_typeConstraintData_set"
  btHingeConstraintFloatData_m_typeConstraintData_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_typeConstraintData_get"
  btHingeConstraintFloatData_m_typeConstraintData_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_rbAFrame_set"
  btHingeConstraintFloatData_m_rbAFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_rbAFrame_get"
  btHingeConstraintFloatData_m_rbAFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_rbBFrame_set"
  btHingeConstraintFloatData_m_rbBFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_rbBFrame_get"
  btHingeConstraintFloatData_m_rbBFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_useReferenceFrameA_set"
  btHingeConstraintFloatData_m_useReferenceFrameA_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_useReferenceFrameA_get"
  btHingeConstraintFloatData_m_useReferenceFrameA_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_angularOnly_set"
  btHingeConstraintFloatData_m_angularOnly_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_angularOnly_get"
  btHingeConstraintFloatData_m_angularOnly_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_enableAngularMotor_set"
  btHingeConstraintFloatData_m_enableAngularMotor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_enableAngularMotor_get"
  btHingeConstraintFloatData_m_enableAngularMotor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_motorTargetVelocity_set"
  btHingeConstraintFloatData_m_motorTargetVelocity_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_motorTargetVelocity_get"
  btHingeConstraintFloatData_m_motorTargetVelocity_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_maxMotorImpulse_set"
  btHingeConstraintFloatData_m_maxMotorImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_maxMotorImpulse_get"
  btHingeConstraintFloatData_m_maxMotorImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_lowerLimit_set"
  btHingeConstraintFloatData_m_lowerLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_lowerLimit_get"
  btHingeConstraintFloatData_m_lowerLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_upperLimit_set"
  btHingeConstraintFloatData_m_upperLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_upperLimit_get"
  btHingeConstraintFloatData_m_upperLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_limitSoftness_set"
  btHingeConstraintFloatData_m_limitSoftness_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_limitSoftness_get"
  btHingeConstraintFloatData_m_limitSoftness_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_biasFactor_set"
  btHingeConstraintFloatData_m_biasFactor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_biasFactor_get"
  btHingeConstraintFloatData_m_biasFactor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_relaxationFactor_set"
  btHingeConstraintFloatData_m_relaxationFactor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btHingeConstraintFloatData_m_relaxationFactor_get"
  btHingeConstraintFloatData_m_relaxationFactor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_new0"
  btJacobianEntry0'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_new2"
  btJacobianEntry2'_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO (C2HSImp.Ptr ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_new3"
  btJacobianEntry3'_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO (C2HSImp.Ptr ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_free"
  btJacobianEntry_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_getDiagonal"
  btJacobianEntry_getDiagonal'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_getRelativeVelocity"
  btJacobianEntry_getRelativeVelocity'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CFloat))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_getRelativeVelocity"
  btJacobianEntry_getRelativeVelocity''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CFloat))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_m_0MinvJt_set"
  btJacobianEntry_m_0MinvJt_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_m_0MinvJt_get"
  btJacobianEntry_m_0MinvJt_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_m_1MinvJt_set"
  btJacobianEntry_m_1MinvJt_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_m_1MinvJt_get"
  btJacobianEntry_m_1MinvJt_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_m_Adiag_set"
  btJacobianEntry_m_Adiag_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_m_Adiag_get"
  btJacobianEntry_m_Adiag_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_m_aJ_set"
  btJacobianEntry_m_aJ_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_m_aJ_get"
  btJacobianEntry_m_aJ_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_m_bJ_set"
  btJacobianEntry_m_bJ_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_m_bJ_get"
  btJacobianEntry_m_bJ_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_m_linearJointAxis_set"
  btJacobianEntry_m_linearJointAxis_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btJacobianEntry_m_linearJointAxis_get"
  btJacobianEntry_m_linearJointAxis_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_new0"
  btPoint2PointConstraint0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO (C2HSImp.Ptr ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_new1"
  btPoint2PointConstraint1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO (C2HSImp.Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_free"
  btPoint2PointConstraint_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_getInfo1NonVirtual"
  btPoint2PointConstraint_getInfo1NonVirtual'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_getInfo2NonVirtual"
  btPoint2PointConstraint_getInfo2NonVirtual'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_getInfo2NonVirtual"
  btPoint2PointConstraint_getInfo2NonVirtual''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_setParam"
  btPoint2PointConstraint_setParam'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (C2HSImp.CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_getPivotInA"
  btPoint2PointConstraint_getPivotInA'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_getPivotInB"
  btPoint2PointConstraint_getPivotInB'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_updateRHS"
  btPoint2PointConstraint_updateRHS'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_serialize"
  btPoint2PointConstraint_serialize'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_buildJacobian"
  btPoint2PointConstraint_buildJacobian'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_calculateSerializeBufferSize"
  btPoint2PointConstraint_calculateSerializeBufferSize'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_getParam"
  btPoint2PointConstraint_getParam'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CFloat))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_getInfo1"
  btPoint2PointConstraint_getInfo1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_getInfo2"
  btPoint2PointConstraint_getInfo2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_setPivotA"
  btPoint2PointConstraint_setPivotA'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_setPivotA"
  btPoint2PointConstraint_setPivotA''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_setPivotB"
  btPoint2PointConstraint_setPivotB'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_setPivotB"
  btPoint2PointConstraint_setPivotB''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_pivotInA_set"
  btPoint2PointConstraint_m_pivotInA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_pivotInA_get"
  btPoint2PointConstraint_m_pivotInA_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_pivotInB_set"
  btPoint2PointConstraint_m_pivotInB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_pivotInB_get"
  btPoint2PointConstraint_m_pivotInB_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_flags_set"
  btPoint2PointConstraint_m_flags_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_flags_get"
  btPoint2PointConstraint_m_flags_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_erp_set"
  btPoint2PointConstraint_m_erp_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_erp_get"
  btPoint2PointConstraint_m_erp_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_cfm_set"
  btPoint2PointConstraint_m_cfm_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_cfm_get"
  btPoint2PointConstraint_m_cfm_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_useSolveConstraintObsolete_set"
  btPoint2PointConstraint_m_useSolveConstraintObsolete_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_useSolveConstraintObsolete_get"
  btPoint2PointConstraint_m_useSolveConstraintObsolete_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_setting_set"
  btPoint2PointConstraint_m_setting_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraint_m_setting_get"
  btPoint2PointConstraint_m_setting_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintDoubleData_new"
  btPoint2PointConstraintDoubleData'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintDoubleData_free"
  btPoint2PointConstraintDoubleData_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintDoubleData_m_typeConstraintData_set"
  btPoint2PointConstraintDoubleData_m_typeConstraintData_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintDoubleData_m_typeConstraintData_get"
  btPoint2PointConstraintDoubleData_m_typeConstraintData_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintDoubleData_m_pivotInA_set"
  btPoint2PointConstraintDoubleData_m_pivotInA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintDoubleData_m_pivotInA_get"
  btPoint2PointConstraintDoubleData_m_pivotInA_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintDoubleData_m_pivotInB_set"
  btPoint2PointConstraintDoubleData_m_pivotInB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintDoubleData_m_pivotInB_get"
  btPoint2PointConstraintDoubleData_m_pivotInB_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintFloatData_new"
  btPoint2PointConstraintFloatData'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintFloatData_free"
  btPoint2PointConstraintFloatData_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintFloatData_m_typeConstraintData_set"
  btPoint2PointConstraintFloatData_m_typeConstraintData_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintFloatData_m_typeConstraintData_get"
  btPoint2PointConstraintFloatData_m_typeConstraintData_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintFloatData_m_pivotInA_set"
  btPoint2PointConstraintFloatData_m_pivotInA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintFloatData_m_pivotInA_get"
  btPoint2PointConstraintFloatData_m_pivotInA_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintFloatData_m_pivotInB_set"
  btPoint2PointConstraintFloatData_m_pivotInB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btPoint2PointConstraintFloatData_m_pivotInB_get"
  btPoint2PointConstraintFloatData_m_pivotInB_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_new"
  btRotationalLimitMotor'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_free"
  btRotationalLimitMotor_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_testLimitValue"
  btRotationalLimitMotor_testLimitValue'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO C2HSImp.CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_solveAngularLimits"
  btRotationalLimitMotor_solveAngularLimits'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat)))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_solveAngularLimits"
  btRotationalLimitMotor_solveAngularLimits''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat)))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_needApplyTorques"
  btRotationalLimitMotor_needApplyTorques'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_isLimited"
  btRotationalLimitMotor_isLimited'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_accumulatedImpulse_set"
  btRotationalLimitMotor_m_accumulatedImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_accumulatedImpulse_get"
  btRotationalLimitMotor_m_accumulatedImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_bounce_set"
  btRotationalLimitMotor_m_bounce_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_bounce_get"
  btRotationalLimitMotor_m_bounce_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_currentLimit_set"
  btRotationalLimitMotor_m_currentLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_currentLimit_get"
  btRotationalLimitMotor_m_currentLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_currentLimitError_set"
  btRotationalLimitMotor_m_currentLimitError_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_currentLimitError_get"
  btRotationalLimitMotor_m_currentLimitError_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_currentPosition_set"
  btRotationalLimitMotor_m_currentPosition_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_currentPosition_get"
  btRotationalLimitMotor_m_currentPosition_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_damping_set"
  btRotationalLimitMotor_m_damping_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_damping_get"
  btRotationalLimitMotor_m_damping_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_enableMotor_set"
  btRotationalLimitMotor_m_enableMotor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_enableMotor_get"
  btRotationalLimitMotor_m_enableMotor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_hiLimit_set"
  btRotationalLimitMotor_m_hiLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_hiLimit_get"
  btRotationalLimitMotor_m_hiLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_limitSoftness_set"
  btRotationalLimitMotor_m_limitSoftness_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_limitSoftness_get"
  btRotationalLimitMotor_m_limitSoftness_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_loLimit_set"
  btRotationalLimitMotor_m_loLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_loLimit_get"
  btRotationalLimitMotor_m_loLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_maxLimitForce_set"
  btRotationalLimitMotor_m_maxLimitForce_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_maxLimitForce_get"
  btRotationalLimitMotor_m_maxLimitForce_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_maxMotorForce_set"
  btRotationalLimitMotor_m_maxMotorForce_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_maxMotorForce_get"
  btRotationalLimitMotor_m_maxMotorForce_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_normalCFM_set"
  btRotationalLimitMotor_m_normalCFM_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_normalCFM_get"
  btRotationalLimitMotor_m_normalCFM_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_stopCFM_set"
  btRotationalLimitMotor_m_stopCFM_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_stopCFM_get"
  btRotationalLimitMotor_m_stopCFM_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_stopERP_set"
  btRotationalLimitMotor_m_stopERP_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_stopERP_get"
  btRotationalLimitMotor_m_stopERP_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_targetVelocity_set"
  btRotationalLimitMotor_m_targetVelocity_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btRotationalLimitMotor_m_targetVelocity_get"
  btRotationalLimitMotor_m_targetVelocity_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_new"
  btSequentialImpulseConstraintSolver'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_free"
  btSequentialImpulseConstraintSolver_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_convertContact"
  btSequentialImpulseConstraintSolver_convertContact'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_setRandSeed"
  btSequentialImpulseConstraintSolver_setRandSeed'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_getFixedBody"
  btSequentialImpulseConstraintSolver_getFixedBody'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_resolveSingleConstraintRowLowerLimitSIMD"
  btSequentialImpulseConstraintSolver_resolveSingleConstraintRowLowerLimitSIMD'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_btRand2"
  btSequentialImpulseConstraintSolver_btRand2'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CULong))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_setFrictionConstraintImpulse"
  btSequentialImpulseConstraintSolver_setFrictionConstraintImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_getOrInitSolverBody"
  btSequentialImpulseConstraintSolver_getOrInitSolverBody'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_resolveSingleConstraintRowGenericSIMD"
  btSequentialImpulseConstraintSolver_resolveSingleConstraintRowGenericSIMD'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_btRandInt2"
  btSequentialImpulseConstraintSolver_btRandInt2'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_resolveSingleConstraintRowLowerLimit"
  btSequentialImpulseConstraintSolver_resolveSingleConstraintRowLowerLimit'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_reset"
  btSequentialImpulseConstraintSolver_reset'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_resolveSplitPenetrationImpulseCacheFriendly"
  btSequentialImpulseConstraintSolver_resolveSplitPenetrationImpulseCacheFriendly'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_setupFrictionConstraint"
  btSequentialImpulseConstraintSolver_setupFrictionConstraint'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_setupFrictionConstraint"
  btSequentialImpulseConstraintSolver_setupFrictionConstraint''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_getRandSeed"
  btSequentialImpulseConstraintSolver_getRandSeed'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CULong))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_addFrictionConstraint"
  btSequentialImpulseConstraintSolver_addFrictionConstraint'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO (C2HSImp.Ptr ())))))))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_addFrictionConstraint"
  btSequentialImpulseConstraintSolver_addFrictionConstraint''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO (C2HSImp.Ptr ())))))))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_restitutionCurve"
  btSequentialImpulseConstraintSolver_restitutionCurve'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO C2HSImp.CFloat))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_resolveSingleConstraintRowGeneric"
  btSequentialImpulseConstraintSolver_resolveSingleConstraintRowGeneric'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_resolveSplitPenetrationSIMD"
  btSequentialImpulseConstraintSolver_resolveSplitPenetrationSIMD'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_tmpSolverContactConstraintPool_set"
  btSequentialImpulseConstraintSolver_m_tmpSolverContactConstraintPool_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_tmpSolverContactConstraintPool_get"
  btSequentialImpulseConstraintSolver_m_tmpSolverContactConstraintPool_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_tmpSolverNonContactConstraintPool_set"
  btSequentialImpulseConstraintSolver_m_tmpSolverNonContactConstraintPool_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_tmpSolverNonContactConstraintPool_get"
  btSequentialImpulseConstraintSolver_m_tmpSolverNonContactConstraintPool_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_tmpSolverContactFrictionConstraintPool_set"
  btSequentialImpulseConstraintSolver_m_tmpSolverContactFrictionConstraintPool_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_tmpSolverContactFrictionConstraintPool_get"
  btSequentialImpulseConstraintSolver_m_tmpSolverContactFrictionConstraintPool_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_orderTmpConstraintPool_set"
  btSequentialImpulseConstraintSolver_m_orderTmpConstraintPool_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_orderTmpConstraintPool_get"
  btSequentialImpulseConstraintSolver_m_orderTmpConstraintPool_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_orderFrictionConstraintPool_set"
  btSequentialImpulseConstraintSolver_m_orderFrictionConstraintPool_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_orderFrictionConstraintPool_get"
  btSequentialImpulseConstraintSolver_m_orderFrictionConstraintPool_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_tmpConstraintSizesPool_set"
  btSequentialImpulseConstraintSolver_m_tmpConstraintSizesPool_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_tmpConstraintSizesPool_get"
  btSequentialImpulseConstraintSolver_m_tmpConstraintSizesPool_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_btSeed2_set"
  btSequentialImpulseConstraintSolver_m_btSeed2_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSequentialImpulseConstraintSolver_m_btSeed2_get"
  btSequentialImpulseConstraintSolver_m_btSeed2_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CULong))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_new0"
  btSliderConstraint0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_new1"
  btSliderConstraint1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_free"
  btSliderConstraint_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getRigidBodyB"
  btSliderConstraint_getRigidBodyB'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getRigidBodyA"
  btSliderConstraint_getRigidBodyA'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getAngDepth"
  btSliderConstraint_getAngDepth'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getTargetAngMotorVelocity"
  btSliderConstraint_getTargetAngMotorVelocity'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getAngularPos"
  btSliderConstraint_getAngularPos'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setRestitutionLimAng"
  btSliderConstraint_setRestitutionLimAng'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getParam"
  btSliderConstraint_getParam'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CFloat))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getInfo1"
  btSliderConstraint_getInfo1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getInfo2"
  btSliderConstraint_getInfo2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getPoweredLinMotor"
  btSliderConstraint_getPoweredLinMotor'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setUseFrameOffset"
  btSliderConstraint_setUseFrameOffset'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setSoftnessLimLin"
  btSliderConstraint_setSoftnessLimLin'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getAncorInA"
  btSliderConstraint_getAncorInA'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getAncorInB"
  btSliderConstraint_getAncorInB'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setDampingDirAng"
  btSliderConstraint_setDampingDirAng'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getSolveLinLimit"
  btSliderConstraint_getSolveLinLimit'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getUseFrameOffset"
  btSliderConstraint_getUseFrameOffset'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getMaxAngMotorForce"
  btSliderConstraint_getMaxAngMotorForce'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setRestitutionDirAng"
  btSliderConstraint_setRestitutionDirAng'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getMaxLinMotorForce"
  btSliderConstraint_getMaxLinMotorForce'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setDampingOrthoLin"
  btSliderConstraint_setDampingOrthoLin'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getSolveAngLimit"
  btSliderConstraint_getSolveAngLimit'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setPoweredAngMotor"
  btSliderConstraint_setPoweredAngMotor'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getLinearPos"
  btSliderConstraint_getLinearPos'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getCalculatedTransformB"
  btSliderConstraint_getCalculatedTransformB'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getCalculatedTransformA"
  btSliderConstraint_getCalculatedTransformA'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_testAngLimits"
  btSliderConstraint_testAngLimits'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setDampingDirLin"
  btSliderConstraint_setDampingDirLin'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getUpperAngLimit"
  btSliderConstraint_getUpperAngLimit'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setUpperAngLimit"
  btSliderConstraint_setUpperAngLimit'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getRestitutionLimAng"
  btSliderConstraint_getRestitutionLimAng'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getSoftnessOrthoLin"
  btSliderConstraint_getSoftnessOrthoLin'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setLowerLinLimit"
  btSliderConstraint_setLowerLinLimit'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getRestitutionDirLin"
  btSliderConstraint_getRestitutionDirLin'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getInfo1NonVirtual"
  btSliderConstraint_getInfo1NonVirtual'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setRestitutionLimLin"
  btSliderConstraint_setRestitutionLimLin'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setTargetLinMotorVelocity"
  btSliderConstraint_setTargetLinMotorVelocity'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getUpperLinLimit"
  btSliderConstraint_getUpperLinLimit'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setMaxLinMotorForce"
  btSliderConstraint_setMaxLinMotorForce'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getLowerAngLimit"
  btSliderConstraint_getLowerAngLimit'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setSoftnessDirLin"
  btSliderConstraint_setSoftnessDirLin'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_initParams"
  btSliderConstraint_initParams'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getInfo2NonVirtual"
  btSliderConstraint_getInfo2NonVirtual'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ())))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getInfo2NonVirtual"
  btSliderConstraint_getInfo2NonVirtual''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ())))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getFrameOffsetA0"
  btSliderConstraint_getFrameOffsetA'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getFrameOffsetA0"
  btSliderConstraint_getFrameOffsetA0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getFrameOffsetA1"
  btSliderConstraint_getFrameOffsetA1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getFrameOffsetB0"
  btSliderConstraint_getFrameOffsetB'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getFrameOffsetB0"
  btSliderConstraint_getFrameOffsetB0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getFrameOffsetB1"
  btSliderConstraint_getFrameOffsetB1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getDampingDirAng"
  btSliderConstraint_getDampingDirAng'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getRestitutionLimLin"
  btSliderConstraint_getRestitutionLimLin'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getSoftnessOrthoAng"
  btSliderConstraint_getSoftnessOrthoAng'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setSoftnessOrthoLin"
  btSliderConstraint_setSoftnessOrthoLin'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setSoftnessLimAng"
  btSliderConstraint_setSoftnessLimAng'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getDampingDirLin"
  btSliderConstraint_getDampingDirLin'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getSoftnessLimLin"
  btSliderConstraint_getSoftnessLimLin'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setPoweredLinMotor"
  btSliderConstraint_setPoweredLinMotor'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_calculateTransforms"
  btSliderConstraint_calculateTransforms'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_calculateTransforms"
  btSliderConstraint_calculateTransforms''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getLinDepth"
  btSliderConstraint_getLinDepth'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_serialize"
  btSliderConstraint_serialize'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getDampingLimLin"
  btSliderConstraint_getDampingLimLin'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getRestitutionDirAng"
  btSliderConstraint_getRestitutionDirAng'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setParam"
  btSliderConstraint_setParam'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (C2HSImp.CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getDampingLimAng"
  btSliderConstraint_getDampingLimAng'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setRestitutionOrthoLin"
  btSliderConstraint_setRestitutionOrthoLin'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setRestitutionDirLin"
  btSliderConstraint_setRestitutionDirLin'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setDampingLimAng"
  btSliderConstraint_setDampingLimAng'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setSoftnessDirAng"
  btSliderConstraint_setSoftnessDirAng'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setUpperLinLimit"
  btSliderConstraint_setUpperLinLimit'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_calculateSerializeBufferSize"
  btSliderConstraint_calculateSerializeBufferSize'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setTargetAngMotorVelocity"
  btSliderConstraint_setTargetAngMotorVelocity'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getSoftnessDirAng"
  btSliderConstraint_getSoftnessDirAng'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setMaxAngMotorForce"
  btSliderConstraint_setMaxAngMotorForce'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setLowerAngLimit"
  btSliderConstraint_setLowerAngLimit'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getPoweredAngMotor"
  btSliderConstraint_getPoweredAngMotor'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getDampingOrthoAng"
  btSliderConstraint_getDampingOrthoAng'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getRestitutionOrthoLin"
  btSliderConstraint_getRestitutionOrthoLin'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getTargetLinMotorVelocity"
  btSliderConstraint_getTargetLinMotorVelocity'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_testLinLimits"
  btSliderConstraint_testLinLimits'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getLowerLinLimit"
  btSliderConstraint_getLowerLinLimit'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setDampingOrthoAng"
  btSliderConstraint_setDampingOrthoAng'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setRestitutionOrthoAng"
  btSliderConstraint_setRestitutionOrthoAng'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getRestitutionOrthoAng"
  btSliderConstraint_getRestitutionOrthoAng'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getDampingOrthoLin"
  btSliderConstraint_getDampingOrthoLin'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getSoftnessLimAng"
  btSliderConstraint_getSoftnessLimAng'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setSoftnessOrthoAng"
  btSliderConstraint_setSoftnessOrthoAng'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setDampingLimLin"
  btSliderConstraint_setDampingLimLin'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setFrames"
  btSliderConstraint_setFrames'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_setFrames"
  btSliderConstraint_setFrames''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getSoftnessDirLin"
  btSliderConstraint_getSoftnessDirLin'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_getUseLinearReferenceFrameA"
  btSliderConstraint_getUseLinearReferenceFrameA'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_useSolveConstraintObsolete_set"
  btSliderConstraint_m_useSolveConstraintObsolete_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_useSolveConstraintObsolete_get"
  btSliderConstraint_m_useSolveConstraintObsolete_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_useOffsetForConstraintFrame_set"
  btSliderConstraint_m_useOffsetForConstraintFrame_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_useOffsetForConstraintFrame_get"
  btSliderConstraint_m_useOffsetForConstraintFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_frameInA_set"
  btSliderConstraint_m_frameInA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_frameInA_get"
  btSliderConstraint_m_frameInA_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_frameInB_set"
  btSliderConstraint_m_frameInB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_frameInB_get"
  btSliderConstraint_m_frameInB_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_useLinearReferenceFrameA_set"
  btSliderConstraint_m_useLinearReferenceFrameA_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_useLinearReferenceFrameA_get"
  btSliderConstraint_m_useLinearReferenceFrameA_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_lowerLinLimit_set"
  btSliderConstraint_m_lowerLinLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_lowerLinLimit_get"
  btSliderConstraint_m_lowerLinLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_upperLinLimit_set"
  btSliderConstraint_m_upperLinLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_upperLinLimit_get"
  btSliderConstraint_m_upperLinLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_lowerAngLimit_set"
  btSliderConstraint_m_lowerAngLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_lowerAngLimit_get"
  btSliderConstraint_m_lowerAngLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_upperAngLimit_set"
  btSliderConstraint_m_upperAngLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_upperAngLimit_get"
  btSliderConstraint_m_upperAngLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_softnessDirLin_set"
  btSliderConstraint_m_softnessDirLin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_softnessDirLin_get"
  btSliderConstraint_m_softnessDirLin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_restitutionDirLin_set"
  btSliderConstraint_m_restitutionDirLin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_restitutionDirLin_get"
  btSliderConstraint_m_restitutionDirLin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_dampingDirLin_set"
  btSliderConstraint_m_dampingDirLin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_dampingDirLin_get"
  btSliderConstraint_m_dampingDirLin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_cfmDirLin_set"
  btSliderConstraint_m_cfmDirLin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_cfmDirLin_get"
  btSliderConstraint_m_cfmDirLin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_softnessDirAng_set"
  btSliderConstraint_m_softnessDirAng_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_softnessDirAng_get"
  btSliderConstraint_m_softnessDirAng_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_restitutionDirAng_set"
  btSliderConstraint_m_restitutionDirAng_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_restitutionDirAng_get"
  btSliderConstraint_m_restitutionDirAng_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_dampingDirAng_set"
  btSliderConstraint_m_dampingDirAng_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_dampingDirAng_get"
  btSliderConstraint_m_dampingDirAng_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_cfmDirAng_set"
  btSliderConstraint_m_cfmDirAng_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_cfmDirAng_get"
  btSliderConstraint_m_cfmDirAng_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_softnessLimLin_set"
  btSliderConstraint_m_softnessLimLin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_softnessLimLin_get"
  btSliderConstraint_m_softnessLimLin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_restitutionLimLin_set"
  btSliderConstraint_m_restitutionLimLin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_restitutionLimLin_get"
  btSliderConstraint_m_restitutionLimLin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_dampingLimLin_set"
  btSliderConstraint_m_dampingLimLin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_dampingLimLin_get"
  btSliderConstraint_m_dampingLimLin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_cfmLimLin_set"
  btSliderConstraint_m_cfmLimLin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_cfmLimLin_get"
  btSliderConstraint_m_cfmLimLin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_softnessLimAng_set"
  btSliderConstraint_m_softnessLimAng_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_softnessLimAng_get"
  btSliderConstraint_m_softnessLimAng_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_restitutionLimAng_set"
  btSliderConstraint_m_restitutionLimAng_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_restitutionLimAng_get"
  btSliderConstraint_m_restitutionLimAng_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_dampingLimAng_set"
  btSliderConstraint_m_dampingLimAng_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_dampingLimAng_get"
  btSliderConstraint_m_dampingLimAng_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_cfmLimAng_set"
  btSliderConstraint_m_cfmLimAng_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_cfmLimAng_get"
  btSliderConstraint_m_cfmLimAng_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_softnessOrthoLin_set"
  btSliderConstraint_m_softnessOrthoLin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_softnessOrthoLin_get"
  btSliderConstraint_m_softnessOrthoLin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_restitutionOrthoLin_set"
  btSliderConstraint_m_restitutionOrthoLin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_restitutionOrthoLin_get"
  btSliderConstraint_m_restitutionOrthoLin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_dampingOrthoLin_set"
  btSliderConstraint_m_dampingOrthoLin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_dampingOrthoLin_get"
  btSliderConstraint_m_dampingOrthoLin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_cfmOrthoLin_set"
  btSliderConstraint_m_cfmOrthoLin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_cfmOrthoLin_get"
  btSliderConstraint_m_cfmOrthoLin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_softnessOrthoAng_set"
  btSliderConstraint_m_softnessOrthoAng_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_softnessOrthoAng_get"
  btSliderConstraint_m_softnessOrthoAng_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_restitutionOrthoAng_set"
  btSliderConstraint_m_restitutionOrthoAng_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_restitutionOrthoAng_get"
  btSliderConstraint_m_restitutionOrthoAng_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_dampingOrthoAng_set"
  btSliderConstraint_m_dampingOrthoAng_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_dampingOrthoAng_get"
  btSliderConstraint_m_dampingOrthoAng_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_cfmOrthoAng_set"
  btSliderConstraint_m_cfmOrthoAng_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_cfmOrthoAng_get"
  btSliderConstraint_m_cfmOrthoAng_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_solveLinLim_set"
  btSliderConstraint_m_solveLinLim_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_solveLinLim_get"
  btSliderConstraint_m_solveLinLim_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_solveAngLim_set"
  btSliderConstraint_m_solveAngLim_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_solveAngLim_get"
  btSliderConstraint_m_solveAngLim_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_flags_set"
  btSliderConstraint_m_flags_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_flags_get"
  btSliderConstraint_m_flags_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_timeStep_set"
  btSliderConstraint_m_timeStep_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_timeStep_get"
  btSliderConstraint_m_timeStep_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_calculatedTransformA_set"
  btSliderConstraint_m_calculatedTransformA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_calculatedTransformA_get"
  btSliderConstraint_m_calculatedTransformA_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_calculatedTransformB_set"
  btSliderConstraint_m_calculatedTransformB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_calculatedTransformB_get"
  btSliderConstraint_m_calculatedTransformB_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_sliderAxis_set"
  btSliderConstraint_m_sliderAxis_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_sliderAxis_get"
  btSliderConstraint_m_sliderAxis_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_realPivotAInW_set"
  btSliderConstraint_m_realPivotAInW_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_realPivotAInW_get"
  btSliderConstraint_m_realPivotAInW_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_realPivotBInW_set"
  btSliderConstraint_m_realPivotBInW_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_realPivotBInW_get"
  btSliderConstraint_m_realPivotBInW_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_projPivotInW_set"
  btSliderConstraint_m_projPivotInW_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_projPivotInW_get"
  btSliderConstraint_m_projPivotInW_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_delta_set"
  btSliderConstraint_m_delta_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_delta_get"
  btSliderConstraint_m_delta_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_depth_set"
  btSliderConstraint_m_depth_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_depth_get"
  btSliderConstraint_m_depth_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_relPosA_set"
  btSliderConstraint_m_relPosA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_relPosA_get"
  btSliderConstraint_m_relPosA_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_relPosB_set"
  btSliderConstraint_m_relPosB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_relPosB_get"
  btSliderConstraint_m_relPosB_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_linPos_set"
  btSliderConstraint_m_linPos_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_linPos_get"
  btSliderConstraint_m_linPos_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_angPos_set"
  btSliderConstraint_m_angPos_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_angPos_get"
  btSliderConstraint_m_angPos_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_angDepth_set"
  btSliderConstraint_m_angDepth_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_angDepth_get"
  btSliderConstraint_m_angDepth_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_kAngle_set"
  btSliderConstraint_m_kAngle_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_kAngle_get"
  btSliderConstraint_m_kAngle_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_poweredLinMotor_set"
  btSliderConstraint_m_poweredLinMotor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_poweredLinMotor_get"
  btSliderConstraint_m_poweredLinMotor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_targetLinMotorVelocity_set"
  btSliderConstraint_m_targetLinMotorVelocity_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_targetLinMotorVelocity_get"
  btSliderConstraint_m_targetLinMotorVelocity_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_maxLinMotorForce_set"
  btSliderConstraint_m_maxLinMotorForce_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_maxLinMotorForce_get"
  btSliderConstraint_m_maxLinMotorForce_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_accumulatedLinMotorImpulse_set"
  btSliderConstraint_m_accumulatedLinMotorImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_accumulatedLinMotorImpulse_get"
  btSliderConstraint_m_accumulatedLinMotorImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_poweredAngMotor_set"
  btSliderConstraint_m_poweredAngMotor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_poweredAngMotor_get"
  btSliderConstraint_m_poweredAngMotor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_targetAngMotorVelocity_set"
  btSliderConstraint_m_targetAngMotorVelocity_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_targetAngMotorVelocity_get"
  btSliderConstraint_m_targetAngMotorVelocity_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_maxAngMotorForce_set"
  btSliderConstraint_m_maxAngMotorForce_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_maxAngMotorForce_get"
  btSliderConstraint_m_maxAngMotorForce_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_accumulatedAngMotorImpulse_set"
  btSliderConstraint_m_accumulatedAngMotorImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraint_m_accumulatedAngMotorImpulse_get"
  btSliderConstraint_m_accumulatedAngMotorImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_new"
  btSliderConstraintData'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_free"
  btSliderConstraintData_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_typeConstraintData_set"
  btSliderConstraintData_m_typeConstraintData_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_typeConstraintData_get"
  btSliderConstraintData_m_typeConstraintData_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_rbAFrame_set"
  btSliderConstraintData_m_rbAFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_rbAFrame_get"
  btSliderConstraintData_m_rbAFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_rbBFrame_set"
  btSliderConstraintData_m_rbBFrame_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_rbBFrame_get"
  btSliderConstraintData_m_rbBFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_linearUpperLimit_set"
  btSliderConstraintData_m_linearUpperLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_linearUpperLimit_get"
  btSliderConstraintData_m_linearUpperLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_linearLowerLimit_set"
  btSliderConstraintData_m_linearLowerLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_linearLowerLimit_get"
  btSliderConstraintData_m_linearLowerLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_angularUpperLimit_set"
  btSliderConstraintData_m_angularUpperLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_angularUpperLimit_get"
  btSliderConstraintData_m_angularUpperLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_angularLowerLimit_set"
  btSliderConstraintData_m_angularLowerLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_angularLowerLimit_get"
  btSliderConstraintData_m_angularLowerLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_useLinearReferenceFrameA_set"
  btSliderConstraintData_m_useLinearReferenceFrameA_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_useLinearReferenceFrameA_get"
  btSliderConstraintData_m_useLinearReferenceFrameA_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_useOffsetForConstraintFrame_set"
  btSliderConstraintData_m_useOffsetForConstraintFrame_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSliderConstraintData_m_useOffsetForConstraintFrame_get"
  btSliderConstraintData_m_useOffsetForConstraintFrame_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_new"
  btSolverBodyObsolete'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_free"
  btSolverBodyObsolete_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_getAngularVelocity"
  btSolverBodyObsolete_getAngularVelocity'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_getAngularVelocity"
  btSolverBodyObsolete_getAngularVelocity''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_writebackVelocity0"
  btSolverBodyObsolete_writebackVelocity'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_writebackVelocity0"
  btSolverBodyObsolete_writebackVelocity0'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_writebackVelocity1"
  btSolverBodyObsolete_writebackVelocity1'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_internalApplyPushImpulse"
  btSolverBodyObsolete_internalApplyPushImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_internalApplyPushImpulse"
  btSolverBodyObsolete_internalApplyPushImpulse''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_getVelocityInLocalPointObsolete"
  btSolverBodyObsolete_getVelocityInLocalPointObsolete'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_getVelocityInLocalPointObsolete"
  btSolverBodyObsolete_getVelocityInLocalPointObsolete''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_deltaLinearVelocity_set"
  btSolverBodyObsolete_m_deltaLinearVelocity_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_deltaLinearVelocity_get"
  btSolverBodyObsolete_m_deltaLinearVelocity_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_deltaAngularVelocity_set"
  btSolverBodyObsolete_m_deltaAngularVelocity_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_deltaAngularVelocity_get"
  btSolverBodyObsolete_m_deltaAngularVelocity_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_angularFactor_set"
  btSolverBodyObsolete_m_angularFactor_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_angularFactor_get"
  btSolverBodyObsolete_m_angularFactor_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_invMass_set"
  btSolverBodyObsolete_m_invMass_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_invMass_get"
  btSolverBodyObsolete_m_invMass_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_originalBody_set"
  btSolverBodyObsolete_m_originalBody_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_originalBody_get"
  btSolverBodyObsolete_m_originalBody_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_pushVelocity_set"
  btSolverBodyObsolete_m_pushVelocity_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_pushVelocity_get"
  btSolverBodyObsolete_m_pushVelocity_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_turnVelocity_set"
  btSolverBodyObsolete_m_turnVelocity_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverBodyObsolete_m_turnVelocity_get"
  btSolverBodyObsolete_m_turnVelocity_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_new"
  btSolverConstraint'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_free"
  btSolverConstraint_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_angularComponentA_set"
  btSolverConstraint_m_angularComponentA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_angularComponentA_get"
  btSolverConstraint_m_angularComponentA_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_angularComponentB_set"
  btSolverConstraint_m_angularComponentB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_angularComponentB_get"
  btSolverConstraint_m_angularComponentB_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_appliedImpulse_set"
  btSolverConstraint_m_appliedImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_appliedImpulse_get"
  btSolverConstraint_m_appliedImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_appliedPushImpulse_set"
  btSolverConstraint_m_appliedPushImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_appliedPushImpulse_get"
  btSolverConstraint_m_appliedPushImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_cfm_set"
  btSolverConstraint_m_cfm_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_cfm_get"
  btSolverConstraint_m_cfm_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_contactNormal_set"
  btSolverConstraint_m_contactNormal_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_contactNormal_get"
  btSolverConstraint_m_contactNormal_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_friction_set"
  btSolverConstraint_m_friction_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_friction_get"
  btSolverConstraint_m_friction_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_jacDiagABInv_set"
  btSolverConstraint_m_jacDiagABInv_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_jacDiagABInv_get"
  btSolverConstraint_m_jacDiagABInv_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_lowerLimit_set"
  btSolverConstraint_m_lowerLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_lowerLimit_get"
  btSolverConstraint_m_lowerLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_relpos1CrossNormal_set"
  btSolverConstraint_m_relpos1CrossNormal_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_relpos1CrossNormal_get"
  btSolverConstraint_m_relpos1CrossNormal_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_relpos2CrossNormal_set"
  btSolverConstraint_m_relpos2CrossNormal_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_relpos2CrossNormal_get"
  btSolverConstraint_m_relpos2CrossNormal_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_rhs_set"
  btSolverConstraint_m_rhs_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_rhs_get"
  btSolverConstraint_m_rhs_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_rhsPenetration_set"
  btSolverConstraint_m_rhsPenetration_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_rhsPenetration_get"
  btSolverConstraint_m_rhsPenetration_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_upperLimit_set"
  btSolverConstraint_m_upperLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btSolverConstraint_m_upperLimit_get"
  btSolverConstraint_m_upperLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_new"
  btTranslationalLimitMotor'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_free"
  btTranslationalLimitMotor_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_testLimitValue"
  btTranslationalLimitMotor_testLimitValue'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO C2HSImp.CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_needApplyForce"
  btTranslationalLimitMotor_needApplyForce'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_solveLinearAxis"
  btTranslationalLimitMotor_solveLinearAxis'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CFloat)))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_solveLinearAxis"
  btTranslationalLimitMotor_solveLinearAxis''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CFloat)))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_isLimited"
  btTranslationalLimitMotor_isLimited'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_accumulatedImpulse_set"
  btTranslationalLimitMotor_m_accumulatedImpulse_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_accumulatedImpulse_get"
  btTranslationalLimitMotor_m_accumulatedImpulse_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_currentLimitError_set"
  btTranslationalLimitMotor_m_currentLimitError_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_currentLimitError_get"
  btTranslationalLimitMotor_m_currentLimitError_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_currentLinearDiff_set"
  btTranslationalLimitMotor_m_currentLinearDiff_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_currentLinearDiff_get"
  btTranslationalLimitMotor_m_currentLinearDiff_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_damping_set"
  btTranslationalLimitMotor_m_damping_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_damping_get"
  btTranslationalLimitMotor_m_damping_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_limitSoftness_set"
  btTranslationalLimitMotor_m_limitSoftness_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_limitSoftness_get"
  btTranslationalLimitMotor_m_limitSoftness_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_lowerLimit_set"
  btTranslationalLimitMotor_m_lowerLimit_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_lowerLimit_get"
  btTranslationalLimitMotor_m_lowerLimit_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_maxMotorForce_set"
  btTranslationalLimitMotor_m_maxMotorForce_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_maxMotorForce_get"
  btTranslationalLimitMotor_m_maxMotorForce_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_normalCFM_set"
  btTranslationalLimitMotor_m_normalCFM_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_normalCFM_get"
  btTranslationalLimitMotor_m_normalCFM_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_restitution_set"
  btTranslationalLimitMotor_m_restitution_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_restitution_get"
  btTranslationalLimitMotor_m_restitution_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_stopCFM_set"
  btTranslationalLimitMotor_m_stopCFM_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_stopCFM_get"
  btTranslationalLimitMotor_m_stopCFM_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_stopERP_set"
  btTranslationalLimitMotor_m_stopERP_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_stopERP_get"
  btTranslationalLimitMotor_m_stopERP_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_targetVelocity_set"
  btTranslationalLimitMotor_m_targetVelocity_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_targetVelocity_get"
  btTranslationalLimitMotor_m_targetVelocity_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_upperLimit_set"
  btTranslationalLimitMotor_m_upperLimit_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTranslationalLimitMotor_m_upperLimit_get"
  btTranslationalLimitMotor_m_upperLimit_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getRigidBodyB0"
  btTypedConstraint_getRigidBodyB'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getRigidBodyB0"
  btTypedConstraint_getRigidBodyB0'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getRigidBodyB1"
  btTypedConstraint_getRigidBodyB1'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_buildJacobian"
  btTypedConstraint_buildJacobian'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getRigidBodyA0"
  btTypedConstraint_getRigidBodyA'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getRigidBodyA0"
  btTypedConstraint_getRigidBodyA0'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getRigidBodyA1"
  btTypedConstraint_getRigidBodyA1'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_serialize"
  btTypedConstraint_serialize'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_enableFeedback"
  btTypedConstraint_enableFeedback'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getUserConstraintId"
  btTypedConstraint_getUserConstraintId'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_setParam"
  btTypedConstraint_setParam'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (C2HSImp.CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getParam"
  btTypedConstraint_getParam'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CFloat))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getInfo1"
  btTypedConstraint_getInfo1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getInfo2"
  btTypedConstraint_getInfo2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_setBreakingImpulseThreshold"
  btTypedConstraint_setBreakingImpulseThreshold'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getFixedBody"
  btTypedConstraint_getFixedBody'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_calculateSerializeBufferSize"
  btTypedConstraint_calculateSerializeBufferSize'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_isEnabled"
  btTypedConstraint_isEnabled'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_setUserConstraintId"
  btTypedConstraint_setUserConstraintId'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getMotorFactor"
  btTypedConstraint_getMotorFactor'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO C2HSImp.CFloat)))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getDbgDrawSize"
  btTypedConstraint_getDbgDrawSize'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_internalSetAppliedImpulse"
  btTypedConstraint_internalSetAppliedImpulse'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_needsFeedback"
  btTypedConstraint_needsFeedback'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getUserConstraintPtr"
  btTypedConstraint_getUserConstraintPtr'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_setEnabled"
  btTypedConstraint_setEnabled'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getUid"
  btTypedConstraint_getUid'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_setDbgDrawSize"
  btTypedConstraint_setDbgDrawSize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_setUserConstraintType"
  btTypedConstraint_setUserConstraintType'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_internalGetAppliedImpulse"
  btTypedConstraint_internalGetAppliedImpulse'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_setupSolverConstraint"
  btTypedConstraint_setupSolverConstraint'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getBreakingImpulseThreshold"
  btTypedConstraint_getBreakingImpulseThreshold'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getUserConstraintType"
  btTypedConstraint_getUserConstraintType'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_solveConstraintObsolete"
  btTypedConstraint_solveConstraintObsolete'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_getAppliedImpulse"
  btTypedConstraint_getAppliedImpulse'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_setUserConstraintPtr"
  btTypedConstraint_setUserConstraintPtr'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_appliedImpulse_set"
  btTypedConstraint_m_appliedImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_appliedImpulse_get"
  btTypedConstraint_m_appliedImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_breakingImpulseThreshold_set"
  btTypedConstraint_m_breakingImpulseThreshold_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_breakingImpulseThreshold_get"
  btTypedConstraint_m_breakingImpulseThreshold_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_dbgDrawSize_set"
  btTypedConstraint_m_dbgDrawSize_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_dbgDrawSize_get"
  btTypedConstraint_m_dbgDrawSize_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_isEnabled_set"
  btTypedConstraint_m_isEnabled_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_isEnabled_get"
  btTypedConstraint_m_isEnabled_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_needsFeedback_set"
  btTypedConstraint_m_needsFeedback_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_needsFeedback_get"
  btTypedConstraint_m_needsFeedback_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_rbA_set"
  btTypedConstraint_m_rbA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_rbA_get"
  btTypedConstraint_m_rbA_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_rbB_set"
  btTypedConstraint_m_rbB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_rbB_get"
  btTypedConstraint_m_rbB_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_userConstraintType_set"
  btTypedConstraint_m_userConstraintType_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraint_m_userConstraintType_get"
  btTypedConstraint_m_userConstraintType_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_new"
  btTypedConstraintData'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_free"
  btTypedConstraintData_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_appliedImpulse_set"
  btTypedConstraintData_m_appliedImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_appliedImpulse_get"
  btTypedConstraintData_m_appliedImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_dbgDrawSize_set"
  btTypedConstraintData_m_dbgDrawSize_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_dbgDrawSize_get"
  btTypedConstraintData_m_dbgDrawSize_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_disableCollisionsBetweenLinkedBodies_set"
  btTypedConstraintData_m_disableCollisionsBetweenLinkedBodies_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_disableCollisionsBetweenLinkedBodies_get"
  btTypedConstraintData_m_disableCollisionsBetweenLinkedBodies_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_name_set"
  btTypedConstraintData_m_name_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_name_get"
  btTypedConstraintData_m_name_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_needsFeedback_set"
  btTypedConstraintData_m_needsFeedback_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_needsFeedback_get"
  btTypedConstraintData_m_needsFeedback_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_objectType_set"
  btTypedConstraintData_m_objectType_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_objectType_get"
  btTypedConstraintData_m_objectType_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_rbA_set"
  btTypedConstraintData_m_rbA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_rbA_get"
  btTypedConstraintData_m_rbA_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_rbB_set"
  btTypedConstraintData_m_rbB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_rbB_get"
  btTypedConstraintData_m_rbB_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_userConstraintId_set"
  btTypedConstraintData_m_userConstraintId_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_userConstraintId_get"
  btTypedConstraintData_m_userConstraintId_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_userConstraintType_set"
  btTypedConstraintData_m_userConstraintType_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btTypedConstraintData_m_userConstraintType_get"
  btTypedConstraintData_m_userConstraintType_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_new"
  btUniversalConstraint'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO (C2HSImp.Ptr ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_free"
  btUniversalConstraint_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_setLowerLimit"
  btUniversalConstraint_setLowerLimit'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_getAnchor2"
  btUniversalConstraint_getAnchor2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_setAxis"
  btUniversalConstraint_setAxis'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_setAxis"
  btUniversalConstraint_setAxis''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_getAxis1"
  btUniversalConstraint_getAxis1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_getAnchor"
  btUniversalConstraint_getAnchor'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_getAxis2"
  btUniversalConstraint_getAxis2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_setUpperLimit"
  btUniversalConstraint_setUpperLimit'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_getAngle2"
  btUniversalConstraint_getAngle2'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_getAngle1"
  btUniversalConstraint_getAngle1'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_m_anchor_set"
  btUniversalConstraint_m_anchor_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_m_anchor_get"
  btUniversalConstraint_m_anchor_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_m_axis1_set"
  btUniversalConstraint_m_axis1_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_m_axis1_get"
  btUniversalConstraint_m_axis1_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_m_axis2_set"
  btUniversalConstraint_m_axis2_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletDynamics/ConstraintSolver.chs.h btUniversalConstraint_m_axis2_get"
  btUniversalConstraint_m_axis2_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))