-- 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/BulletSoftBody.chs" #-}
{-#LANGUAGE ForeignFunctionInterface#-}

module Physics.Bullet.Raw.BulletSoftBody (
module Physics.Bullet.Raw.BulletSoftBody
) 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
-- * AJoint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#526>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint :: IO ((BtSoftBody_AJoint))
btSoftBody_AJoint =
  btSoftBody_AJoint'_ >>= \res ->
  mkBtSoftBody_AJoint res >>= \res' ->
  return (res')

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

btSoftBody_AJoint_free :: ( BtSoftBody_AJointClass bc ) => (bc) -> IO ()
btSoftBody_AJoint_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_AJoint_free'_ a1' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#543>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_Terminate :: ( BtSoftBody_AJointClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> IO ()
btSoftBody_AJoint_Terminate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_AJoint_Terminate'_ a1' a2' >>
  return ()

{-# LINE 24 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#542>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_Solve :: ( BtSoftBody_AJointClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> (Float) -- ^ sor
 -> IO ()
btSoftBody_AJoint_Solve a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btSoftBody_AJoint_Solve'_ a1' a2' a3' >>
  return ()

{-# LINE 31 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#541>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_Prepare :: ( BtSoftBody_AJointClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> (Int) -- ^ iterations
 -> IO ()
btSoftBody_AJoint_Prepare a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = fromIntegral a3} in 
  btSoftBody_AJoint_Prepare'_ a1' a2' a3' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#540>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_m_icontrol_set :: ( BtSoftBody_AJointClass bc , BtSoftBody_AJoint_IControlClass a ) => (bc) -> (a) -> IO ()
btSoftBody_AJoint_m_icontrol_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_AJoint_m_icontrol_set'_ a1' a2' >>
  return ()

{-# LINE 42 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#540>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_m_icontrol_get :: ( BtSoftBody_AJointClass bc ) => (bc) -> IO ((BtSoftBody_AJoint_IControl))
btSoftBody_AJoint_m_icontrol_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_AJoint_m_icontrol_get'_ a1' >>= \res ->
  mkBtSoftBody_AJoint_IControl res >>= \res' ->
  return (res')

{-# LINE 46 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Anchor
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#284>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor :: IO ((BtSoftBody_Anchor))
btSoftBody_Anchor =
  btSoftBody_Anchor'_ >>= \res ->
  mkBtSoftBody_Anchor res >>= \res' ->
  return (res')

{-# LINE 51 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Anchor_free :: ( BtSoftBody_AnchorClass bc ) => (bc) -> IO ()
btSoftBody_Anchor_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Anchor_free'_ a1' >>
  return ()

{-# LINE 52 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#285>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_node_set :: ( BtSoftBody_AnchorClass bc , BtSoftBody_NodeClass a ) => (bc) -> (a) -> IO ()
btSoftBody_Anchor_m_node_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Anchor_m_node_set'_ a1' a2' >>
  return ()

{-# LINE 56 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#285>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_node_get :: ( BtSoftBody_AnchorClass bc ) => (bc) -> IO ((BtSoftBody_Node))
btSoftBody_Anchor_m_node_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Anchor_m_node_get'_ a1' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')

{-# LINE 60 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#286>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_local_set :: ( BtSoftBody_AnchorClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Anchor_m_local_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Anchor_m_local_set'_ a1' a2' >>
  return ()

{-# LINE 64 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#286>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_local_get :: ( BtSoftBody_AnchorClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Anchor_m_local_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Anchor_m_local_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#287>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_body_set :: ( BtSoftBody_AnchorClass bc , BtRigidBodyClass a ) => (bc) -> (a) -> IO ()
btSoftBody_Anchor_m_body_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Anchor_m_body_set'_ a1' a2' >>
  return ()

{-# LINE 72 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#287>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_body_get :: ( BtSoftBody_AnchorClass bc ) => (bc) -> IO ((BtRigidBody))
btSoftBody_Anchor_m_body_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Anchor_m_body_get'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

{-# LINE 76 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#288>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_influence_set :: ( BtSoftBody_AnchorClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Anchor_m_influence_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Anchor_m_influence_set'_ a1' a2' >>
  return ()

{-# LINE 80 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#288>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_influence_get :: ( BtSoftBody_AnchorClass bc ) => (bc) -> IO ((Float))
btSoftBody_Anchor_m_influence_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Anchor_m_influence_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 84 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#289>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_c0_set :: ( BtSoftBody_AnchorClass bc ) => (bc) -> (Mat3) -> IO ()
btSoftBody_Anchor_m_c0_set a1 a2 =
  withBt a1 $ \a1' -> 
  withMat3 a2 $ \a2' -> 
  btSoftBody_Anchor_m_c0_set'_ a1' a2' >>
  return ()

{-# LINE 88 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#289>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_c0_get :: ( BtSoftBody_AnchorClass bc ) => (bc) -> IO ((Mat3))
btSoftBody_Anchor_m_c0_get a1 =
  withBt a1 $ \a1' -> 
  allocaMat3 $ \a2' -> 
  btSoftBody_Anchor_m_c0_get'_ a1' a2' >>
  peekMat3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 92 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#290>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_c1_set :: ( BtSoftBody_AnchorClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Anchor_m_c1_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Anchor_m_c1_set'_ a1' a2' >>
  return ()

{-# LINE 96 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#290>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_c1_get :: ( BtSoftBody_AnchorClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Anchor_m_c1_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Anchor_m_c1_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 100 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#291>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_c2_set :: ( BtSoftBody_AnchorClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Anchor_m_c2_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Anchor_m_c2_set'_ a1' a2' >>
  return ()

{-# LINE 104 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#291>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Anchor_m_c2_get :: ( BtSoftBody_AnchorClass bc ) => (bc) -> IO ((Float))
btSoftBody_Anchor_m_c2_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Anchor_m_c2_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 108 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Body
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#379>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body0 :: IO ((BtSoftBody_Body))
btSoftBody_Body0 =
  btSoftBody_Body0'_ >>= \res ->
  mkBtSoftBody_Body res >>= \res' ->
  return (res')

{-# LINE 113 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#380>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body1 :: ( BtSoftBody_ClusterClass p0 ) => (p0) -> IO ((BtSoftBody_Body))
btSoftBody_Body1 a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Body1'_ a1' >>= \res ->
  mkBtSoftBody_Body res >>= \res' ->
  return (res')

{-# LINE 117 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#381>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body2 :: ( BtCollisionObjectClass p0 ) => (p0) -> IO ((BtSoftBody_Body))
btSoftBody_Body2 a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Body2'_ a1' >>= \res ->
  mkBtSoftBody_Body res >>= \res' ->
  return (res')

{-# LINE 121 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Body_free :: ( BtSoftBody_BodyClass bc ) => (bc) -> IO ()
btSoftBody_Body_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Body_free'_ a1' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#394>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_invWorldInertia :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> IO ((Mat3))
btSoftBody_Body_invWorldInertia a1 =
  withBt a1 $ \a1' -> 
  allocaMat3 $ \a2' -> 
  btSoftBody_Body_invWorldInertia'_ a1' a2' >>
  peekMat3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 128 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#386>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_activate :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_Body_activate a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Body_activate'_ a1' >>
  return ()

{-# LINE 133 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#414>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_linearVelocity :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_Body_linearVelocity a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Body_linearVelocity'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 139 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#436>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_applyVImpulse :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ impulse
 -> (Vec3) -- ^ rpos
 -> IO ((Vec3), (Vec3))
btSoftBody_Body_applyVImpulse a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btSoftBody_Body_applyVImpulse'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 146 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 153 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#441>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_applyDImpulse :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ impulse
 -> (Vec3) -- ^ rpos
 -> IO ((Vec3), (Vec3))
btSoftBody_Body_applyDImpulse a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btSoftBody_Body_applyDImpulse'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 160 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#474>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_applyDCImpulse :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ impulse
 -> IO ((Vec3))
btSoftBody_Body_applyDCImpulse a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Body_applyDCImpulse'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#474>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_applyDCImpulse' :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_Body_applyDCImpulse' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Body_applyDCImpulse''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#469>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_applyAImpulse :: ( BtSoftBody_BodyClass bc , BtSoftBody_ImpulseClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ impulse
 -> IO ()
btSoftBody_Body_applyAImpulse a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Body_applyAImpulse'_ a1' a2' >>
  return ()

{-# LINE 185 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#420>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_angularVelocity :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ rpos
 -> IO ((Vec3), (Vec3))
btSoftBody_Body_angularVelocity a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btSoftBody_Body_angularVelocity'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 192 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 199 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#420>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_angularVelocity0 :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ rpos
 -> IO ((Vec3), (Vec3))
btSoftBody_Body_angularVelocity0 a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btSoftBody_Body_angularVelocity0'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

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

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

{-# LINE 213 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#426>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_angularVelocity1 :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_Body_angularVelocity1 a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Body_angularVelocity1'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 219 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#459>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_applyVAImpulse :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ impulse
 -> IO ((Vec3))
btSoftBody_Body_applyVAImpulse a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Body_applyVAImpulse'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 225 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#459>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_applyVAImpulse' :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_Body_applyVAImpulse' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Body_applyVAImpulse''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 231 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#446>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_applyImpulse :: ( BtSoftBody_BodyClass bc , BtSoftBody_ImpulseClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ impulse
 -> (Vec3) -- ^ rpos
 -> IO ((Vec3))
btSoftBody_Body_applyImpulse a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btSoftBody_Body_applyImpulse'_ a1' a2' a3' >>
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')

{-# LINE 238 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#446>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_applyImpulse' :: ( BtSoftBody_BodyClass bc , BtSoftBody_ImpulseClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ impulse
 -> IO ((Vec3))
btSoftBody_Body_applyImpulse' a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btSoftBody_Body_applyImpulse''_ a1' a2' a3' >>
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')

{-# LINE 245 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#464>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_applyDAImpulse :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ impulse
 -> IO ((Vec3))
btSoftBody_Body_applyDAImpulse a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Body_applyDAImpulse'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 251 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#464>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_applyDAImpulse' :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_Body_applyDAImpulse' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Body_applyDAImpulse''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 257 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#432>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_velocity :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ rpos
 -> IO ((Vec3), (Vec3))
btSoftBody_Body_velocity a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btSoftBody_Body_velocity'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

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

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

{-# LINE 271 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#401>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_invMass :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSoftBody_Body_invMass a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Body_invMass'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 276 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#407>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_xform :: ( BtSoftBody_BodyClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btSoftBody_Body_xform a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSoftBody_Body_xform'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#375>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_m_soft_set :: ( BtSoftBody_BodyClass bc , BtSoftBody_ClusterClass a ) => (bc) -> (a) -> IO ()
btSoftBody_Body_m_soft_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Body_m_soft_set'_ a1' a2' >>
  return ()

{-# LINE 286 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#375>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_m_soft_get :: ( BtSoftBody_BodyClass bc ) => (bc) -> IO ((BtSoftBody_Cluster))
btSoftBody_Body_m_soft_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Body_m_soft_get'_ a1' >>= \res ->
  mkBtSoftBody_Cluster res >>= \res' ->
  return (res')

{-# LINE 290 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_m_rigid_set :: ( BtSoftBody_BodyClass bc , BtRigidBodyClass a ) => (bc) -> (a) -> IO ()
btSoftBody_Body_m_rigid_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Body_m_rigid_set'_ a1' a2' >>
  return ()

{-# LINE 294 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_m_rigid_get :: ( BtSoftBody_BodyClass bc ) => (bc) -> IO ((BtRigidBody))
btSoftBody_Body_m_rigid_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Body_m_rigid_get'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#377>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_m_collisionObject_set :: ( BtSoftBody_BodyClass bc , BtCollisionObjectClass a ) => (bc) -> (a) -> IO ()
btSoftBody_Body_m_collisionObject_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Body_m_collisionObject_set'_ a1' a2' >>
  return ()

{-# LINE 302 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#377>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Body_m_collisionObject_get :: ( BtSoftBody_BodyClass bc ) => (bc) -> IO ((BtCollisionObject))
btSoftBody_Body_m_collisionObject_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Body_m_collisionObject_get'_ a1' >>= \res ->
  mkBtCollisionObject res >>= \res' ->
  return (res')

{-# LINE 306 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * CJoint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#548>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_CJoint :: IO ((BtSoftBody_CJoint))
btSoftBody_CJoint =
  btSoftBody_CJoint'_ >>= \res ->
  mkBtSoftBody_CJoint res >>= \res' ->
  return (res')

{-# LINE 311 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_CJoint_free :: ( BtSoftBody_CJointClass bc ) => (bc) -> IO ()
btSoftBody_CJoint_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_CJoint_free'_ a1' >>
  return ()

{-# LINE 312 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#556>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_CJoint_Terminate :: ( BtSoftBody_CJointClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> IO ()
btSoftBody_CJoint_Terminate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_CJoint_Terminate'_ a1' a2' >>
  return ()

{-# LINE 318 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#555>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_CJoint_Solve :: ( BtSoftBody_CJointClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> (Float) -- ^ sor
 -> IO ()
btSoftBody_CJoint_Solve a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btSoftBody_CJoint_Solve'_ a1' a2' a3' >>
  return ()

{-# LINE 325 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#554>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_CJoint_Prepare :: ( BtSoftBody_CJointClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> (Int) -- ^ iterations
 -> IO ()
btSoftBody_CJoint_Prepare a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = fromIntegral a3} in 
  btSoftBody_CJoint_Prepare'_ a1' a2' a3' >>
  return ()

{-# LINE 332 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#549>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_CJoint_m_life_set :: ( BtSoftBody_CJointClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_CJoint_m_life_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_CJoint_m_life_set'_ a1' a2' >>
  return ()

{-# LINE 336 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#549>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_CJoint_m_life_get :: ( BtSoftBody_CJointClass bc ) => (bc) -> IO ((Int))
btSoftBody_CJoint_m_life_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_CJoint_m_life_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 340 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#550>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_CJoint_m_maxlife_set :: ( BtSoftBody_CJointClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_CJoint_m_maxlife_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_CJoint_m_maxlife_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#550>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_CJoint_m_maxlife_get :: ( BtSoftBody_CJointClass bc ) => (bc) -> IO ((Int))
btSoftBody_CJoint_m_maxlife_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_CJoint_m_maxlife_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 348 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#552>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_CJoint_m_normal_set :: ( BtSoftBody_CJointClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_CJoint_m_normal_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_CJoint_m_normal_set'_ a1' a2' >>
  return ()

{-# LINE 352 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#552>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_CJoint_m_normal_get :: ( BtSoftBody_CJointClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_CJoint_m_normal_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_CJoint_m_normal_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 356 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#553>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_CJoint_m_friction_set :: ( BtSoftBody_CJointClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_CJoint_m_friction_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_CJoint_m_friction_set'_ a1' a2' >>
  return ()

{-# LINE 360 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#553>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_CJoint_m_friction_get :: ( BtSoftBody_CJointClass bc ) => (bc) -> IO ((Float))
btSoftBody_CJoint_m_friction_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_CJoint_m_friction_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 364 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Cluster
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#343>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster :: IO ((BtSoftBody_Cluster))
btSoftBody_Cluster =
  btSoftBody_Cluster'_ >>= \res ->
  mkBtSoftBody_Cluster res >>= \res' ->
  return (res')

{-# LINE 369 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Cluster_free :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ()
btSoftBody_Cluster_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_free'_ a1' >>
  return ()

{-# LINE 370 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#336>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_adamping_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Cluster_m_adamping_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Cluster_m_adamping_set'_ a1' a2' >>
  return ()

{-# LINE 374 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#336>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_adamping_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Float))
btSoftBody_Cluster_m_adamping_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_adamping_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 378 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#332>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_av_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Cluster_m_av_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Cluster_m_av_set'_ a1' a2' >>
  return ()

{-# LINE 382 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#332>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_av_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Cluster_m_av_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Cluster_m_av_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 386 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#342>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_clusterIndex_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Cluster_m_clusterIndex_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Cluster_m_clusterIndex_set'_ a1' a2' >>
  return ()

{-# LINE 390 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#342>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_clusterIndex_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Int))
btSoftBody_Cluster_m_clusterIndex_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_clusterIndex_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#341>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_collide_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Bool) -> IO ()
btSoftBody_Cluster_m_collide_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSoftBody_Cluster_m_collide_set'_ a1' a2' >>
  return ()

{-# LINE 398 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#341>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_collide_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Bool))
btSoftBody_Cluster_m_collide_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_collide_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 402 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#326>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_com_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Cluster_m_com_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Cluster_m_com_set'_ a1' a2' >>
  return ()

{-# LINE 406 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#326>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_com_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Cluster_m_com_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Cluster_m_com_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 410 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#340>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_containsAnchor_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Bool) -> IO ()
btSoftBody_Cluster_m_containsAnchor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSoftBody_Cluster_m_containsAnchor_set'_ a1' a2' >>
  return ()

{-# LINE 414 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#340>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_containsAnchor_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Bool))
btSoftBody_Cluster_m_containsAnchor_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_containsAnchor_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 418 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#320>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_framerefs_set :: ( BtSoftBody_ClusterClass bc , BtAlignedObjectArray_btVector3_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_Cluster_m_framerefs_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Cluster_m_framerefs_set'_ a1' a2' >>
  return ()

{-# LINE 422 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#320>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_framerefs_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btVector3_))
btSoftBody_Cluster_m_framerefs_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_framerefs_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btVector3_ res >>= \res' ->
  return (res')

{-# LINE 426 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#321>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_framexform_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Transform) -> IO ()
btSoftBody_Cluster_m_framexform_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btSoftBody_Cluster_m_framexform_set'_ a1' a2' >>
  return ()

{-# LINE 430 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#321>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_framexform_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Transform))
btSoftBody_Cluster_m_framexform_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSoftBody_Cluster_m_framexform_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 434 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#322>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_idmass_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Cluster_m_idmass_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Cluster_m_idmass_set'_ a1' a2' >>
  return ()

{-# LINE 438 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#322>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_idmass_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Float))
btSoftBody_Cluster_m_idmass_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_idmass_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 442 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#323>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_imass_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Cluster_m_imass_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Cluster_m_imass_set'_ a1' a2' >>
  return ()

{-# LINE 446 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#323>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_imass_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Float))
btSoftBody_Cluster_m_imass_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_imass_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 450 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#325>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_invwi_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Mat3) -> IO ()
btSoftBody_Cluster_m_invwi_set a1 a2 =
  withBt a1 $ \a1' -> 
  withMat3 a2 $ \a2' -> 
  btSoftBody_Cluster_m_invwi_set'_ a1' a2' >>
  return ()

{-# LINE 454 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#325>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_invwi_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Mat3))
btSoftBody_Cluster_m_invwi_get a1 =
  withBt a1 $ \a1' -> 
  allocaMat3 $ \a2' -> 
  btSoftBody_Cluster_m_invwi_get'_ a1' a2' >>
  peekMat3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 458 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#335>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_ldamping_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Cluster_m_ldamping_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Cluster_m_ldamping_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#335>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_ldamping_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Float))
btSoftBody_Cluster_m_ldamping_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_ldamping_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#333>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_leaf_set :: ( BtSoftBody_ClusterClass bc , BtDbvtNodeClass a ) => (bc) -> (a) -> IO ()
btSoftBody_Cluster_m_leaf_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Cluster_m_leaf_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#333>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_leaf_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((BtDbvtNode))
btSoftBody_Cluster_m_leaf_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_leaf_get'_ a1' >>= \res ->
  mkBtDbvtNode res >>= \res' ->
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#324>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_locii_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Mat3) -> IO ()
btSoftBody_Cluster_m_locii_set a1 a2 =
  withBt a1 $ \a1' -> 
  withMat3 a2 $ \a2' -> 
  btSoftBody_Cluster_m_locii_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#324>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_locii_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Mat3))
btSoftBody_Cluster_m_locii_get a1 =
  withBt a1 $ \a1' -> 
  allocaMat3 $ \a2' -> 
  btSoftBody_Cluster_m_locii_get'_ a1' a2' >>
  peekMat3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#331>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_lv_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Cluster_m_lv_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Cluster_m_lv_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#331>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_lv_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Cluster_m_lv_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Cluster_m_lv_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#318>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_masses_set :: ( BtSoftBody_ClusterClass bc , BtAlignedObjectArray_float_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_Cluster_m_masses_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Cluster_m_masses_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#318>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_masses_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((BtAlignedObjectArray_float_))
btSoftBody_Cluster_m_masses_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_masses_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_float_ res >>= \res' ->
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#337>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_matching_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Cluster_m_matching_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Cluster_m_matching_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#337>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_matching_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Float))
btSoftBody_Cluster_m_matching_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_matching_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#338>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_maxSelfCollisionImpulse_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Cluster_m_maxSelfCollisionImpulse_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Cluster_m_maxSelfCollisionImpulse_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#338>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_maxSelfCollisionImpulse_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Float))
btSoftBody_Cluster_m_maxSelfCollisionImpulse_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_maxSelfCollisionImpulse_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#334>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_ndamping_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Cluster_m_ndamping_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Cluster_m_ndamping_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#334>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_ndamping_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Float))
btSoftBody_Cluster_m_ndamping_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_ndamping_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#330>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_ndimpulses_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Cluster_m_ndimpulses_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Cluster_m_ndimpulses_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#330>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_ndimpulses_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Int))
btSoftBody_Cluster_m_ndimpulses_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_ndimpulses_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#319>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_nodes_set :: ( BtSoftBody_ClusterClass bc , BtAlignedObjectArray_btSoftBody_Node_ptr_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_Cluster_m_nodes_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Cluster_m_nodes_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#319>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_nodes_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_Node_ptr_))
btSoftBody_Cluster_m_nodes_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_nodes_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Node_ptr_ res >>= \res' ->
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#329>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_nvimpulses_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Cluster_m_nvimpulses_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Cluster_m_nvimpulses_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#329>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_nvimpulses_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Int))
btSoftBody_Cluster_m_nvimpulses_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_nvimpulses_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#339>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_selfCollisionImpulseFactor_set :: ( BtSoftBody_ClusterClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Cluster_m_selfCollisionImpulseFactor_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Cluster_m_selfCollisionImpulseFactor_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#339>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Cluster_m_selfCollisionImpulseFactor_get :: ( BtSoftBody_ClusterClass bc ) => (bc) -> IO ((Float))
btSoftBody_Cluster_m_selfCollisionImpulseFactor_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Cluster_m_selfCollisionImpulseFactor_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

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

-- * Config
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#561>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config :: IO ((BtSoftBody_Config))
btSoftBody_Config =
  btSoftBody_Config'_ >>= \res ->
  mkBtSoftBody_Config res >>= \res' ->
  return (res')

{-# LINE 559 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Config_free :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ()
btSoftBody_Config_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_free'_ a1' >>
  return ()

{-# LINE 560 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#563>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kVCF_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kVCF_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kVCF_set'_ a1' a2' >>
  return ()

{-# LINE 564 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#563>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kVCF_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kVCF_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kVCF_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 568 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#564>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kDP_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kDP_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kDP_set'_ a1' a2' >>
  return ()

{-# LINE 572 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#564>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kDP_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kDP_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kDP_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 576 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#565>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kDG_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kDG_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kDG_set'_ a1' a2' >>
  return ()

{-# LINE 580 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#565>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kDG_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kDG_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kDG_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 584 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#566>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kLF_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kLF_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kLF_set'_ a1' a2' >>
  return ()

{-# LINE 588 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#566>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kLF_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kLF_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kLF_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 592 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#567>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kPR_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kPR_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kPR_set'_ a1' a2' >>
  return ()

{-# LINE 596 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#567>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kPR_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kPR_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kPR_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 600 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#568>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kVC_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kVC_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kVC_set'_ a1' a2' >>
  return ()

{-# LINE 604 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#568>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kVC_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kVC_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kVC_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 608 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#569>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kDF_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kDF_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kDF_set'_ a1' a2' >>
  return ()

{-# LINE 612 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#569>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kDF_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kDF_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kDF_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 616 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#570>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kMT_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kMT_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kMT_set'_ a1' a2' >>
  return ()

{-# LINE 620 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#570>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kMT_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kMT_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kMT_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 624 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#571>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kCHR_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kCHR_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kCHR_set'_ a1' a2' >>
  return ()

{-# LINE 628 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#571>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kCHR_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kCHR_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kCHR_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 632 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#572>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kKHR_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kKHR_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kKHR_set'_ a1' a2' >>
  return ()

{-# LINE 636 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#572>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kKHR_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kKHR_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kKHR_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 640 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#573>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSHR_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kSHR_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kSHR_set'_ a1' a2' >>
  return ()

{-# LINE 644 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#573>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSHR_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kSHR_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kSHR_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 648 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#574>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kAHR_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kAHR_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kAHR_set'_ a1' a2' >>
  return ()

{-# LINE 652 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#574>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kAHR_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kAHR_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kAHR_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 656 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#575>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSRHR_CL_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kSRHR_CL_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kSRHR_CL_set'_ a1' a2' >>
  return ()

{-# LINE 660 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#575>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSRHR_CL_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kSRHR_CL_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kSRHR_CL_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 664 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#576>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSKHR_CL_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kSKHR_CL_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kSKHR_CL_set'_ a1' a2' >>
  return ()

{-# LINE 668 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#576>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSKHR_CL_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kSKHR_CL_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kSKHR_CL_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 672 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#577>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSSHR_CL_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kSSHR_CL_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kSSHR_CL_set'_ a1' a2' >>
  return ()

{-# LINE 676 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#577>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSSHR_CL_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kSSHR_CL_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kSSHR_CL_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 680 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#578>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSR_SPLT_CL_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kSR_SPLT_CL_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kSR_SPLT_CL_set'_ a1' a2' >>
  return ()

{-# LINE 684 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#578>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSR_SPLT_CL_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kSR_SPLT_CL_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kSR_SPLT_CL_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 688 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#579>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSK_SPLT_CL_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kSK_SPLT_CL_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kSK_SPLT_CL_set'_ a1' a2' >>
  return ()

{-# LINE 692 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#579>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSK_SPLT_CL_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kSK_SPLT_CL_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kSK_SPLT_CL_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 696 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#580>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSS_SPLT_CL_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_kSS_SPLT_CL_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_kSS_SPLT_CL_set'_ a1' a2' >>
  return ()

{-# LINE 700 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#580>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_kSS_SPLT_CL_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_kSS_SPLT_CL_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_kSS_SPLT_CL_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 704 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#581>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_maxvolume_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_maxvolume_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_maxvolume_set'_ a1' a2' >>
  return ()

{-# LINE 708 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#581>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_maxvolume_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_maxvolume_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_maxvolume_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 712 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#582>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_timescale_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Config_timescale_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Config_timescale_set'_ a1' a2' >>
  return ()

{-# LINE 716 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#582>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_timescale_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Float))
btSoftBody_Config_timescale_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_timescale_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 720 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#583>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_viterations_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Config_viterations_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Config_viterations_set'_ a1' a2' >>
  return ()

{-# LINE 724 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#583>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_viterations_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Int))
btSoftBody_Config_viterations_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_viterations_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 728 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#584>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_piterations_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Config_piterations_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Config_piterations_set'_ a1' a2' >>
  return ()

{-# LINE 732 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#584>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_piterations_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Int))
btSoftBody_Config_piterations_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_piterations_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 736 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#585>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_diterations_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Config_diterations_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Config_diterations_set'_ a1' a2' >>
  return ()

{-# LINE 740 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#585>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_diterations_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Int))
btSoftBody_Config_diterations_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_diterations_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 744 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#586>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_citerations_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Config_citerations_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Config_citerations_set'_ a1' a2' >>
  return ()

{-# LINE 748 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#586>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_citerations_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Int))
btSoftBody_Config_citerations_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_citerations_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 752 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#587>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_collisions_set :: ( BtSoftBody_ConfigClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Config_collisions_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Config_collisions_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#587>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_collisions_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((Int))
btSoftBody_Config_collisions_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_collisions_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#588>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_m_vsequence_set :: ( BtSoftBody_ConfigClass bc , BtAlignedObjectArray_btSoftBody_eVSolver___Class a ) => (bc) -> (a) -> IO ()
btSoftBody_Config_m_vsequence_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Config_m_vsequence_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#588>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_m_vsequence_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_eVSolver___))
btSoftBody_Config_m_vsequence_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_m_vsequence_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_eVSolver___ res >>= \res' ->
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#589>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_m_psequence_set :: ( BtSoftBody_ConfigClass bc , BtAlignedObjectArray_btSoftBody_ePSolver___Class a ) => (bc) -> (a) -> IO ()
btSoftBody_Config_m_psequence_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Config_m_psequence_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#589>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_m_psequence_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_ePSolver___))
btSoftBody_Config_m_psequence_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_m_psequence_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_ePSolver___ res >>= \res' ->
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#590>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_m_dsequence_set :: ( BtSoftBody_ConfigClass bc , BtAlignedObjectArray_btSoftBody_ePSolver___Class a ) => (bc) -> (a) -> IO ()
btSoftBody_Config_m_dsequence_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Config_m_dsequence_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#590>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Config_m_dsequence_get :: ( BtSoftBody_ConfigClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_ePSolver___))
btSoftBody_Config_m_dsequence_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Config_m_dsequence_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_ePSolver___ res >>= \res' ->
  return (res')

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

-- * Element
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#202>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Element :: IO ((BtSoftBody_Element))
btSoftBody_Element =
  btSoftBody_Element'_ >>= \res ->
  mkBtSoftBody_Element res >>= \res' ->
  return (res')

{-# LINE 789 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Element_free :: ( BtSoftBody_ElementClass bc ) => (bc) -> IO ()
btSoftBody_Element_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Element_free'_ a1' >>
  return ()

{-# LINE 790 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#201>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Element_m_tag_set :: ( BtSoftBody_ElementClass bc ) => (bc) -> (VoidPtr) -> IO ()
btSoftBody_Element_m_tag_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  btSoftBody_Element_m_tag_set'_ a1' a2' >>
  return ()

{-# LINE 794 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#201>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Element_m_tag_get :: ( BtSoftBody_ElementClass bc ) => (bc) -> IO ((VoidPtr))
btSoftBody_Element_m_tag_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Element_m_tag_get'_ a1' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')

{-# LINE 798 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Face
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#244>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Face :: IO ((BtSoftBody_Face))
btSoftBody_Face =
  btSoftBody_Face'_ >>= \res ->
  mkBtSoftBody_Face res >>= \res' ->
  return (res')

{-# LINE 803 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Face_free :: ( BtSoftBody_FaceClass bc ) => (bc) -> IO ()
btSoftBody_Face_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Face_free'_ a1' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Face_m_normal_set :: ( BtSoftBody_FaceClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Face_m_normal_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Face_m_normal_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Face_m_normal_get :: ( BtSoftBody_FaceClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Face_m_normal_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Face_m_normal_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#247>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Face_m_ra_set :: ( BtSoftBody_FaceClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Face_m_ra_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Face_m_ra_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#247>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Face_m_ra_get :: ( BtSoftBody_FaceClass bc ) => (bc) -> IO ((Float))
btSoftBody_Face_m_ra_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Face_m_ra_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#248>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Face_m_leaf_set :: ( BtSoftBody_FaceClass bc , BtDbvtNodeClass a ) => (bc) -> (a) -> IO ()
btSoftBody_Face_m_leaf_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Face_m_leaf_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#248>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Face_m_leaf_get :: ( BtSoftBody_FaceClass bc ) => (bc) -> IO ((BtDbvtNode))
btSoftBody_Face_m_leaf_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Face_m_leaf_get'_ a1' >>= \res ->
  mkBtDbvtNode res >>= \res' ->
  return (res')

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

-- * Feature
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#215>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Feature :: IO ((BtSoftBody_Feature))
btSoftBody_Feature =
  btSoftBody_Feature'_ >>= \res ->
  mkBtSoftBody_Feature res >>= \res' ->
  return (res')

{-# LINE 833 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Feature_free :: ( BtSoftBody_FeatureClass bc ) => (bc) -> IO ()
btSoftBody_Feature_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Feature_free'_ a1' >>
  return ()

{-# LINE 834 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#216>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Feature_m_material_set :: ( BtSoftBody_FeatureClass bc , BtSoftBody_MaterialClass a ) => (bc) -> (a) -> IO ()
btSoftBody_Feature_m_material_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Feature_m_material_set'_ a1' a2' >>
  return ()

{-# LINE 838 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#216>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Feature_m_material_get :: ( BtSoftBody_FeatureClass bc ) => (bc) -> IO ((BtSoftBody_Material))
btSoftBody_Feature_m_material_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Feature_m_material_get'_ a1' >>= \res ->
  mkBtSoftBody_Material res >>= \res' ->
  return (res')

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

-- * IControl
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#528>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_IControl :: IO ((BtSoftBody_AJoint_IControl))
btSoftBody_AJoint_IControl =
  btSoftBody_AJoint_IControl'_ >>= \res ->
  mkBtSoftBody_AJoint_IControl res >>= \res' ->
  return (res')

{-# LINE 847 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_AJoint_IControl_free :: ( BtSoftBody_AJoint_IControlClass bc ) => (bc) -> IO ()
btSoftBody_AJoint_IControl_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_AJoint_IControl_free'_ a1' >>
  return ()

{-# LINE 848 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#531>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_IControl_Default :: ( ) => IO ((BtSoftBody_AJoint_IControl))
btSoftBody_AJoint_IControl_Default =
  btSoftBody_AJoint_IControl_Default'_ >>= \res ->
  mkBtSoftBody_AJoint_IControl res >>= \res' ->
  return (res')

{-# LINE 852 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#530>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_IControl_Speed :: ( BtSoftBody_AJoint_IControlClass bc , BtSoftBody_AJointClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ arg0
 -> (Float) -- ^ current
 -> IO ((Float))
btSoftBody_AJoint_IControl_Speed a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btSoftBody_AJoint_IControl_Speed'_ a1' a2' a3' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 859 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#529>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_IControl_Prepare :: ( BtSoftBody_AJoint_IControlClass bc , BtSoftBody_AJointClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ arg0
 -> IO ()
btSoftBody_AJoint_IControl_Prepare a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_AJoint_IControl_Prepare'_ a1' a2' >>
  return ()

{-# LINE 865 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * ImplicitFn
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#172>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_ImplicitFn_Eval :: ( BtSoftBody_ImplicitFnClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ x
 -> IO ((Float), (Vec3))
btSoftBody_ImplicitFn_Eval a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_ImplicitFn_Eval'_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  peekVec3  a2'>>= \a2'' -> 
  return (res', a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#172>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_ImplicitFn_Eval' :: ( BtSoftBody_ImplicitFnClass bc ) => (bc) -- ^ 
 -> IO ((Float), (Vec3))
btSoftBody_ImplicitFn_Eval' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_ImplicitFn_Eval''_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  peekVec3  a2'>>= \a2'' -> 
  return (res', a2'')

{-# LINE 878 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Impulse
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#356>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Impulse :: IO ((BtSoftBody_Impulse))
btSoftBody_Impulse =
  btSoftBody_Impulse'_ >>= \res ->
  mkBtSoftBody_Impulse res >>= \res' ->
  return (res')

{-# LINE 883 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Impulse_free :: ( BtSoftBody_ImpulseClass bc ) => (bc) -> IO ()
btSoftBody_Impulse_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Impulse_free'_ a1' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#355>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Impulse_m_asDrift_set :: ( BtSoftBody_ImpulseClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Impulse_m_asDrift_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Impulse_m_asDrift_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#355>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Impulse_m_asDrift_get :: ( BtSoftBody_ImpulseClass bc ) => (bc) -> IO ((Int))
btSoftBody_Impulse_m_asDrift_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Impulse_m_asDrift_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#354>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Impulse_m_asVelocity_set :: ( BtSoftBody_ImpulseClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Impulse_m_asVelocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Impulse_m_asVelocity_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#354>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Impulse_m_asVelocity_get :: ( BtSoftBody_ImpulseClass bc ) => (bc) -> IO ((Int))
btSoftBody_Impulse_m_asVelocity_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Impulse_m_asVelocity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#353>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Impulse_m_drift_set :: ( BtSoftBody_ImpulseClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Impulse_m_drift_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Impulse_m_drift_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#353>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Impulse_m_drift_get :: ( BtSoftBody_ImpulseClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Impulse_m_drift_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Impulse_m_drift_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 908 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#352>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Impulse_m_velocity_set :: ( BtSoftBody_ImpulseClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Impulse_m_velocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Impulse_m_velocity_set'_ a1' a2' >>
  return ()

{-# LINE 912 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#352>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Impulse_m_velocity_get :: ( BtSoftBody_ImpulseClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Impulse_m_velocity_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Impulse_m_velocity_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 916 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Joint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#508>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_Terminate :: ( BtSoftBody_JointClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> IO ()
btSoftBody_Joint_Terminate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Joint_Terminate'_ a1' a2' >>
  return ()

{-# LINE 923 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#507>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_Solve :: ( BtSoftBody_JointClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> (Float) -- ^ sor
 -> IO ()
btSoftBody_Joint_Solve a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btSoftBody_Joint_Solve'_ a1' a2' a3' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#506>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_Prepare :: ( BtSoftBody_JointClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> (Int) -- ^ iterations
 -> IO ()
btSoftBody_Joint_Prepare a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = fromIntegral a3} in 
  btSoftBody_Joint_Prepare'_ a1' a2' a3' >>
  return ()

{-# LINE 937 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#497>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_cfm_set :: ( BtSoftBody_JointClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Joint_m_cfm_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Joint_m_cfm_set'_ a1' a2' >>
  return ()

{-# LINE 941 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#497>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_cfm_get :: ( BtSoftBody_JointClass bc ) => (bc) -> IO ((Float))
btSoftBody_Joint_m_cfm_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Joint_m_cfm_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 945 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#498>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_erp_set :: ( BtSoftBody_JointClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Joint_m_erp_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Joint_m_erp_set'_ a1' a2' >>
  return ()

{-# LINE 949 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#498>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_erp_get :: ( BtSoftBody_JointClass bc ) => (bc) -> IO ((Float))
btSoftBody_Joint_m_erp_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Joint_m_erp_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 953 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#499>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_split_set :: ( BtSoftBody_JointClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Joint_m_split_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Joint_m_split_set'_ a1' a2' >>
  return ()

{-# LINE 957 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#499>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_split_get :: ( BtSoftBody_JointClass bc ) => (bc) -> IO ((Float))
btSoftBody_Joint_m_split_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Joint_m_split_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 961 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#500>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_drift_set :: ( BtSoftBody_JointClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Joint_m_drift_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Joint_m_drift_set'_ a1' a2' >>
  return ()

{-# LINE 965 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#500>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_drift_get :: ( BtSoftBody_JointClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Joint_m_drift_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Joint_m_drift_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 969 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#501>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_sdrift_set :: ( BtSoftBody_JointClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Joint_m_sdrift_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Joint_m_sdrift_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#501>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_sdrift_get :: ( BtSoftBody_JointClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Joint_m_sdrift_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Joint_m_sdrift_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 977 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#502>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_massmatrix_set :: ( BtSoftBody_JointClass bc ) => (bc) -> (Mat3) -> IO ()
btSoftBody_Joint_m_massmatrix_set a1 a2 =
  withBt a1 $ \a1' -> 
  withMat3 a2 $ \a2' -> 
  btSoftBody_Joint_m_massmatrix_set'_ a1' a2' >>
  return ()

{-# LINE 981 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#502>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_massmatrix_get :: ( BtSoftBody_JointClass bc ) => (bc) -> IO ((Mat3))
btSoftBody_Joint_m_massmatrix_get a1 =
  withBt a1 $ \a1' -> 
  allocaMat3 $ \a2' -> 
  btSoftBody_Joint_m_massmatrix_get'_ a1' a2' >>
  peekMat3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 985 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#503>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_delete_set :: ( BtSoftBody_JointClass bc ) => (bc) -> (Bool) -> IO ()
btSoftBody_Joint_m_delete_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSoftBody_Joint_m_delete_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#503>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_m_delete_get :: ( BtSoftBody_JointClass bc ) => (bc) -> IO ((Bool))
btSoftBody_Joint_m_delete_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Joint_m_delete_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 993 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * LJoint
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#513>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_LJoint :: IO ((BtSoftBody_LJoint))
btSoftBody_LJoint =
  btSoftBody_LJoint'_ >>= \res ->
  mkBtSoftBody_LJoint res >>= \res' ->
  return (res')

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

btSoftBody_LJoint_free :: ( BtSoftBody_LJointClass bc ) => (bc) -> IO ()
btSoftBody_LJoint_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_LJoint_free'_ a1' >>
  return ()

{-# LINE 999 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#521>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_LJoint_Terminate :: ( BtSoftBody_LJointClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> IO ()
btSoftBody_LJoint_Terminate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_LJoint_Terminate'_ a1' a2' >>
  return ()

{-# LINE 1005 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#520>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_LJoint_Solve :: ( BtSoftBody_LJointClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> (Float) -- ^ sor
 -> IO ()
btSoftBody_LJoint_Solve a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btSoftBody_LJoint_Solve'_ a1' a2' a3' >>
  return ()

{-# LINE 1012 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#519>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_LJoint_Prepare :: ( BtSoftBody_LJointClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> (Int) -- ^ iterations
 -> IO ()
btSoftBody_LJoint_Prepare a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = fromIntegral a3} in 
  btSoftBody_LJoint_Prepare'_ a1' a2' a3' >>
  return ()

{-# LINE 1019 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Link
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#233>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Link :: IO ((BtSoftBody_Link))
btSoftBody_Link =
  btSoftBody_Link'_ >>= \res ->
  mkBtSoftBody_Link res >>= \res' ->
  return (res')

{-# LINE 1024 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Link_free :: ( BtSoftBody_LinkClass bc ) => (bc) -> IO ()
btSoftBody_Link_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Link_free'_ a1' >>
  return ()

{-# LINE 1025 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#235>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Link_m_rl_set :: ( BtSoftBody_LinkClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Link_m_rl_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Link_m_rl_set'_ a1' a2' >>
  return ()

{-# LINE 1029 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#235>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Link_m_rl_get :: ( BtSoftBody_LinkClass bc ) => (bc) -> IO ((Float))
btSoftBody_Link_m_rl_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Link_m_rl_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1033 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#236>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Link_m_bbending_set :: ( BtSoftBody_LinkClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Link_m_bbending_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Link_m_bbending_set'_ a1' a2' >>
  return ()

{-# LINE 1037 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#236>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Link_m_bbending_get :: ( BtSoftBody_LinkClass bc ) => (bc) -> IO ((Int))
btSoftBody_Link_m_bbending_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Link_m_bbending_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1041 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#237>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Link_m_c0_set :: ( BtSoftBody_LinkClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Link_m_c0_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Link_m_c0_set'_ a1' a2' >>
  return ()

{-# LINE 1045 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#237>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Link_m_c0_get :: ( BtSoftBody_LinkClass bc ) => (bc) -> IO ((Float))
btSoftBody_Link_m_c0_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Link_m_c0_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1049 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#238>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Link_m_c1_set :: ( BtSoftBody_LinkClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Link_m_c1_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Link_m_c1_set'_ a1' a2' >>
  return ()

{-# LINE 1053 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 1057 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#239>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Link_m_c2_set :: ( BtSoftBody_LinkClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Link_m_c2_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Link_m_c2_set'_ a1' a2' >>
  return ()

{-# LINE 1061 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#239>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Link_m_c2_get :: ( BtSoftBody_LinkClass bc ) => (bc) -> IO ((Float))
btSoftBody_Link_m_c2_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Link_m_c2_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1065 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#240>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Link_m_c3_set :: ( BtSoftBody_LinkClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Link_m_c3_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Link_m_c3_set'_ a1' a2' >>
  return ()

{-# LINE 1069 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#240>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Link_m_c3_get :: ( BtSoftBody_LinkClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Link_m_c3_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Link_m_c3_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1073 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Material
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#206>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Material :: IO ((BtSoftBody_Material))
btSoftBody_Material =
  btSoftBody_Material'_ >>= \res ->
  mkBtSoftBody_Material res >>= \res' ->
  return (res')

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

btSoftBody_Material_free :: ( BtSoftBody_MaterialClass bc ) => (bc) -> IO ()
btSoftBody_Material_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Material_free'_ a1' >>
  return ()

{-# LINE 1079 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#210>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Material_m_flags_set :: ( BtSoftBody_MaterialClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Material_m_flags_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Material_m_flags_set'_ a1' a2' >>
  return ()

{-# LINE 1083 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#210>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Material_m_flags_get :: ( BtSoftBody_MaterialClass bc ) => (bc) -> IO ((Int))
btSoftBody_Material_m_flags_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Material_m_flags_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1087 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#208>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Material_m_kAST_set :: ( BtSoftBody_MaterialClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Material_m_kAST_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Material_m_kAST_set'_ a1' a2' >>
  return ()

{-# LINE 1091 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#208>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Material_m_kAST_get :: ( BtSoftBody_MaterialClass bc ) => (bc) -> IO ((Float))
btSoftBody_Material_m_kAST_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Material_m_kAST_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1095 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#207>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Material_m_kLST_set :: ( BtSoftBody_MaterialClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Material_m_kLST_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Material_m_kLST_set'_ a1' a2' >>
  return ()

{-# LINE 1099 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#207>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Material_m_kLST_get :: ( BtSoftBody_MaterialClass bc ) => (bc) -> IO ((Float))
btSoftBody_Material_m_kLST_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Material_m_kLST_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1103 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#209>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Material_m_kVST_set :: ( BtSoftBody_MaterialClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Material_m_kVST_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Material_m_kVST_set'_ a1' a2' >>
  return ()

{-# LINE 1107 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#209>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Material_m_kVST_get :: ( BtSoftBody_MaterialClass bc ) => (bc) -> IO ((Float))
btSoftBody_Material_m_kVST_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Material_m_kVST_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1111 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Node
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#220>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node :: IO ((BtSoftBody_Node))
btSoftBody_Node =
  btSoftBody_Node'_ >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')

{-# LINE 1116 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Node_free :: ( BtSoftBody_NodeClass bc ) => (bc) -> IO ()
btSoftBody_Node_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Node_free'_ a1' >>
  return ()

{-# LINE 1117 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_area_set :: ( BtSoftBody_NodeClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Node_m_area_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Node_m_area_set'_ a1' a2' >>
  return ()

{-# LINE 1121 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_area_get :: ( BtSoftBody_NodeClass bc ) => (bc) -> IO ((Float))
btSoftBody_Node_m_area_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Node_m_area_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1125 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#229>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_battach_set :: ( BtSoftBody_NodeClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Node_m_battach_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Node_m_battach_set'_ a1' a2' >>
  return ()

{-# LINE 1129 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#229>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_battach_get :: ( BtSoftBody_NodeClass bc ) => (bc) -> IO ((Int))
btSoftBody_Node_m_battach_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Node_m_battach_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1133 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_f_set :: ( BtSoftBody_NodeClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Node_m_f_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Node_m_f_set'_ a1' a2' >>
  return ()

{-# LINE 1137 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_f_get :: ( BtSoftBody_NodeClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Node_m_f_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Node_m_f_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1141 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#226>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_im_set :: ( BtSoftBody_NodeClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Node_m_im_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Node_m_im_set'_ a1' a2' >>
  return ()

{-# LINE 1145 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#226>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_im_get :: ( BtSoftBody_NodeClass bc ) => (bc) -> IO ((Float))
btSoftBody_Node_m_im_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Node_m_im_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1149 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_leaf_set :: ( BtSoftBody_NodeClass bc , BtDbvtNodeClass a ) => (bc) -> (a) -> IO ()
btSoftBody_Node_m_leaf_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Node_m_leaf_set'_ a1' a2' >>
  return ()

{-# LINE 1153 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_leaf_get :: ( BtSoftBody_NodeClass bc ) => (bc) -> IO ((BtDbvtNode))
btSoftBody_Node_m_leaf_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Node_m_leaf_get'_ a1' >>= \res ->
  mkBtDbvtNode res >>= \res' ->
  return (res')

{-# LINE 1157 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_n_set :: ( BtSoftBody_NodeClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Node_m_n_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Node_m_n_set'_ a1' a2' >>
  return ()

{-# LINE 1161 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_n_get :: ( BtSoftBody_NodeClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Node_m_n_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Node_m_n_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1165 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#222>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_q_set :: ( BtSoftBody_NodeClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Node_m_q_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Node_m_q_set'_ a1' a2' >>
  return ()

{-# LINE 1169 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#222>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_q_get :: ( BtSoftBody_NodeClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Node_m_q_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Node_m_q_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#223>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_v_set :: ( BtSoftBody_NodeClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Node_m_v_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Node_m_v_set'_ a1' a2' >>
  return ()

{-# LINE 1177 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#223>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_v_get :: ( BtSoftBody_NodeClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Node_m_v_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Node_m_v_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#221>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_x_set :: ( BtSoftBody_NodeClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Node_m_x_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Node_m_x_set'_ a1' a2' >>
  return ()

{-# LINE 1185 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#221>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Node_m_x_get :: ( BtSoftBody_NodeClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Node_m_x_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Node_m_x_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1189 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Note
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#295>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Note :: IO ((BtSoftBody_Note))
btSoftBody_Note =
  btSoftBody_Note'_ >>= \res ->
  mkBtSoftBody_Note res >>= \res' ->
  return (res')

{-# LINE 1194 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Note_free :: ( BtSoftBody_NoteClass bc ) => (bc) -> IO ()
btSoftBody_Note_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Note_free'_ a1' >>
  return ()

{-# LINE 1195 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#296>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Note_m_text_set :: ( BtSoftBody_NoteClass bc ) => (bc) -> (String) -> IO ()
btSoftBody_Note_m_text_set a1 a2 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  btSoftBody_Note_m_text_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#296>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Note_m_text_get :: ( BtSoftBody_NoteClass bc ) => (bc) -> IO ((String))
btSoftBody_Note_m_text_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Note_m_text_get'_ a1' >>= \res ->
  C2HSImp.peekCString res >>= \res' ->
  return (res')

{-# LINE 1203 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#297>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Note_m_offset_set :: ( BtSoftBody_NoteClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Note_m_offset_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Note_m_offset_set'_ a1' a2' >>
  return ()

{-# LINE 1207 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#297>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Note_m_offset_get :: ( BtSoftBody_NoteClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Note_m_offset_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Note_m_offset_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#298>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Note_m_rank_set :: ( BtSoftBody_NoteClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_Note_m_rank_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_Note_m_rank_set'_ a1' a2' >>
  return ()

{-# LINE 1215 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#298>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Note_m_rank_get :: ( BtSoftBody_NoteClass bc ) => (bc) -> IO ((Int))
btSoftBody_Note_m_rank_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Note_m_rank_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1219 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Pose
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#304>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose :: IO ((BtSoftBody_Pose))
btSoftBody_Pose =
  btSoftBody_Pose'_ >>= \res ->
  mkBtSoftBody_Pose res >>= \res' ->
  return (res')

{-# LINE 1224 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Pose_free :: ( BtSoftBody_PoseClass bc ) => (bc) -> IO ()
btSoftBody_Pose_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Pose_free'_ a1' >>
  return ()

{-# LINE 1225 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#305>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_bvolume_set :: ( BtSoftBody_PoseClass bc ) => (bc) -> (Bool) -> IO ()
btSoftBody_Pose_m_bvolume_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSoftBody_Pose_m_bvolume_set'_ a1' a2' >>
  return ()

{-# LINE 1229 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#305>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_bvolume_get :: ( BtSoftBody_PoseClass bc ) => (bc) -> IO ((Bool))
btSoftBody_Pose_m_bvolume_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Pose_m_bvolume_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1233 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#306>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_bframe_set :: ( BtSoftBody_PoseClass bc ) => (bc) -> (Bool) -> IO ()
btSoftBody_Pose_m_bframe_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSoftBody_Pose_m_bframe_set'_ a1' a2' >>
  return ()

{-# LINE 1237 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#306>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_bframe_get :: ( BtSoftBody_PoseClass bc ) => (bc) -> IO ((Bool))
btSoftBody_Pose_m_bframe_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Pose_m_bframe_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1241 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 1245 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 1249 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#308>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_pos_set :: ( BtSoftBody_PoseClass bc , BtAlignedObjectArray_btVector3_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_Pose_m_pos_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Pose_m_pos_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#308>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_pos_get :: ( BtSoftBody_PoseClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btVector3_))
btSoftBody_Pose_m_pos_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Pose_m_pos_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btVector3_ res >>= \res' ->
  return (res')

{-# LINE 1257 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#309>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_wgh_set :: ( BtSoftBody_PoseClass bc , BtAlignedObjectArray_float_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_Pose_m_wgh_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Pose_m_wgh_set'_ a1' a2' >>
  return ()

{-# LINE 1261 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#309>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_wgh_get :: ( BtSoftBody_PoseClass bc ) => (bc) -> IO ((BtAlignedObjectArray_float_))
btSoftBody_Pose_m_wgh_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Pose_m_wgh_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_float_ res >>= \res' ->
  return (res')

{-# LINE 1265 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#310>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_com_set :: ( BtSoftBody_PoseClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_Pose_m_com_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_Pose_m_com_set'_ a1' a2' >>
  return ()

{-# LINE 1269 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#310>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_com_get :: ( BtSoftBody_PoseClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_Pose_m_com_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_Pose_m_com_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#311>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_rot_set :: ( BtSoftBody_PoseClass bc ) => (bc) -> (Mat3) -> IO ()
btSoftBody_Pose_m_rot_set a1 a2 =
  withBt a1 $ \a1' -> 
  withMat3 a2 $ \a2' -> 
  btSoftBody_Pose_m_rot_set'_ a1' a2' >>
  return ()

{-# LINE 1277 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#311>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_rot_get :: ( BtSoftBody_PoseClass bc ) => (bc) -> IO ((Mat3))
btSoftBody_Pose_m_rot_get a1 =
  withBt a1 $ \a1' -> 
  allocaMat3 $ \a2' -> 
  btSoftBody_Pose_m_rot_get'_ a1' a2' >>
  peekMat3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1281 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#312>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_scl_set :: ( BtSoftBody_PoseClass bc ) => (bc) -> (Mat3) -> IO ()
btSoftBody_Pose_m_scl_set a1 a2 =
  withBt a1 $ \a1' -> 
  withMat3 a2 $ \a2' -> 
  btSoftBody_Pose_m_scl_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#312>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_scl_get :: ( BtSoftBody_PoseClass bc ) => (bc) -> IO ((Mat3))
btSoftBody_Pose_m_scl_get a1 =
  withBt a1 $ \a1' -> 
  allocaMat3 $ \a2' -> 
  btSoftBody_Pose_m_scl_get'_ a1' a2' >>
  peekMat3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1289 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#313>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_aqq_set :: ( BtSoftBody_PoseClass bc ) => (bc) -> (Mat3) -> IO ()
btSoftBody_Pose_m_aqq_set a1 a2 =
  withBt a1 $ \a1' -> 
  withMat3 a2 $ \a2' -> 
  btSoftBody_Pose_m_aqq_set'_ a1' a2' >>
  return ()

{-# LINE 1293 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#313>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Pose_m_aqq_get :: ( BtSoftBody_PoseClass bc ) => (bc) -> IO ((Mat3))
btSoftBody_Pose_m_aqq_get a1 =
  withBt a1 $ \a1' -> 
  allocaMat3 $ \a2' -> 
  btSoftBody_Pose_m_aqq_get'_ a1' a2' >>
  peekMat3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1297 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * RContact
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#262>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact :: IO ((BtSoftBody_RContact))
btSoftBody_RContact =
  btSoftBody_RContact'_ >>= \res ->
  mkBtSoftBody_RContact res >>= \res' ->
  return (res')

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

btSoftBody_RContact_free :: ( BtSoftBody_RContactClass bc ) => (bc) -> IO ()
btSoftBody_RContact_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_RContact_free'_ a1' >>
  return ()

{-# LINE 1303 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#263>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_cti_set :: ( BtSoftBody_RContactClass bc , BtSoftBody_sCtiClass a ) => (bc) -> (a) -> IO ()
btSoftBody_RContact_m_cti_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_RContact_m_cti_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#263>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_cti_get :: ( BtSoftBody_RContactClass bc ) => (bc) -> IO ((BtSoftBody_sCti))
btSoftBody_RContact_m_cti_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_RContact_m_cti_get'_ a1' >>= \res ->
  mkBtSoftBody_sCti res >>= \res' ->
  return (res')

{-# LINE 1311 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#264>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_node_set :: ( BtSoftBody_RContactClass bc , BtSoftBody_NodeClass a ) => (bc) -> (a) -> IO ()
btSoftBody_RContact_m_node_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_RContact_m_node_set'_ a1' a2' >>
  return ()

{-# LINE 1315 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#264>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_node_get :: ( BtSoftBody_RContactClass bc ) => (bc) -> IO ((BtSoftBody_Node))
btSoftBody_RContact_m_node_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_RContact_m_node_get'_ a1' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')

{-# LINE 1319 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_c0_set :: ( BtSoftBody_RContactClass bc ) => (bc) -> (Mat3) -> IO ()
btSoftBody_RContact_m_c0_set a1 a2 =
  withBt a1 $ \a1' -> 
  withMat3 a2 $ \a2' -> 
  btSoftBody_RContact_m_c0_set'_ a1' a2' >>
  return ()

{-# LINE 1323 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_c0_get :: ( BtSoftBody_RContactClass bc ) => (bc) -> IO ((Mat3))
btSoftBody_RContact_m_c0_get a1 =
  withBt a1 $ \a1' -> 
  allocaMat3 $ \a2' -> 
  btSoftBody_RContact_m_c0_get'_ a1' a2' >>
  peekMat3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1327 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#266>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_c1_set :: ( BtSoftBody_RContactClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_RContact_m_c1_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_RContact_m_c1_set'_ a1' a2' >>
  return ()

{-# LINE 1331 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#266>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_c1_get :: ( BtSoftBody_RContactClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_RContact_m_c1_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_RContact_m_c1_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1335 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#267>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_c2_set :: ( BtSoftBody_RContactClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_RContact_m_c2_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_RContact_m_c2_set'_ a1' a2' >>
  return ()

{-# LINE 1339 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#267>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_c2_get :: ( BtSoftBody_RContactClass bc ) => (bc) -> IO ((Float))
btSoftBody_RContact_m_c2_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_RContact_m_c2_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1343 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#268>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_c3_set :: ( BtSoftBody_RContactClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_RContact_m_c3_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_RContact_m_c3_set'_ a1' a2' >>
  return ()

{-# LINE 1347 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#268>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_c3_get :: ( BtSoftBody_RContactClass bc ) => (bc) -> IO ((Float))
btSoftBody_RContact_m_c3_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_RContact_m_c3_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#269>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_c4_set :: ( BtSoftBody_RContactClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_RContact_m_c4_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_RContact_m_c4_set'_ a1' a2' >>
  return ()

{-# LINE 1355 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#269>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RContact_m_c4_get :: ( BtSoftBody_RContactClass bc ) => (bc) -> IO ((Float))
btSoftBody_RContact_m_c4_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_RContact_m_c4_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1359 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * RayFromToCaster
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#610>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster :: (Vec3) -> (Vec3) -> (Float) -> IO ((BtSoftBody_RayFromToCaster))
btSoftBody_RayFromToCaster a1 a2 a3 =
  withVec3 a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btSoftBody_RayFromToCaster'_ a1' a2' a3' >>= \res ->
  mkBtSoftBody_RayFromToCaster res >>= \res' ->
  return (res')

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

btSoftBody_RayFromToCaster_free :: ( BtSoftBody_RayFromToCasterClass bc ) => (bc) -> IO ()
btSoftBody_RayFromToCaster_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_RayFromToCaster_free'_ a1' >>
  return ()

{-# LINE 1365 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#611>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster_Process :: ( BtSoftBody_RayFromToCasterClass bc , BtDbvtNodeClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ leaf
 -> IO ()
btSoftBody_RayFromToCaster_Process a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_RayFromToCaster_Process'_ a1' a2' >>
  return ()

{-# LINE 1371 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#604>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster_m_rayFrom_set :: ( BtSoftBody_RayFromToCasterClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_RayFromToCaster_m_rayFrom_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_RayFromToCaster_m_rayFrom_set'_ a1' a2' >>
  return ()

{-# LINE 1375 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#604>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster_m_rayFrom_get :: ( BtSoftBody_RayFromToCasterClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_RayFromToCaster_m_rayFrom_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_RayFromToCaster_m_rayFrom_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1379 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#605>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster_m_rayTo_set :: ( BtSoftBody_RayFromToCasterClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_RayFromToCaster_m_rayTo_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_RayFromToCaster_m_rayTo_set'_ a1' a2' >>
  return ()

{-# LINE 1383 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#605>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster_m_rayTo_get :: ( BtSoftBody_RayFromToCasterClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_RayFromToCaster_m_rayTo_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_RayFromToCaster_m_rayTo_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1387 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#606>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster_m_rayNormalizedDirection_set :: ( BtSoftBody_RayFromToCasterClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_RayFromToCaster_m_rayNormalizedDirection_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_RayFromToCaster_m_rayNormalizedDirection_set'_ a1' a2' >>
  return ()

{-# LINE 1391 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#606>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster_m_rayNormalizedDirection_get :: ( BtSoftBody_RayFromToCasterClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_RayFromToCaster_m_rayNormalizedDirection_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_RayFromToCaster_m_rayNormalizedDirection_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1395 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#607>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster_m_mint_set :: ( BtSoftBody_RayFromToCasterClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_RayFromToCaster_m_mint_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_RayFromToCaster_m_mint_set'_ a1' a2' >>
  return ()

{-# LINE 1399 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#607>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster_m_mint_get :: ( BtSoftBody_RayFromToCasterClass bc ) => (bc) -> IO ((Float))
btSoftBody_RayFromToCaster_m_mint_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_RayFromToCaster_m_mint_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1403 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#608>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster_m_face_set :: ( BtSoftBody_RayFromToCasterClass bc , BtSoftBody_FaceClass a ) => (bc) -> (a) -> IO ()
btSoftBody_RayFromToCaster_m_face_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_RayFromToCaster_m_face_set'_ a1' a2' >>
  return ()

{-# LINE 1407 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#608>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster_m_face_get :: ( BtSoftBody_RayFromToCasterClass bc ) => (bc) -> IO ((BtSoftBody_Face))
btSoftBody_RayFromToCaster_m_face_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_RayFromToCaster_m_face_get'_ a1' >>= \res ->
  mkBtSoftBody_Face res >>= \res' ->
  return (res')

{-# LINE 1411 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#609>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster_m_tests_set :: ( BtSoftBody_RayFromToCasterClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_RayFromToCaster_m_tests_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_RayFromToCaster_m_tests_set'_ a1' a2' >>
  return ()

{-# LINE 1415 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#609>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_RayFromToCaster_m_tests_get :: ( BtSoftBody_RayFromToCasterClass bc ) => (bc) -> IO ((Int))
btSoftBody_RayFromToCaster_m_tests_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_RayFromToCaster_m_tests_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1419 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * SContact
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#273>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SContact :: IO ((BtSoftBody_SContact))
btSoftBody_SContact =
  btSoftBody_SContact'_ >>= \res ->
  mkBtSoftBody_SContact res >>= \res' ->
  return (res')

{-# LINE 1424 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_SContact_free :: ( BtSoftBody_SContactClass bc ) => (bc) -> IO ()
btSoftBody_SContact_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_SContact_free'_ a1' >>
  return ()

{-# LINE 1425 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#274>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SContact_m_node_set :: ( BtSoftBody_SContactClass bc , BtSoftBody_NodeClass a ) => (bc) -> (a) -> IO ()
btSoftBody_SContact_m_node_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_SContact_m_node_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#274>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SContact_m_node_get :: ( BtSoftBody_SContactClass bc ) => (bc) -> IO ((BtSoftBody_Node))
btSoftBody_SContact_m_node_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_SContact_m_node_get'_ a1' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')

{-# LINE 1433 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#275>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SContact_m_face_set :: ( BtSoftBody_SContactClass bc , BtSoftBody_FaceClass a ) => (bc) -> (a) -> IO ()
btSoftBody_SContact_m_face_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_SContact_m_face_set'_ a1' a2' >>
  return ()

{-# LINE 1437 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#275>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SContact_m_face_get :: ( BtSoftBody_SContactClass bc ) => (bc) -> IO ((BtSoftBody_Face))
btSoftBody_SContact_m_face_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_SContact_m_face_get'_ a1' >>= \res ->
  mkBtSoftBody_Face res >>= \res' ->
  return (res')

{-# LINE 1441 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#276>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SContact_m_weights_set :: ( BtSoftBody_SContactClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_SContact_m_weights_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_SContact_m_weights_set'_ a1' a2' >>
  return ()

{-# LINE 1445 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#276>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SContact_m_weights_get :: ( BtSoftBody_SContactClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_SContact_m_weights_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_SContact_m_weights_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1449 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#277>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SContact_m_normal_set :: ( BtSoftBody_SContactClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_SContact_m_normal_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_SContact_m_normal_set'_ a1' a2' >>
  return ()

{-# LINE 1453 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#277>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SContact_m_normal_get :: ( BtSoftBody_SContactClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_SContact_m_normal_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_SContact_m_normal_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#278>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SContact_m_margin_set :: ( BtSoftBody_SContactClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_SContact_m_margin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_SContact_m_margin_set'_ a1' a2' >>
  return ()

{-# LINE 1461 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#278>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SContact_m_margin_get :: ( BtSoftBody_SContactClass bc ) => (bc) -> IO ((Float))
btSoftBody_SContact_m_margin_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_SContact_m_margin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1465 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#279>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SContact_m_friction_set :: ( BtSoftBody_SContactClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_SContact_m_friction_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_SContact_m_friction_set'_ a1' a2' >>
  return ()

{-# LINE 1469 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#279>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SContact_m_friction_get :: ( BtSoftBody_SContactClass bc ) => (bc) -> IO ((Float))
btSoftBody_SContact_m_friction_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_SContact_m_friction_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1473 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * SolverState
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#594>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SolverState :: IO ((BtSoftBody_SolverState))
btSoftBody_SolverState =
  btSoftBody_SolverState'_ >>= \res ->
  mkBtSoftBody_SolverState res >>= \res' ->
  return (res')

{-# LINE 1478 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_SolverState_free :: ( BtSoftBody_SolverStateClass bc ) => (bc) -> IO ()
btSoftBody_SolverState_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_SolverState_free'_ a1' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#595>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SolverState_sdt_set :: ( BtSoftBody_SolverStateClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_SolverState_sdt_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_SolverState_sdt_set'_ a1' a2' >>
  return ()

{-# LINE 1483 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#595>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SolverState_sdt_get :: ( BtSoftBody_SolverStateClass bc ) => (bc) -> IO ((Float))
btSoftBody_SolverState_sdt_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_SolverState_sdt_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1487 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#596>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SolverState_isdt_set :: ( BtSoftBody_SolverStateClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_SolverState_isdt_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_SolverState_isdt_set'_ a1' a2' >>
  return ()

{-# LINE 1491 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#596>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SolverState_isdt_get :: ( BtSoftBody_SolverStateClass bc ) => (bc) -> IO ((Float))
btSoftBody_SolverState_isdt_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_SolverState_isdt_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1495 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#597>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SolverState_velmrg_set :: ( BtSoftBody_SolverStateClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_SolverState_velmrg_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_SolverState_velmrg_set'_ a1' a2' >>
  return ()

{-# LINE 1499 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#597>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SolverState_velmrg_get :: ( BtSoftBody_SolverStateClass bc ) => (bc) -> IO ((Float))
btSoftBody_SolverState_velmrg_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_SolverState_velmrg_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1503 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#598>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SolverState_radmrg_set :: ( BtSoftBody_SolverStateClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_SolverState_radmrg_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_SolverState_radmrg_set'_ a1' a2' >>
  return ()

{-# LINE 1507 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#598>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SolverState_radmrg_get :: ( BtSoftBody_SolverStateClass bc ) => (bc) -> IO ((Float))
btSoftBody_SolverState_radmrg_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_SolverState_radmrg_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1511 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#599>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SolverState_updmrg_set :: ( BtSoftBody_SolverStateClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_SolverState_updmrg_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_SolverState_updmrg_set'_ a1' a2' >>
  return ()

{-# LINE 1515 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#599>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_SolverState_updmrg_get :: ( BtSoftBody_SolverStateClass bc ) => (bc) -> IO ((Float))
btSoftBody_SolverState_updmrg_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_SolverState_updmrg_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1519 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Specs
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#490>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_Specs :: IO ((BtSoftBody_Joint_Specs))
btSoftBody_Joint_Specs =
  btSoftBody_Joint_Specs'_ >>= \res ->
  mkBtSoftBody_Joint_Specs res >>= \res' ->
  return (res')

{-# LINE 1524 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Joint_Specs_free :: ( BtSoftBody_Joint_SpecsClass bc ) => (bc) -> IO ()
btSoftBody_Joint_Specs_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Joint_Specs_free'_ a1' >>
  return ()

{-# LINE 1525 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#491>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_Specs_erp_set :: ( BtSoftBody_Joint_SpecsClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Joint_Specs_erp_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Joint_Specs_erp_set'_ a1' a2' >>
  return ()

{-# LINE 1529 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#491>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_Specs_erp_get :: ( BtSoftBody_Joint_SpecsClass bc ) => (bc) -> IO ((Float))
btSoftBody_Joint_Specs_erp_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Joint_Specs_erp_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1533 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#492>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_Specs_cfm_set :: ( BtSoftBody_Joint_SpecsClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Joint_Specs_cfm_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Joint_Specs_cfm_set'_ a1' a2' >>
  return ()

{-# LINE 1537 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#492>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_Specs_cfm_get :: ( BtSoftBody_Joint_SpecsClass bc ) => (bc) -> IO ((Float))
btSoftBody_Joint_Specs_cfm_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Joint_Specs_cfm_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1541 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#493>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_Specs_split_set :: ( BtSoftBody_Joint_SpecsClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Joint_Specs_split_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Joint_Specs_split_set'_ a1' a2' >>
  return ()

{-# LINE 1545 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#493>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_Specs_split_get :: ( BtSoftBody_Joint_SpecsClass bc ) => (bc) -> IO ((Float))
btSoftBody_Joint_Specs_split_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Joint_Specs_split_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1549 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Specs
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#515>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_LJoint_Specs :: IO ((BtSoftBody_LJoint_Specs))
btSoftBody_LJoint_Specs =
  btSoftBody_LJoint_Specs'_ >>= \res ->
  mkBtSoftBody_LJoint_Specs res >>= \res' ->
  return (res')

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

btSoftBody_LJoint_Specs_free :: ( BtSoftBody_LJoint_SpecsClass bc ) => (bc) -> IO ()
btSoftBody_LJoint_Specs_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_LJoint_Specs_free'_ a1' >>
  return ()

{-# LINE 1555 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#516>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_LJoint_Specs_position_set :: ( BtSoftBody_LJoint_SpecsClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_LJoint_Specs_position_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_LJoint_Specs_position_set'_ a1' a2' >>
  return ()

{-# LINE 1559 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#516>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_LJoint_Specs_position_get :: ( BtSoftBody_LJoint_SpecsClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_LJoint_Specs_position_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_LJoint_Specs_position_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1563 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Specs
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#535>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_Specs :: IO ((BtSoftBody_AJoint_Specs))
btSoftBody_AJoint_Specs =
  btSoftBody_AJoint_Specs'_ >>= \res ->
  mkBtSoftBody_AJoint_Specs res >>= \res' ->
  return (res')

{-# LINE 1568 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_AJoint_Specs_free :: ( BtSoftBody_AJoint_SpecsClass bc ) => (bc) -> IO ()
btSoftBody_AJoint_Specs_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_AJoint_Specs_free'_ a1' >>
  return ()

{-# LINE 1569 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#536>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_Specs_axis_set :: ( BtSoftBody_AJoint_SpecsClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_AJoint_Specs_axis_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_AJoint_Specs_axis_set'_ a1' a2' >>
  return ()

{-# LINE 1573 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#536>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_Specs_axis_get :: ( BtSoftBody_AJoint_SpecsClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_AJoint_Specs_axis_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_AJoint_Specs_axis_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1577 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#537>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_Specs_icontrol_set :: ( BtSoftBody_AJoint_SpecsClass bc , BtSoftBody_AJoint_IControlClass a ) => (bc) -> (a) -> IO ()
btSoftBody_AJoint_Specs_icontrol_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_AJoint_Specs_icontrol_set'_ a1' a2' >>
  return ()

{-# LINE 1581 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#537>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_AJoint_Specs_icontrol_get :: ( BtSoftBody_AJoint_SpecsClass bc ) => (bc) -> IO ((BtSoftBody_AJoint_IControl))
btSoftBody_AJoint_Specs_icontrol_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_AJoint_Specs_icontrol_get'_ a1' >>= \res ->
  mkBtSoftBody_AJoint_IControl res >>= \res' ->
  return (res')

{-# LINE 1585 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * Tetra
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#252>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Tetra :: IO ((BtSoftBody_Tetra))
btSoftBody_Tetra =
  btSoftBody_Tetra'_ >>= \res ->
  mkBtSoftBody_Tetra res >>= \res' ->
  return (res')

{-# LINE 1590 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Tetra_free :: ( BtSoftBody_TetraClass bc ) => (bc) -> IO ()
btSoftBody_Tetra_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Tetra_free'_ a1' >>
  return ()

{-# LINE 1591 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#254>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Tetra_m_rv_set :: ( BtSoftBody_TetraClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Tetra_m_rv_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Tetra_m_rv_set'_ a1' a2' >>
  return ()

{-# LINE 1595 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 1599 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#255>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Tetra_m_leaf_set :: ( BtSoftBody_TetraClass bc , BtDbvtNodeClass a ) => (bc) -> (a) -> IO ()
btSoftBody_Tetra_m_leaf_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_Tetra_m_leaf_set'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#255>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Tetra_m_leaf_get :: ( BtSoftBody_TetraClass bc ) => (bc) -> IO ((BtDbvtNode))
btSoftBody_Tetra_m_leaf_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Tetra_m_leaf_get'_ a1' >>= \res ->
  mkBtDbvtNode res >>= \res' ->
  return (res')

{-# LINE 1607 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#257>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Tetra_m_c1_set :: ( BtSoftBody_TetraClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Tetra_m_c1_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Tetra_m_c1_set'_ a1' a2' >>
  return ()

{-# LINE 1611 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#257>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Tetra_m_c1_get :: ( BtSoftBody_TetraClass bc ) => (bc) -> IO ((Float))
btSoftBody_Tetra_m_c1_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Tetra_m_c1_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#258>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Tetra_m_c2_set :: ( BtSoftBody_TetraClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_Tetra_m_c2_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_Tetra_m_c2_set'_ a1' a2' >>
  return ()

{-# LINE 1619 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#258>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Tetra_m_c2_get :: ( BtSoftBody_TetraClass bc ) => (bc) -> IO ((Float))
btSoftBody_Tetra_m_c2_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Tetra_m_c2_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1623 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * btSoftBody
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#682>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody1 :: ( BtSoftBodyWorldInfoClass p0 ) => (p0) -> IO ((BtSoftBody))
btSoftBody1 a1 =
  withBt a1 $ \a1' -> 
  btSoftBody1'_ a1' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  return (res')

{-# LINE 1628 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_free :: ( BtSoftBodyClass bc ) => (bc) -> IO ()
btSoftBody_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_free'_ a1' >>
  return ()

{-# LINE 1629 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#811>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_getVolume :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSoftBody_getVolume a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_getVolume'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#842>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_cutLink :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ node0
 -> (Int) -- ^ node1
 -> (Float) -- ^ position
 -> IO ((Bool))
btSoftBody_cutLink a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = realToFrac a4} in 
  btSoftBody_cutLink'_ a1' a2' a3' a4' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1642 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#842>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_cutLink0 :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ node0
 -> (Int) -- ^ node1
 -> (Float) -- ^ position
 -> IO ((Bool))
btSoftBody_cutLink0 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = realToFrac a4} in 
  btSoftBody_cutLink0'_ a1' a2' a3' a4' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1650 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#843>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_cutLink1 :: ( BtSoftBodyClass bc , BtSoftBody_NodeClass p0 , BtSoftBody_NodeClass p1 ) => (bc) -- ^ 
 -> (p0) -- ^ node0
 -> (p1) -- ^ node1
 -> (Float) -- ^ position
 -> IO ((Bool))
btSoftBody_cutLink1 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  btSoftBody_cutLink1'_ a1' a2' a3' a4' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1658 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#962>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_PSolve_Links :: (  BtSoftBodyClass p0 ) => (p0) -- ^ psb
 -> (Float) -- ^ kst
 -> (Float) -- ^ ti
 -> IO ()
btSoftBody_PSolve_Links a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btSoftBody_PSolve_Links'_ a1' a2' a3' >>
  return ()

{-# LINE 1665 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#838>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_generateClusters :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ k
 -> (Int) -- ^ maxiterations
 -> IO ((Int))
btSoftBody_generateClusters a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btSoftBody_generateClusters'_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 1672 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#698>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_setCollisionShape :: ( BtSoftBodyClass bc , BtCollisionShapeClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ collisionShape
 -> IO ()
btSoftBody_setCollisionShape a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_setCollisionShape'_ a1' a2' >>
  return ()

{-# LINE 1678 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#951>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_initializeClusters :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_initializeClusters a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_initializeClusters'_ a1' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#823>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterVAImpulse :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> (Vec3) -- ^ impulse
 -> IO ((Vec3))
btSoftBody_clusterVAImpulse a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_clusterVAImpulse'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1689 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#823>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterVAImpulse' :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> IO ((Vec3))
btSoftBody_clusterVAImpulse' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_clusterVAImpulse''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#770>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_addForce :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ force
 -> IO ((Vec3))
btSoftBody_addForce a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_addForce'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1701 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#770>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_addForce' :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_addForce' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_addForce''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#770>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_addForce0 :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ force
 -> IO ((Vec3))
btSoftBody_addForce0 a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_addForce0'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1713 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#770>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_addForce0' :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_addForce0' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_addForce0''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#773>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_addForce1 :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ force
 -> (Int) -- ^ node
 -> IO ((Vec3))
btSoftBody_addForce1 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  btSoftBody_addForce1'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1726 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#773>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_addForce1' :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ node
 -> IO ((Vec3))
btSoftBody_addForce1' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  btSoftBody_addForce1''_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1733 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 1740 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#948>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_updateBounds :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_updateBounds a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_updateBounds'_ a1' >>
  return ()

{-# LINE 1745 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#804>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_rotate :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (UnitQuaternion) -- ^ rot
 -> IO ((UnitQuaternion))
btSoftBody_rotate a1 a2 =
  withBt a1 $ \a1' -> 
  withUnitQuaternion a2 $ \a2' -> 
  btSoftBody_rotate'_ a1' a2' >>
  peekUnitQuaternion  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#804>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_rotate' :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((UnitQuaternion))
btSoftBody_rotate' a1 =
  withBt a1 $ \a1' -> 
  allocaUnitQuaternion $ \a2' -> 
  btSoftBody_rotate''_ a1' a2' >>
  peekUnitQuaternion  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1757 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#947>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_updateNormals :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_updateNormals a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_updateNormals'_ a1' >>
  return ()

{-# LINE 1768 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#954>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_prepareClusters :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ iterations
 -> IO ()
btSoftBody_prepareClusters a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_prepareClusters'_ a1' a2' >>
  return ()

{-# LINE 1774 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#834>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_releaseClusters :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_releaseClusters a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_releaseClusters'_ a1' >>
  return ()

{-# LINE 1779 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#789>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_getTotalMass :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Float))
btSoftBody_getTotalMass a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_getTotalMass'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 1784 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#946>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_checkContact :: ( BtSoftBodyClass bc , BtCollisionObjectClass p0 , BtSoftBody_sCtiClass p3 ) => (bc) -- ^ 
 -> (p0) -- ^ colObj
 -> (Vec3) -- ^ x
 -> (Float) -- ^ margin
 -> (p3) -- ^ cti
 -> IO ((Bool), (Vec3))
btSoftBody_checkContact a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  withBt a5 $ \a5' -> 
  btSoftBody_checkContact'_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  peekVec3  a3'>>= \a3'' -> 
  return (res', a3'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#946>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_checkContact' :: ( BtSoftBodyClass bc , BtCollisionObjectClass p0 , BtSoftBody_sCtiClass p3 ) => (bc) -- ^ 
 -> (p0) -- ^ colObj
 -> (Float) -- ^ margin
 -> (p3) -- ^ cti
 -> IO ((Bool), (Vec3))
btSoftBody_checkContact' a1 a2 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  withBt a5 $ \a5' -> 
  btSoftBody_checkContact''_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  peekVec3  a3'>>= \a3'' -> 
  return (res', a3'')

{-# LINE 1802 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#821>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterDImpulse :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> (Vec3) -- ^ rpos
 -> (Vec3) -- ^ impulse
 -> IO ((Vec3), (Vec3))
btSoftBody_clusterDImpulse a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btSoftBody_clusterDImpulse'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#821>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterDImpulse' :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> IO ((Vec3), (Vec3))
btSoftBody_clusterDImpulse' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btSoftBody_clusterDImpulse''_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 1816 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#684>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_initDefaults :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_initDefaults a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_initDefaults'_ a1' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#704>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_checkLink :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ node0
 -> (Int) -- ^ node1
 -> IO ((Bool))
btSoftBody_checkLink a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btSoftBody_checkLink'_ a1' a2' a3' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1828 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#704>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_checkLink0 :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ node0
 -> (Int) -- ^ node1
 -> IO ((Bool))
btSoftBody_checkLink0 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btSoftBody_checkLink0'_ a1' a2' a3' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1835 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#706>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_checkLink1 :: ( BtSoftBodyClass bc , BtSoftBody_NodeClass p0 , BtSoftBody_NodeClass p1 ) => (bc) -- ^ 
 -> (p0) -- ^ node0
 -> (p1) -- ^ node1
 -> IO ((Bool))
btSoftBody_checkLink1 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btSoftBody_checkLink1'_ a1' a2' a3' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1842 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#796>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_setVolumeMass :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ mass
 -> IO ()
btSoftBody_setVolumeMass a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_setVolumeMass'_ a1' a2' >>
  return ()

{-# LINE 1848 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#822>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterImpulse :: (  BtSoftBody_ClusterClass p0 , BtSoftBody_ImpulseClass p2 ) => (p0) -- ^ cluster
 -> (Vec3) -- ^ rpos
 -> (p2) -- ^ impulse
 -> IO ((Vec3))
btSoftBody_clusterImpulse a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btSoftBody_clusterImpulse'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1855 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#822>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterImpulse' :: (  BtSoftBody_ClusterClass p0 , BtSoftBody_ImpulseClass p2 ) => (p0) -- ^ cluster
 -> (p2) -- ^ impulse
 -> IO ((Vec3))
btSoftBody_clusterImpulse' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btSoftBody_clusterImpulse''_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1862 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#710>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_checkFace :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ node0
 -> (Int) -- ^ node1
 -> (Int) -- ^ node2
 -> IO ((Bool))
btSoftBody_checkFace a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btSoftBody_checkFace'_ a1' a2' a3' a4' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 1870 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#945>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_evaluateCom :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_evaluateCom a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_evaluateCom'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1876 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#824>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterDAImpulse :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> (Vec3) -- ^ impulse
 -> IO ((Vec3))
btSoftBody_clusterDAImpulse a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_clusterDAImpulse'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1882 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#824>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterDAImpulse' :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> IO ((Vec3))
btSoftBody_clusterDAImpulse' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_clusterDAImpulse''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1888 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#963>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_VSolve_Links :: (  BtSoftBodyClass p0 ) => (p0) -- ^ psb
 -> (Float) -- ^ kst
 -> IO ()
btSoftBody_VSolve_Links a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_VSolve_Links'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#792>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_setTotalMass :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ mass
 -> (Bool) -- ^ fromfaces
 -> IO ()
btSoftBody_setTotalMass a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = C2HSImp.fromBool a3} in 
  btSoftBody_setTotalMass'_ a1' a2' a3' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#826>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterDCImpulse :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> (Vec3) -- ^ impulse
 -> IO ((Vec3))
btSoftBody_clusterDCImpulse a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_clusterDCImpulse'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1907 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#826>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterDCImpulse' :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> IO ((Vec3))
btSoftBody_clusterDCImpulse' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_clusterDCImpulse''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1913 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#818>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterVelocity :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> (Vec3) -- ^ rpos
 -> IO ((Vec3), (Vec3))
btSoftBody_clusterVelocity a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btSoftBody_clusterVelocity'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 1920 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#818>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterVelocity' :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> IO ((Vec3), (Vec3))
btSoftBody_clusterVelocity' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btSoftBody_clusterVelocity''_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#829>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_generateBendingConstraints :: ( BtSoftBodyClass bc , BtSoftBody_MaterialClass p1 ) => (bc) -- ^ 
 -> (Int) -- ^ distance
 -> (p1) -- ^ mat
 -> IO ((Int))
btSoftBody_generateBendingConstraints a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btSoftBody_generateBendingConstraints'_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#952>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_updateClusters :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_updateClusters a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_updateClusters'_ a1' >>
  return ()

{-# LINE 1939 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#759>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendAnchor :: ( BtSoftBodyClass bc , BtRigidBodyClass p1 ) => (bc) -- ^ 
 -> (Int) -- ^ node
 -> (p1) -- ^ body
 -> (Bool) -- ^ disableCollisionBetweenLinkedBodies
 -> (Float) -- ^ influence
 -> IO ()
btSoftBody_appendAnchor a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  let {a4' = C2HSImp.fromBool a4} in 
  let {a5' = realToFrac a5} in 
  btSoftBody_appendAnchor'_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 1948 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#759>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendAnchor0 :: ( BtSoftBodyClass bc , BtRigidBodyClass p1 ) => (bc) -- ^ 
 -> (Int) -- ^ node
 -> (p1) -- ^ body
 -> (Bool) -- ^ disableCollisionBetweenLinkedBodies
 -> (Float) -- ^ influence
 -> IO ()
btSoftBody_appendAnchor0 a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  let {a4' = C2HSImp.fromBool a4} in 
  let {a5' = realToFrac a5} in 
  btSoftBody_appendAnchor0'_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 1957 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#760>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendAnchor1 :: ( BtSoftBodyClass bc , BtRigidBodyClass p1 ) => (bc) -- ^ 
 -> (Int) -- ^ node
 -> (p1) -- ^ body
 -> (Vec3) -- ^ localPivot
 -> (Bool) -- ^ disableCollisionBetweenLinkedBodies
 -> (Float) -- ^ influence
 -> IO ((Vec3))
btSoftBody_appendAnchor1 a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  let {a5' = C2HSImp.fromBool a5} in 
  let {a6' = realToFrac a6} in 
  btSoftBody_appendAnchor1'_ a1' a2' a3' a4' a5' a6' >>
  peekVec3  a4'>>= \a4'' -> 
  return (a4'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#760>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendAnchor1' :: ( BtSoftBodyClass bc , BtRigidBodyClass p1 ) => (bc) -- ^ 
 -> (Int) -- ^ node
 -> (p1) -- ^ body
 -> (Bool) -- ^ disableCollisionBetweenLinkedBodies
 -> (Float) -- ^ influence
 -> IO ((Vec3))
btSoftBody_appendAnchor1' a1 a2 a3 a5 a6 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  let {a5' = C2HSImp.fromBool a5} in 
  let {a6' = realToFrac a6} in 
  btSoftBody_appendAnchor1''_ a1' a2' a3' a4' a5' a6' >>
  peekVec3  a4'>>= \a4'' -> 
  return (a4'')

{-# LINE 1977 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#956>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_applyClusters :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ drift
 -> IO ()
btSoftBody_applyClusters a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSoftBody_applyClusters'_ a1' a2' >>
  return ()

{-# LINE 1983 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#778>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_setVelocity :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ velocity
 -> IO ((Vec3))
btSoftBody_setVelocity a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_setVelocity'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1989 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#778>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_setVelocity' :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_setVelocity' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_setVelocity''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 1995 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#813>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterCount :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btSoftBody_clusterCount a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_clusterCount'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 2000 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#914>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_upcast :: (  BtCollisionObjectClass p0 ) => (p0) -- ^ colObj
 -> IO ((BtSoftBody))
btSoftBody_upcast a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_upcast'_ a1' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  return (res')

{-# LINE 2005 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#914>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_upcast0 :: (  BtCollisionObjectClass p0 ) => (p0) -- ^ colObj
 -> IO ((BtSoftBody))
btSoftBody_upcast0 a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_upcast0'_ a1' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  return (res')

{-# LINE 2010 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#920>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_upcast1 :: (  BtCollisionObjectClass p0 ) => (p0) -- ^ colObj
 -> IO ((BtSoftBody))
btSoftBody_upcast1 a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_upcast1'_ a1' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  return (res')

{-# LINE 2015 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#882>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_getWindVelocity :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_getWindVelocity a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_getWindVelocity'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2021 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#852>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_predictMotion :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ dt
 -> IO ()
btSoftBody_predictMotion a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_predictMotion'_ a1' a2' >>
  return ()

{-# LINE 2027 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#939>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_pointersToIndices :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_pointersToIndices a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_pointersToIndices'_ a1' >>
  return ()

{-# LINE 2032 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#787>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_getMass :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ node
 -> IO ((Float))
btSoftBody_getMass a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_getMass'_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2038 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#960>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_PSolve_RContacts :: (  BtSoftBodyClass p0 ) => (p0) -- ^ psb
 -> (Float) -- ^ kst
 -> (Float) -- ^ ti
 -> IO ()
btSoftBody_PSolve_RContacts a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btSoftBody_PSolve_RContacts'_ a1' a2' a3' >>
  return ()

{-# LINE 2045 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#944>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_initializeFaceTree :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_initializeFaceTree a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_initializeFaceTree'_ a1' >>
  return ()

{-# LINE 2050 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#775>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_addVelocity :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ velocity
 -> IO ((Vec3))
btSoftBody_addVelocity a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_addVelocity'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2056 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#775>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_addVelocity' :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_addVelocity' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_addVelocity''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2062 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#775>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_addVelocity0 :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ velocity
 -> IO ((Vec3))
btSoftBody_addVelocity0 a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_addVelocity0'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2068 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#775>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_addVelocity0' :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_addVelocity0' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_addVelocity0''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2074 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#782>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_addVelocity1 :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ velocity
 -> (Int) -- ^ node
 -> IO ((Vec3))
btSoftBody_addVelocity1 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  btSoftBody_addVelocity1'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2081 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#782>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_addVelocity1' :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ node
 -> IO ((Vec3))
btSoftBody_addVelocity1' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  btSoftBody_addVelocity1''_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2088 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#959>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_PSolve_Anchors :: (  BtSoftBodyClass p0 ) => (p0) -- ^ psb
 -> (Float) -- ^ kst
 -> (Float) -- ^ ti
 -> IO ()
btSoftBody_PSolve_Anchors a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btSoftBody_PSolve_Anchors'_ a1' a2' a3' >>
  return ()

{-# LINE 2095 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#953>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_cleanupClusters :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_cleanupClusters a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_cleanupClusters'_ a1' >>
  return ()

{-# LINE 2100 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#800>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_transform :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Transform) -- ^ trs
 -> IO ((Transform))
btSoftBody_transform a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btSoftBody_transform'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2106 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#800>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_transform' :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Transform))
btSoftBody_transform' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSoftBody_transform''_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2112 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#764>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendLinearJoint2 :: ( BtSoftBodyClass bc , BtSoftBody_LJoint_SpecsClass p0 , BtSoftBodyClass p1 ) => (bc) -- ^ 
 -> (p0) -- ^ specs
 -> (p1) -- ^ body
 -> IO ()
btSoftBody_appendLinearJoint2 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btSoftBody_appendLinearJoint2'_ a1' a2' a3' >>
  return ()

{-# LINE 2119 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#831>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_randomizeConstraints :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_randomizeConstraints a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_randomizeConstraints'_ a1' >>
  return ()

{-# LINE 2124 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#949>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_updatePose :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_updatePose a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_updatePose'_ a1' >>
  return ()

{-# LINE 2129 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#802>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_translate :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ trs
 -> IO ((Vec3))
btSoftBody_translate a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_translate'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2135 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#802>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_translate' :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_translate' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_translate''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2141 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#931>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_getAabb :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ aabbMin
 -> (Vec3) -- ^ aabbMax
 -> IO ((Vec3), (Vec3))
btSoftBody_getAabb a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btSoftBody_getAabb'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 2148 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 2155 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#961>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_PSolve_SContacts :: (  BtSoftBodyClass p0 ) => (p0) -- ^ psb
 -> (Float) -- ^ arg1
 -> (Float) -- ^ ti
 -> IO ()
btSoftBody_PSolve_SContacts a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btSoftBody_PSolve_SContacts'_ a1' a2' a3' >>
  return ()

{-# LINE 2162 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#712>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendMaterial :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((BtSoftBody_Material))
btSoftBody_appendMaterial a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_appendMaterial'_ a1' >>= \res ->
  mkBtSoftBody_Material res >>= \res' ->
  return (res')

{-# LINE 2167 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#731>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendNode :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ x
 -> (Float) -- ^ m
 -> IO ((Vec3))
btSoftBody_appendNode a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btSoftBody_appendNode'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2174 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#731>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendNode' :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ m
 -> IO ((Vec3))
btSoftBody_appendNode' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btSoftBody_appendNode''_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2181 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#785>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_setMass :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ node
 -> (Float) -- ^ mass
 -> IO ()
btSoftBody_setMass a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = realToFrac a3} in 
  btSoftBody_setMass'_ a1' a2' a3' >>
  return ()

{-# LINE 2188 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#862>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_integrateMotion :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_integrateMotion a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_integrateMotion'_ a1' >>
  return ()

{-# LINE 2193 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#864>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_defaultCollisionHandler :: ( BtSoftBodyClass bc , BtCollisionObjectClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ pco
 -> IO ()
btSoftBody_defaultCollisionHandler a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_defaultCollisionHandler'_ a1' a2' >>
  return ()

{-# LINE 2199 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#864>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_defaultCollisionHandler0 :: ( BtSoftBodyClass bc , BtCollisionObjectClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ pco
 -> IO ()
btSoftBody_defaultCollisionHandler0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_defaultCollisionHandler0'_ a1' a2' >>
  return ()

{-# LINE 2205 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#865>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_defaultCollisionHandler1 :: ( BtSoftBodyClass bc , BtSoftBodyClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ psb
 -> IO ()
btSoftBody_defaultCollisionHandler1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_defaultCollisionHandler1'_ a1' a2' >>
  return ()

{-# LINE 2211 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#854>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_solveConstraints :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_solveConstraints a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_solveConstraints'_ a1' >>
  return ()

{-# LINE 2216 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#794>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_setTotalDensity :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ density
 -> IO ()
btSoftBody_setTotalDensity a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_setTotalDensity'_ a1' a2' >>
  return ()

{-# LINE 2222 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#720>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendNote :: ( BtSoftBodyClass bc , BtSoftBody_NodeClass p3 , BtSoftBody_NodeClass p4 , BtSoftBody_NodeClass p5 , BtSoftBody_NodeClass p6 ) => (bc) -- ^ 
 -> (String) -- ^ text
 -> (Vec3) -- ^ o
 -> (Vec4) -- ^ c
 -> (p3) -- ^ n0
 -> (p4) -- ^ n1
 -> (p5) -- ^ n2
 -> (p6) -- ^ n3
 -> IO ((Vec3), (Vec4))
btSoftBody_appendNote a1 a2 a3 a4 a5 a6 a7 a8 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec4 a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  withBt a7 $ \a7' -> 
  withBt a8 $ \a8' -> 
  btSoftBody_appendNote'_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  peekVec3  a3'>>= \a3'' -> 
  peekVec4  a4'>>= \a4'' -> 
  return (a3'', a4'')

{-# LINE 2234 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#720>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendNote' :: ( BtSoftBodyClass bc , BtSoftBody_NodeClass p3 , BtSoftBody_NodeClass p4 , BtSoftBody_NodeClass p5 , BtSoftBody_NodeClass p6 ) => (bc) -- ^ 
 -> (String) -- ^ text
 -> (p3) -- ^ n0
 -> (p4) -- ^ n1
 -> (p5) -- ^ n2
 -> (p6) -- ^ n3
 -> IO ((Vec3), (Vec4))
btSoftBody_appendNote' a1 a2 a5 a6 a7 a8 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  withBt a7 $ \a7' -> 
  withBt a8 $ \a8' -> 
  btSoftBody_appendNote''_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  peekVec3  a3'>>= \a3'' -> 
  peekVec4  a4'>>= \a4'' -> 
  return (a3'', a4'')

{-# LINE 2246 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#720>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendNote0 :: ( BtSoftBodyClass bc , BtSoftBody_NodeClass p3 , BtSoftBody_NodeClass p4 , BtSoftBody_NodeClass p5 , BtSoftBody_NodeClass p6 ) => (bc) -- ^ 
 -> (String) -- ^ text
 -> (Vec3) -- ^ o
 -> (Vec4) -- ^ c
 -> (p3) -- ^ n0
 -> (p4) -- ^ n1
 -> (p5) -- ^ n2
 -> (p6) -- ^ n3
 -> IO ((Vec3), (Vec4))
btSoftBody_appendNote0 a1 a2 a3 a4 a5 a6 a7 a8 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec4 a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  withBt a7 $ \a7' -> 
  withBt a8 $ \a8' -> 
  btSoftBody_appendNote0'_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  peekVec3  a3'>>= \a3'' -> 
  peekVec4  a4'>>= \a4'' -> 
  return (a3'', a4'')

{-# LINE 2258 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#720>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendNote0' :: ( BtSoftBodyClass bc , BtSoftBody_NodeClass p3 , BtSoftBody_NodeClass p4 , BtSoftBody_NodeClass p5 , BtSoftBody_NodeClass p6 ) => (bc) -- ^ 
 -> (String) -- ^ text
 -> (p3) -- ^ n0
 -> (p4) -- ^ n1
 -> (p5) -- ^ n2
 -> (p6) -- ^ n3
 -> IO ((Vec3), (Vec4))
btSoftBody_appendNote0' a1 a2 a5 a6 a7 a8 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  withBt a7 $ \a7' -> 
  withBt a8 $ \a8' -> 
  btSoftBody_appendNote0''_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  peekVec3  a3'>>= \a3'' -> 
  peekVec4  a4'>>= \a4'' -> 
  return (a3'', a4'')

{-# LINE 2270 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#723>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendNote1 :: ( BtSoftBodyClass bc , BtSoftBody_NodeClass p2 ) => (bc) -- ^ 
 -> (String) -- ^ text
 -> (Vec3) -- ^ o
 -> (p2) -- ^ feature
 -> IO ((Vec3))
btSoftBody_appendNote1 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSoftBody_appendNote1'_ a1' a2' a3' a4' >>
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')

{-# LINE 2278 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#723>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendNote1' :: ( BtSoftBodyClass bc , BtSoftBody_NodeClass p2 ) => (bc) -- ^ 
 -> (String) -- ^ text
 -> (p2) -- ^ feature
 -> IO ((Vec3))
btSoftBody_appendNote1' a1 a2 a4 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSoftBody_appendNote1''_ a1' a2' a3' a4' >>
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')

{-# LINE 2286 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#726>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendNote2 :: ( BtSoftBodyClass bc , BtSoftBody_LinkClass p2 ) => (bc) -- ^ 
 -> (String) -- ^ text
 -> (Vec3) -- ^ o
 -> (p2) -- ^ feature
 -> IO ((Vec3))
btSoftBody_appendNote2 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSoftBody_appendNote2'_ a1' a2' a3' a4' >>
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')

{-# LINE 2294 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#726>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendNote2' :: ( BtSoftBodyClass bc , BtSoftBody_LinkClass p2 ) => (bc) -- ^ 
 -> (String) -- ^ text
 -> (p2) -- ^ feature
 -> IO ((Vec3))
btSoftBody_appendNote2' a1 a2 a4 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSoftBody_appendNote2''_ a1' a2' a3' a4' >>
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')

{-# LINE 2302 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#729>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendNote3 :: ( BtSoftBodyClass bc , BtSoftBody_FaceClass p2 ) => (bc) -- ^ 
 -> (String) -- ^ text
 -> (Vec3) -- ^ o
 -> (p2) -- ^ feature
 -> IO ((Vec3))
btSoftBody_appendNote3 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSoftBody_appendNote3'_ a1' a2' a3' a4' >>
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')

{-# LINE 2310 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#729>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendNote3' :: ( BtSoftBodyClass bc , BtSoftBody_FaceClass p2 ) => (bc) -- ^ 
 -> (String) -- ^ text
 -> (p2) -- ^ feature
 -> IO ((Vec3))
btSoftBody_appendNote3' a1 a2 a4 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSoftBody_appendNote3''_ a1' a2' a3' a4' >>
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')

{-# LINE 2318 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#798>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_setVolumeDensity :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ density
 -> IO ()
btSoftBody_setVolumeDensity a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_setVolumeDensity'_ a1' a2' >>
  return ()

{-# LINE 2324 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#950>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_updateConstants :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_updateConstants a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_updateConstants'_ a1' >>
  return ()

{-# LINE 2329 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#856>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_staticSolve :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ iterations
 -> IO ()
btSoftBody_staticSolve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_staticSolve'_ a1' a2' >>
  return ()

{-# LINE 2335 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#840>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_refine :: ( BtSoftBodyClass bc , BtSoftBody_ImplicitFnClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ ifn
 -> (Float) -- ^ accurary
 -> (Bool) -- ^ cut
 -> IO ()
btSoftBody_refine a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  let {a4' = C2HSImp.fromBool a4} in 
  btSoftBody_refine'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 2343 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#733>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendLink :: ( BtSoftBodyClass bc , BtSoftBody_MaterialClass p1 ) => (bc) -- ^ 
 -> (Int) -- ^ model
 -> (p1) -- ^ mat
 -> IO ()
btSoftBody_appendLink a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btSoftBody_appendLink'_ a1' a2' a3' >>
  return ()

{-# LINE 2350 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#733>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendLink0 :: ( BtSoftBodyClass bc , BtSoftBody_MaterialClass p1 ) => (bc) -- ^ 
 -> (Int) -- ^ model
 -> (p1) -- ^ mat
 -> IO ()
btSoftBody_appendLink0 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btSoftBody_appendLink0'_ a1' a2' a3' >>
  return ()

{-# LINE 2357 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#737>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendLink1 :: ( BtSoftBodyClass bc , BtSoftBody_MaterialClass p2 ) => (bc) -- ^ 
 -> (Int) -- ^ node0
 -> (Int) -- ^ node1
 -> (p2) -- ^ mat
 -> (Bool) -- ^ bcheckexist
 -> IO ()
btSoftBody_appendLink1 a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  let {a5' = C2HSImp.fromBool a5} in 
  btSoftBody_appendLink1'_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 2366 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#741>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendLink2 :: ( BtSoftBodyClass bc , BtSoftBody_NodeClass p0 , BtSoftBody_NodeClass p1 , BtSoftBody_MaterialClass p2 ) => (bc) -- ^ 
 -> (p0) -- ^ node0
 -> (p1) -- ^ node1
 -> (p2) -- ^ mat
 -> (Bool) -- ^ bcheckexist
 -> IO ()
btSoftBody_appendLink2 a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  let {a5' = C2HSImp.fromBool a5} in 
  btSoftBody_appendLink2'_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 2375 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#968>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_calculateSerializeBufferSize :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btSoftBody_calculateSerializeBufferSize a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_calculateSerializeBufferSize'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 2380 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#860>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_solveClusters :: (  BtAlignedObjectArray_btSoftBody_ptr_Class p0 ) => (p0) -- ^ bodies
 -> IO ()
btSoftBody_solveClusters a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_solveClusters'_ a1' >>
  return ()

{-# LINE 2385 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#860>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_solveClusters0 :: (  BtAlignedObjectArray_btSoftBody_ptr_Class p0 ) => (p0) -- ^ bodies
 -> IO ()
btSoftBody_solveClusters0 a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_solveClusters0'_ a1' >>
  return ()

{-# LINE 2390 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#955>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_solveClusters1 :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ sor
 -> IO ()
btSoftBody_solveClusters1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_solveClusters1'_ a1' a2' >>
  return ()

{-# LINE 2396 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#848>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_rayTest :: ( BtSoftBodyClass bc , BtSoftBody_sRayCastClass p2 ) => (bc) -- ^ 
 -> (Vec3) -- ^ rayFrom
 -> (Vec3) -- ^ rayTo
 -> (p2) -- ^ results
 -> IO ((Bool), (Vec3), (Vec3))
btSoftBody_rayTest a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSoftBody_rayTest'_ a1' a2' a3' a4' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (res', a2'', a3'')

{-# LINE 2404 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#848>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_rayTest' :: ( BtSoftBodyClass bc , BtSoftBody_sRayCastClass p2 ) => (bc) -- ^ 
 -> (p2) -- ^ results
 -> IO ((Bool), (Vec3), (Vec3))
btSoftBody_rayTest' a1 a4 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSoftBody_rayTest''_ a1' a2' a3' a4' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (res', a2'', a3'')

{-# LINE 2412 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#848>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_rayTest0 :: ( BtSoftBodyClass bc , BtSoftBody_sRayCastClass p2 ) => (bc) -- ^ 
 -> (Vec3) -- ^ rayFrom
 -> (Vec3) -- ^ rayTo
 -> (p2) -- ^ results
 -> IO ((Bool), (Vec3), (Vec3))
btSoftBody_rayTest0 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSoftBody_rayTest0'_ a1' a2' a3' a4' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (res', a2'', a3'')

{-# LINE 2420 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#848>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_rayTest0' :: ( BtSoftBodyClass bc , BtSoftBody_sRayCastClass p2 ) => (bc) -- ^ 
 -> (p2) -- ^ results
 -> IO ((Bool), (Vec3), (Vec3))
btSoftBody_rayTest0' a1 a4 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSoftBody_rayTest0''_ a1' a2' a3' a4' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (res', a2'', a3'')

{-# LINE 2428 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#809>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_setPose :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Bool) -- ^ bvolume
 -> (Bool) -- ^ bframe
 -> IO ()
btSoftBody_setPose a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  let {a3' = C2HSImp.fromBool a3} in 
  btSoftBody_setPose'_ a1' a2' a3' >>
  return ()

{-# LINE 2435 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#743>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendFace :: ( BtSoftBodyClass bc , BtSoftBody_MaterialClass p1 ) => (bc) -- ^ 
 -> (Int) -- ^ model
 -> (p1) -- ^ mat
 -> IO ()
btSoftBody_appendFace a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btSoftBody_appendFace'_ a1' a2' a3' >>
  return ()

{-# LINE 2442 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#743>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendFace0 :: ( BtSoftBodyClass bc , BtSoftBody_MaterialClass p1 ) => (bc) -- ^ 
 -> (Int) -- ^ model
 -> (p1) -- ^ mat
 -> IO ()
btSoftBody_appendFace0 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btSoftBody_appendFace0'_ a1' a2' a3' >>
  return ()

{-# LINE 2449 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#747>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendFace1 :: ( BtSoftBodyClass bc , BtSoftBody_MaterialClass p3 ) => (bc) -- ^ 
 -> (Int) -- ^ node0
 -> (Int) -- ^ node1
 -> (Int) -- ^ node2
 -> (p3) -- ^ mat
 -> IO ()
btSoftBody_appendFace1 a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  withBt a5 $ \a5' -> 
  btSoftBody_appendFace1'_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 2458 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#957>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_dampClusters :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_dampClusters a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_dampClusters'_ a1' >>
  return ()

{-# LINE 2463 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#692>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_getWorldInfo :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((BtSoftBodyWorldInfo))
btSoftBody_getWorldInfo a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_getWorldInfo'_ a1' >>= \res ->
  mkBtSoftBodyWorldInfo res >>= \res' ->
  return (res')

{-# LINE 2468 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#768>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendAngularJoint2 :: ( BtSoftBodyClass bc , BtSoftBody_AJoint_SpecsClass p0 , BtSoftBodyClass p1 ) => (bc) -- ^ 
 -> (p0) -- ^ specs
 -> (p1) -- ^ body
 -> IO ()
btSoftBody_appendAngularJoint2 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btSoftBody_appendAngularJoint2'_ a1' a2' a3' >>
  return ()

{-# LINE 2475 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#820>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterVImpulse :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> (Vec3) -- ^ rpos
 -> (Vec3) -- ^ impulse
 -> IO ((Vec3), (Vec3))
btSoftBody_clusterVImpulse a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btSoftBody_clusterVImpulse'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 2482 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#820>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterVImpulse' :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> IO ((Vec3), (Vec3))
btSoftBody_clusterVImpulse' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btSoftBody_clusterVImpulse''_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 2489 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#806>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_scale :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ scl
 -> IO ((Vec3))
btSoftBody_scale a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_scale'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2495 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#806>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_scale' :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_scale' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_scale''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2501 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#825>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterAImpulse :: (  BtSoftBody_ClusterClass p0 , BtSoftBody_ImpulseClass p1 ) => (p0) -- ^ cluster
 -> (p1) -- ^ impulse
 -> IO ()
btSoftBody_clusterAImpulse a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_clusterAImpulse'_ a1' a2' >>
  return ()

{-# LINE 2507 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#815>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterCom :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> IO ((Vec3))
btSoftBody_clusterCom a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_clusterCom'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2513 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#815>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterCom0 :: (  BtSoftBody_ClusterClass p0 ) => (p0) -- ^ cluster
 -> IO ((Vec3))
btSoftBody_clusterCom0 a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_clusterCom0'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2519 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#816>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_clusterCom1 :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ cluster
 -> IO ((Vec3))
btSoftBody_clusterCom1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaVec3 $ \a3' -> 
  btSoftBody_clusterCom1'_ a1' a2' a3' >>
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')

{-# LINE 2526 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#876>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_setWindVelocity :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ velocity
 -> IO ((Vec3))
btSoftBody_setWindVelocity a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_setWindVelocity'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2532 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#876>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_setWindVelocity' :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ((Vec3))
btSoftBody_setWindVelocity' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_setWindVelocity''_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2538 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#958>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_applyForces :: ( BtSoftBodyClass bc ) => (bc) -- ^ 
 -> IO ()
btSoftBody_applyForces a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_applyForces'_ a1' >>
  return ()

{-# LINE 2543 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#748>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendTetra :: ( BtSoftBodyClass bc , BtSoftBody_MaterialClass p1 ) => (bc) -- ^ 
 -> (Int) -- ^ model
 -> (p1) -- ^ mat
 -> IO ()
btSoftBody_appendTetra a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btSoftBody_appendTetra'_ a1' a2' a3' >>
  return ()

{-# LINE 2550 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#748>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendTetra0 :: ( BtSoftBodyClass bc , BtSoftBody_MaterialClass p1 ) => (bc) -- ^ 
 -> (Int) -- ^ model
 -> (p1) -- ^ mat
 -> IO ()
btSoftBody_appendTetra0 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btSoftBody_appendTetra0'_ a1' a2' a3' >>
  return ()

{-# LINE 2557 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#754>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_appendTetra1 :: ( BtSoftBodyClass bc , BtSoftBody_MaterialClass p4 ) => (bc) -- ^ 
 -> (Int) -- ^ node0
 -> (Int) -- ^ node1
 -> (Int) -- ^ node2
 -> (Int) -- ^ node3
 -> (p4) -- ^ mat
 -> IO ()
btSoftBody_appendTetra1 a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  withBt a6 $ \a6' -> 
  btSoftBody_appendTetra1'_ a1' a2' a3' a4' a5' a6' >>
  return ()

{-# LINE 2567 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#656>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_anchors_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_btSoftBody_Anchor_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_anchors_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_anchors_set'_ a1' a2' >>
  return ()

{-# LINE 2571 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#656>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_anchors_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_Anchor_))
btSoftBody_m_anchors_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_anchors_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Anchor_ res >>= \res' ->
  return (res')

{-# LINE 2575 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#663>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_bUpdateRtCst_set :: ( BtSoftBodyClass bc ) => (bc) -> (Bool) -> IO ()
btSoftBody_m_bUpdateRtCst_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSoftBody_m_bUpdateRtCst_set'_ a1' a2' >>
  return ()

{-# LINE 2579 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#663>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_bUpdateRtCst_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((Bool))
btSoftBody_m_bUpdateRtCst_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_bUpdateRtCst_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 2583 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#666>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_cdbvt_set :: ( BtSoftBodyClass bc , BtDbvtClass a ) => (bc) -> (a) -> IO ()
btSoftBody_m_cdbvt_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_cdbvt_set'_ a1' a2' >>
  return ()

{-# LINE 2587 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#666>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_cdbvt_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtDbvt))
btSoftBody_m_cdbvt_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_cdbvt_get'_ a1' >>= \res ->
  mkBtDbvt res >>= \res' ->
  return (res')

{-# LINE 2591 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#646>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_cfg_set :: ( BtSoftBodyClass bc , BtSoftBody_ConfigClass a ) => (bc) -> (a) -> IO ()
btSoftBody_m_cfg_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_cfg_set'_ a1' a2' >>
  return ()

{-# LINE 2595 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#646>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_cfg_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtSoftBody_Config))
btSoftBody_m_cfg_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_cfg_get'_ a1' >>= \res ->
  mkBtSoftBody_Config res >>= \res' ->
  return (res')

{-# LINE 2599 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#669>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_clusterConnectivity_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_bool_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_clusterConnectivity_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_clusterConnectivity_set'_ a1' a2' >>
  return ()

{-# LINE 2603 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#669>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_clusterConnectivity_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_bool_))
btSoftBody_m_clusterConnectivity_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_clusterConnectivity_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_bool_ res >>= \res' ->
  return (res')

{-# LINE 2607 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#667>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_clusters_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_clusters_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_clusters_set'_ a1' a2' >>
  return ()

{-# LINE 2611 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#667>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_clusters_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_Cluster_ptr_))
btSoftBody_m_clusters_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_clusters_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Cluster_ptr_ res >>= \res' ->
  return (res')

{-# LINE 2615 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_collisionDisabledObjects_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_btCollisionObject_ptr_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_collisionDisabledObjects_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_collisionDisabledObjects_set'_ a1' a2' >>
  return ()

{-# LINE 2619 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_collisionDisabledObjects_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btCollisionObject_ptr_))
btSoftBody_m_collisionDisabledObjects_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_collisionDisabledObjects_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btCollisionObject_ptr_ res >>= \res' ->
  return (res')

{-# LINE 2623 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#654>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_faces_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_btSoftBody_Face_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_faces_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_faces_set'_ a1' a2' >>
  return ()

{-# LINE 2627 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#654>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_faces_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_Face_))
btSoftBody_m_faces_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_faces_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Face_ res >>= \res' ->
  return (res')

{-# LINE 2631 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#665>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_fdbvt_set :: ( BtSoftBodyClass bc , BtDbvtClass a ) => (bc) -> (a) -> IO ()
btSoftBody_m_fdbvt_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_fdbvt_set'_ a1' a2' >>
  return ()

{-# LINE 2635 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#665>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_fdbvt_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtDbvt))
btSoftBody_m_fdbvt_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_fdbvt_get'_ a1' >>= \res ->
  mkBtDbvt res >>= \res' ->
  return (res')

{-# LINE 2639 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#671>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_initialWorldTransform_set :: ( BtSoftBodyClass bc ) => (bc) -> (Transform) -> IO ()
btSoftBody_m_initialWorldTransform_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btSoftBody_m_initialWorldTransform_set'_ a1' a2' >>
  return ()

{-# LINE 2643 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#671>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_initialWorldTransform_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((Transform))
btSoftBody_m_initialWorldTransform_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btSoftBody_m_initialWorldTransform_get'_ a1' a2' >>
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2647 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#659>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_joints_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_btSoftBody_Joint_ptr_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_joints_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_joints_set'_ a1' a2' >>
  return ()

{-# LINE 2651 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#659>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_joints_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_Joint_ptr_))
btSoftBody_m_joints_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_joints_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Joint_ptr_ res >>= \res' ->
  return (res')

{-# LINE 2655 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#653>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_links_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_btSoftBody_Link_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_links_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_links_set'_ a1' a2' >>
  return ()

{-# LINE 2659 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#653>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_links_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_Link_))
btSoftBody_m_links_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_links_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Link_ res >>= \res' ->
  return (res')

{-# LINE 2663 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#660>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_materials_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_btSoftBody_Material_ptr_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_materials_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_materials_set'_ a1' a2' >>
  return ()

{-# LINE 2667 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#660>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_materials_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_Material_ptr_))
btSoftBody_m_materials_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_materials_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Material_ptr_ res >>= \res' ->
  return (res')

{-# LINE 2671 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#664>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_ndbvt_set :: ( BtSoftBodyClass bc , BtDbvtClass a ) => (bc) -> (a) -> IO ()
btSoftBody_m_ndbvt_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_ndbvt_set'_ a1' a2' >>
  return ()

{-# LINE 2675 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#664>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_ndbvt_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtDbvt))
btSoftBody_m_ndbvt_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_ndbvt_get'_ a1' >>= \res ->
  mkBtDbvt res >>= \res' ->
  return (res')

{-# LINE 2679 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#652>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_nodes_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_btSoftBody_Node_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_nodes_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_nodes_set'_ a1' a2' >>
  return ()

{-# LINE 2683 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#652>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_nodes_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_Node_))
btSoftBody_m_nodes_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_nodes_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Node_ res >>= \res' ->
  return (res')

{-# LINE 2687 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#651>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_notes_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_btSoftBody_Note_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_notes_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_notes_set'_ a1' a2' >>
  return ()

{-# LINE 2691 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#651>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_notes_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_Note_))
btSoftBody_m_notes_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_notes_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Note_ res >>= \res' ->
  return (res')

{-# LINE 2695 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#648>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_pose_set :: ( BtSoftBodyClass bc , BtSoftBody_PoseClass a ) => (bc) -> (a) -> IO ()
btSoftBody_m_pose_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_pose_set'_ a1' a2' >>
  return ()

{-# LINE 2699 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#648>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_pose_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtSoftBody_Pose))
btSoftBody_m_pose_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_pose_get'_ a1' >>= \res ->
  mkBtSoftBody_Pose res >>= \res' ->
  return (res')

{-# LINE 2703 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#657>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_rcontacts_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_btSoftBody_RContact_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_rcontacts_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_rcontacts_set'_ a1' a2' >>
  return ()

{-# LINE 2707 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#657>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_rcontacts_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_RContact_))
btSoftBody_m_rcontacts_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_rcontacts_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_RContact_ res >>= \res' ->
  return (res')

{-# LINE 2711 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#658>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_scontacts_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_btSoftBody_SContact_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_scontacts_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_scontacts_set'_ a1' a2' >>
  return ()

{-# LINE 2715 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#658>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_scontacts_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_SContact_))
btSoftBody_m_scontacts_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_scontacts_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_SContact_ res >>= \res' ->
  return (res')

{-# LINE 2719 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#647>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_sst_set :: ( BtSoftBodyClass bc , BtSoftBody_SolverStateClass a ) => (bc) -> (a) -> IO ()
btSoftBody_m_sst_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_sst_set'_ a1' a2' >>
  return ()

{-# LINE 2723 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#647>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_sst_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtSoftBody_SolverState))
btSoftBody_m_sst_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_sst_get'_ a1' >>= \res ->
  mkBtSoftBody_SolverState res >>= \res' ->
  return (res')

{-# LINE 2727 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#649>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_tag_set :: ( BtSoftBodyClass bc ) => (bc) -> (VoidPtr) -> IO ()
btSoftBody_m_tag_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  btSoftBody_m_tag_set'_ a1' a2' >>
  return ()

{-# LINE 2731 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#649>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_tag_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((VoidPtr))
btSoftBody_m_tag_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_tag_get'_ a1' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')

{-# LINE 2735 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#655>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_tetras_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_btSoftBody_Tetra_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_tetras_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_tetras_set'_ a1' a2' >>
  return ()

{-# LINE 2739 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#655>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_tetras_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_Tetra_))
btSoftBody_m_tetras_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_tetras_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Tetra_ res >>= \res' ->
  return (res')

{-# LINE 2743 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#661>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_timeacc_set :: ( BtSoftBodyClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_m_timeacc_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_m_timeacc_set'_ a1' a2' >>
  return ()

{-# LINE 2747 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#661>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_timeacc_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((Float))
btSoftBody_m_timeacc_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_timeacc_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2751 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#690>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_userIndexMapping_set :: ( BtSoftBodyClass bc , BtAlignedObjectArray_int_Class a ) => (bc) -> (a) -> IO ()
btSoftBody_m_userIndexMapping_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_userIndexMapping_set'_ a1' a2' >>
  return ()

{-# LINE 2755 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#690>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_userIndexMapping_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtAlignedObjectArray_int_))
btSoftBody_m_userIndexMapping_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_userIndexMapping_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')

{-# LINE 2759 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#673>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_windVelocity_set :: ( BtSoftBodyClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_m_windVelocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_m_windVelocity_set'_ a1' a2' >>
  return ()

{-# LINE 2763 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#673>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_windVelocity_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_m_windVelocity_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_m_windVelocity_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2767 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#650>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_worldInfo_set :: ( BtSoftBodyClass bc , BtSoftBodyWorldInfoClass a ) => (bc) -> (a) -> IO ()
btSoftBody_m_worldInfo_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_m_worldInfo_set'_ a1' a2' >>
  return ()

{-# LINE 2771 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#650>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_m_worldInfo_get :: ( BtSoftBodyClass bc ) => (bc) -> IO ((BtSoftBodyWorldInfo))
btSoftBody_m_worldInfo_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_m_worldInfo_get'_ a1' >>= \res ->
  mkBtSoftBodyWorldInfo res >>= \res' ->
  return (res')

{-# LINE 2775 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * btSoftBodyHelpers
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#46>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers :: IO ((BtSoftBodyHelpers))
btSoftBodyHelpers =
  btSoftBodyHelpers'_ >>= \res ->
  mkBtSoftBodyHelpers res >>= \res' ->
  return (res')

{-# LINE 2780 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBodyHelpers_free :: ( BtSoftBodyHelpersClass bc ) => (bc) -> IO ()
btSoftBodyHelpers_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBodyHelpers_free'_ a1' >>
  return ()

{-# LINE 2781 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#56>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_DrawInfos :: (  BtSoftBodyClass p0 , BtIDebugDrawClass p1 ) => (p0) -- ^ psb
 -> (p1) -- ^ idraw
 -> (Bool) -- ^ masses
 -> (Bool) -- ^ areas
 -> (Bool) -- ^ stress
 -> IO ()
btSoftBodyHelpers_DrawInfos a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = C2HSImp.fromBool a3} in 
  let {a4' = C2HSImp.fromBool a4} in 
  let {a5' = C2HSImp.fromBool a5} in 
  btSoftBodyHelpers_DrawInfos'_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 2790 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_Draw :: (  BtSoftBodyClass p0 , BtIDebugDrawClass p1 ) => (p0) -- ^ psb
 -> (p1) -- ^ idraw
 -> (Int) -- ^ drawflags
 -> IO ()
btSoftBodyHelpers_Draw a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  btSoftBodyHelpers_Draw'_ a1' a2' a3' >>
  return ()

{-# LINE 2797 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#107>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_CreateEllipsoid :: (  BtSoftBodyWorldInfoClass p0 ) => (p0) -- ^ worldInfo
 -> (Vec3) -- ^ center
 -> (Vec3) -- ^ radius
 -> (Int) -- ^ res
 -> IO ((BtSoftBody), (Vec3), (Vec3))
btSoftBodyHelpers_CreateEllipsoid a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  let {a4' = fromIntegral a4} in 
  btSoftBodyHelpers_CreateEllipsoid'_ a1' a2' a3' a4' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (res', a2'', a3'')

{-# LINE 2805 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#107>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_CreateEllipsoid' :: (  BtSoftBodyWorldInfoClass p0 ) => (p0) -- ^ worldInfo
 -> (Int) -- ^ res
 -> IO ((BtSoftBody), (Vec3), (Vec3))
btSoftBodyHelpers_CreateEllipsoid' a1 a4 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  let {a4' = fromIntegral a4} in 
  btSoftBodyHelpers_CreateEllipsoid''_ a1' a2' a3' a4' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (res', a2'', a3'')

{-# LINE 2813 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#139>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_CreateFromTetGenData :: (  BtSoftBodyWorldInfoClass p0 ) => (p0) -- ^ worldInfo
 -> (String) -- ^ ele
 -> (String) -- ^ face
 -> (String) -- ^ node
 -> (Bool) -- ^ bfacelinks
 -> (Bool) -- ^ btetralinks
 -> (Bool) -- ^ bfacesfromtetras
 -> IO ((BtSoftBody))
btSoftBodyHelpers_CreateFromTetGenData a1 a2 a3 a4 a5 a6 a7 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  C2HSImp.withCString a3 $ \a3' -> 
  C2HSImp.withCString a4 $ \a4' -> 
  let {a5' = C2HSImp.fromBool a5} in 
  let {a6' = C2HSImp.fromBool a6} in 
  let {a7' = C2HSImp.fromBool a7} in 
  btSoftBodyHelpers_CreateFromTetGenData'_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  return (res')

{-# LINE 2824 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#74>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_DrawFrame :: (  BtSoftBodyClass p0 , BtIDebugDrawClass p1 ) => (p0) -- ^ psb
 -> (p1) -- ^ idraw
 -> IO ()
btSoftBodyHelpers_DrawFrame a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBodyHelpers_DrawFrame'_ a1' a2' >>
  return ()

{-# LINE 2830 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_CreateRope :: (  BtSoftBodyWorldInfoClass p0 ) => (p0) -- ^ worldInfo
 -> (Vec3) -- ^ from
 -> (Vec3) -- ^ to
 -> (Int) -- ^ res
 -> (Int) -- ^ fixeds
 -> IO ((BtSoftBody), (Vec3), (Vec3))
btSoftBodyHelpers_CreateRope a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  btSoftBodyHelpers_CreateRope'_ a1' a2' a3' a4' a5' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (res', a2'', a3'')

{-# LINE 2839 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_CreateRope' :: (  BtSoftBodyWorldInfoClass p0 ) => (p0) -- ^ worldInfo
 -> (Int) -- ^ res
 -> (Int) -- ^ fixeds
 -> IO ((BtSoftBody), (Vec3), (Vec3))
btSoftBodyHelpers_CreateRope' a1 a4 a5 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  btSoftBodyHelpers_CreateRope''_ a1' a2' a3' a4' a5' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (res', a2'', a3'')

{-# LINE 2848 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#102>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_CalculateUV :: ( ) => (Int) -- ^ resx
 -> (Int) -- ^ resy
 -> (Int) -- ^ ix
 -> (Int) -- ^ iy
 -> (Int) -- ^ id
 -> IO ((Float))
btSoftBodyHelpers_CalculateUV a1 a2 a3 a4 a5 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  btSoftBodyHelpers_CalculateUV'_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 2857 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_DrawFaceTree :: (  BtSoftBodyClass p0 , BtIDebugDrawClass p1 ) => (p0) -- ^ psb
 -> (p1) -- ^ idraw
 -> (Int) -- ^ mindepth
 -> (Int) -- ^ maxdepth
 -> IO ()
btSoftBodyHelpers_DrawFaceTree a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btSoftBodyHelpers_DrawFaceTree'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 2865 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#71>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_DrawClusterTree :: (  BtSoftBodyClass p0 , BtIDebugDrawClass p1 ) => (p0) -- ^ psb
 -> (p1) -- ^ idraw
 -> (Int) -- ^ mindepth
 -> (Int) -- ^ maxdepth
 -> IO ()
btSoftBodyHelpers_DrawClusterTree a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btSoftBodyHelpers_DrawClusterTree'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 2873 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_DrawNodeTree :: (  BtSoftBodyClass p0 , BtIDebugDrawClass p1 ) => (p0) -- ^ psb
 -> (p1) -- ^ idraw
 -> (Int) -- ^ mindepth
 -> (Int) -- ^ maxdepth
 -> IO ()
btSoftBodyHelpers_DrawNodeTree a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btSoftBodyHelpers_DrawNodeTree'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 2881 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#90>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_CreatePatch :: (  BtSoftBodyWorldInfoClass p0 ) => (p0) -- ^ worldInfo
 -> (Vec3) -- ^ corner00
 -> (Vec3) -- ^ corner10
 -> (Vec3) -- ^ corner01
 -> (Vec3) -- ^ corner11
 -> (Int) -- ^ resx
 -> (Int) -- ^ resy
 -> (Int) -- ^ fixeds
 -> (Bool) -- ^ gendiags
 -> IO ((BtSoftBody), (Vec3), (Vec3), (Vec3), (Vec3))
btSoftBodyHelpers_CreatePatch a1 a2 a3 a4 a5 a6 a7 a8 a9 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  let {a6' = fromIntegral a6} in 
  let {a7' = fromIntegral a7} in 
  let {a8' = fromIntegral a8} in 
  let {a9' = C2HSImp.fromBool a9} in 
  btSoftBodyHelpers_CreatePatch'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (res', a2'', a3'', a4'', a5'')

{-# LINE 2894 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#90>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
btSoftBodyHelpers_CreatePatch' :: (  BtSoftBodyWorldInfoClass p0 ) => (p0) -- ^ worldInfo
 -> (Int) -- ^ resx
 -> (Int) -- ^ resy
 -> (Int) -- ^ fixeds
 -> (Bool) -- ^ gendiags
 -> IO ((BtSoftBody), (Vec3), (Vec3), (Vec3), (Vec3))
btSoftBodyHelpers_CreatePatch' a1 a6 a7 a8 a9 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  let {a6' = fromIntegral a6} in 
  let {a7' = fromIntegral a7} in 
  let {a8' = fromIntegral a8} in 
  let {a9' = C2HSImp.fromBool a9} in 
  btSoftBodyHelpers_CreatePatch''_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (res', a2'', a3'', a4'', a5'')

{-# LINE 2907 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * btSoftBodyRigidBodyCollisionConfiguration
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.h?r=2223#38>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.cpp?r=2223>
-}
btSoftBodyRigidBodyCollisionConfiguration :: ( BtDefaultCollisionConstructionInfoClass p0 ) => (p0) -> IO ((BtSoftBodyRigidBodyCollisionConfiguration))
btSoftBodyRigidBodyCollisionConfiguration a1 =
  withBt a1 $ \a1' -> 
  btSoftBodyRigidBodyCollisionConfiguration'_ a1' >>= \res ->
  mkBtSoftBodyRigidBodyCollisionConfiguration res >>= \res' ->
  return (res')

{-# LINE 2912 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBodyRigidBodyCollisionConfiguration_free :: ( BtSoftBodyRigidBodyCollisionConfigurationClass bc ) => (bc) -> IO ()
btSoftBodyRigidBodyCollisionConfiguration_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBodyRigidBodyCollisionConfiguration_free'_ a1' >>
  return ()

{-# LINE 2913 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.h?r=2223#43>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.cpp?r=2223>
-}
btSoftBodyRigidBodyCollisionConfiguration_getCollisionAlgorithmCreateFunc :: ( BtSoftBodyRigidBodyCollisionConfigurationClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ proxyType0
 -> (Int) -- ^ proxyType1
 -> IO ((BtCollisionAlgorithmCreateFunc))
btSoftBodyRigidBodyCollisionConfiguration_getCollisionAlgorithmCreateFunc a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btSoftBodyRigidBodyCollisionConfiguration_getCollisionAlgorithmCreateFunc'_ a1' a2' a3' >>= \res ->
  mkBtCollisionAlgorithmCreateFunc res >>= \res' ->
  return (res')

{-# LINE 2920 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.h?r=2223#30>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.cpp?r=2223>
-}
btSoftBodyRigidBodyCollisionConfiguration_m_softSoftCreateFunc_set :: ( BtSoftBodyRigidBodyCollisionConfigurationClass bc , BtCollisionAlgorithmCreateFuncClass a ) => (bc) -> (a) -> IO ()
btSoftBodyRigidBodyCollisionConfiguration_m_softSoftCreateFunc_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBodyRigidBodyCollisionConfiguration_m_softSoftCreateFunc_set'_ a1' a2' >>
  return ()

{-# LINE 2924 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.h?r=2223#30>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.cpp?r=2223>
-}
btSoftBodyRigidBodyCollisionConfiguration_m_softSoftCreateFunc_get :: ( BtSoftBodyRigidBodyCollisionConfigurationClass bc ) => (bc) -> IO ((BtCollisionAlgorithmCreateFunc))
btSoftBodyRigidBodyCollisionConfiguration_m_softSoftCreateFunc_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBodyRigidBodyCollisionConfiguration_m_softSoftCreateFunc_get'_ a1' >>= \res ->
  mkBtCollisionAlgorithmCreateFunc res >>= \res' ->
  return (res')

{-# LINE 2928 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.h?r=2223#31>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.cpp?r=2223>
-}
btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConvexCreateFunc_set :: ( BtSoftBodyRigidBodyCollisionConfigurationClass bc , BtCollisionAlgorithmCreateFuncClass a ) => (bc) -> (a) -> IO ()
btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConvexCreateFunc_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConvexCreateFunc_set'_ a1' a2' >>
  return ()

{-# LINE 2932 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.h?r=2223#31>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.cpp?r=2223>
-}
btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConvexCreateFunc_get :: ( BtSoftBodyRigidBodyCollisionConfigurationClass bc ) => (bc) -> IO ((BtCollisionAlgorithmCreateFunc))
btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConvexCreateFunc_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConvexCreateFunc_get'_ a1' >>= \res ->
  mkBtCollisionAlgorithmCreateFunc res >>= \res' ->
  return (res')

{-# LINE 2936 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.h?r=2223#32>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.cpp?r=2223>
-}
btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConvexCreateFunc_set :: ( BtSoftBodyRigidBodyCollisionConfigurationClass bc , BtCollisionAlgorithmCreateFuncClass a ) => (bc) -> (a) -> IO ()
btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConvexCreateFunc_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConvexCreateFunc_set'_ a1' a2' >>
  return ()

{-# LINE 2940 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.h?r=2223#32>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.cpp?r=2223>
-}
btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConvexCreateFunc_get :: ( BtSoftBodyRigidBodyCollisionConfigurationClass bc ) => (bc) -> IO ((BtCollisionAlgorithmCreateFunc))
btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConvexCreateFunc_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConvexCreateFunc_get'_ a1' >>= \res ->
  mkBtCollisionAlgorithmCreateFunc res >>= \res' ->
  return (res')

{-# LINE 2944 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.h?r=2223#33>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.cpp?r=2223>
-}
btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConcaveCreateFunc_set :: ( BtSoftBodyRigidBodyCollisionConfigurationClass bc , BtCollisionAlgorithmCreateFuncClass a ) => (bc) -> (a) -> IO ()
btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConcaveCreateFunc_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConcaveCreateFunc_set'_ a1' a2' >>
  return ()

{-# LINE 2948 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.h?r=2223#33>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.cpp?r=2223>
-}
btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConcaveCreateFunc_get :: ( BtSoftBodyRigidBodyCollisionConfigurationClass bc ) => (bc) -> IO ((BtCollisionAlgorithmCreateFunc))
btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConcaveCreateFunc_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConcaveCreateFunc_get'_ a1' >>= \res ->
  mkBtCollisionAlgorithmCreateFunc res >>= \res' ->
  return (res')

{-# LINE 2952 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.h?r=2223#34>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.cpp?r=2223>
-}
btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConcaveCreateFunc_set :: ( BtSoftBodyRigidBodyCollisionConfigurationClass bc , BtCollisionAlgorithmCreateFuncClass a ) => (bc) -> (a) -> IO ()
btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConcaveCreateFunc_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConcaveCreateFunc_set'_ a1' a2' >>
  return ()

{-# LINE 2956 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.h?r=2223#34>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyRigidBodyCollisionConfiguration.cpp?r=2223>
-}
btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConcaveCreateFunc_get :: ( BtSoftBodyRigidBodyCollisionConfigurationClass bc ) => (bc) -> IO ((BtCollisionAlgorithmCreateFunc))
btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConcaveCreateFunc_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConcaveCreateFunc_get'_ a1' >>= \res ->
  mkBtCollisionAlgorithmCreateFunc res >>= \res' ->
  return (res')

{-# LINE 2960 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * btSoftBodyWorldInfo
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBodyWorldInfo :: IO ((BtSoftBodyWorldInfo))
btSoftBodyWorldInfo =
  btSoftBodyWorldInfo'_ >>= \res ->
  mkBtSoftBodyWorldInfo res >>= \res' ->
  return (res')

{-# LINE 2965 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBodyWorldInfo_free :: ( BtSoftBodyWorldInfoClass bc ) => (bc) -> IO ()
btSoftBodyWorldInfo_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBodyWorldInfo_free'_ a1' >>
  return ()

{-# LINE 2966 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 2970 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 2974 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#49>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBodyWorldInfo_m_broadphase_set :: ( BtSoftBodyWorldInfoClass bc , BtBroadphaseInterfaceClass a ) => (bc) -> (a) -> IO ()
btSoftBodyWorldInfo_m_broadphase_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBodyWorldInfo_m_broadphase_set'_ a1' a2' >>
  return ()

{-# LINE 2978 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#49>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBodyWorldInfo_m_broadphase_get :: ( BtSoftBodyWorldInfoClass bc ) => (bc) -> IO ((BtBroadphaseInterface))
btSoftBodyWorldInfo_m_broadphase_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBodyWorldInfo_m_broadphase_get'_ a1' >>= \res ->
  mkBtBroadphaseInterface res >>= \res' ->
  return (res')

{-# LINE 2982 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBodyWorldInfo_m_dispatcher_set :: ( BtSoftBodyWorldInfoClass bc , BtDispatcherClass a ) => (bc) -> (a) -> IO ()
btSoftBodyWorldInfo_m_dispatcher_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBodyWorldInfo_m_dispatcher_set'_ a1' a2' >>
  return ()

{-# LINE 2986 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBodyWorldInfo_m_dispatcher_get :: ( BtSoftBodyWorldInfoClass bc ) => (bc) -> IO ((BtDispatcher))
btSoftBodyWorldInfo_m_dispatcher_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBodyWorldInfo_m_dispatcher_get'_ a1' >>= \res ->
  mkBtDispatcher res >>= \res' ->
  return (res')

{-# LINE 2990 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBodyWorldInfo_m_gravity_set :: ( BtSoftBodyWorldInfoClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBodyWorldInfo_m_gravity_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBodyWorldInfo_m_gravity_set'_ a1' a2' >>
  return ()

{-# LINE 2994 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBodyWorldInfo_m_gravity_get :: ( BtSoftBodyWorldInfoClass bc ) => (bc) -> IO ((Vec3))
btSoftBodyWorldInfo_m_gravity_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBodyWorldInfo_m_gravity_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 2998 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBodyWorldInfo_m_sparsesdf_set :: ( BtSoftBodyWorldInfoClass bc , BtSparseSdf_3_Class a ) => (bc) -> (a) -> IO ()
btSoftBodyWorldInfo_m_sparsesdf_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBodyWorldInfo_m_sparsesdf_set'_ a1' a2' >>
  return ()

{-# LINE 3002 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBodyWorldInfo_m_sparsesdf_get :: ( BtSoftBodyWorldInfoClass bc ) => (bc) -> IO ((BtSparseSdf_3_))
btSoftBodyWorldInfo_m_sparsesdf_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBodyWorldInfo_m_sparsesdf_get'_ a1' >>= \res ->
  mkBtSparseSdf_3_ res >>= \res' ->
  return (res')

{-# LINE 3006 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 3010 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 3014 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBodyWorldInfo_water_normal_set :: ( BtSoftBodyWorldInfoClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBodyWorldInfo_water_normal_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBodyWorldInfo_water_normal_set'_ a1' a2' >>
  return ()

{-# LINE 3018 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBodyWorldInfo_water_normal_get :: ( BtSoftBodyWorldInfoClass bc ) => (bc) -> IO ((Vec3))
btSoftBodyWorldInfo_water_normal_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBodyWorldInfo_water_normal_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3022 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 3026 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 3030 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * btSoftRigidDynamicsWorld
btSoftRigidDynamicsWorld_free :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -> IO ()
btSoftRigidDynamicsWorld_free a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_free'_ a1' >>
  return ()

{-# LINE 3032 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 3038 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#67>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_getWorldInfo :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -- ^ 
 -> IO ((BtSoftBodyWorldInfo))
btSoftRigidDynamicsWorld_getWorldInfo a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_getWorldInfo'_ a1' >>= \res ->
  mkBtSoftBodyWorldInfo res >>= \res' ->
  return (res')

{-# LINE 3043 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#67>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_getWorldInfo0 :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -- ^ 
 -> IO ((BtSoftBodyWorldInfo))
btSoftRigidDynamicsWorld_getWorldInfo0 a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_getWorldInfo0'_ a1' >>= \res ->
  mkBtSoftBodyWorldInfo res >>= \res' ->
  return (res')

{-# LINE 3048 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#71>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_getWorldInfo1 :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -- ^ 
 -> IO ((BtSoftBodyWorldInfo))
btSoftRigidDynamicsWorld_getWorldInfo1 a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_getWorldInfo1'_ a1' >>= \res ->
  mkBtSoftBodyWorldInfo res >>= \res' ->
  return (res')

{-# LINE 3053 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#65>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_setDrawFlags :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ f
 -> IO ()
btSoftRigidDynamicsWorld_setDrawFlags a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftRigidDynamicsWorld_setDrawFlags'_ a1' a2' >>
  return ()

{-# LINE 3059 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_getSoftBodyArray :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -- ^ 
 -> IO ((BtAlignedObjectArray_btSoftBody_ptr_))
btSoftRigidDynamicsWorld_getSoftBodyArray a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_getSoftBodyArray'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_ptr_ res >>= \res' ->
  return (res')

{-# LINE 3064 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_getSoftBodyArray0 :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -- ^ 
 -> IO ((BtAlignedObjectArray_btSoftBody_ptr_))
btSoftRigidDynamicsWorld_getSoftBodyArray0 a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_getSoftBodyArray0'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_ptr_ res >>= \res' ->
  return (res')

{-# LINE 3069 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#86>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_getSoftBodyArray1 :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -- ^ 
 -> IO ((BtAlignedObjectArray_btSoftBody_ptr_))
btSoftRigidDynamicsWorld_getSoftBodyArray1 a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_getSoftBodyArray1'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_ptr_ res >>= \res' ->
  return (res')

{-# LINE 3074 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#103>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_serialize :: ( BtSoftRigidDynamicsWorldClass bc , BtSerializerClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ serializer
 -> IO ()
btSoftRigidDynamicsWorld_serialize a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftRigidDynamicsWorld_serialize'_ a1' a2' >>
  return ()

{-# LINE 3080 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_rayTest :: ( BtSoftRigidDynamicsWorldClass bc , BtCollisionWorld_RayResultCallbackClass p2 ) => (bc) -- ^ 
 -> (Vec3) -- ^ rayFromWorld
 -> (Vec3) -- ^ rayToWorld
 -> (p2) -- ^ resultCallback
 -> IO ((Vec3), (Vec3))
btSoftRigidDynamicsWorld_rayTest a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSoftRigidDynamicsWorld_rayTest'_ a1' a2' a3' a4' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 3088 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_rayTest' :: ( BtSoftRigidDynamicsWorldClass bc , BtCollisionWorld_RayResultCallbackClass p2 ) => (bc) -- ^ 
 -> (p2) -- ^ resultCallback
 -> IO ((Vec3), (Vec3))
btSoftRigidDynamicsWorld_rayTest' a1 a4 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btSoftRigidDynamicsWorld_rayTest''_ a1' a2' a3' a4' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 3096 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 3102 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_removeCollisionObject :: ( BtSoftRigidDynamicsWorldClass bc , BtCollisionObjectClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ collisionObject
 -> IO ()
btSoftRigidDynamicsWorld_removeCollisionObject a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftRigidDynamicsWorld_removeCollisionObject'_ a1' a2' >>
  return ()

{-# LINE 3108 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_addSoftBody :: ( BtSoftRigidDynamicsWorldClass bc , BtSoftBodyClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ body
 -> (Int) -- ^ collisionFilterGroup
 -> (Int) -- ^ collisionFilterMask
 -> IO ()
btSoftRigidDynamicsWorld_addSoftBody a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btSoftRigidDynamicsWorld_addSoftBody'_ a1' a2' a3' a4' >>
  return ()

{-# LINE 3116 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#101>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_rayTestSingle :: (  BtCollisionObjectClass p2 , BtCollisionShapeClass p3 , BtCollisionWorld_RayResultCallbackClass p5 ) => (Transform) -- ^ rayFromTrans
 -> (Transform) -- ^ rayToTrans
 -> (p2) -- ^ collisionObject
 -> (p3) -- ^ collisionShape
 -> (Transform) -- ^ colObjWorldTransform
 -> (p5) -- ^ resultCallback
 -> IO ((Transform), (Transform), (Transform))
btSoftRigidDynamicsWorld_rayTestSingle a1 a2 a3 a4 a5 a6 =
  withTransform a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withTransform a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  btSoftRigidDynamicsWorld_rayTestSingle'_ a1' a2' a3' a4' a5' a6' >>
  peekTransform  a1'>>= \a1'' -> 
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a5'>>= \a5'' -> 
  return (a1'', a2'', a5'')

{-# LINE 3126 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#101>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_rayTestSingle' :: (  BtCollisionObjectClass p2 , BtCollisionShapeClass p3 , BtCollisionWorld_RayResultCallbackClass p5 ) => (p2) -- ^ collisionObject
 -> (p3) -- ^ collisionShape
 -> (p5) -- ^ resultCallback
 -> IO ((Transform), (Transform), (Transform))
btSoftRigidDynamicsWorld_rayTestSingle' a3 a4 a6 =
  allocaTransform $ \a1' -> 
  allocaTransform $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  allocaTransform $ \a5' -> 
  withBt a6 $ \a6' -> 
  btSoftRigidDynamicsWorld_rayTestSingle''_ a1' a2' a3' a4' a5' a6' >>
  peekTransform  a1'>>= \a1'' -> 
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a5'>>= \a5'' -> 
  return (a1'', a2'', a5'')

{-# LINE 3136 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 3142 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#47>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_serializeSoftBodies :: ( BtSoftRigidDynamicsWorldClass bc , BtSerializerClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ serializer
 -> IO ()
btSoftRigidDynamicsWorld_serializeSoftBodies a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftRigidDynamicsWorld_serializeSoftBodies'_ a1' a2' >>
  return ()

{-# LINE 3148 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#59>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_removeSoftBody :: ( BtSoftRigidDynamicsWorldClass bc , BtSoftBodyClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ body
 -> IO ()
btSoftRigidDynamicsWorld_removeSoftBody a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftRigidDynamicsWorld_removeSoftBody'_ a1' a2' >>
  return ()

{-# LINE 3154 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#64>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_getDrawFlags :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -- ^ 
 -> IO ((Int))
btSoftRigidDynamicsWorld_getDrawFlags a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_getDrawFlags'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3159 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 3164 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#29>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_softBodies_set :: ( BtSoftRigidDynamicsWorldClass bc , BtAlignedObjectArray_btSoftBody_ptr_Class a ) => (bc) -> (a) -> IO ()
btSoftRigidDynamicsWorld_m_softBodies_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftRigidDynamicsWorld_m_softBodies_set'_ a1' a2' >>
  return ()

{-# LINE 3168 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#29>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_softBodies_get :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -> IO ((BtAlignedObjectArray_btSoftBody_ptr_))
btSoftRigidDynamicsWorld_m_softBodies_get a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_m_softBodies_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_ptr_ res >>= \res' ->
  return (res')

{-# LINE 3172 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#30>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_drawFlags_set :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -> (Int) -> IO ()
btSoftRigidDynamicsWorld_m_drawFlags_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftRigidDynamicsWorld_m_drawFlags_set'_ a1' a2' >>
  return ()

{-# LINE 3176 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#30>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_drawFlags_get :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -> IO ((Int))
btSoftRigidDynamicsWorld_m_drawFlags_get a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_m_drawFlags_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3180 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#31>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_drawNodeTree_set :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -> (Bool) -> IO ()
btSoftRigidDynamicsWorld_m_drawNodeTree_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSoftRigidDynamicsWorld_m_drawNodeTree_set'_ a1' a2' >>
  return ()

{-# LINE 3184 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#31>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_drawNodeTree_get :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -> IO ((Bool))
btSoftRigidDynamicsWorld_m_drawNodeTree_get a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_m_drawNodeTree_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 3188 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#32>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_drawFaceTree_set :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -> (Bool) -> IO ()
btSoftRigidDynamicsWorld_m_drawFaceTree_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSoftRigidDynamicsWorld_m_drawFaceTree_set'_ a1' a2' >>
  return ()

{-# LINE 3192 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#32>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_drawFaceTree_get :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -> IO ((Bool))
btSoftRigidDynamicsWorld_m_drawFaceTree_get a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_m_drawFaceTree_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 3196 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#33>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_drawClusterTree_set :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -> (Bool) -> IO ()
btSoftRigidDynamicsWorld_m_drawClusterTree_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSoftRigidDynamicsWorld_m_drawClusterTree_set'_ a1' a2' >>
  return ()

{-# LINE 3200 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#33>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_drawClusterTree_get :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -> IO ((Bool))
btSoftRigidDynamicsWorld_m_drawClusterTree_get a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_m_drawClusterTree_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 3204 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#34>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_sbi_set :: ( BtSoftRigidDynamicsWorldClass bc , BtSoftBodyWorldInfoClass a ) => (bc) -> (a) -> IO ()
btSoftRigidDynamicsWorld_m_sbi_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftRigidDynamicsWorld_m_sbi_set'_ a1' a2' >>
  return ()

{-# LINE 3208 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#34>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_sbi_get :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -> IO ((BtSoftBodyWorldInfo))
btSoftRigidDynamicsWorld_m_sbi_get a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_m_sbi_get'_ a1' >>= \res ->
  mkBtSoftBodyWorldInfo res >>= \res' ->
  return (res')

{-# LINE 3212 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#37>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_ownsSolver_set :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -> (Bool) -> IO ()
btSoftRigidDynamicsWorld_m_ownsSolver_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = C2HSImp.fromBool a2} in 
  btSoftRigidDynamicsWorld_m_ownsSolver_set'_ a1' a2' >>
  return ()

{-# LINE 3216 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.h?r=2223#37>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftRigidDynamicsWorld.cpp?r=2223>
-}
btSoftRigidDynamicsWorld_m_ownsSolver_get :: ( BtSoftRigidDynamicsWorldClass bc ) => (bc) -> IO ((Bool))
btSoftRigidDynamicsWorld_m_ownsSolver_get a1 =
  withBt a1 $ \a1' -> 
  btSoftRigidDynamicsWorld_m_ownsSolver_get'_ a1' >>= \res ->
  let {res' = C2HSImp.toBool res} in
  return (res')

{-# LINE 3220 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * btSparseSdf<3>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#45>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3_ :: IO ((BtSparseSdf_3_))
btSparseSdf_3_ =
  btSparseSdf_3_'_ >>= \res ->
  mkBtSparseSdf_3_ res >>= \res' ->
  return (res')

{-# LINE 3225 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSparseSdf_3__free :: ( BtSparseSdf_3_Class bc ) => (bc) -> IO ()
btSparseSdf_3__free a1 =
  withBt a1 $ \a1' -> 
  btSparseSdf_3__free'_ a1' >>
  return ()

{-# LINE 3226 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#86>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__Reset :: ( BtSparseSdf_3_Class bc ) => (bc) -- ^ 
 -> IO ()
btSparseSdf_3__Reset a1 =
  withBt a1 $ \a1' -> 
  btSparseSdf_3__Reset'_ a1' >>
  return ()

{-# LINE 3231 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#285>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__Hash :: (  BtCollisionShapeClass p3 ) => (Int) -- ^ x
 -> (Int) -- ^ y
 -> (Int) -- ^ z
 -> (p3) -- ^ shape
 -> IO ((Word32))
btSparseSdf_3__Hash a1 a2 a3 a4 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btSparseSdf_3__Hash'_ a1' a2' a3' a4' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3239 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#132>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__RemoveReferences :: ( BtSparseSdf_3_Class bc , BtCollisionShapeClass p0 ) => (bc) -- ^ 
 -> (p0) -- ^ pcs
 -> IO ((Int))
btSparseSdf_3__RemoveReferences a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSparseSdf_3__RemoveReferences'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3245 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#277>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__Lerp :: ( ) => (Float) -- ^ a
 -> (Float) -- ^ b
 -> (Float) -- ^ t
 -> IO ((Float))
btSparseSdf_3__Lerp a1 a2 a3 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btSparseSdf_3__Lerp'_ a1' a2' a3' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3252 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#157>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__Evaluate :: ( BtSparseSdf_3_Class bc , BtCollisionShapeClass p1 ) => (bc) -- ^ 
 -> (Vec3) -- ^ x
 -> (p1) -- ^ shape
 -> (Vec3) -- ^ normal
 -> (Float) -- ^ margin
 -> IO ((Float), (Vec3), (Vec3))
btSparseSdf_3__Evaluate a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  let {a5' = realToFrac a5} in 
  btSparseSdf_3__Evaluate'_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = realToFrac res} in
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (res', a2'', a4'')

{-# LINE 3261 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#157>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__Evaluate' :: ( BtSparseSdf_3_Class bc , BtCollisionShapeClass p1 ) => (bc) -- ^ 
 -> (p1) -- ^ shape
 -> (Float) -- ^ margin
 -> IO ((Float), (Vec3), (Vec3))
btSparseSdf_3__Evaluate' a1 a3 a5 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  withBt a3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  let {a5' = realToFrac a5} in 
  btSparseSdf_3__Evaluate''_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = realToFrac res} in
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (res', a2'', a4'')

{-# LINE 3270 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#106>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__GarbageCollect :: ( BtSparseSdf_3_Class bc ) => (bc) -- ^ 
 -> (Int) -- ^ lifetime
 -> IO ()
btSparseSdf_3__GarbageCollect a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSparseSdf_3__GarbageCollect'_ a1' a2' >>
  return ()

{-# LINE 3276 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#251>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__DistanceToShape :: (  BtCollisionShapeClass p1 ) => (Vec3) -- ^ x
 -> (p1) -- ^ shape
 -> IO ((Float), (Vec3))
btSparseSdf_3__DistanceToShape a1 a2 =
  withVec3 a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSparseSdf_3__DistanceToShape'_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  peekVec3  a1'>>= \a1'' -> 
  return (res', a1'')

{-# LINE 3282 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#251>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__DistanceToShape' :: (  BtCollisionShapeClass p1 ) => (p1) -- ^ shape
 -> IO ((Float), (Vec3))
btSparseSdf_3__DistanceToShape' a2 =
  allocaVec3 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSparseSdf_3__DistanceToShape''_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  peekVec3  a1'>>= \a1'' -> 
  return (res', a1'')

{-# LINE 3288 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__Initialize :: ( BtSparseSdf_3_Class bc ) => (bc) -- ^ 
 -> (Int) -- ^ hashsize
 -> IO ()
btSparseSdf_3__Initialize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSparseSdf_3__Initialize'_ a1' a2' >>
  return ()

{-# LINE 3294 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__cells_set :: ( BtSparseSdf_3_Class bc , BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class a ) => (bc) -> (a) -> IO ()
btSparseSdf_3__cells_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSparseSdf_3__cells_set'_ a1' a2' >>
  return ()

{-# LINE 3298 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__cells_get :: ( BtSparseSdf_3_Class bc ) => (bc) -> IO ((BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_))
btSparseSdf_3__cells_get a1 =
  withBt a1 $ \a1' -> 
  btSparseSdf_3__cells_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btSparseSdf_3__Cell_ptr_ res >>= \res' ->
  return (res')

{-# LINE 3302 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#71>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__ncells_set :: ( BtSparseSdf_3_Class bc ) => (bc) -> (Int) -> IO ()
btSparseSdf_3__ncells_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSparseSdf_3__ncells_set'_ a1' a2' >>
  return ()

{-# LINE 3306 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#71>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__ncells_get :: ( BtSparseSdf_3_Class bc ) => (bc) -> IO ((Int))
btSparseSdf_3__ncells_get a1 =
  withBt a1 $ \a1' -> 
  btSparseSdf_3__ncells_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3310 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__nprobes_set :: ( BtSparseSdf_3_Class bc ) => (bc) -> (Int) -> IO ()
btSparseSdf_3__nprobes_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSparseSdf_3__nprobes_set'_ a1' a2' >>
  return ()

{-# LINE 3314 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__nprobes_get :: ( BtSparseSdf_3_Class bc ) => (bc) -> IO ((Int))
btSparseSdf_3__nprobes_get a1 =
  withBt a1 $ \a1' -> 
  btSparseSdf_3__nprobes_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3318 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#73>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__nqueries_set :: ( BtSparseSdf_3_Class bc ) => (bc) -> (Int) -> IO ()
btSparseSdf_3__nqueries_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSparseSdf_3__nqueries_set'_ a1' a2' >>
  return ()

{-# LINE 3322 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#73>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__nqueries_get :: ( BtSparseSdf_3_Class bc ) => (bc) -> IO ((Int))
btSparseSdf_3__nqueries_get a1 =
  withBt a1 $ \a1' -> 
  btSparseSdf_3__nqueries_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3326 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#70>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__puid_set :: ( BtSparseSdf_3_Class bc ) => (bc) -> (Int) -> IO ()
btSparseSdf_3__puid_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSparseSdf_3__puid_set'_ a1' a2' >>
  return ()

{-# LINE 3330 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.h?r=2223#70>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSparseSDF.cpp?r=2223>
-}
btSparseSdf_3__puid_get :: ( BtSparseSdf_3_Class bc ) => (bc) -> IO ((Int))
btSparseSdf_3__puid_get a1 =
  withBt a1 $ \a1' -> 
  btSparseSdf_3__puid_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3334 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 3338 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

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

{-# LINE 3342 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * eAeroModel
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_eAeroModel :: IO ((BtSoftBody_eAeroModel))
btSoftBody_eAeroModel =
  btSoftBody_eAeroModel'_ >>= \res ->
  mkBtSoftBody_eAeroModel res >>= \res' ->
  return (res')

{-# LINE 3347 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_eAeroModel_free :: ( BtSoftBody_eAeroModelClass bc ) => (bc) -> IO ()
btSoftBody_eAeroModel_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_eAeroModel_free'_ a1' >>
  return ()

{-# LINE 3348 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * eFeature
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#117>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_eFeature :: IO ((BtSoftBody_eFeature))
btSoftBody_eFeature =
  btSoftBody_eFeature'_ >>= \res ->
  mkBtSoftBody_eFeature res >>= \res' ->
  return (res')

{-# LINE 3353 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_eFeature_free :: ( BtSoftBody_eFeatureClass bc ) => (bc) -> IO ()
btSoftBody_eFeature_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_eFeature_free'_ a1' >>
  return ()

{-# LINE 3354 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * ePSolver
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#100>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_ePSolver :: IO ((BtSoftBody_ePSolver))
btSoftBody_ePSolver =
  btSoftBody_ePSolver'_ >>= \res ->
  mkBtSoftBody_ePSolver res >>= \res' ->
  return (res')

{-# LINE 3359 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_ePSolver_free :: ( BtSoftBody_ePSolverClass bc ) => (bc) -> IO ()
btSoftBody_ePSolver_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_ePSolver_free'_ a1' >>
  return ()

{-# LINE 3360 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * eSolverPresets
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#109>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_eSolverPresets :: IO ((BtSoftBody_eSolverPresets))
btSoftBody_eSolverPresets =
  btSoftBody_eSolverPresets'_ >>= \res ->
  mkBtSoftBody_eSolverPresets res >>= \res' ->
  return (res')

{-# LINE 3365 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_eSolverPresets_free :: ( BtSoftBody_eSolverPresetsClass bc ) => (bc) -> IO ()
btSoftBody_eSolverPresets_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_eSolverPresets_free'_ a1' >>
  return ()

{-# LINE 3366 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * eType
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#483>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_Joint_eType :: IO ((BtSoftBody_Joint_eType))
btSoftBody_Joint_eType =
  btSoftBody_Joint_eType'_ >>= \res ->
  mkBtSoftBody_Joint_eType res >>= \res' ->
  return (res')

{-# LINE 3371 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_Joint_eType_free :: ( BtSoftBody_Joint_eTypeClass bc ) => (bc) -> IO ()
btSoftBody_Joint_eType_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_Joint_eType_free'_ a1' >>
  return ()

{-# LINE 3372 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * eVSolver
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#94>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_eVSolver :: IO ((BtSoftBody_eVSolver))
btSoftBody_eVSolver =
  btSoftBody_eVSolver'_ >>= \res ->
  mkBtSoftBody_eVSolver res >>= \res' ->
  return (res')

{-# LINE 3377 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_eVSolver_free :: ( BtSoftBody_eVSolverClass bc ) => (bc) -> IO ()
btSoftBody_eVSolver_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_eVSolver_free'_ a1' >>
  return ()

{-# LINE 3378 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * fCollision
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#134>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_fCollision :: IO ((BtSoftBody_fCollision))
btSoftBody_fCollision =
  btSoftBody_fCollision'_ >>= \res ->
  mkBtSoftBody_fCollision res >>= \res' ->
  return (res')

{-# LINE 3383 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_fCollision_free :: ( BtSoftBody_fCollisionClass bc ) => (bc) -> IO ()
btSoftBody_fCollision_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_fCollision_free'_ a1' >>
  return ()

{-# LINE 3384 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * fDrawFlags
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.h?r=2223#26>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBodyHelpers.cpp?r=2223>
-}
fDrawFlags :: IO ((FDrawFlags))
fDrawFlags =
  fDrawFlags'_ >>= \res ->
  mkFDrawFlags res >>= \res' ->
  return (res')

{-# LINE 3389 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

fDrawFlags_free :: ( FDrawFlagsClass bc ) => (bc) -> IO ()
fDrawFlags_free a1 =
  withBt a1 $ \a1' -> 
  fDrawFlags_free'_ a1' >>
  return ()

{-# LINE 3390 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * fMaterial
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#149>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_fMaterial :: IO ((BtSoftBody_fMaterial))
btSoftBody_fMaterial =
  btSoftBody_fMaterial'_ >>= \res ->
  mkBtSoftBody_fMaterial res >>= \res' ->
  return (res')

{-# LINE 3395 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_fMaterial_free :: ( BtSoftBody_fMaterialClass bc ) => (bc) -> IO ()
btSoftBody_fMaterial_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_fMaterial_free'_ a1' >>
  return ()

{-# LINE 3396 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * sCti
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#184>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sCti :: IO ((BtSoftBody_sCti))
btSoftBody_sCti =
  btSoftBody_sCti'_ >>= \res ->
  mkBtSoftBody_sCti res >>= \res' ->
  return (res')

{-# LINE 3401 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_sCti_free :: ( BtSoftBody_sCtiClass bc ) => (bc) -> IO ()
btSoftBody_sCti_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_sCti_free'_ a1' >>
  return ()

{-# LINE 3402 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#185>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sCti_m_colObj_set :: ( BtSoftBody_sCtiClass bc , BtCollisionObjectClass a ) => (bc) -> (a) -> IO ()
btSoftBody_sCti_m_colObj_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_sCti_m_colObj_set'_ a1' a2' >>
  return ()

{-# LINE 3406 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#185>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sCti_m_colObj_get :: ( BtSoftBody_sCtiClass bc ) => (bc) -> IO ((BtCollisionObject))
btSoftBody_sCti_m_colObj_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_sCti_m_colObj_get'_ a1' >>= \res ->
  mkBtCollisionObject res >>= \res' ->
  return (res')

{-# LINE 3410 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#186>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sCti_m_normal_set :: ( BtSoftBody_sCtiClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_sCti_m_normal_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_sCti_m_normal_set'_ a1' a2' >>
  return ()

{-# LINE 3414 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#186>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sCti_m_normal_get :: ( BtSoftBody_sCtiClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_sCti_m_normal_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_sCti_m_normal_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3418 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#187>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sCti_m_offset_set :: ( BtSoftBody_sCtiClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_sCti_m_offset_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_sCti_m_offset_set'_ a1' a2' >>
  return ()

{-# LINE 3422 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#187>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sCti_m_offset_get :: ( BtSoftBody_sCtiClass bc ) => (bc) -> IO ((Float))
btSoftBody_sCti_m_offset_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_sCti_m_offset_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3426 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * sMedium
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#192>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sMedium :: IO ((BtSoftBody_sMedium))
btSoftBody_sMedium =
  btSoftBody_sMedium'_ >>= \res ->
  mkBtSoftBody_sMedium res >>= \res' ->
  return (res')

{-# LINE 3431 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_sMedium_free :: ( BtSoftBody_sMediumClass bc ) => (bc) -> IO ()
btSoftBody_sMedium_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_sMedium_free'_ a1' >>
  return ()

{-# LINE 3432 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#195>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sMedium_m_density_set :: ( BtSoftBody_sMediumClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_sMedium_m_density_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_sMedium_m_density_set'_ a1' a2' >>
  return ()

{-# LINE 3436 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#195>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sMedium_m_density_get :: ( BtSoftBody_sMediumClass bc ) => (bc) -> IO ((Float))
btSoftBody_sMedium_m_density_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_sMedium_m_density_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3440 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#194>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sMedium_m_pressure_set :: ( BtSoftBody_sMediumClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_sMedium_m_pressure_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_sMedium_m_pressure_set'_ a1' a2' >>
  return ()

{-# LINE 3444 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#194>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sMedium_m_pressure_get :: ( BtSoftBody_sMediumClass bc ) => (bc) -> IO ((Float))
btSoftBody_sMedium_m_pressure_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_sMedium_m_pressure_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3448 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#193>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sMedium_m_velocity_set :: ( BtSoftBody_sMediumClass bc ) => (bc) -> (Vec3) -> IO ()
btSoftBody_sMedium_m_velocity_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btSoftBody_sMedium_m_velocity_set'_ a1' a2' >>
  return ()

{-# LINE 3452 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#193>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sMedium_m_velocity_get :: ( BtSoftBody_sMediumClass bc ) => (bc) -> IO ((Vec3))
btSoftBody_sMedium_m_velocity_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btSoftBody_sMedium_m_velocity_get'_ a1' a2' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

{-# LINE 3456 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

-- * sRayCast
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#162>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sRayCast :: IO ((BtSoftBody_sRayCast))
btSoftBody_sRayCast =
  btSoftBody_sRayCast'_ >>= \res ->
  mkBtSoftBody_sRayCast res >>= \res' ->
  return (res')

{-# LINE 3461 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

btSoftBody_sRayCast_free :: ( BtSoftBody_sRayCastClass bc ) => (bc) -> IO ()
btSoftBody_sRayCast_free a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_sRayCast_free'_ a1' >>
  return ()

{-# LINE 3462 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#163>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sRayCast_body_set :: ( BtSoftBody_sRayCastClass bc , BtSoftBodyClass a ) => (bc) -> (a) -> IO ()
btSoftBody_sRayCast_body_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btSoftBody_sRayCast_body_set'_ a1' a2' >>
  return ()

{-# LINE 3466 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#163>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sRayCast_body_get :: ( BtSoftBody_sRayCastClass bc ) => (bc) -> IO ((BtSoftBody))
btSoftBody_sRayCast_body_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_sRayCast_body_get'_ a1' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  return (res')

{-# LINE 3470 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#166>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sRayCast_fraction_set :: ( BtSoftBody_sRayCastClass bc ) => (bc) -> (Float) -> IO ()
btSoftBody_sRayCast_fraction_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btSoftBody_sRayCast_fraction_set'_ a1' a2' >>
  return ()

{-# LINE 3474 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#166>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sRayCast_fraction_get :: ( BtSoftBody_sRayCastClass bc ) => (bc) -> IO ((Float))
btSoftBody_sRayCast_fraction_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_sRayCast_fraction_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 3478 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#165>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sRayCast_index_set :: ( BtSoftBody_sRayCastClass bc ) => (bc) -> (Int) -> IO ()
btSoftBody_sRayCast_index_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSoftBody_sRayCast_index_set'_ a1' a2' >>
  return ()

{-# LINE 3482 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.h?r=2223#165>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletSoftBody/btSoftBody.cpp?r=2223>
-}
btSoftBody_sRayCast_index_get :: ( BtSoftBody_sRayCastClass bc ) => (bc) -> IO ((Int))
btSoftBody_sRayCast_index_get a1 =
  withBt a1 $ \a1' -> 
  btSoftBody_sRayCast_index_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 3486 "./Physics/Bullet/Raw/BulletSoftBody.chs" #-}


foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_new"
  btSoftBody_AJoint'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_free"
  btSoftBody_AJoint_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_Terminate"
  btSoftBody_AJoint_Terminate'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_Solve"
  btSoftBody_AJoint_Solve'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_Prepare"
  btSoftBody_AJoint_Prepare'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_m_icontrol_set"
  btSoftBody_AJoint_m_icontrol_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_m_icontrol_get"
  btSoftBody_AJoint_m_icontrol_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_new"
  btSoftBody_Anchor'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_free"
  btSoftBody_Anchor_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_node_set"
  btSoftBody_Anchor_m_node_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_node_get"
  btSoftBody_Anchor_m_node_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_local_set"
  btSoftBody_Anchor_m_local_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_local_get"
  btSoftBody_Anchor_m_local_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_body_set"
  btSoftBody_Anchor_m_body_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_body_get"
  btSoftBody_Anchor_m_body_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_influence_set"
  btSoftBody_Anchor_m_influence_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_influence_get"
  btSoftBody_Anchor_m_influence_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_c0_set"
  btSoftBody_Anchor_m_c0_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_c0_get"
  btSoftBody_Anchor_m_c0_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_c1_set"
  btSoftBody_Anchor_m_c1_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_c1_get"
  btSoftBody_Anchor_m_c1_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_c2_set"
  btSoftBody_Anchor_m_c2_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Anchor_m_c2_get"
  btSoftBody_Anchor_m_c2_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_new0"
  btSoftBody_Body0'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_new1"
  btSoftBody_Body1'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_new2"
  btSoftBody_Body2'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_free"
  btSoftBody_Body_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_invWorldInertia"
  btSoftBody_Body_invWorldInertia'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_activate"
  btSoftBody_Body_activate'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_linearVelocity"
  btSoftBody_Body_linearVelocity'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_applyVImpulse"
  btSoftBody_Body_applyVImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_applyVImpulse"
  btSoftBody_Body_applyVImpulse''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_applyDImpulse"
  btSoftBody_Body_applyDImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_applyDImpulse"
  btSoftBody_Body_applyDImpulse''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_applyDCImpulse"
  btSoftBody_Body_applyDCImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_applyDCImpulse"
  btSoftBody_Body_applyDCImpulse''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_applyAImpulse"
  btSoftBody_Body_applyAImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_angularVelocity0"
  btSoftBody_Body_angularVelocity'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_angularVelocity0"
  btSoftBody_Body_angularVelocity''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_angularVelocity0"
  btSoftBody_Body_angularVelocity0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_angularVelocity0"
  btSoftBody_Body_angularVelocity0''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_angularVelocity1"
  btSoftBody_Body_angularVelocity1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_applyVAImpulse"
  btSoftBody_Body_applyVAImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_applyVAImpulse"
  btSoftBody_Body_applyVAImpulse''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_applyImpulse"
  btSoftBody_Body_applyImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_applyImpulse"
  btSoftBody_Body_applyImpulse''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_applyDAImpulse"
  btSoftBody_Body_applyDAImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_applyDAImpulse"
  btSoftBody_Body_applyDAImpulse''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_velocity"
  btSoftBody_Body_velocity'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_velocity"
  btSoftBody_Body_velocity''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_invMass"
  btSoftBody_Body_invMass'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_xform"
  btSoftBody_Body_xform'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_m_soft_set"
  btSoftBody_Body_m_soft_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_m_soft_get"
  btSoftBody_Body_m_soft_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_m_rigid_set"
  btSoftBody_Body_m_rigid_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_m_rigid_get"
  btSoftBody_Body_m_rigid_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_m_collisionObject_set"
  btSoftBody_Body_m_collisionObject_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Body_m_collisionObject_get"
  btSoftBody_Body_m_collisionObject_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_CJoint_new"
  btSoftBody_CJoint'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_CJoint_free"
  btSoftBody_CJoint_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_CJoint_Terminate"
  btSoftBody_CJoint_Terminate'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_CJoint_Solve"
  btSoftBody_CJoint_Solve'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_CJoint_Prepare"
  btSoftBody_CJoint_Prepare'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_CJoint_m_life_set"
  btSoftBody_CJoint_m_life_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_CJoint_m_life_get"
  btSoftBody_CJoint_m_life_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_CJoint_m_maxlife_set"
  btSoftBody_CJoint_m_maxlife_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_CJoint_m_maxlife_get"
  btSoftBody_CJoint_m_maxlife_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_CJoint_m_normal_set"
  btSoftBody_CJoint_m_normal_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_CJoint_m_normal_get"
  btSoftBody_CJoint_m_normal_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_CJoint_m_friction_set"
  btSoftBody_CJoint_m_friction_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_CJoint_m_friction_get"
  btSoftBody_CJoint_m_friction_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_new"
  btSoftBody_Cluster'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_free"
  btSoftBody_Cluster_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_adamping_set"
  btSoftBody_Cluster_m_adamping_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_adamping_get"
  btSoftBody_Cluster_m_adamping_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_av_set"
  btSoftBody_Cluster_m_av_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_av_get"
  btSoftBody_Cluster_m_av_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_clusterIndex_set"
  btSoftBody_Cluster_m_clusterIndex_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_clusterIndex_get"
  btSoftBody_Cluster_m_clusterIndex_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_collide_set"
  btSoftBody_Cluster_m_collide_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_collide_get"
  btSoftBody_Cluster_m_collide_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_com_set"
  btSoftBody_Cluster_m_com_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_com_get"
  btSoftBody_Cluster_m_com_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_containsAnchor_set"
  btSoftBody_Cluster_m_containsAnchor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_containsAnchor_get"
  btSoftBody_Cluster_m_containsAnchor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_framerefs_set"
  btSoftBody_Cluster_m_framerefs_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_framerefs_get"
  btSoftBody_Cluster_m_framerefs_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_framexform_set"
  btSoftBody_Cluster_m_framexform_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_framexform_get"
  btSoftBody_Cluster_m_framexform_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_idmass_set"
  btSoftBody_Cluster_m_idmass_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_idmass_get"
  btSoftBody_Cluster_m_idmass_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_imass_set"
  btSoftBody_Cluster_m_imass_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_imass_get"
  btSoftBody_Cluster_m_imass_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_invwi_set"
  btSoftBody_Cluster_m_invwi_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_invwi_get"
  btSoftBody_Cluster_m_invwi_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_ldamping_set"
  btSoftBody_Cluster_m_ldamping_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_ldamping_get"
  btSoftBody_Cluster_m_ldamping_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_leaf_set"
  btSoftBody_Cluster_m_leaf_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_leaf_get"
  btSoftBody_Cluster_m_leaf_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_locii_set"
  btSoftBody_Cluster_m_locii_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_locii_get"
  btSoftBody_Cluster_m_locii_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_lv_set"
  btSoftBody_Cluster_m_lv_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_lv_get"
  btSoftBody_Cluster_m_lv_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_masses_set"
  btSoftBody_Cluster_m_masses_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_masses_get"
  btSoftBody_Cluster_m_masses_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_matching_set"
  btSoftBody_Cluster_m_matching_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_matching_get"
  btSoftBody_Cluster_m_matching_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_maxSelfCollisionImpulse_set"
  btSoftBody_Cluster_m_maxSelfCollisionImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_maxSelfCollisionImpulse_get"
  btSoftBody_Cluster_m_maxSelfCollisionImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_ndamping_set"
  btSoftBody_Cluster_m_ndamping_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_ndamping_get"
  btSoftBody_Cluster_m_ndamping_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_ndimpulses_set"
  btSoftBody_Cluster_m_ndimpulses_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_ndimpulses_get"
  btSoftBody_Cluster_m_ndimpulses_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_nodes_set"
  btSoftBody_Cluster_m_nodes_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_nodes_get"
  btSoftBody_Cluster_m_nodes_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_nvimpulses_set"
  btSoftBody_Cluster_m_nvimpulses_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_nvimpulses_get"
  btSoftBody_Cluster_m_nvimpulses_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_selfCollisionImpulseFactor_set"
  btSoftBody_Cluster_m_selfCollisionImpulseFactor_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Cluster_m_selfCollisionImpulseFactor_get"
  btSoftBody_Cluster_m_selfCollisionImpulseFactor_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_new"
  btSoftBody_Config'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_free"
  btSoftBody_Config_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kVCF_set"
  btSoftBody_Config_kVCF_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kVCF_get"
  btSoftBody_Config_kVCF_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kDP_set"
  btSoftBody_Config_kDP_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kDP_get"
  btSoftBody_Config_kDP_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kDG_set"
  btSoftBody_Config_kDG_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kDG_get"
  btSoftBody_Config_kDG_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kLF_set"
  btSoftBody_Config_kLF_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kLF_get"
  btSoftBody_Config_kLF_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kPR_set"
  btSoftBody_Config_kPR_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kPR_get"
  btSoftBody_Config_kPR_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kVC_set"
  btSoftBody_Config_kVC_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kVC_get"
  btSoftBody_Config_kVC_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kDF_set"
  btSoftBody_Config_kDF_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kDF_get"
  btSoftBody_Config_kDF_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kMT_set"
  btSoftBody_Config_kMT_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kMT_get"
  btSoftBody_Config_kMT_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kCHR_set"
  btSoftBody_Config_kCHR_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kCHR_get"
  btSoftBody_Config_kCHR_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kKHR_set"
  btSoftBody_Config_kKHR_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kKHR_get"
  btSoftBody_Config_kKHR_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSHR_set"
  btSoftBody_Config_kSHR_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSHR_get"
  btSoftBody_Config_kSHR_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kAHR_set"
  btSoftBody_Config_kAHR_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kAHR_get"
  btSoftBody_Config_kAHR_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSRHR_CL_set"
  btSoftBody_Config_kSRHR_CL_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSRHR_CL_get"
  btSoftBody_Config_kSRHR_CL_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSKHR_CL_set"
  btSoftBody_Config_kSKHR_CL_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSKHR_CL_get"
  btSoftBody_Config_kSKHR_CL_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSSHR_CL_set"
  btSoftBody_Config_kSSHR_CL_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSSHR_CL_get"
  btSoftBody_Config_kSSHR_CL_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSR_SPLT_CL_set"
  btSoftBody_Config_kSR_SPLT_CL_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSR_SPLT_CL_get"
  btSoftBody_Config_kSR_SPLT_CL_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSK_SPLT_CL_set"
  btSoftBody_Config_kSK_SPLT_CL_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSK_SPLT_CL_get"
  btSoftBody_Config_kSK_SPLT_CL_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSS_SPLT_CL_set"
  btSoftBody_Config_kSS_SPLT_CL_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_kSS_SPLT_CL_get"
  btSoftBody_Config_kSS_SPLT_CL_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_maxvolume_set"
  btSoftBody_Config_maxvolume_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_maxvolume_get"
  btSoftBody_Config_maxvolume_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_timescale_set"
  btSoftBody_Config_timescale_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_timescale_get"
  btSoftBody_Config_timescale_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_viterations_set"
  btSoftBody_Config_viterations_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_viterations_get"
  btSoftBody_Config_viterations_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_piterations_set"
  btSoftBody_Config_piterations_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_piterations_get"
  btSoftBody_Config_piterations_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_diterations_set"
  btSoftBody_Config_diterations_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_diterations_get"
  btSoftBody_Config_diterations_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_citerations_set"
  btSoftBody_Config_citerations_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_citerations_get"
  btSoftBody_Config_citerations_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_collisions_set"
  btSoftBody_Config_collisions_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_collisions_get"
  btSoftBody_Config_collisions_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_m_vsequence_set"
  btSoftBody_Config_m_vsequence_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_m_vsequence_get"
  btSoftBody_Config_m_vsequence_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_m_psequence_set"
  btSoftBody_Config_m_psequence_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_m_psequence_get"
  btSoftBody_Config_m_psequence_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_m_dsequence_set"
  btSoftBody_Config_m_dsequence_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Config_m_dsequence_get"
  btSoftBody_Config_m_dsequence_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Element_new"
  btSoftBody_Element'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Element_free"
  btSoftBody_Element_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Element_m_tag_set"
  btSoftBody_Element_m_tag_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Element_m_tag_get"
  btSoftBody_Element_m_tag_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Face_new"
  btSoftBody_Face'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Face_free"
  btSoftBody_Face_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Face_m_normal_set"
  btSoftBody_Face_m_normal_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Face_m_normal_get"
  btSoftBody_Face_m_normal_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Face_m_ra_set"
  btSoftBody_Face_m_ra_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Face_m_ra_get"
  btSoftBody_Face_m_ra_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Face_m_leaf_set"
  btSoftBody_Face_m_leaf_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Face_m_leaf_get"
  btSoftBody_Face_m_leaf_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Feature_new"
  btSoftBody_Feature'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Feature_free"
  btSoftBody_Feature_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Feature_m_material_set"
  btSoftBody_Feature_m_material_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Feature_m_material_get"
  btSoftBody_Feature_m_material_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_IControl_new"
  btSoftBody_AJoint_IControl'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_IControl_free"
  btSoftBody_AJoint_IControl_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_IControl_Default"
  btSoftBody_AJoint_IControl_Default'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_IControl_Speed"
  btSoftBody_AJoint_IControl_Speed'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO C2HSImp.CFloat))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_IControl_Prepare"
  btSoftBody_AJoint_IControl_Prepare'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_ImplicitFn_Eval"
  btSoftBody_ImplicitFn_Eval'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CFloat)))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_ImplicitFn_Eval"
  btSoftBody_ImplicitFn_Eval''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CFloat)))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Impulse_new"
  btSoftBody_Impulse'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Impulse_free"
  btSoftBody_Impulse_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Impulse_m_asDrift_set"
  btSoftBody_Impulse_m_asDrift_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Impulse_m_asDrift_get"
  btSoftBody_Impulse_m_asDrift_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Impulse_m_asVelocity_set"
  btSoftBody_Impulse_m_asVelocity_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Impulse_m_asVelocity_get"
  btSoftBody_Impulse_m_asVelocity_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Impulse_m_drift_set"
  btSoftBody_Impulse_m_drift_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Impulse_m_drift_get"
  btSoftBody_Impulse_m_drift_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Impulse_m_velocity_set"
  btSoftBody_Impulse_m_velocity_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Impulse_m_velocity_get"
  btSoftBody_Impulse_m_velocity_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_Terminate"
  btSoftBody_Joint_Terminate'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_Solve"
  btSoftBody_Joint_Solve'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_Prepare"
  btSoftBody_Joint_Prepare'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_cfm_set"
  btSoftBody_Joint_m_cfm_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_cfm_get"
  btSoftBody_Joint_m_cfm_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_erp_set"
  btSoftBody_Joint_m_erp_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_erp_get"
  btSoftBody_Joint_m_erp_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_split_set"
  btSoftBody_Joint_m_split_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_split_get"
  btSoftBody_Joint_m_split_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_drift_set"
  btSoftBody_Joint_m_drift_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_drift_get"
  btSoftBody_Joint_m_drift_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_sdrift_set"
  btSoftBody_Joint_m_sdrift_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_sdrift_get"
  btSoftBody_Joint_m_sdrift_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_massmatrix_set"
  btSoftBody_Joint_m_massmatrix_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_massmatrix_get"
  btSoftBody_Joint_m_massmatrix_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_delete_set"
  btSoftBody_Joint_m_delete_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_m_delete_get"
  btSoftBody_Joint_m_delete_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_LJoint_new"
  btSoftBody_LJoint'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_LJoint_free"
  btSoftBody_LJoint_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_LJoint_Terminate"
  btSoftBody_LJoint_Terminate'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_LJoint_Solve"
  btSoftBody_LJoint_Solve'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_LJoint_Prepare"
  btSoftBody_LJoint_Prepare'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_new"
  btSoftBody_Link'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_free"
  btSoftBody_Link_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_m_rl_set"
  btSoftBody_Link_m_rl_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_m_rl_get"
  btSoftBody_Link_m_rl_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_m_bbending_set"
  btSoftBody_Link_m_bbending_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_m_bbending_get"
  btSoftBody_Link_m_bbending_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_m_c0_set"
  btSoftBody_Link_m_c0_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_m_c0_get"
  btSoftBody_Link_m_c0_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_m_c1_set"
  btSoftBody_Link_m_c1_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_m_c1_get"
  btSoftBody_Link_m_c1_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_m_c2_set"
  btSoftBody_Link_m_c2_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_m_c2_get"
  btSoftBody_Link_m_c2_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_m_c3_set"
  btSoftBody_Link_m_c3_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Link_m_c3_get"
  btSoftBody_Link_m_c3_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Material_new"
  btSoftBody_Material'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Material_free"
  btSoftBody_Material_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Material_m_flags_set"
  btSoftBody_Material_m_flags_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Material_m_flags_get"
  btSoftBody_Material_m_flags_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Material_m_kAST_set"
  btSoftBody_Material_m_kAST_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Material_m_kAST_get"
  btSoftBody_Material_m_kAST_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Material_m_kLST_set"
  btSoftBody_Material_m_kLST_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Material_m_kLST_get"
  btSoftBody_Material_m_kLST_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Material_m_kVST_set"
  btSoftBody_Material_m_kVST_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Material_m_kVST_get"
  btSoftBody_Material_m_kVST_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_new"
  btSoftBody_Node'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_free"
  btSoftBody_Node_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_area_set"
  btSoftBody_Node_m_area_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_area_get"
  btSoftBody_Node_m_area_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_battach_set"
  btSoftBody_Node_m_battach_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_battach_get"
  btSoftBody_Node_m_battach_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_f_set"
  btSoftBody_Node_m_f_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_f_get"
  btSoftBody_Node_m_f_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_im_set"
  btSoftBody_Node_m_im_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_im_get"
  btSoftBody_Node_m_im_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_leaf_set"
  btSoftBody_Node_m_leaf_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_leaf_get"
  btSoftBody_Node_m_leaf_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_n_set"
  btSoftBody_Node_m_n_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_n_get"
  btSoftBody_Node_m_n_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_q_set"
  btSoftBody_Node_m_q_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_q_get"
  btSoftBody_Node_m_q_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_v_set"
  btSoftBody_Node_m_v_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_v_get"
  btSoftBody_Node_m_v_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_x_set"
  btSoftBody_Node_m_x_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Node_m_x_get"
  btSoftBody_Node_m_x_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Note_new"
  btSoftBody_Note'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Note_free"
  btSoftBody_Note_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Note_m_text_set"
  btSoftBody_Note_m_text_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Note_m_text_get"
  btSoftBody_Note_m_text_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Note_m_offset_set"
  btSoftBody_Note_m_offset_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Note_m_offset_get"
  btSoftBody_Note_m_offset_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Note_m_rank_set"
  btSoftBody_Note_m_rank_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Note_m_rank_get"
  btSoftBody_Note_m_rank_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_new"
  btSoftBody_Pose'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_free"
  btSoftBody_Pose_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_bvolume_set"
  btSoftBody_Pose_m_bvolume_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_bvolume_get"
  btSoftBody_Pose_m_bvolume_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_bframe_set"
  btSoftBody_Pose_m_bframe_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_bframe_get"
  btSoftBody_Pose_m_bframe_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_volume_set"
  btSoftBody_Pose_m_volume_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_volume_get"
  btSoftBody_Pose_m_volume_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_pos_set"
  btSoftBody_Pose_m_pos_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_pos_get"
  btSoftBody_Pose_m_pos_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_wgh_set"
  btSoftBody_Pose_m_wgh_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_wgh_get"
  btSoftBody_Pose_m_wgh_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_com_set"
  btSoftBody_Pose_m_com_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_com_get"
  btSoftBody_Pose_m_com_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_rot_set"
  btSoftBody_Pose_m_rot_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_rot_get"
  btSoftBody_Pose_m_rot_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_scl_set"
  btSoftBody_Pose_m_scl_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_scl_get"
  btSoftBody_Pose_m_scl_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_aqq_set"
  btSoftBody_Pose_m_aqq_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Pose_m_aqq_get"
  btSoftBody_Pose_m_aqq_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_new"
  btSoftBody_RContact'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_free"
  btSoftBody_RContact_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_cti_set"
  btSoftBody_RContact_m_cti_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_cti_get"
  btSoftBody_RContact_m_cti_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_node_set"
  btSoftBody_RContact_m_node_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_node_get"
  btSoftBody_RContact_m_node_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_c0_set"
  btSoftBody_RContact_m_c0_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_c0_get"
  btSoftBody_RContact_m_c0_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_c1_set"
  btSoftBody_RContact_m_c1_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_c1_get"
  btSoftBody_RContact_m_c1_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_c2_set"
  btSoftBody_RContact_m_c2_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_c2_get"
  btSoftBody_RContact_m_c2_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_c3_set"
  btSoftBody_RContact_m_c3_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_c3_get"
  btSoftBody_RContact_m_c3_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_c4_set"
  btSoftBody_RContact_m_c4_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RContact_m_c4_get"
  btSoftBody_RContact_m_c4_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_new"
  btSoftBody_RayFromToCaster'_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO (C2HSImp.Ptr ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_free"
  btSoftBody_RayFromToCaster_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_Process"
  btSoftBody_RayFromToCaster_Process'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_m_rayFrom_set"
  btSoftBody_RayFromToCaster_m_rayFrom_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_m_rayFrom_get"
  btSoftBody_RayFromToCaster_m_rayFrom_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_m_rayTo_set"
  btSoftBody_RayFromToCaster_m_rayTo_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_m_rayTo_get"
  btSoftBody_RayFromToCaster_m_rayTo_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_m_rayNormalizedDirection_set"
  btSoftBody_RayFromToCaster_m_rayNormalizedDirection_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_m_rayNormalizedDirection_get"
  btSoftBody_RayFromToCaster_m_rayNormalizedDirection_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_m_mint_set"
  btSoftBody_RayFromToCaster_m_mint_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_m_mint_get"
  btSoftBody_RayFromToCaster_m_mint_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_m_face_set"
  btSoftBody_RayFromToCaster_m_face_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_m_face_get"
  btSoftBody_RayFromToCaster_m_face_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_m_tests_set"
  btSoftBody_RayFromToCaster_m_tests_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_RayFromToCaster_m_tests_get"
  btSoftBody_RayFromToCaster_m_tests_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_new"
  btSoftBody_SContact'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_free"
  btSoftBody_SContact_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_m_node_set"
  btSoftBody_SContact_m_node_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_m_node_get"
  btSoftBody_SContact_m_node_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_m_face_set"
  btSoftBody_SContact_m_face_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_m_face_get"
  btSoftBody_SContact_m_face_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_m_weights_set"
  btSoftBody_SContact_m_weights_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_m_weights_get"
  btSoftBody_SContact_m_weights_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_m_normal_set"
  btSoftBody_SContact_m_normal_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_m_normal_get"
  btSoftBody_SContact_m_normal_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_m_margin_set"
  btSoftBody_SContact_m_margin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_m_margin_get"
  btSoftBody_SContact_m_margin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_m_friction_set"
  btSoftBody_SContact_m_friction_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SContact_m_friction_get"
  btSoftBody_SContact_m_friction_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SolverState_new"
  btSoftBody_SolverState'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SolverState_free"
  btSoftBody_SolverState_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SolverState_sdt_set"
  btSoftBody_SolverState_sdt_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SolverState_sdt_get"
  btSoftBody_SolverState_sdt_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SolverState_isdt_set"
  btSoftBody_SolverState_isdt_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SolverState_isdt_get"
  btSoftBody_SolverState_isdt_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SolverState_velmrg_set"
  btSoftBody_SolverState_velmrg_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SolverState_velmrg_get"
  btSoftBody_SolverState_velmrg_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SolverState_radmrg_set"
  btSoftBody_SolverState_radmrg_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SolverState_radmrg_get"
  btSoftBody_SolverState_radmrg_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SolverState_updmrg_set"
  btSoftBody_SolverState_updmrg_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_SolverState_updmrg_get"
  btSoftBody_SolverState_updmrg_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_Specs_new"
  btSoftBody_Joint_Specs'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_Specs_free"
  btSoftBody_Joint_Specs_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_Specs_erp_set"
  btSoftBody_Joint_Specs_erp_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_Specs_erp_get"
  btSoftBody_Joint_Specs_erp_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_Specs_cfm_set"
  btSoftBody_Joint_Specs_cfm_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_Specs_cfm_get"
  btSoftBody_Joint_Specs_cfm_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_Specs_split_set"
  btSoftBody_Joint_Specs_split_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_Specs_split_get"
  btSoftBody_Joint_Specs_split_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_LJoint_Specs_new"
  btSoftBody_LJoint_Specs'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_LJoint_Specs_free"
  btSoftBody_LJoint_Specs_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_LJoint_Specs_position_set"
  btSoftBody_LJoint_Specs_position_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_LJoint_Specs_position_get"
  btSoftBody_LJoint_Specs_position_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_Specs_new"
  btSoftBody_AJoint_Specs'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_Specs_free"
  btSoftBody_AJoint_Specs_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_Specs_axis_set"
  btSoftBody_AJoint_Specs_axis_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_Specs_axis_get"
  btSoftBody_AJoint_Specs_axis_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_Specs_icontrol_set"
  btSoftBody_AJoint_Specs_icontrol_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_AJoint_Specs_icontrol_get"
  btSoftBody_AJoint_Specs_icontrol_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Tetra_new"
  btSoftBody_Tetra'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Tetra_free"
  btSoftBody_Tetra_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Tetra_m_rv_set"
  btSoftBody_Tetra_m_rv_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Tetra_m_rv_get"
  btSoftBody_Tetra_m_rv_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Tetra_m_leaf_set"
  btSoftBody_Tetra_m_leaf_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Tetra_m_leaf_get"
  btSoftBody_Tetra_m_leaf_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Tetra_m_c1_set"
  btSoftBody_Tetra_m_c1_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Tetra_m_c1_get"
  btSoftBody_Tetra_m_c1_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Tetra_m_c2_set"
  btSoftBody_Tetra_m_c2_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Tetra_m_c2_get"
  btSoftBody_Tetra_m_c2_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_new1"
  btSoftBody1'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_free"
  btSoftBody_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_getVolume"
  btSoftBody_getVolume'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_cutLink0"
  btSoftBody_cutLink'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_cutLink0"
  btSoftBody_cutLink0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_cutLink1"
  btSoftBody_cutLink1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_PSolve_Links"
  btSoftBody_PSolve_Links'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_generateClusters"
  btSoftBody_generateClusters'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_setCollisionShape"
  btSoftBody_setCollisionShape'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_initializeClusters"
  btSoftBody_initializeClusters'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterVAImpulse"
  btSoftBody_clusterVAImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterVAImpulse"
  btSoftBody_clusterVAImpulse''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_addForce0"
  btSoftBody_addForce'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_addForce0"
  btSoftBody_addForce''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_addForce0"
  btSoftBody_addForce0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_addForce0"
  btSoftBody_addForce0''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_addForce1"
  btSoftBody_addForce1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_addForce1"
  btSoftBody_addForce1''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_serialize"
  btSoftBody_serialize'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_updateBounds"
  btSoftBody_updateBounds'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_rotate"
  btSoftBody_rotate'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_rotate"
  btSoftBody_rotate''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_releaseCluster"
  btSoftBody_releaseCluster'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_updateNormals"
  btSoftBody_updateNormals'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_prepareClusters"
  btSoftBody_prepareClusters'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_releaseClusters"
  btSoftBody_releaseClusters'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_getTotalMass"
  btSoftBody_getTotalMass'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_checkContact"
  btSoftBody_checkContact'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_checkContact"
  btSoftBody_checkContact''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterDImpulse"
  btSoftBody_clusterDImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterDImpulse"
  btSoftBody_clusterDImpulse''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_initDefaults"
  btSoftBody_initDefaults'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_checkLink0"
  btSoftBody_checkLink'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_checkLink0"
  btSoftBody_checkLink0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_checkLink1"
  btSoftBody_checkLink1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_setVolumeMass"
  btSoftBody_setVolumeMass'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterImpulse"
  btSoftBody_clusterImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterImpulse"
  btSoftBody_clusterImpulse''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_checkFace"
  btSoftBody_checkFace'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_evaluateCom"
  btSoftBody_evaluateCom'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterDAImpulse"
  btSoftBody_clusterDAImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterDAImpulse"
  btSoftBody_clusterDAImpulse''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_VSolve_Links"
  btSoftBody_VSolve_Links'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_setTotalMass"
  btSoftBody_setTotalMass'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterDCImpulse"
  btSoftBody_clusterDCImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterDCImpulse"
  btSoftBody_clusterDCImpulse''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterVelocity"
  btSoftBody_clusterVelocity'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterVelocity"
  btSoftBody_clusterVelocity''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_generateBendingConstraints"
  btSoftBody_generateBendingConstraints'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_updateClusters"
  btSoftBody_updateClusters'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendAnchor0"
  btSoftBody_appendAnchor'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendAnchor0"
  btSoftBody_appendAnchor0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendAnchor1"
  btSoftBody_appendAnchor1'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendAnchor1"
  btSoftBody_appendAnchor1''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_applyClusters"
  btSoftBody_applyClusters'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_setVelocity"
  btSoftBody_setVelocity'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_setVelocity"
  btSoftBody_setVelocity''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterCount"
  btSoftBody_clusterCount'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_upcast0"
  btSoftBody_upcast'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_upcast0"
  btSoftBody_upcast0'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_upcast1"
  btSoftBody_upcast1'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_getWindVelocity"
  btSoftBody_getWindVelocity'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_predictMotion"
  btSoftBody_predictMotion'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_pointersToIndices"
  btSoftBody_pointersToIndices'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_getMass"
  btSoftBody_getMass'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CFloat)))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_PSolve_RContacts"
  btSoftBody_PSolve_RContacts'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_initializeFaceTree"
  btSoftBody_initializeFaceTree'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_addVelocity0"
  btSoftBody_addVelocity'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_addVelocity0"
  btSoftBody_addVelocity''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_addVelocity0"
  btSoftBody_addVelocity0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_addVelocity0"
  btSoftBody_addVelocity0''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_addVelocity1"
  btSoftBody_addVelocity1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_addVelocity1"
  btSoftBody_addVelocity1''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_PSolve_Anchors"
  btSoftBody_PSolve_Anchors'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_cleanupClusters"
  btSoftBody_cleanupClusters'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_transform"
  btSoftBody_transform'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_transform"
  btSoftBody_transform''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendLinearJoint2"
  btSoftBody_appendLinearJoint2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_randomizeConstraints"
  btSoftBody_randomizeConstraints'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_updatePose"
  btSoftBody_updatePose'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_translate"
  btSoftBody_translate'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_translate"
  btSoftBody_translate''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_getAabb"
  btSoftBody_getAabb'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_getAabb"
  btSoftBody_getAabb''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_PSolve_SContacts"
  btSoftBody_PSolve_SContacts'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendMaterial"
  btSoftBody_appendMaterial'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendNode"
  btSoftBody_appendNode'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendNode"
  btSoftBody_appendNode''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_setMass"
  btSoftBody_setMass'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_integrateMotion"
  btSoftBody_integrateMotion'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_defaultCollisionHandler0"
  btSoftBody_defaultCollisionHandler'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_defaultCollisionHandler0"
  btSoftBody_defaultCollisionHandler0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_defaultCollisionHandler1"
  btSoftBody_defaultCollisionHandler1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_solveConstraints"
  btSoftBody_solveConstraints'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_setTotalDensity"
  btSoftBody_setTotalDensity'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendNote0"
  btSoftBody_appendNote'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendNote0"
  btSoftBody_appendNote''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendNote0"
  btSoftBody_appendNote0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendNote0"
  btSoftBody_appendNote0''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendNote1"
  btSoftBody_appendNote1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendNote1"
  btSoftBody_appendNote1''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendNote2"
  btSoftBody_appendNote2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendNote2"
  btSoftBody_appendNote2''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendNote3"
  btSoftBody_appendNote3'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendNote3"
  btSoftBody_appendNote3''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_setVolumeDensity"
  btSoftBody_setVolumeDensity'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_updateConstants"
  btSoftBody_updateConstants'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_staticSolve"
  btSoftBody_staticSolve'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_refine"
  btSoftBody_refine'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendLink0"
  btSoftBody_appendLink'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendLink0"
  btSoftBody_appendLink0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendLink1"
  btSoftBody_appendLink1'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendLink2"
  btSoftBody_appendLink2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_calculateSerializeBufferSize"
  btSoftBody_calculateSerializeBufferSize'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_solveClusters0"
  btSoftBody_solveClusters'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_solveClusters0"
  btSoftBody_solveClusters0'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_solveClusters1"
  btSoftBody_solveClusters1'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_rayTest0"
  btSoftBody_rayTest'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_rayTest0"
  btSoftBody_rayTest''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_rayTest0"
  btSoftBody_rayTest0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_rayTest0"
  btSoftBody_rayTest0''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_setPose"
  btSoftBody_setPose'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendFace0"
  btSoftBody_appendFace'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendFace0"
  btSoftBody_appendFace0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendFace1"
  btSoftBody_appendFace1'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_dampClusters"
  btSoftBody_dampClusters'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_getWorldInfo"
  btSoftBody_getWorldInfo'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendAngularJoint2"
  btSoftBody_appendAngularJoint2'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterVImpulse"
  btSoftBody_clusterVImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterVImpulse"
  btSoftBody_clusterVImpulse''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_scale"
  btSoftBody_scale'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_scale"
  btSoftBody_scale''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterAImpulse"
  btSoftBody_clusterAImpulse'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterCom0"
  btSoftBody_clusterCom'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterCom0"
  btSoftBody_clusterCom0'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_clusterCom1"
  btSoftBody_clusterCom1'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_setWindVelocity"
  btSoftBody_setWindVelocity'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_setWindVelocity"
  btSoftBody_setWindVelocity''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_applyForces"
  btSoftBody_applyForces'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendTetra0"
  btSoftBody_appendTetra'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendTetra0"
  btSoftBody_appendTetra0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_appendTetra1"
  btSoftBody_appendTetra1'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_anchors_set"
  btSoftBody_m_anchors_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_anchors_get"
  btSoftBody_m_anchors_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_bUpdateRtCst_set"
  btSoftBody_m_bUpdateRtCst_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_bUpdateRtCst_get"
  btSoftBody_m_bUpdateRtCst_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_cdbvt_set"
  btSoftBody_m_cdbvt_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_cdbvt_get"
  btSoftBody_m_cdbvt_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_cfg_set"
  btSoftBody_m_cfg_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_cfg_get"
  btSoftBody_m_cfg_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_clusterConnectivity_set"
  btSoftBody_m_clusterConnectivity_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_clusterConnectivity_get"
  btSoftBody_m_clusterConnectivity_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_clusters_set"
  btSoftBody_m_clusters_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_clusters_get"
  btSoftBody_m_clusters_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_collisionDisabledObjects_set"
  btSoftBody_m_collisionDisabledObjects_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_collisionDisabledObjects_get"
  btSoftBody_m_collisionDisabledObjects_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_faces_set"
  btSoftBody_m_faces_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_faces_get"
  btSoftBody_m_faces_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_fdbvt_set"
  btSoftBody_m_fdbvt_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_fdbvt_get"
  btSoftBody_m_fdbvt_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_initialWorldTransform_set"
  btSoftBody_m_initialWorldTransform_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_initialWorldTransform_get"
  btSoftBody_m_initialWorldTransform_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_joints_set"
  btSoftBody_m_joints_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_joints_get"
  btSoftBody_m_joints_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_links_set"
  btSoftBody_m_links_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_links_get"
  btSoftBody_m_links_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_materials_set"
  btSoftBody_m_materials_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_materials_get"
  btSoftBody_m_materials_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_ndbvt_set"
  btSoftBody_m_ndbvt_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_ndbvt_get"
  btSoftBody_m_ndbvt_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_nodes_set"
  btSoftBody_m_nodes_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_nodes_get"
  btSoftBody_m_nodes_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_notes_set"
  btSoftBody_m_notes_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_notes_get"
  btSoftBody_m_notes_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_pose_set"
  btSoftBody_m_pose_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_pose_get"
  btSoftBody_m_pose_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_rcontacts_set"
  btSoftBody_m_rcontacts_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_rcontacts_get"
  btSoftBody_m_rcontacts_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_scontacts_set"
  btSoftBody_m_scontacts_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_scontacts_get"
  btSoftBody_m_scontacts_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_sst_set"
  btSoftBody_m_sst_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_sst_get"
  btSoftBody_m_sst_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_tag_set"
  btSoftBody_m_tag_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_tag_get"
  btSoftBody_m_tag_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_tetras_set"
  btSoftBody_m_tetras_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_tetras_get"
  btSoftBody_m_tetras_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_timeacc_set"
  btSoftBody_m_timeacc_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_timeacc_get"
  btSoftBody_m_timeacc_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_userIndexMapping_set"
  btSoftBody_m_userIndexMapping_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_userIndexMapping_get"
  btSoftBody_m_userIndexMapping_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_windVelocity_set"
  btSoftBody_m_windVelocity_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_windVelocity_get"
  btSoftBody_m_windVelocity_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_worldInfo_set"
  btSoftBody_m_worldInfo_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_m_worldInfo_get"
  btSoftBody_m_worldInfo_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_new"
  btSoftBodyHelpers'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_free"
  btSoftBodyHelpers_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_DrawInfos"
  btSoftBodyHelpers_DrawInfos'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_Draw"
  btSoftBodyHelpers_Draw'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_CreateEllipsoid"
  btSoftBodyHelpers_CreateEllipsoid'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_CreateEllipsoid"
  btSoftBodyHelpers_CreateEllipsoid''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_CreateFromTetGenData"
  btSoftBodyHelpers_CreateFromTetGenData'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_DrawFrame"
  btSoftBodyHelpers_DrawFrame'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_CreateRope"
  btSoftBodyHelpers_CreateRope'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_CreateRope"
  btSoftBodyHelpers_CreateRope''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_CalculateUV"
  btSoftBodyHelpers_CalculateUV'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CFloat))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_DrawFaceTree"
  btSoftBodyHelpers_DrawFaceTree'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_DrawClusterTree"
  btSoftBodyHelpers_DrawClusterTree'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_DrawNodeTree"
  btSoftBodyHelpers_DrawNodeTree'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_CreatePatch"
  btSoftBodyHelpers_CreatePatch'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyHelpers_CreatePatch"
  btSoftBodyHelpers_CreatePatch''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyRigidBodyCollisionConfiguration_new"
  btSoftBodyRigidBodyCollisionConfiguration'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyRigidBodyCollisionConfiguration_free"
  btSoftBodyRigidBodyCollisionConfiguration_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyRigidBodyCollisionConfiguration_getCollisionAlgorithmCreateFunc"
  btSoftBodyRigidBodyCollisionConfiguration_getCollisionAlgorithmCreateFunc'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyRigidBodyCollisionConfiguration_m_softSoftCreateFunc_set"
  btSoftBodyRigidBodyCollisionConfiguration_m_softSoftCreateFunc_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyRigidBodyCollisionConfiguration_m_softSoftCreateFunc_get"
  btSoftBodyRigidBodyCollisionConfiguration_m_softSoftCreateFunc_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConvexCreateFunc_set"
  btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConvexCreateFunc_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConvexCreateFunc_get"
  btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConvexCreateFunc_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConvexCreateFunc_set"
  btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConvexCreateFunc_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConvexCreateFunc_get"
  btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConvexCreateFunc_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConcaveCreateFunc_set"
  btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConcaveCreateFunc_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConcaveCreateFunc_get"
  btSoftBodyRigidBodyCollisionConfiguration_m_softRigidConcaveCreateFunc_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConcaveCreateFunc_set"
  btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConcaveCreateFunc_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConcaveCreateFunc_get"
  btSoftBodyRigidBodyCollisionConfiguration_m_swappedSoftRigidConcaveCreateFunc_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_new"
  btSoftBodyWorldInfo'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_free"
  btSoftBodyWorldInfo_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_air_density_set"
  btSoftBodyWorldInfo_air_density_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_air_density_get"
  btSoftBodyWorldInfo_air_density_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_m_broadphase_set"
  btSoftBodyWorldInfo_m_broadphase_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_m_broadphase_get"
  btSoftBodyWorldInfo_m_broadphase_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_m_dispatcher_set"
  btSoftBodyWorldInfo_m_dispatcher_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_m_dispatcher_get"
  btSoftBodyWorldInfo_m_dispatcher_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_m_gravity_set"
  btSoftBodyWorldInfo_m_gravity_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_m_gravity_get"
  btSoftBodyWorldInfo_m_gravity_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_m_sparsesdf_set"
  btSoftBodyWorldInfo_m_sparsesdf_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_m_sparsesdf_get"
  btSoftBodyWorldInfo_m_sparsesdf_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_water_density_set"
  btSoftBodyWorldInfo_water_density_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_water_density_get"
  btSoftBodyWorldInfo_water_density_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_water_normal_set"
  btSoftBodyWorldInfo_water_normal_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_water_normal_get"
  btSoftBodyWorldInfo_water_normal_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_water_offset_set"
  btSoftBodyWorldInfo_water_offset_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBodyWorldInfo_water_offset_get"
  btSoftBodyWorldInfo_water_offset_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_free"
  btSoftRigidDynamicsWorld_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_predictUnconstraintMotion"
  btSoftRigidDynamicsWorld_predictUnconstraintMotion'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_getWorldInfo0"
  btSoftRigidDynamicsWorld_getWorldInfo'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_getWorldInfo0"
  btSoftRigidDynamicsWorld_getWorldInfo0'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_getWorldInfo1"
  btSoftRigidDynamicsWorld_getWorldInfo1'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_setDrawFlags"
  btSoftRigidDynamicsWorld_setDrawFlags'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_getSoftBodyArray0"
  btSoftRigidDynamicsWorld_getSoftBodyArray'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_getSoftBodyArray0"
  btSoftRigidDynamicsWorld_getSoftBodyArray0'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_getSoftBodyArray1"
  btSoftRigidDynamicsWorld_getSoftBodyArray1'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_serialize"
  btSoftRigidDynamicsWorld_serialize'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_rayTest"
  btSoftRigidDynamicsWorld_rayTest'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_rayTest"
  btSoftRigidDynamicsWorld_rayTest''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_solveSoftBodiesConstraints"
  btSoftRigidDynamicsWorld_solveSoftBodiesConstraints'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_removeCollisionObject"
  btSoftRigidDynamicsWorld_removeCollisionObject'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_addSoftBody"
  btSoftRigidDynamicsWorld_addSoftBody'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CShort -> (C2HSImp.CShort -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_rayTestSingle"
  btSoftRigidDynamicsWorld_rayTestSingle'_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_rayTestSingle"
  btSoftRigidDynamicsWorld_rayTestSingle''_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_internalSingleStepSimulation"
  btSoftRigidDynamicsWorld_internalSingleStepSimulation'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_serializeSoftBodies"
  btSoftRigidDynamicsWorld_serializeSoftBodies'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_removeSoftBody"
  btSoftRigidDynamicsWorld_removeSoftBody'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_getDrawFlags"
  btSoftRigidDynamicsWorld_getDrawFlags'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_debugDrawWorld"
  btSoftRigidDynamicsWorld_debugDrawWorld'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_softBodies_set"
  btSoftRigidDynamicsWorld_m_softBodies_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_softBodies_get"
  btSoftRigidDynamicsWorld_m_softBodies_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_drawFlags_set"
  btSoftRigidDynamicsWorld_m_drawFlags_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_drawFlags_get"
  btSoftRigidDynamicsWorld_m_drawFlags_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_drawNodeTree_set"
  btSoftRigidDynamicsWorld_m_drawNodeTree_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_drawNodeTree_get"
  btSoftRigidDynamicsWorld_m_drawNodeTree_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_drawFaceTree_set"
  btSoftRigidDynamicsWorld_m_drawFaceTree_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_drawFaceTree_get"
  btSoftRigidDynamicsWorld_m_drawFaceTree_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_drawClusterTree_set"
  btSoftRigidDynamicsWorld_m_drawClusterTree_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_drawClusterTree_get"
  btSoftRigidDynamicsWorld_m_drawClusterTree_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_sbi_set"
  btSoftRigidDynamicsWorld_m_sbi_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_sbi_get"
  btSoftRigidDynamicsWorld_m_sbi_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_ownsSolver_set"
  btSoftRigidDynamicsWorld_m_ownsSolver_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftRigidDynamicsWorld_m_ownsSolver_get"
  btSoftRigidDynamicsWorld_m_ownsSolver_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__new"
  btSparseSdf_3_'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__free"
  btSparseSdf_3__free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__Reset"
  btSparseSdf_3__Reset'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__Hash"
  btSparseSdf_3__Hash'_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__RemoveReferences"
  btSparseSdf_3__RemoveReferences'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__Lerp"
  btSparseSdf_3__Lerp'_ :: (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO C2HSImp.CFloat))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__Evaluate"
  btSparseSdf_3__Evaluate'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO C2HSImp.CFloat))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__Evaluate"
  btSparseSdf_3__Evaluate''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO C2HSImp.CFloat))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__GarbageCollect"
  btSparseSdf_3__GarbageCollect'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__DistanceToShape"
  btSparseSdf_3__DistanceToShape'_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat)))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__DistanceToShape"
  btSparseSdf_3__DistanceToShape''_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat)))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__Initialize"
  btSparseSdf_3__Initialize'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__cells_set"
  btSparseSdf_3__cells_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__cells_get"
  btSparseSdf_3__cells_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__ncells_set"
  btSparseSdf_3__ncells_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__ncells_get"
  btSparseSdf_3__ncells_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__nprobes_set"
  btSparseSdf_3__nprobes_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__nprobes_get"
  btSparseSdf_3__nprobes_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__nqueries_set"
  btSparseSdf_3__nqueries_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__nqueries_get"
  btSparseSdf_3__nqueries_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__puid_set"
  btSparseSdf_3__puid_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__puid_get"
  btSparseSdf_3__puid_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__voxelsz_set"
  btSparseSdf_3__voxelsz_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSparseSdf_3__voxelsz_get"
  btSparseSdf_3__voxelsz_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_eAeroModel_new"
  btSoftBody_eAeroModel'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_eAeroModel_free"
  btSoftBody_eAeroModel_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_eFeature_new"
  btSoftBody_eFeature'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_eFeature_free"
  btSoftBody_eFeature_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_ePSolver_new"
  btSoftBody_ePSolver'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_ePSolver_free"
  btSoftBody_ePSolver_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_eSolverPresets_new"
  btSoftBody_eSolverPresets'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_eSolverPresets_free"
  btSoftBody_eSolverPresets_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_eType_new"
  btSoftBody_Joint_eType'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_Joint_eType_free"
  btSoftBody_Joint_eType_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_eVSolver_new"
  btSoftBody_eVSolver'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_eVSolver_free"
  btSoftBody_eVSolver_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_fCollision_new"
  btSoftBody_fCollision'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_fCollision_free"
  btSoftBody_fCollision_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h fDrawFlags_new"
  fDrawFlags'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h fDrawFlags_free"
  fDrawFlags_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_fMaterial_new"
  btSoftBody_fMaterial'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_fMaterial_free"
  btSoftBody_fMaterial_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sCti_new"
  btSoftBody_sCti'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sCti_free"
  btSoftBody_sCti_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sCti_m_colObj_set"
  btSoftBody_sCti_m_colObj_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sCti_m_colObj_get"
  btSoftBody_sCti_m_colObj_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sCti_m_normal_set"
  btSoftBody_sCti_m_normal_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sCti_m_normal_get"
  btSoftBody_sCti_m_normal_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sCti_m_offset_set"
  btSoftBody_sCti_m_offset_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sCti_m_offset_get"
  btSoftBody_sCti_m_offset_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sMedium_new"
  btSoftBody_sMedium'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sMedium_free"
  btSoftBody_sMedium_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sMedium_m_density_set"
  btSoftBody_sMedium_m_density_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sMedium_m_density_get"
  btSoftBody_sMedium_m_density_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sMedium_m_pressure_set"
  btSoftBody_sMedium_m_pressure_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sMedium_m_pressure_get"
  btSoftBody_sMedium_m_pressure_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sMedium_m_velocity_set"
  btSoftBody_sMedium_m_velocity_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sMedium_m_velocity_get"
  btSoftBody_sMedium_m_velocity_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sRayCast_new"
  btSoftBody_sRayCast'_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sRayCast_free"
  btSoftBody_sRayCast_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sRayCast_body_set"
  btSoftBody_sRayCast_body_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sRayCast_body_get"
  btSoftBody_sRayCast_body_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sRayCast_fraction_set"
  btSoftBody_sRayCast_fraction_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sRayCast_fraction_get"
  btSoftBody_sRayCast_fraction_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sRayCast_index_set"
  btSoftBody_sRayCast_index_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletSoftBody.chs.h btSoftBody_sRayCast_index_get"
  btSoftBody_sRayCast_index_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))