-- GENERATED by C->Haskell Compiler, version 0.16.4 Crystal Seed, 24 Jan 2009 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}{-#LANGUAGE ForeignFunctionInterface#-}
module Physics.Bullet.Raw.BulletCollision.Gimpact (
module Physics.Bullet.Raw.BulletCollision.Gimpact
) where
import Control.Monad
import Foreign.Marshal.Alloc
import Foreign.ForeignPtr
import Foreign.Ptr
import Physics.Bullet.Raw.C2HS
import Physics.Bullet.Raw.Types
import Physics.Bullet.Raw.Class
-- * BT_BOX_BOX_TRANSFORM_CACHE
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#187>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE :: IO (BT_BOX_BOX_TRANSFORM_CACHE)
bT_BOX_BOX_TRANSFORM_CACHE =
  bT_BOX_BOX_TRANSFORM_CACHE'_ >>= \res ->
  mkBT_BOX_BOX_TRANSFORM_CACHE res >>= \res' ->
  return (res')
{-# LINE 17 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
bT_BOX_BOX_TRANSFORM_CACHE_free :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> IO ()
bT_BOX_BOX_TRANSFORM_CACHE_free a1 =
  withBt a1 $ \a1' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_free'_ a1' >>= \res ->
  return ()
{-# LINE 18 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#208>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE_calc_from_full_invert :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> Transform -> Transform -> IO (Transform, Transform)
bT_BOX_BOX_TRANSFORM_CACHE_calc_from_full_invert a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_calc_from_full_invert'_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 25 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#208>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE_calc_from_full_invert' :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> IO (Transform, Transform)
bT_BOX_BOX_TRANSFORM_CACHE_calc_from_full_invert' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_calc_from_full_invert''_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 32 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#194>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE_calc_from_homogenic :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> Transform -> Transform -> IO (Transform, Transform)
bT_BOX_BOX_TRANSFORM_CACHE_calc_from_homogenic a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_calc_from_homogenic'_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 39 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#194>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE_calc_from_homogenic' :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> IO (Transform, Transform)
bT_BOX_BOX_TRANSFORM_CACHE_calc_from_homogenic' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_calc_from_homogenic''_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 46 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#219>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE_transform :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> Vec3 -> IO (Vec3, Vec3)
bT_BOX_BOX_TRANSFORM_CACHE_transform a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_transform'_ a1' a2' a3' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 53 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#219>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE_transform' :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> IO (Vec3, Vec3)
bT_BOX_BOX_TRANSFORM_CACHE_transform' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_transform''_ a1' a2' a3' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 60 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#168>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE_calc_absolute_matrix :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> IO ()
bT_BOX_BOX_TRANSFORM_CACHE_calc_absolute_matrix a1 =
  withBt a1 $ \a1' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_calc_absolute_matrix'_ a1' >>= \res ->
  return ()
{-# LINE 65 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#164>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE_m_T1to0_set :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> Vec3 -> IO ()
bT_BOX_BOX_TRANSFORM_CACHE_m_T1to0_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_m_T1to0_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 69 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#164>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE_m_T1to0_get :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> IO (Vec3)
bT_BOX_BOX_TRANSFORM_CACHE_m_T1to0_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_m_T1to0_get'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 73 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#165>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE_m_R1to0_set :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> Mat3 -> IO ()
bT_BOX_BOX_TRANSFORM_CACHE_m_R1to0_set a1 a2 =
  withBt a1 $ \a1' -> 
  withMat3 a2 $ \a2' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_m_R1to0_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 77 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#165>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE_m_R1to0_get :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> IO (Mat3)
bT_BOX_BOX_TRANSFORM_CACHE_m_R1to0_get a1 =
  withBt a1 $ \a1' -> 
  allocaMat3 $ \a2' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_m_R1to0_get'_ a1' a2' >>= \res ->
  peekMat3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 81 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#166>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE_m_AR_set :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> Mat3 -> IO ()
bT_BOX_BOX_TRANSFORM_CACHE_m_AR_set a1 a2 =
  withBt a1 $ \a1' -> 
  withMat3 a2 $ \a2' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_m_AR_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 85 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#166>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
bT_BOX_BOX_TRANSFORM_CACHE_m_AR_get :: ( BT_BOX_BOX_TRANSFORM_CACHEClass bc ) => bc -> IO (Mat3)
bT_BOX_BOX_TRANSFORM_CACHE_m_AR_get a1 =
  withBt a1 $ \a1' -> 
  allocaMat3 $ \a2' -> 
  bT_BOX_BOX_TRANSFORM_CACHE_m_AR_get'_ a1' a2' >>= \res ->
  peekMat3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 89 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * BT_QUANTIZED_BVH_NODE
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#44>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
bT_QUANTIZED_BVH_NODE :: IO (BT_QUANTIZED_BVH_NODE)
bT_QUANTIZED_BVH_NODE =
  bT_QUANTIZED_BVH_NODE'_ >>= \res ->
  mkBT_QUANTIZED_BVH_NODE res >>= \res' ->
  return (res')
{-# LINE 94 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
bT_QUANTIZED_BVH_NODE_free :: ( BT_QUANTIZED_BVH_NODEClass bc ) => bc -> IO ()
bT_QUANTIZED_BVH_NODE_free a1 =
  withBt a1 $ \a1' -> 
  bT_QUANTIZED_BVH_NODE_free'_ a1' >>= \res ->
  return ()
{-# LINE 95 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#55>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
bT_QUANTIZED_BVH_NODE_getEscapeIndex :: ( BT_QUANTIZED_BVH_NODEClass bc ) => bc -> IO (Int)
bT_QUANTIZED_BVH_NODE_getEscapeIndex a1 =
  withBt a1 $ \a1' -> 
  bT_QUANTIZED_BVH_NODE_getEscapeIndex'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 100 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
bT_QUANTIZED_BVH_NODE_getDataIndex :: ( BT_QUANTIZED_BVH_NODEClass bc ) => bc -> IO (Int)
bT_QUANTIZED_BVH_NODE_getDataIndex a1 =
  withBt a1 $ \a1' -> 
  bT_QUANTIZED_BVH_NODE_getDataIndex'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 105 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
bT_QUANTIZED_BVH_NODE_setEscapeIndex :: ( BT_QUANTIZED_BVH_NODEClass bc ) => bc -> Int -> IO ()
bT_QUANTIZED_BVH_NODE_setEscapeIndex a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  bT_QUANTIZED_BVH_NODE_setEscapeIndex'_ a1' a2' >>= \res ->
  return ()
{-# LINE 111 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#73>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
bT_QUANTIZED_BVH_NODE_setDataIndex :: ( BT_QUANTIZED_BVH_NODEClass bc ) => bc -> Int -> IO ()
bT_QUANTIZED_BVH_NODE_setDataIndex a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  bT_QUANTIZED_BVH_NODE_setDataIndex'_ a1' a2' >>= \res ->
  return ()
{-# LINE 117 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#49>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
bT_QUANTIZED_BVH_NODE_isLeafNode :: ( BT_QUANTIZED_BVH_NODEClass bc ) => bc -> IO (Bool)
bT_QUANTIZED_BVH_NODE_isLeafNode a1 =
  withBt a1 $ \a1' -> 
  bT_QUANTIZED_BVH_NODE_isLeafNode'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 122 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
bT_QUANTIZED_BVH_NODE_m_escapeIndexOrDataIndex_set :: ( BT_QUANTIZED_BVH_NODEClass bc ) => bc -> Int -> IO ()
bT_QUANTIZED_BVH_NODE_m_escapeIndexOrDataIndex_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  bT_QUANTIZED_BVH_NODE_m_escapeIndexOrDataIndex_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 126 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
bT_QUANTIZED_BVH_NODE_m_escapeIndexOrDataIndex_get :: ( BT_QUANTIZED_BVH_NODEClass bc ) => bc -> IO (Int)
bT_QUANTIZED_BVH_NODE_m_escapeIndexOrDataIndex_get a1 =
  withBt a1 $ \a1' -> 
  bT_QUANTIZED_BVH_NODE_m_escapeIndexOrDataIndex_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 130 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * CompoundPrimitiveManager
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#317>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_CompoundPrimitiveManager0 :: ( BtGImpactCompoundShapeClass p0 ) => p0 -> IO (BtGImpactCompoundShape_CompoundPrimitiveManager)
btGImpactCompoundShape_CompoundPrimitiveManager0 a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_CompoundPrimitiveManager0'_ a1' >>= \res ->
  mkBtGImpactCompoundShape_CompoundPrimitiveManager res >>= \res' ->
  return (res')
{-# LINE 135 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#322>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_CompoundPrimitiveManager1 :: IO (BtGImpactCompoundShape_CompoundPrimitiveManager)
btGImpactCompoundShape_CompoundPrimitiveManager1 =
  btGImpactCompoundShape_CompoundPrimitiveManager1'_ >>= \res ->
  mkBtGImpactCompoundShape_CompoundPrimitiveManager res >>= \res' ->
  return (res')
{-# LINE 139 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btGImpactCompoundShape_CompoundPrimitiveManager_free :: ( BtGImpactCompoundShape_CompoundPrimitiveManagerClass bc ) => bc -> IO ()
btGImpactCompoundShape_CompoundPrimitiveManager_free a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_CompoundPrimitiveManager_free'_ a1' >>= \res ->
  return ()
{-# LINE 140 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#332>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_count :: ( BtGImpactCompoundShape_CompoundPrimitiveManagerClass bc ) => bc -> IO (Int)
btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_count a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_count'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 145 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#352>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_triangle :: ( BtGImpactCompoundShape_CompoundPrimitiveManagerClass bc , BtPrimitiveTriangleClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_triangle a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_triangle'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 152 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#337>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_box :: ( BtGImpactCompoundShape_CompoundPrimitiveManagerClass bc , BtAABBClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_box a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_box'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 159 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#327>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_CompoundPrimitiveManager_is_trimesh :: ( BtGImpactCompoundShape_CompoundPrimitiveManagerClass bc ) => bc -> IO (Bool)
btGImpactCompoundShape_CompoundPrimitiveManager_is_trimesh a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_CompoundPrimitiveManager_is_trimesh'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 164 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#308>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_CompoundPrimitiveManager_m_compoundShape_set :: ( BtGImpactCompoundShape_CompoundPrimitiveManagerClass bc , BtGImpactCompoundShapeClass a ) => bc -> a -> IO ()
btGImpactCompoundShape_CompoundPrimitiveManager_m_compoundShape_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactCompoundShape_CompoundPrimitiveManager_m_compoundShape_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 168 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#308>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_CompoundPrimitiveManager_m_compoundShape_get :: ( BtGImpactCompoundShape_CompoundPrimitiveManagerClass bc ) => bc -> IO (BtGImpactCompoundShape)
btGImpactCompoundShape_CompoundPrimitiveManager_m_compoundShape_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_CompoundPrimitiveManager_m_compoundShape_get'_ a1' >>= \res ->
  mkBtGImpactCompoundShape res >>= \res' ->
  return (res')
{-# LINE 172 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * CreateFunc
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#215>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_CreateFunc :: IO (BtGImpactCollisionAlgorithm_CreateFunc)
btGImpactCollisionAlgorithm_CreateFunc =
  btGImpactCollisionAlgorithm_CreateFunc'_ >>= \res ->
  mkBtGImpactCollisionAlgorithm_CreateFunc res >>= \res' ->
  return (res')
{-# LINE 177 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btGImpactCollisionAlgorithm_CreateFunc_free :: ( BtGImpactCollisionAlgorithm_CreateFuncClass bc ) => bc -> IO ()
btGImpactCollisionAlgorithm_CreateFunc_free a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_CreateFunc_free'_ a1' >>= \res ->
  return ()
{-# LINE 178 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#216>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_CreateFunc_CreateCollisionAlgorithm :: ( BtGImpactCollisionAlgorithm_CreateFuncClass bc , BtCollisionAlgorithmConstructionInfoClass p0 , BtCollisionObjectClass p1 , BtCollisionObjectClass p2 ) => bc -> p0 -> p1 -> p2 -> IO (BtCollisionAlgorithm)
btGImpactCollisionAlgorithm_CreateFunc_CreateCollisionAlgorithm a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btGImpactCollisionAlgorithm_CreateFunc_CreateCollisionAlgorithm'_ a1' a2' a3' a4' >>= \res ->
  mkBtCollisionAlgorithm res >>= \res' ->
  return (res')
{-# LINE 186 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * GIM_BVH_DATA
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_DATA :: IO (GIM_BVH_DATA)
gIM_BVH_DATA =
  gIM_BVH_DATA'_ >>= \res ->
  mkGIM_BVH_DATA res >>= \res' ->
  return (res')
{-# LINE 191 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
gIM_BVH_DATA_free :: ( GIM_BVH_DATAClass bc ) => bc -> IO ()
gIM_BVH_DATA_free a1 =
  withBt a1 $ \a1' -> 
  gIM_BVH_DATA_free'_ a1' >>= \res ->
  return ()
{-# LINE 192 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_DATA_m_bound_set :: ( GIM_BVH_DATAClass bc , BtAABBClass a ) => bc -> a -> IO ()
gIM_BVH_DATA_m_bound_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  gIM_BVH_DATA_m_bound_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 196 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_DATA_m_bound_get :: ( GIM_BVH_DATAClass bc ) => bc -> IO (BtAABB)
gIM_BVH_DATA_m_bound_get a1 =
  withBt a1 $ \a1' -> 
  gIM_BVH_DATA_m_bound_get'_ a1' >>= \res ->
  mkBtAABB res >>= \res' ->
  return (res')
{-# LINE 200 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_DATA_m_data_set :: ( GIM_BVH_DATAClass bc ) => bc -> Int -> IO ()
gIM_BVH_DATA_m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  gIM_BVH_DATA_m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 204 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_DATA_m_data_get :: ( GIM_BVH_DATAClass bc ) => bc -> IO (Int)
gIM_BVH_DATA_m_data_get a1 =
  withBt a1 $ \a1' -> 
  gIM_BVH_DATA_m_data_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 208 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * GIM_BVH_DATA_ARRAY
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#131>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_DATA_ARRAY :: IO (GIM_BVH_DATA_ARRAY)
gIM_BVH_DATA_ARRAY =
  gIM_BVH_DATA_ARRAY'_ >>= \res ->
  mkGIM_BVH_DATA_ARRAY res >>= \res' ->
  return (res')
{-# LINE 213 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
gIM_BVH_DATA_ARRAY_free :: ( GIM_BVH_DATA_ARRAYClass bc ) => bc -> IO ()
gIM_BVH_DATA_ARRAY_free a1 =
  withBt a1 $ \a1' -> 
  gIM_BVH_DATA_ARRAY_free'_ a1' >>= \res ->
  return ()
{-# LINE 214 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * GIM_BVH_TREE_NODE
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#93>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_TREE_NODE :: IO (GIM_BVH_TREE_NODE)
gIM_BVH_TREE_NODE =
  gIM_BVH_TREE_NODE'_ >>= \res ->
  mkGIM_BVH_TREE_NODE res >>= \res' ->
  return (res')
{-# LINE 219 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
gIM_BVH_TREE_NODE_free :: ( GIM_BVH_TREE_NODEClass bc ) => bc -> IO ()
gIM_BVH_TREE_NODE_free a1 =
  withBt a1 $ \a1' -> 
  gIM_BVH_TREE_NODE_free'_ a1' >>= \res ->
  return ()
{-# LINE 220 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#122>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_TREE_NODE_setDataIndex :: ( GIM_BVH_TREE_NODEClass bc ) => bc -> Int -> IO ()
gIM_BVH_TREE_NODE_setDataIndex a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  gIM_BVH_TREE_NODE_setDataIndex'_ a1' a2' >>= \res ->
  return ()
{-# LINE 226 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#104>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_TREE_NODE_getEscapeIndex :: ( GIM_BVH_TREE_NODEClass bc ) => bc -> IO (Int)
gIM_BVH_TREE_NODE_getEscapeIndex a1 =
  withBt a1 $ \a1' -> 
  gIM_BVH_TREE_NODE_getEscapeIndex'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 231 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#115>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_TREE_NODE_getDataIndex :: ( GIM_BVH_TREE_NODEClass bc ) => bc -> IO (Int)
gIM_BVH_TREE_NODE_getDataIndex a1 =
  withBt a1 $ \a1' -> 
  gIM_BVH_TREE_NODE_getDataIndex'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 236 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#110>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_TREE_NODE_setEscapeIndex :: ( GIM_BVH_TREE_NODEClass bc ) => bc -> Int -> IO ()
gIM_BVH_TREE_NODE_setEscapeIndex a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  gIM_BVH_TREE_NODE_setEscapeIndex'_ a1' a2' >>= \res ->
  return ()
{-# LINE 242 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#98>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_TREE_NODE_isLeafNode :: ( GIM_BVH_TREE_NODEClass bc ) => bc -> IO (Bool)
gIM_BVH_TREE_NODE_isLeafNode a1 =
  withBt a1 $ \a1' -> 
  gIM_BVH_TREE_NODE_isLeafNode'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 247 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_TREE_NODE_m_bound_set :: ( GIM_BVH_TREE_NODEClass bc , BtAABBClass a ) => bc -> a -> IO ()
gIM_BVH_TREE_NODE_m_bound_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  gIM_BVH_TREE_NODE_m_bound_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 251 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_TREE_NODE_m_bound_get :: ( GIM_BVH_TREE_NODEClass bc ) => bc -> IO (BtAABB)
gIM_BVH_TREE_NODE_m_bound_get a1 =
  withBt a1 $ \a1' -> 
  gIM_BVH_TREE_NODE_m_bound_get'_ a1' >>= \res ->
  mkBtAABB res >>= \res' ->
  return (res')
{-# LINE 255 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#91>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_TREE_NODE_m_escapeIndexOrDataIndex_set :: ( GIM_BVH_TREE_NODEClass bc ) => bc -> Int -> IO ()
gIM_BVH_TREE_NODE_m_escapeIndexOrDataIndex_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  gIM_BVH_TREE_NODE_m_escapeIndexOrDataIndex_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 259 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#91>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_TREE_NODE_m_escapeIndexOrDataIndex_get :: ( GIM_BVH_TREE_NODEClass bc ) => bc -> IO (Int)
gIM_BVH_TREE_NODE_m_escapeIndexOrDataIndex_get a1 =
  withBt a1 $ \a1' -> 
  gIM_BVH_TREE_NODE_m_escapeIndexOrDataIndex_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 263 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * GIM_BVH_TREE_NODE_ARRAY
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_BVH_TREE_NODE_ARRAY :: IO (GIM_BVH_TREE_NODE_ARRAY)
gIM_BVH_TREE_NODE_ARRAY =
  gIM_BVH_TREE_NODE_ARRAY'_ >>= \res ->
  mkGIM_BVH_TREE_NODE_ARRAY res >>= \res' ->
  return (res')
{-# LINE 268 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
gIM_BVH_TREE_NODE_ARRAY_free :: ( GIM_BVH_TREE_NODE_ARRAYClass bc ) => bc -> IO ()
gIM_BVH_TREE_NODE_ARRAY_free a1 =
  withBt a1 $ \a1' -> 
  gIM_BVH_TREE_NODE_ARRAY_free'_ a1' >>= \res ->
  return ()
{-# LINE 269 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * GIM_PAIR
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_PAIR0 :: IO (GIM_PAIR)
gIM_PAIR0 =
  gIM_PAIR0'_ >>= \res ->
  mkGIM_PAIR res >>= \res' ->
  return (res')
{-# LINE 274 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_PAIR1 :: Int -> Int -> IO (GIM_PAIR)
gIM_PAIR1 a1 a2 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  gIM_PAIR1'_ a1' a2' >>= \res ->
  mkGIM_PAIR res >>= \res' ->
  return (res')
{-# LINE 278 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
gIM_PAIR_free :: ( GIM_PAIRClass bc ) => bc -> IO ()
gIM_PAIR_free a1 =
  withBt a1 $ \a1' -> 
  gIM_PAIR_free'_ a1' >>= \res ->
  return ()
{-# LINE 279 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#40>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_PAIR_m_index1_set :: ( GIM_PAIRClass bc ) => bc -> Int -> IO ()
gIM_PAIR_m_index1_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  gIM_PAIR_m_index1_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 283 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#40>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_PAIR_m_index1_get :: ( GIM_PAIRClass bc ) => bc -> IO (Int)
gIM_PAIR_m_index1_get a1 =
  withBt a1 $ \a1' -> 
  gIM_PAIR_m_index1_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 287 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#41>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_PAIR_m_index2_set :: ( GIM_PAIRClass bc ) => bc -> Int -> IO ()
gIM_PAIR_m_index2_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  gIM_PAIR_m_index2_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 291 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#41>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
gIM_PAIR_m_index2_get :: ( GIM_PAIRClass bc ) => bc -> IO (Int)
gIM_PAIR_m_index2_get a1 =
  withBt a1 $ \a1' -> 
  gIM_PAIR_m_index2_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 295 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * GIM_QUANTIZED_BVH_NODE_ARRAY
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#98>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
gIM_QUANTIZED_BVH_NODE_ARRAY :: IO (GIM_QUANTIZED_BVH_NODE_ARRAY)
gIM_QUANTIZED_BVH_NODE_ARRAY =
  gIM_QUANTIZED_BVH_NODE_ARRAY'_ >>= \res ->
  mkGIM_QUANTIZED_BVH_NODE_ARRAY res >>= \res' ->
  return (res')
{-# LINE 300 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
gIM_QUANTIZED_BVH_NODE_ARRAY_free :: ( GIM_QUANTIZED_BVH_NODE_ARRAYClass bc ) => bc -> IO ()
gIM_QUANTIZED_BVH_NODE_ARRAY_free a1 =
  withBt a1 $ \a1' -> 
  gIM_QUANTIZED_BVH_NODE_ARRAY_free'_ a1' >>= \res ->
  return ()
{-# LINE 301 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * GIM_TRIANGLE_CONTACT
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
gIM_TRIANGLE_CONTACT :: IO (GIM_TRIANGLE_CONTACT)
gIM_TRIANGLE_CONTACT =
  gIM_TRIANGLE_CONTACT'_ >>= \res ->
  mkGIM_TRIANGLE_CONTACT res >>= \res' ->
  return (res')
{-# LINE 306 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
gIM_TRIANGLE_CONTACT_free :: ( GIM_TRIANGLE_CONTACTClass bc ) => bc -> IO ()
gIM_TRIANGLE_CONTACT_free a1 =
  withBt a1 $ \a1' -> 
  gIM_TRIANGLE_CONTACT_free'_ a1' >>= \res ->
  return ()
{-# LINE 307 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#45>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
gIM_TRIANGLE_CONTACT_copy_from :: ( GIM_TRIANGLE_CONTACTClass bc , GIM_TRIANGLE_CONTACTClass p0 ) => bc -> p0 -> IO ()
gIM_TRIANGLE_CONTACT_copy_from a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  gIM_TRIANGLE_CONTACT_copy_from'_ a1' a2' >>= \res ->
  return ()
{-# LINE 313 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#40>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
gIM_TRIANGLE_CONTACT_m_penetration_depth_set :: ( GIM_TRIANGLE_CONTACTClass bc ) => bc -> Float -> IO ()
gIM_TRIANGLE_CONTACT_m_penetration_depth_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  gIM_TRIANGLE_CONTACT_m_penetration_depth_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 317 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#40>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
gIM_TRIANGLE_CONTACT_m_penetration_depth_get :: ( GIM_TRIANGLE_CONTACTClass bc ) => bc -> IO (Float)
gIM_TRIANGLE_CONTACT_m_penetration_depth_get a1 =
  withBt a1 $ \a1' -> 
  gIM_TRIANGLE_CONTACT_m_penetration_depth_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 321 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#41>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
gIM_TRIANGLE_CONTACT_m_point_count_set :: ( GIM_TRIANGLE_CONTACTClass bc ) => bc -> Int -> IO ()
gIM_TRIANGLE_CONTACT_m_point_count_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  gIM_TRIANGLE_CONTACT_m_point_count_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 325 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#41>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
gIM_TRIANGLE_CONTACT_m_point_count_get :: ( GIM_TRIANGLE_CONTACTClass bc ) => bc -> IO (Int)
gIM_TRIANGLE_CONTACT_m_point_count_get a1 =
  withBt a1 $ \a1' -> 
  gIM_TRIANGLE_CONTACT_m_point_count_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 329 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
gIM_TRIANGLE_CONTACT_m_separating_normal_set :: ( GIM_TRIANGLE_CONTACTClass bc ) => bc -> Vec4 -> IO ()
gIM_TRIANGLE_CONTACT_m_separating_normal_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec4 a2 $ \a2' -> 
  gIM_TRIANGLE_CONTACT_m_separating_normal_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 333 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#42>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
gIM_TRIANGLE_CONTACT_m_separating_normal_get :: ( GIM_TRIANGLE_CONTACTClass bc ) => bc -> IO (Vec4)
gIM_TRIANGLE_CONTACT_m_separating_normal_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec4 $ \a2' -> 
  gIM_TRIANGLE_CONTACT_m_separating_normal_get'_ a1' a2' >>= \res ->
  peekVec4  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 337 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * TrimeshPrimitiveManager
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#545>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager0 :: IO (BtGImpactMeshShapePart_TrimeshPrimitiveManager)
btGImpactMeshShapePart_TrimeshPrimitiveManager0 =
  btGImpactMeshShapePart_TrimeshPrimitiveManager0'_ >>= \res ->
  mkBtGImpactMeshShapePart_TrimeshPrimitiveManager res >>= \res' ->
  return (res')
{-# LINE 342 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#578>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager1 :: ( BtStridingMeshInterfaceClass p0 ) => p0 -> Int -> IO (BtGImpactMeshShapePart_TrimeshPrimitiveManager)
btGImpactMeshShapePart_TrimeshPrimitiveManager1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShapePart_TrimeshPrimitiveManager1'_ a1' a2' >>= \res ->
  mkBtGImpactMeshShapePart_TrimeshPrimitiveManager res >>= \res' ->
  return (res')
{-# LINE 346 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_free :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_free a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_free'_ a1' >>= \res ->
  return ()
{-# LINE 347 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#633>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex_count :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO (Int)
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex_count a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex_count'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 352 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#656>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> Int -> Vec3 -> IO (Vec3)
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withVec3 a3 $ \a3' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex'_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 359 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#656>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex' :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> Int -> IO (Vec3)
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaVec3 $ \a3' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex''_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 366 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#623>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_is_trimesh :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO (Bool)
btGImpactMeshShapePart_TrimeshPrimitiveManager_is_trimesh a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_is_trimesh'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 371 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#596>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_lock :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_lock a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_lock'_ a1' >>= \res ->
  return ()
{-# LINE 376 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#674>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_box :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc , BtAABBClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_box a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_box'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 383 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#683>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_triangle :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc , BtPrimitiveTriangleClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_triangle a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_triangle'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 390 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#610>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_unlock :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_unlock a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_unlock'_ a1' >>= \res ->
  return ()
{-# LINE 395 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#693>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_bullet_triangle :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc , BtTriangleShapeExClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_bullet_triangle a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_bullet_triangle'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 402 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#628>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_count :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO (Int)
btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_count a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_count'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 407 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#531>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_margin_set :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> Float -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_margin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_margin_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 411 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#531>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_margin_get :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO (Float)
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_margin_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_margin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 415 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#532>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_meshInterface_set :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc , BtStridingMeshInterfaceClass a ) => bc -> a -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_meshInterface_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_meshInterface_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 419 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#532>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_meshInterface_get :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO (BtStridingMeshInterface)
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_meshInterface_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_meshInterface_get'_ a1' >>= \res ->
  mkBtStridingMeshInterface res >>= \res' ->
  return (res')
{-# LINE 423 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#533>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_scale_set :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> Vec3 -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_scale_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_scale_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 427 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#533>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_scale_get :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO (Vec3)
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_scale_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_scale_get'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 431 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#534>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_part_set :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> Int -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_part_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_part_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 435 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#534>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_part_get :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO (Int)
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_part_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_part_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 439 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#535>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_lock_count_set :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> Int -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_lock_count_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_lock_count_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 443 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#535>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_lock_count_get :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO (Int)
btGImpactMeshShapePart_TrimeshPrimitiveManager_m_lock_count_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_lock_count_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 447 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#537>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_numverts_set :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> Int -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_numverts_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_numverts_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 451 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#537>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_numverts_get :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO (Int)
btGImpactMeshShapePart_TrimeshPrimitiveManager_numverts_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_numverts_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 455 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#539>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_stride_set :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> Int -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_stride_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_stride_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 459 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#539>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_stride_get :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO (Int)
btGImpactMeshShapePart_TrimeshPrimitiveManager_stride_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_stride_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 463 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#541>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_indexstride_set :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> Int -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_indexstride_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_indexstride_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 467 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#541>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_indexstride_get :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO (Int)
btGImpactMeshShapePart_TrimeshPrimitiveManager_indexstride_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_indexstride_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 471 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#542>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_numfaces_set :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> Int -> IO ()
btGImpactMeshShapePart_TrimeshPrimitiveManager_numfaces_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_numfaces_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 475 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#542>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_TrimeshPrimitiveManager_numfaces_get :: ( BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass bc ) => bc -> IO (Int)
btGImpactMeshShapePart_TrimeshPrimitiveManager_numfaces_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_TrimeshPrimitiveManager_numfaces_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 479 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btAABB
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#237>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB0 :: IO (BtAABB)
btAABB0 =
  btAABB0'_ >>= \res ->
  mkBtAABB res >>= \res' ->
  return (res')
{-# LINE 484 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#243>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB1 :: Vec3 -> Vec3 -> Vec3 -> IO (BtAABB)
btAABB1 a1 a2 a3 =
  withVec3 a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btAABB1'_ a1' a2' a3' >>= \res ->
  mkBtAABB res >>= \res' ->
  return (res')
{-# LINE 488 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#257>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB2 :: Vec3 -> Vec3 -> Vec3 -> Float -> IO (BtAABB)
btAABB2 a1 a2 a3 a4 =
  withVec3 a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  btAABB2'_ a1' a2' a3' a4' >>= \res ->
  mkBtAABB res >>= \res' ->
  return (res')
{-# LINE 492 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#280>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB3 :: ( BtAABBClass p0 ) => p0 -> Float -> IO (BtAABB)
btAABB3 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btAABB3'_ a1' a2' >>= \res ->
  mkBtAABB res >>= \res' ->
  return (res')
{-# LINE 496 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btAABB_free :: ( BtAABBClass bc ) => bc -> IO ()
btAABB_free a1 =
  withBt a1 $ \a1' -> 
  btAABB_free'_ a1' >>= \res ->
  return ()
{-# LINE 497 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#507>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_overlapping_trans_conservative :: ( BtAABBClass bc , BtAABBClass p0 ) => bc -> p0 -> Transform -> IO (Bool, Transform)
btAABB_overlapping_trans_conservative a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  btAABB_overlapping_trans_conservative'_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  let {res' = toBool res} in
  return (res', a3'')
{-# LINE 504 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#507>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_overlapping_trans_conservative' :: ( BtAABBClass bc , BtAABBClass p0 ) => bc -> p0 -> IO (Bool, Transform)
btAABB_overlapping_trans_conservative' a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaTransform $ \a3' -> 
  btAABB_overlapping_trans_conservative''_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  let {res' = toBool res} in
  return (res', a3'')
{-# LINE 511 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#360>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_appy_transform :: ( BtAABBClass bc ) => bc -> Transform -> IO (Transform)
btAABB_appy_transform a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btAABB_appy_transform'_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 517 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#360>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_appy_transform' :: ( BtAABBClass bc ) => bc -> IO (Transform)
btAABB_appy_transform' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btAABB_appy_transform''_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 523 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#425>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_find_intersection :: ( BtAABBClass bc , BtAABBClass p0 , BtAABBClass p1 ) => bc -> p0 -> p1 -> IO ()
btAABB_find_intersection a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAABB_find_intersection'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 530 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#456>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_collide_ray :: ( BtAABBClass bc ) => bc -> Vec3 -> Vec3 -> IO (Bool, Vec3, Vec3)
btAABB_collide_ray a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btAABB_collide_ray'_ a1' a2' a3' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  let {res' = toBool res} in
  return (res', a2'', a3'')
{-# LINE 537 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#456>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_collide_ray' :: ( BtAABBClass bc ) => bc -> IO (Bool, Vec3, Vec3)
btAABB_collide_ray' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btAABB_collide_ray''_ a1' a2' a3' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  let {res' = toBool res} in
  return (res', a2'', a3'')
{-# LINE 544 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#524>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_overlapping_trans_cache :: ( BtAABBClass bc , BtAABBClass p0 , BT_BOX_BOX_TRANSFORM_CACHEClass p1 ) => bc -> p0 -> p1 -> Bool -> IO (Bool)
btAABB_overlapping_trans_cache a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  let {a4' = fromBool a4} in 
  btAABB_overlapping_trans_cache'_ a1' a2' a3' a4' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 552 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#418>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_get_center_extend :: ( BtAABBClass bc ) => bc -> Vec3 -> Vec3 -> IO (Vec3, Vec3)
btAABB_get_center_extend a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btAABB_get_center_extend'_ a1' a2' a3' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 559 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#418>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_get_center_extend' :: ( BtAABBClass bc ) => bc -> IO (Vec3, Vec3)
btAABB_get_center_extend' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btAABB_get_center_extend''_ a1' a2' a3' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 566 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#291>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_invalidate :: ( BtAABBClass bc ) => bc -> IO ()
btAABB_invalidate a1 =
  withBt a1 $ \a1' -> 
  btAABB_invalidate'_ a1' >>= \res ->
  return ()
{-# LINE 571 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#437>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_has_collision :: ( BtAABBClass bc , BtAABBClass p0 ) => bc -> p0 -> IO (Bool)
btAABB_has_collision a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAABB_has_collision'_ a1' a2' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 577 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#377>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_appy_transform_trans_cache :: ( BtAABBClass bc , BT_BOX_BOX_TRANSFORM_CACHEClass p0 ) => bc -> p0 -> IO ()
btAABB_appy_transform_trans_cache a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAABB_appy_transform_trans_cache'_ a1' a2' >>= \res ->
  return ()
{-# LINE 583 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#341>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_calc_from_triangle_margin :: ( BtAABBClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> Float -> IO (Vec3, Vec3, Vec3)
btAABB_calc_from_triangle_margin a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  let {a5' = realToFrac a5} in 
  btAABB_calc_from_triangle_margin'_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 592 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#341>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_calc_from_triangle_margin' :: ( BtAABBClass bc ) => bc -> Float -> IO (Vec3, Vec3, Vec3)
btAABB_calc_from_triangle_margin' a1 a5 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  let {a5' = realToFrac a5} in 
  btAABB_calc_from_triangle_margin''_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 601 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#301>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_increment_margin :: ( BtAABBClass bc ) => bc -> Float -> IO ()
btAABB_increment_margin a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btAABB_increment_margin'_ a1' a2' >>= \res ->
  return ()
{-# LINE 607 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#393>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_merge :: ( BtAABBClass bc , BtAABBClass p0 ) => bc -> p0 -> IO ()
btAABB_merge a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAABB_merge'_ a1' a2' >>= \res ->
  return ()
{-# LINE 613 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#578>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_collide_plane :: ( BtAABBClass bc ) => bc -> Vec4 -> IO (Bool, Vec4)
btAABB_collide_plane a1 a2 =
  withBt a1 $ \a1' -> 
  withVec4 a2 $ \a2' -> 
  btAABB_collide_plane'_ a1' a2' >>= \res ->
  peekVec4  a2'>>= \a2'' -> 
  let {res' = toBool res} in
  return (res', a2'')
{-# LINE 619 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#578>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_collide_plane' :: ( BtAABBClass bc ) => bc -> IO (Bool, Vec4)
btAABB_collide_plane' a1 =
  withBt a1 $ \a1' -> 
  allocaVec4 $ \a2' -> 
  btAABB_collide_plane''_ a1' a2' >>= \res ->
  peekVec4  a2'>>= \a2'' -> 
  let {res' = toBool res} in
  return (res', a2'')
{-# LINE 625 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#515>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_overlapping_trans_conservative2 :: ( BtAABBClass bc , BtAABBClass p0 , BT_BOX_BOX_TRANSFORM_CACHEClass p1 ) => bc -> p0 -> p1 -> IO (Bool)
btAABB_overlapping_trans_conservative2 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAABB_overlapping_trans_conservative2'_ a1' a2' a3' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 632 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#311>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_copy_with_margin :: ( BtAABBClass bc , BtAABBClass p0 ) => bc -> p0 -> Float -> IO ()
btAABB_copy_with_margin a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btAABB_copy_with_margin'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 639 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#589>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_collide_triangle_exact :: ( BtAABBClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> Vec4 -> IO (Bool, Vec3, Vec3, Vec3, Vec4)
btAABB_collide_triangle_exact a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec4 a5 $ \a5' -> 
  btAABB_collide_triangle_exact'_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec4  a5'>>= \a5'' -> 
  let {res' = toBool res} in
  return (res', a2'', a3'', a4'', a5'')
{-# LINE 648 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#589>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_collide_triangle_exact' :: ( BtAABBClass bc ) => bc -> IO (Bool, Vec3, Vec3, Vec3, Vec4)
btAABB_collide_triangle_exact' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec4 $ \a5' -> 
  btAABB_collide_triangle_exact''_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec4  a5'>>= \a5'' -> 
  let {res' = toBool res} in
  return (res', a2'', a3'', a4'', a5'')
{-# LINE 657 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#235>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_m_max_set :: ( BtAABBClass bc ) => bc -> Vec3 -> IO ()
btAABB_m_max_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btAABB_m_max_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 661 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#235>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_m_max_get :: ( BtAABBClass bc ) => bc -> IO (Vec3)
btAABB_m_max_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btAABB_m_max_get'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 665 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#234>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_m_min_set :: ( BtAABBClass bc ) => bc -> Vec3 -> IO ()
btAABB_m_min_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btAABB_m_min_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 669 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.h?r=2223#234>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btBoxCollision.cpp?r=2223>
-}
btAABB_m_min_get :: ( BtAABBClass bc ) => bc -> IO (Vec3)
btAABB_m_min_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btAABB_m_min_get'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 673 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btBvhTree
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#157>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree :: IO (BtBvhTree)
btBvhTree =
  btBvhTree'_ >>= \res ->
  mkBtBvhTree res >>= \res' ->
  return (res')
{-# LINE 678 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btBvhTree_free :: ( BtBvhTreeClass bc ) => bc -> IO ()
btBvhTree_free a1 =
  withBt a1 $ \a1' -> 
  btBvhTree_free'_ a1' >>= \res ->
  return ()
{-# LINE 679 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#173>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_getNodeCount :: ( BtBvhTreeClass bc ) => bc -> IO (Int)
btBvhTree_getNodeCount a1 =
  withBt a1 $ \a1' -> 
  btBvhTree_getNodeCount'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 684 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#164>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_build_tree :: ( BtBvhTreeClass bc , GIM_BVH_DATA_ARRAYClass p0 ) => bc -> p0 -> IO ()
btBvhTree_build_tree a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btBvhTree_build_tree'_ a1' a2' >>= \res ->
  return ()
{-# LINE 690 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#194>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_setNodeBound :: ( BtBvhTreeClass bc , BtAABBClass p1 ) => bc -> Int -> p1 -> IO ()
btBvhTree_setNodeBound a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btBvhTree_setNodeBound'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 697 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#199>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_getLeftNode :: ( BtBvhTreeClass bc ) => bc -> Int -> IO (Int)
btBvhTree_getLeftNode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btBvhTree_getLeftNode'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 703 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#155>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree__build_sub_tree :: ( BtBvhTreeClass bc , GIM_BVH_DATA_ARRAYClass p0 ) => bc -> p0 -> Int -> Int -> IO ()
btBvhTree__build_sub_tree a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btBvhTree__build_sub_tree'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 711 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#166>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_clearNodes :: ( BtBvhTreeClass bc ) => bc -> IO ()
btBvhTree_clearNodes a1 =
  withBt a1 $ \a1' -> 
  btBvhTree_clearNodes'_ a1' >>= \res ->
  return ()
{-# LINE 716 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#151>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree__sort_and_calc_splitting_index :: ( BtBvhTreeClass bc , GIM_BVH_DATA_ARRAYClass p0 ) => bc -> p0 -> Int -> Int -> Int -> IO (Int)
btBvhTree__sort_and_calc_splitting_index a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  btBvhTree__sort_and_calc_splitting_index'_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 725 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#210>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_getEscapeNodeIndex :: ( BtBvhTreeClass bc ) => bc -> Int -> IO (Int)
btBvhTree_getEscapeNodeIndex a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btBvhTree_getEscapeNodeIndex'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 731 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#179>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_isLeafNode :: ( BtBvhTreeClass bc ) => bc -> Int -> IO (Bool)
btBvhTree_isLeafNode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btBvhTree_isLeafNode'_ a1' a2' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 737 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#215>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_get_node_pointer :: ( BtBvhTreeClass bc ) => bc -> Int -> IO (GIM_BVH_TREE_NODE)
btBvhTree_get_node_pointer a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btBvhTree_get_node_pointer'_ a1' a2' >>= \res ->
  mkGIM_BVH_TREE_NODE res >>= \res' ->
  return (res')
{-# LINE 743 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#184>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_getNodeData :: ( BtBvhTreeClass bc ) => bc -> Int -> IO (Int)
btBvhTree_getNodeData a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btBvhTree_getNodeData'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 749 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_getNodeBound :: ( BtBvhTreeClass bc , BtAABBClass p1 ) => bc -> Int -> p1 -> IO ()
btBvhTree_getNodeBound a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btBvhTree_getNodeBound'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 756 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#204>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_getRightNode :: ( BtBvhTreeClass bc ) => bc -> Int -> IO (Int)
btBvhTree_getRightNode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btBvhTree_getRightNode'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 762 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#153>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree__calc_splitting_axis :: ( BtBvhTreeClass bc , GIM_BVH_DATA_ARRAYClass p0 ) => bc -> p0 -> Int -> Int -> IO (Int)
btBvhTree__calc_splitting_axis a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btBvhTree__calc_splitting_axis'_ a1' a2' a3' a4' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 770 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#146>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_m_num_nodes_set :: ( BtBvhTreeClass bc ) => bc -> Int -> IO ()
btBvhTree_m_num_nodes_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btBvhTree_m_num_nodes_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 774 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#146>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_m_num_nodes_get :: ( BtBvhTreeClass bc ) => bc -> IO (Int)
btBvhTree_m_num_nodes_get a1 =
  withBt a1 $ \a1' -> 
  btBvhTree_m_num_nodes_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 778 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_m_node_array_set :: ( BtBvhTreeClass bc , GIM_BVH_TREE_NODE_ARRAYClass a ) => bc -> a -> IO ()
btBvhTree_m_node_array_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btBvhTree_m_node_array_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 782 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btBvhTree_m_node_array_get :: ( BtBvhTreeClass bc ) => bc -> IO (GIM_BVH_TREE_NODE_ARRAY)
btBvhTree_m_node_array_get a1 =
  withBt a1 $ \a1' -> 
  btBvhTree_m_node_array_get'_ a1' >>= \res ->
  mkGIM_BVH_TREE_NODE_ARRAY res >>= \res' ->
  return (res')
{-# LINE 786 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btGImpactBvh
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#262>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh0 :: IO (BtGImpactBvh)
btGImpactBvh0 =
  btGImpactBvh0'_ >>= \res ->
  mkBtGImpactBvh res >>= \res' ->
  return (res')
{-# LINE 791 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#268>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh1 :: ( BtPrimitiveManagerBaseClass p0 ) => p0 -> IO (BtGImpactBvh)
btGImpactBvh1 a1 =
  withBt a1 $ \a1' -> 
  btGImpactBvh1'_ a1' >>= \res ->
  mkBtGImpactBvh res >>= \res' ->
  return (res')
{-# LINE 795 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btGImpactBvh_free :: ( BtGImpactBvhClass bc ) => bc -> IO ()
btGImpactBvh_free a1 =
  withBt a1 $ \a1' -> 
  btGImpactBvh_free'_ a1' >>= \res ->
  return ()
{-# LINE 796 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#354>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_setNodeBound :: ( BtGImpactBvhClass bc , BtAABBClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactBvh_setNodeBound a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactBvh_setNodeBound'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 803 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#370>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_getEscapeNodeIndex :: ( BtGImpactBvhClass bc ) => bc -> Int -> IO (Int)
btGImpactBvh_getEscapeNodeIndex a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactBvh_getEscapeNodeIndex'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 809 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#339>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_isLeafNode :: ( BtGImpactBvhClass bc ) => bc -> Int -> IO (Bool)
btGImpactBvh_isLeafNode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactBvh_isLeafNode'_ a1' a2' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 815 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#285>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_getPrimitiveManager :: ( BtGImpactBvhClass bc ) => bc -> IO (BtPrimitiveManagerBase)
btGImpactBvh_getPrimitiveManager a1 =
  withBt a1 $ \a1' -> 
  btGImpactBvh_getPrimitiveManager'_ a1' >>= \res ->
  mkBtPrimitiveManagerBase res >>= \res' ->
  return (res')
{-# LINE 820 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#349>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_getNodeBound :: ( BtGImpactBvhClass bc , BtAABBClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactBvh_getNodeBound a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactBvh_getNodeBound'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 827 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#365>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_getRightNode :: ( BtGImpactBvhClass bc ) => bc -> Int -> IO (Int)
btGImpactBvh_getRightNode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactBvh_getRightNode'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 833 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#360>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_getLeftNode :: ( BtGImpactBvhClass bc ) => bc -> Int -> IO (Int)
btGImpactBvh_getLeftNode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactBvh_getLeftNode'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 839 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#280>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_setPrimitiveManager :: ( BtGImpactBvhClass bc , BtPrimitiveManagerBaseClass p0 ) => bc -> p0 -> IO ()
btGImpactBvh_setPrimitiveManager a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactBvh_setPrimitiveManager'_ a1' a2' >>= \res ->
  return ()
{-# LINE 845 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#301>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_buildSet :: ( BtGImpactBvhClass bc ) => bc -> IO ()
btGImpactBvh_buildSet a1 =
  withBt a1 $ \a1' -> 
  btGImpactBvh_buildSet'_ a1' >>= \res ->
  return ()
{-# LINE 850 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#375>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_getNodeTriangle :: ( BtGImpactBvhClass bc , BtPrimitiveTriangleClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactBvh_getNodeTriangle a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactBvh_getNodeTriangle'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 857 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#333>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_getNodeCount :: ( BtGImpactBvhClass bc ) => bc -> IO (Int)
btGImpactBvh_getNodeCount a1 =
  withBt a1 $ \a1' -> 
  btGImpactBvh_getNodeCount'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 862 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#321>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_hasHierarchy :: ( BtGImpactBvhClass bc ) => bc -> IO (Bool)
btGImpactBvh_hasHierarchy a1 =
  withBt a1 $ \a1' -> 
  btGImpactBvh_hasHierarchy'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 867 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#318>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_rayQuery :: ( BtGImpactBvhClass bc , BtAlignedObjectArray_int_Class p2 ) => bc -> Vec3 -> Vec3 -> p2 -> IO (Bool, Vec3, Vec3)
btGImpactBvh_rayQuery a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btGImpactBvh_rayQuery'_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  let {res' = toBool res} in
  return (res', a2'', a3'')
{-# LINE 875 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#318>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_rayQuery' :: ( BtGImpactBvhClass bc , BtAlignedObjectArray_int_Class p2 ) => bc -> p2 -> IO (Bool, Vec3, Vec3)
btGImpactBvh_rayQuery' a1 a4 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btGImpactBvh_rayQuery''_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  let {res' = toBool res} in
  return (res', a2'', a3'')
{-# LINE 883 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#295>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_update :: ( BtGImpactBvhClass bc ) => bc -> IO ()
btGImpactBvh_update a1 =
  withBt a1 $ \a1' -> 
  btGImpactBvh_update'_ a1' >>= \res ->
  return ()
{-# LINE 888 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#258>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_refit :: ( BtGImpactBvhClass bc ) => bc -> IO ()
btGImpactBvh_refit a1 =
  withBt a1 $ \a1' -> 
  btGImpactBvh_refit'_ a1' >>= \res ->
  return ()
{-# LINE 893 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#327>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_isTrimesh :: ( BtGImpactBvhClass bc ) => bc -> IO (Bool)
btGImpactBvh_isTrimesh a1 =
  withBt a1 $ \a1' -> 
  btGImpactBvh_isTrimesh'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 898 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#304>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_boxQuery :: ( BtGImpactBvhClass bc , BtAABBClass p0 , BtAlignedObjectArray_int_Class p1 ) => bc -> p0 -> p1 -> IO (Bool)
btGImpactBvh_boxQuery a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGImpactBvh_boxQuery'_ a1' a2' a3' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 905 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#392>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_find_collision :: (  BtGImpactBvhClass p0 , BtGImpactBvhClass p2 , BtPairSetClass p4 ) => p0 -> Transform -> p2 -> Transform -> p4 -> IO (Transform, Transform)
btGImpactBvh_find_collision a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  btGImpactBvh_find_collision'_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a4'>>= \a4'' -> 
  return (a2'', a4'')
{-# LINE 914 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#392>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_find_collision' :: (  BtGImpactBvhClass p0 , BtGImpactBvhClass p2 , BtPairSetClass p4 ) => p0 -> p2 -> p4 -> IO (Transform, Transform)
btGImpactBvh_find_collision' a1 a3 a5 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  withBt a3 $ \a3' -> 
  allocaTransform $ \a4' -> 
  withBt a5 $ \a5' -> 
  btGImpactBvh_find_collision''_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a4'>>= \a4'' -> 
  return (a2'', a4'')
{-# LINE 923 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#381>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_get_node_pointer :: ( BtGImpactBvhClass bc ) => bc -> Int -> IO (GIM_BVH_TREE_NODE)
btGImpactBvh_get_node_pointer a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactBvh_get_node_pointer'_ a1' a2' >>= \res ->
  mkGIM_BVH_TREE_NODE res >>= \res' ->
  return (res')
{-# LINE 929 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#308>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_boxQueryTrans :: ( BtGImpactBvhClass bc , BtAABBClass p0 , BtAlignedObjectArray_int_Class p2 ) => bc -> p0 -> Transform -> p2 -> IO (Bool, Transform)
btGImpactBvh_boxQueryTrans a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btGImpactBvh_boxQueryTrans'_ a1' a2' a3' a4' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  let {res' = toBool res} in
  return (res', a3'')
{-# LINE 937 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#308>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_boxQueryTrans' :: ( BtGImpactBvhClass bc , BtAABBClass p0 , BtAlignedObjectArray_int_Class p2 ) => bc -> p0 -> p2 -> IO (Bool, Transform)
btGImpactBvh_boxQueryTrans' a1 a2 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaTransform $ \a3' -> 
  withBt a4 $ \a4' -> 
  btGImpactBvh_boxQueryTrans''_ a1' a2' a3' a4' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  let {res' = toBool res} in
  return (res', a3'')
{-# LINE 945 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#344>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_getNodeData :: ( BtGImpactBvhClass bc ) => bc -> Int -> IO (Int)
btGImpactBvh_getNodeData a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactBvh_getNodeData'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 951 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#253>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_m_box_tree_set :: ( BtGImpactBvhClass bc , BtBvhTreeClass a ) => bc -> a -> IO ()
btGImpactBvh_m_box_tree_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactBvh_m_box_tree_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 955 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#253>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_m_box_tree_get :: ( BtGImpactBvhClass bc ) => bc -> IO (BtBvhTree)
btGImpactBvh_m_box_tree_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactBvh_m_box_tree_get'_ a1' >>= \res ->
  mkBtBvhTree res >>= \res' ->
  return (res')
{-# LINE 959 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#254>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_m_primitive_manager_set :: ( BtGImpactBvhClass bc , BtPrimitiveManagerBaseClass a ) => bc -> a -> IO ()
btGImpactBvh_m_primitive_manager_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactBvh_m_primitive_manager_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 963 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#254>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btGImpactBvh_m_primitive_manager_get :: ( BtGImpactBvhClass bc ) => bc -> IO (BtPrimitiveManagerBase)
btGImpactBvh_m_primitive_manager_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactBvh_m_primitive_manager_get'_ a1' >>= \res ->
  mkBtPrimitiveManagerBase res >>= \res' ->
  return (res')
{-# LINE 967 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btGImpactCollisionAlgorithm
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#199>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm :: ( BtCollisionAlgorithmConstructionInfoClass p0 , BtCollisionObjectClass p1 , BtCollisionObjectClass p2 ) => p0 -> p1 -> p2 -> IO (BtGImpactCollisionAlgorithm)
btGImpactCollisionAlgorithm a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGImpactCollisionAlgorithm'_ a1' a2' a3' >>= \res ->
  mkBtGImpactCollisionAlgorithm res >>= \res' ->
  return (res')
{-# LINE 972 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btGImpactCollisionAlgorithm_free :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO ()
btGImpactCollisionAlgorithm_free a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_free'_ a1' >>= \res ->
  return ()
{-# LINE 973 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#276>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_getFace1 :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO (Int)
btGImpactCollisionAlgorithm_getFace1 a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_getFace1'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 978 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#268>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_getFace0 :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO (Int)
btGImpactCollisionAlgorithm_getFace0 a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_getFace0'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 983 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#252>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_gimpact_vs_compoundshape :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 , BtGImpactShapeInterfaceClass p2 , BtCompoundShapeClass p3 ) => bc -> p0 -> p1 -> p2 -> p3 -> Bool -> IO ()
btGImpactCollisionAlgorithm_gimpact_vs_compoundshape a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  let {a6' = fromBool a6} in 
  btGImpactCollisionAlgorithm_gimpact_vs_compoundshape'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  return ()
{-# LINE 993 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#247>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_gimpact_vs_shape :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 , BtGImpactShapeInterfaceClass p2 , BtCollisionShapeClass p3 ) => bc -> p0 -> p1 -> p2 -> p3 -> Bool -> IO ()
btGImpactCollisionAlgorithm_gimpact_vs_shape a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  let {a6' = fromBool a6} in 
  btGImpactCollisionAlgorithm_gimpact_vs_shape'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  return ()
{-# LINE 1003 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#172>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_convex_vs_convex_collision :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 , BtCollisionShapeClass p2 , BtCollisionShapeClass p3 ) => bc -> p0 -> p1 -> p2 -> p3 -> IO ()
btGImpactCollisionAlgorithm_convex_vs_convex_collision a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  btGImpactCollisionAlgorithm_convex_vs_convex_collision'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 1012 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#264>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_setFace0 :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> Int -> IO ()
btGImpactCollisionAlgorithm_setFace0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactCollisionAlgorithm_setFace0'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1018 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#272>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_setFace1 :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> Int -> IO ()
btGImpactCollisionAlgorithm_setFace1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactCollisionAlgorithm_setFace1'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1024 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#109>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_checkManifold :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 ) => bc -> p0 -> p1 -> IO ()
btGImpactCollisionAlgorithm_checkManifold a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGImpactCollisionAlgorithm_checkManifold'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1031 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_newContactManifold :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 ) => bc -> p0 -> p1 -> IO (BtPersistentManifold)
btGImpactCollisionAlgorithm_newContactManifold a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGImpactCollisionAlgorithm_newContactManifold'_ a1' a2' a3' >>= \res ->
  mkBtPersistentManifold res >>= \res' ->
  return (res')
{-# LINE 1038 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#143>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_addContactPoint :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 ) => bc -> p0 -> p1 -> Vec3 -> Vec3 -> Float -> IO (Vec3, Vec3)
btGImpactCollisionAlgorithm_addContactPoint a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  let {a6' = realToFrac a6} in 
  btGImpactCollisionAlgorithm_addContactPoint'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a4'', a5'')
{-# LINE 1048 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#143>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_addContactPoint' :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 ) => bc -> p0 -> p1 -> Float -> IO (Vec3, Vec3)
btGImpactCollisionAlgorithm_addContactPoint' a1 a2 a3 a6 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  let {a6' = realToFrac a6} in 
  btGImpactCollisionAlgorithm_addContactPoint''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a4'', a5'')
{-# LINE 1058 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#194>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_gimpacttrimeshpart_vs_plane_collision :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 , BtGImpactMeshShapePartClass p2 , BtStaticPlaneShapeClass p3 ) => bc -> p0 -> p1 -> p2 -> p3 -> Bool -> IO ()
btGImpactCollisionAlgorithm_gimpacttrimeshpart_vs_plane_collision a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  let {a6' = fromBool a6} in 
  btGImpactCollisionAlgorithm_gimpacttrimeshpart_vs_plane_collision'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  return ()
{-# LINE 1068 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_registerAlgorithm :: (  BtCollisionDispatcherClass p0 ) => p0 -> IO ()
btGImpactCollisionAlgorithm_registerAlgorithm a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_registerAlgorithm'_ a1' >>= \res ->
  return ()
{-# LINE 1073 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#203>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_processCollision :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 , BtDispatcherInfoClass p2 , BtManifoldResultClass p3 ) => bc -> p0 -> p1 -> p2 -> p3 -> IO ()
btGImpactCollisionAlgorithm_processCollision a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  btGImpactCollisionAlgorithm_processCollision'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 1082 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#84>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_destroyContactManifolds :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO ()
btGImpactCollisionAlgorithm_destroyContactManifolds a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_destroyContactManifolds'_ a1' >>= \res ->
  return ()
{-# LINE 1087 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_gimpact_vs_gimpact_find_pairs :: ( BtGImpactCollisionAlgorithmClass bc , BtGImpactShapeInterfaceClass p2 , BtGImpactShapeInterfaceClass p3 , BtPairSetClass p4 ) => bc -> Transform -> Transform -> p2 -> p3 -> p4 -> IO (Transform, Transform)
btGImpactCollisionAlgorithm_gimpact_vs_gimpact_find_pairs a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  btGImpactCollisionAlgorithm_gimpact_vs_gimpact_find_pairs'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 1097 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_gimpact_vs_gimpact_find_pairs' :: ( BtGImpactCollisionAlgorithmClass bc , BtGImpactShapeInterfaceClass p2 , BtGImpactShapeInterfaceClass p3 , BtPairSetClass p4 ) => bc -> p2 -> p3 -> p4 -> IO (Transform, Transform)
btGImpactCollisionAlgorithm_gimpact_vs_gimpact_find_pairs' a1 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  btGImpactCollisionAlgorithm_gimpact_vs_gimpact_find_pairs''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 1107 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#102>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_getLastManifold :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO (BtPersistentManifold)
btGImpactCollisionAlgorithm_getLastManifold a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_getLastManifold'_ a1' >>= \res ->
  mkBtPersistentManifold res >>= \res' ->
  return (res')
{-# LINE 1112 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#187>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_gimpact_vs_shape_find_pairs :: ( BtGImpactCollisionAlgorithmClass bc , BtGImpactShapeInterfaceClass p2 , BtCollisionShapeClass p3 , BtAlignedObjectArray_int_Class p4 ) => bc -> Transform -> Transform -> p2 -> p3 -> p4 -> IO (Transform, Transform)
btGImpactCollisionAlgorithm_gimpact_vs_shape_find_pairs a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  btGImpactCollisionAlgorithm_gimpact_vs_shape_find_pairs'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 1122 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#187>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_gimpact_vs_shape_find_pairs' :: ( BtGImpactCollisionAlgorithmClass bc , BtGImpactShapeInterfaceClass p2 , BtCollisionShapeClass p3 , BtAlignedObjectArray_int_Class p4 ) => bc -> p2 -> p3 -> p4 -> IO (Transform, Transform)
btGImpactCollisionAlgorithm_gimpact_vs_shape_find_pairs' a1 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  withBt a6 $ \a6' -> 
  btGImpactCollisionAlgorithm_gimpact_vs_shape_find_pairs''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 1132 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#74>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_destroyConvexAlgorithm :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO ()
btGImpactCollisionAlgorithm_destroyConvexAlgorithm a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_destroyConvexAlgorithm'_ a1' >>= \res ->
  return ()
{-# LINE 1137 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#130>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_checkConvexAlgorithm :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 ) => bc -> p0 -> p1 -> IO ()
btGImpactCollisionAlgorithm_checkConvexAlgorithm a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGImpactCollisionAlgorithm_checkConvexAlgorithm'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1144 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#120>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_newAlgorithm :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 ) => bc -> p0 -> p1 -> IO (BtCollisionAlgorithm)
btGImpactCollisionAlgorithm_newAlgorithm a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGImpactCollisionAlgorithm_newAlgorithm'_ a1' a2' a3' >>= \res ->
  mkBtCollisionAlgorithm res >>= \res' ->
  return (res')
{-# LINE 1151 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#167>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_shape_vs_shape_collision :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 , BtCollisionShapeClass p2 , BtCollisionShapeClass p3 ) => bc -> p0 -> p1 -> p2 -> p3 -> IO ()
btGImpactCollisionAlgorithm_shape_vs_shape_collision a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  btGImpactCollisionAlgorithm_shape_vs_shape_collision'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 1160 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#288>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_setPart1 :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> Int -> IO ()
btGImpactCollisionAlgorithm_setPart1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactCollisionAlgorithm_setPart1'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1166 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#280>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_setPart0 :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> Int -> IO ()
btGImpactCollisionAlgorithm_setPart0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactCollisionAlgorithm_setPart0'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1172 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#91>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_clearCache :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO ()
btGImpactCollisionAlgorithm_clearCache a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_clearCache'_ a1' >>= \res ->
  return ()
{-# LINE 1177 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#292>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_getPart1 :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO (Int)
btGImpactCollisionAlgorithm_getPart1 a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_getPart1'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1182 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#284>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_getPart0 :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO (Int)
btGImpactCollisionAlgorithm_getPart0 a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_getPart0'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1187 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#258>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_gimpact_vs_concave :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 , BtGImpactShapeInterfaceClass p2 , BtConcaveShapeClass p3 ) => bc -> p0 -> p1 -> p2 -> p3 -> Bool -> IO ()
btGImpactCollisionAlgorithm_gimpact_vs_concave a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  let {a6' = fromBool a6} in 
  btGImpactCollisionAlgorithm_gimpact_vs_concave'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  return ()
{-# LINE 1197 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#205>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_calculateTimeOfImpact :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 , BtDispatcherInfoClass p2 , BtManifoldResultClass p3 ) => bc -> p0 -> p1 -> p2 -> p3 -> IO (Float)
btGImpactCollisionAlgorithm_calculateTimeOfImpact a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  btGImpactCollisionAlgorithm_calculateTimeOfImpact'_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 1206 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#242>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_gimpact_vs_gimpact :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionObjectClass p0 , BtCollisionObjectClass p1 , BtGImpactShapeInterfaceClass p2 , BtGImpactShapeInterfaceClass p3 ) => bc -> p0 -> p1 -> p2 -> p3 -> IO ()
btGImpactCollisionAlgorithm_gimpact_vs_gimpact a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  btGImpactCollisionAlgorithm_gimpact_vs_gimpact'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 1215 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#207>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_getAllContactManifolds :: ( BtGImpactCollisionAlgorithmClass bc , BtAlignedObjectArray_btPersistentManifold_ptr_Class p0 ) => bc -> p0 -> IO ()
btGImpactCollisionAlgorithm_getAllContactManifolds a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactCollisionAlgorithm_getAllContactManifolds'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1221 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_convex_algorithm_set :: ( BtGImpactCollisionAlgorithmClass bc , BtCollisionAlgorithmClass a ) => bc -> a -> IO ()
btGImpactCollisionAlgorithm_m_convex_algorithm_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactCollisionAlgorithm_m_convex_algorithm_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1225 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_convex_algorithm_get :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO (BtCollisionAlgorithm)
btGImpactCollisionAlgorithm_m_convex_algorithm_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_m_convex_algorithm_get'_ a1' >>= \res ->
  mkBtCollisionAlgorithm res >>= \res' ->
  return (res')
{-# LINE 1229 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#58>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_manifoldPtr_set :: ( BtGImpactCollisionAlgorithmClass bc , BtPersistentManifoldClass a ) => bc -> a -> IO ()
btGImpactCollisionAlgorithm_m_manifoldPtr_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactCollisionAlgorithm_m_manifoldPtr_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1233 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#58>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_manifoldPtr_get :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO (BtPersistentManifold)
btGImpactCollisionAlgorithm_m_manifoldPtr_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_m_manifoldPtr_get'_ a1' >>= \res ->
  mkBtPersistentManifold res >>= \res' ->
  return (res')
{-# LINE 1237 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#59>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_resultOut_set :: ( BtGImpactCollisionAlgorithmClass bc , BtManifoldResultClass a ) => bc -> a -> IO ()
btGImpactCollisionAlgorithm_m_resultOut_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactCollisionAlgorithm_m_resultOut_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1241 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#59>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_resultOut_get :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO (BtManifoldResult)
btGImpactCollisionAlgorithm_m_resultOut_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_m_resultOut_get'_ a1' >>= \res ->
  mkBtManifoldResult res >>= \res' ->
  return (res')
{-# LINE 1245 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#60>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_dispatchInfo_set :: ( BtGImpactCollisionAlgorithmClass bc , BtDispatcherInfoClass a ) => bc -> a -> IO ()
btGImpactCollisionAlgorithm_m_dispatchInfo_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactCollisionAlgorithm_m_dispatchInfo_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1249 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#60>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_dispatchInfo_get :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO (BtDispatcherInfo)
btGImpactCollisionAlgorithm_m_dispatchInfo_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_m_dispatchInfo_get'_ a1' >>= \res ->
  mkBtDispatcherInfo res >>= \res' ->
  return (res')
{-# LINE 1253 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_triface0_set :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> Int -> IO ()
btGImpactCollisionAlgorithm_m_triface0_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactCollisionAlgorithm_m_triface0_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1257 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_triface0_get :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO (Int)
btGImpactCollisionAlgorithm_m_triface0_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_m_triface0_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1261 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_part0_set :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> Int -> IO ()
btGImpactCollisionAlgorithm_m_part0_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactCollisionAlgorithm_m_part0_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1265 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_part0_get :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO (Int)
btGImpactCollisionAlgorithm_m_part0_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_m_part0_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1269 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#63>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_triface1_set :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> Int -> IO ()
btGImpactCollisionAlgorithm_m_triface1_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactCollisionAlgorithm_m_triface1_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1273 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#63>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_triface1_get :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO (Int)
btGImpactCollisionAlgorithm_m_triface1_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_m_triface1_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1277 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#64>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_part1_set :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> Int -> IO ()
btGImpactCollisionAlgorithm_m_part1_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactCollisionAlgorithm_m_part1_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1281 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.h?r=2223#64>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactCollisionAlgorithm.cpp?r=2223>
-}
btGImpactCollisionAlgorithm_m_part1_get :: ( BtGImpactCollisionAlgorithmClass bc ) => bc -> IO (Int)
btGImpactCollisionAlgorithm_m_part1_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactCollisionAlgorithm_m_part1_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1285 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btGImpactCompoundShape
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#370>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape :: Bool -> IO (BtGImpactCompoundShape)
btGImpactCompoundShape a1 =
  let {a1' = fromBool a1} in 
  btGImpactCompoundShape'_ a1' >>= \res ->
  mkBtGImpactCompoundShape res >>= \res' ->
  return (res')
{-# LINE 1290 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btGImpactCompoundShape_free :: ( BtGImpactCompoundShapeClass bc ) => bc -> IO ()
btGImpactCompoundShape_free a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_free'_ a1' >>= \res ->
  return ()
{-# LINE 1291 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#498>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_calculateLocalInertia :: ( BtGImpactCompoundShapeClass bc ) => bc -> Float -> Vec3 -> IO (Vec3)
btGImpactCompoundShape_calculateLocalInertia a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  withVec3 a3 $ \a3' -> 
  btGImpactCompoundShape_calculateLocalInertia'_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1298 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#498>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_calculateLocalInertia' :: ( BtGImpactCompoundShapeClass bc ) => bc -> Float -> IO (Vec3)
btGImpactCompoundShape_calculateLocalInertia' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  allocaVec3 $ \a3' -> 
  btGImpactCompoundShape_calculateLocalInertia''_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1305 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#410>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_addChildShape :: ( BtGImpactCompoundShapeClass bc , BtCollisionShapeClass p1 ) => bc -> Transform -> p1 -> IO (Transform)
btGImpactCompoundShape_addChildShape a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGImpactCompoundShape_addChildShape'_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 1312 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#410>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_addChildShape' :: ( BtGImpactCompoundShapeClass bc , BtCollisionShapeClass p1 ) => bc -> p1 -> IO (Transform)
btGImpactCompoundShape_addChildShape' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGImpactCompoundShape_addChildShape''_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 1319 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#410>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_addChildShape0 :: ( BtGImpactCompoundShapeClass bc , BtCollisionShapeClass p1 ) => bc -> Transform -> p1 -> IO (Transform)
btGImpactCompoundShape_addChildShape0 a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGImpactCompoundShape_addChildShape0'_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 1326 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#410>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_addChildShape0' :: ( BtGImpactCompoundShapeClass bc , BtCollisionShapeClass p1 ) => bc -> p1 -> IO (Transform)
btGImpactCompoundShape_addChildShape0' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGImpactCompoundShape_addChildShape0''_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 1333 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#418>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_addChildShape1 :: ( BtGImpactCompoundShapeClass bc , BtCollisionShapeClass p0 ) => bc -> p0 -> IO ()
btGImpactCompoundShape_addChildShape1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactCompoundShape_addChildShape1'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1339 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#397>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_getCompoundPrimitiveManager :: ( BtGImpactCompoundShapeClass bc ) => bc -> IO (BtGImpactCompoundShape_CompoundPrimitiveManager)
btGImpactCompoundShape_getCompoundPrimitiveManager a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_getCompoundPrimitiveManager'_ a1' >>= \res ->
  mkBtGImpactCompoundShape_CompoundPrimitiveManager res >>= \res' ->
  return (res')
{-# LINE 1344 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#464>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_setChildTransform :: ( BtGImpactCompoundShapeClass bc ) => bc -> Int -> Transform -> IO (Transform)
btGImpactCompoundShape_setChildTransform a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withTransform a3 $ \a3' -> 
  btGImpactCompoundShape_setChildTransform'_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1351 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#464>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_setChildTransform' :: ( BtGImpactCompoundShapeClass bc ) => bc -> Int -> IO (Transform)
btGImpactCompoundShape_setChildTransform' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  btGImpactCompoundShape_setChildTransform''_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1358 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#454>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_getChildTransform :: ( BtGImpactCompoundShapeClass bc ) => bc -> Int -> IO (Transform)
btGImpactCompoundShape_getChildTransform a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  btGImpactCompoundShape_getChildTransform'_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1365 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#490>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_getBulletTetrahedron :: ( BtGImpactCompoundShapeClass bc , BtTetrahedronShapeExClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactCompoundShape_getBulletTetrahedron a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactCompoundShape_getBulletTetrahedron'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1372 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#500>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_getName :: ( BtGImpactCompoundShapeClass bc ) => bc -> IO (String)
btGImpactCompoundShape_getName a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_getName'_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')
{-# LINE 1377 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#478>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_needsRetrieveTetrahedrons :: ( BtGImpactCompoundShapeClass bc ) => bc -> IO (Bool)
btGImpactCompoundShape_needsRetrieveTetrahedrons a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_needsRetrieveTetrahedrons'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 1382 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#425>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_getChildShape :: ( BtGImpactCompoundShapeClass bc ) => bc -> Int -> IO (BtCollisionShape)
btGImpactCompoundShape_getChildShape a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactCompoundShape_getChildShape'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 1388 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#425>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_getChildShape0 :: ( BtGImpactCompoundShapeClass bc ) => bc -> Int -> IO (BtCollisionShape)
btGImpactCompoundShape_getChildShape0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactCompoundShape_getChildShape0'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 1394 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#431>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_getChildShape1 :: ( BtGImpactCompoundShapeClass bc ) => bc -> Int -> IO (BtCollisionShape)
btGImpactCompoundShape_getChildShape1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactCompoundShape_getChildShape1'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 1400 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#484>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_getBulletTriangle :: ( BtGImpactCompoundShapeClass bc , BtTriangleShapeExClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactCompoundShape_getBulletTriangle a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactCompoundShape_getBulletTriangle'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1407 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#472>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_needsRetrieveTriangles :: ( BtGImpactCompoundShapeClass bc ) => bc -> IO (Bool)
btGImpactCompoundShape_needsRetrieveTriangles a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_needsRetrieveTriangles'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 1412 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#383>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_childrenHasTransform :: ( BtGImpactCompoundShapeClass bc ) => bc -> IO (Bool)
btGImpactCompoundShape_childrenHasTransform a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_childrenHasTransform'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 1417 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#403>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_getNumChildShapes :: ( BtGImpactCompoundShapeClass bc ) => bc -> IO (Int)
btGImpactCompoundShape_getNumChildShapes a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_getNumChildShapes'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1422 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#391>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_getPrimitiveManager :: ( BtGImpactCompoundShapeClass bc ) => bc -> IO (BtPrimitiveManagerBase)
btGImpactCompoundShape_getPrimitiveManager a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_getPrimitiveManager'_ a1' >>= \res ->
  mkBtPrimitiveManagerBase res >>= \res' ->
  return (res')
{-# LINE 1427 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#439>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_getChildAabb :: ( BtGImpactCompoundShapeClass bc ) => bc -> Int -> Transform -> Vec3 -> Vec3 -> IO (Transform, Vec3, Vec3)
btGImpactCompoundShape_getChildAabb a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withTransform a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btGImpactCompoundShape_getChildAabb'_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a3'', a4'', a5'')
{-# LINE 1436 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#439>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_getChildAabb' :: ( BtGImpactCompoundShapeClass bc ) => bc -> Int -> IO (Transform, Vec3, Vec3)
btGImpactCompoundShape_getChildAabb' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  btGImpactCompoundShape_getChildAabb''_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a3'', a4'', a5'')
{-# LINE 1445 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#365>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_m_childShapes_set :: ( BtGImpactCompoundShapeClass bc , BtAlignedObjectArray_btCollisionShape_ptr_Class a ) => bc -> a -> IO ()
btGImpactCompoundShape_m_childShapes_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactCompoundShape_m_childShapes_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1449 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#365>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_m_childShapes_get :: ( BtGImpactCompoundShapeClass bc ) => bc -> IO (BtAlignedObjectArray_btCollisionShape_ptr_)
btGImpactCompoundShape_m_childShapes_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_m_childShapes_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btCollisionShape_ptr_ res >>= \res' ->
  return (res')
{-# LINE 1453 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#364>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_m_childTransforms_set :: ( BtGImpactCompoundShapeClass bc , BtAlignedObjectArray_btTransform_Class a ) => bc -> a -> IO ()
btGImpactCompoundShape_m_childTransforms_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactCompoundShape_m_childTransforms_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1457 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#364>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_m_childTransforms_get :: ( BtGImpactCompoundShapeClass bc ) => bc -> IO (BtAlignedObjectArray_btTransform_)
btGImpactCompoundShape_m_childTransforms_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_m_childTransforms_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btTransform_ res >>= \res' ->
  return (res')
{-# LINE 1461 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#363>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_m_primitive_manager_set :: ( BtGImpactCompoundShapeClass bc , BtGImpactCompoundShape_CompoundPrimitiveManagerClass a ) => bc -> a -> IO ()
btGImpactCompoundShape_m_primitive_manager_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactCompoundShape_m_primitive_manager_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1465 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#363>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactCompoundShape_m_primitive_manager_get :: ( BtGImpactCompoundShapeClass bc ) => bc -> IO (BtGImpactCompoundShape_CompoundPrimitiveManager)
btGImpactCompoundShape_m_primitive_manager_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactCompoundShape_m_primitive_manager_get'_ a1' >>= \res ->
  mkBtGImpactCompoundShape_CompoundPrimitiveManager res >>= \res' ->
  return (res')
{-# LINE 1469 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btGImpactMeshShape
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#927>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape :: ( BtStridingMeshInterfaceClass p0 ) => p0 -> IO (BtGImpactMeshShape)
btGImpactMeshShape a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape'_ a1' >>= \res ->
  mkBtGImpactMeshShape res >>= \res' ->
  return (res')
{-# LINE 1474 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btGImpactMeshShape_free :: ( BtGImpactMeshShapeClass bc ) => bc -> IO ()
btGImpactMeshShape_free a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_free'_ a1' >>= \res ->
  return ()
{-# LINE 1475 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1014>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_calculateLocalInertia :: ( BtGImpactMeshShapeClass bc ) => bc -> Float -> Vec3 -> IO (Vec3)
btGImpactMeshShape_calculateLocalInertia a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  withVec3 a3 $ \a3' -> 
  btGImpactMeshShape_calculateLocalInertia'_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1482 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1014>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_calculateLocalInertia' :: ( BtGImpactMeshShapeClass bc ) => bc -> Float -> IO (Vec3)
btGImpactMeshShape_calculateLocalInertia' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  allocaVec3 $ \a3' -> 
  btGImpactMeshShape_calculateLocalInertia''_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1489 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1118>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_setChildTransform :: ( BtGImpactMeshShapeClass bc ) => bc -> Int -> Transform -> IO (Transform)
btGImpactMeshShape_setChildTransform a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withTransform a3 $ \a3' -> 
  btGImpactMeshShape_setChildTransform'_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1496 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1118>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_setChildTransform' :: ( BtGImpactMeshShapeClass bc ) => bc -> Int -> IO (Transform)
btGImpactMeshShape_setChildTransform' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  btGImpactMeshShape_setChildTransform''_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1503 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#945>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getMeshInterface :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (BtStridingMeshInterface)
btGImpactMeshShape_getMeshInterface a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_getMeshInterface'_ a1' >>= \res ->
  mkBtStridingMeshInterface res >>= \res' ->
  return (res')
{-# LINE 1508 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#945>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getMeshInterface0 :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (BtStridingMeshInterface)
btGImpactMeshShape_getMeshInterface0 a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_getMeshInterface0'_ a1' >>= \res ->
  mkBtStridingMeshInterface res >>= \res' ->
  return (res')
{-# LINE 1513 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#950>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getMeshInterface1 :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (BtStridingMeshInterface)
btGImpactMeshShape_getMeshInterface1 a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_getMeshInterface1'_ a1' >>= \res ->
  mkBtStridingMeshInterface res >>= \res' ->
  return (res')
{-# LINE 1518 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1018>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getPrimitiveManager :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (BtPrimitiveManagerBase)
btGImpactMeshShape_getPrimitiveManager a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_getPrimitiveManager'_ a1' >>= \res ->
  mkBtPrimitiveManagerBase res >>= \res' ->
  return (res')
{-# LINE 1523 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1142>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_processAllTriangles :: ( BtGImpactMeshShapeClass bc , BtTriangleCallbackClass p0 ) => bc -> p0 -> Vec3 -> Vec3 -> IO (Vec3, Vec3)
btGImpactMeshShape_processAllTriangles a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btGImpactMeshShape_processAllTriangles'_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a3'', a4'')
{-# LINE 1531 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1142>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_processAllTriangles' :: ( BtGImpactMeshShapeClass bc , BtTriangleCallbackClass p0 ) => bc -> p0 -> IO (Vec3, Vec3)
btGImpactMeshShape_processAllTriangles' a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  btGImpactMeshShape_processAllTriangles''_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a3'', a4'')
{-# LINE 1539 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#955>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getMeshPartCount :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (Int)
btGImpactMeshShape_getMeshPartCount a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_getMeshPartCount'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1544 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1165>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_calculateSerializeBufferSize :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (Int)
btGImpactMeshShape_calculateSerializeBufferSize a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_calculateSerializeBufferSize'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1549 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_rayTest :: ( BtGImpactMeshShapeClass bc , BtCollisionWorld_RayResultCallbackClass p2 ) => bc -> Vec3 -> Vec3 -> p2 -> IO (Vec3, Vec3)
btGImpactMeshShape_rayTest a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btGImpactMeshShape_rayTest'_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 1557 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_rayTest' :: ( BtGImpactMeshShapeClass bc , BtCollisionWorld_RayResultCallbackClass p2 ) => bc -> p2 -> IO (Vec3, Vec3)
btGImpactMeshShape_rayTest' a1 a4 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btGImpactMeshShape_rayTest''_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 1565 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#905>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_buildMeshParts :: ( BtGImpactMeshShapeClass bc , BtStridingMeshInterfaceClass p0 ) => bc -> p0 -> IO ()
btGImpactMeshShape_buildMeshParts a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactMeshShape_buildMeshParts'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1571 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1131>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getName :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (String)
btGImpactMeshShape_getName a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_getName'_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')
{-# LINE 1576 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1054>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getBulletTriangle :: ( BtGImpactMeshShapeClass bc , BtTriangleShapeExClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactMeshShape_getBulletTriangle a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactMeshShape_getBulletTriangle'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1583 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#973>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_setLocalScaling :: ( BtGImpactMeshShapeClass bc ) => bc -> Vec3 -> IO (Vec3)
btGImpactMeshShape_setLocalScaling a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGImpactMeshShape_setLocalScaling'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 1589 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#973>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_setLocalScaling' :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (Vec3)
btGImpactMeshShape_setLocalScaling' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGImpactMeshShape_setLocalScaling''_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 1595 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1041>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_needsRetrieveTriangles :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (Bool)
btGImpactMeshShape_needsRetrieveTriangles a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_needsRetrieveTriangles'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 1600 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1034>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_childrenHasTransform :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (Bool)
btGImpactMeshShape_childrenHasTransform a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_childrenHasTransform'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 1605 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1090>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getChildShape :: ( BtGImpactMeshShapeClass bc ) => bc -> Int -> IO (BtCollisionShape)
btGImpactMeshShape_getChildShape a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShape_getChildShape'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 1611 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1090>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getChildShape0 :: ( BtGImpactMeshShapeClass bc ) => bc -> Int -> IO (BtCollisionShape)
btGImpactMeshShape_getChildShape0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShape_getChildShape0'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 1617 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1099>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getChildShape1 :: ( BtGImpactMeshShapeClass bc ) => bc -> Int -> IO (BtCollisionShape)
btGImpactMeshShape_getChildShape1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShape_getChildShape1'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 1623 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#915>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_calcLocalAABB :: ( BtGImpactMeshShapeClass bc ) => bc -> IO ()
btGImpactMeshShape_calcLocalAABB a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_calcLocalAABB'_ a1' >>= \res ->
  return ()
{-# LINE 1628 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1107>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getChildTransform :: ( BtGImpactMeshShapeClass bc ) => bc -> Int -> IO (Transform)
btGImpactMeshShape_getChildTransform a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  btGImpactMeshShape_getChildTransform'_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1635 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_serialize :: ( BtGImpactMeshShapeClass bc , BtSerializerClass p1 ) => bc -> VoidPtr -> p1 -> IO (String)
btGImpactMeshShape_serialize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGImpactMeshShape_serialize'_ a1' a2' a3' >>= \res ->
  peekCString res >>= \res' ->
  return (res')
{-# LINE 1642 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1067>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_lockChildShapes :: ( BtGImpactMeshShapeClass bc ) => bc -> IO ()
btGImpactMeshShape_lockChildShapes a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_lockChildShapes'_ a1' >>= \res ->
  return ()
{-# LINE 1647 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#987>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_setMargin :: ( BtGImpactMeshShapeClass bc ) => bc -> Float -> IO ()
btGImpactMeshShape_setMargin a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btGImpactMeshShape_setMargin'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1653 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1026>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getNumChildShapes :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (Int)
btGImpactMeshShape_getNumChildShapes a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_getNumChildShapes'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1658 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1083>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getChildAabb :: ( BtGImpactMeshShapeClass bc ) => bc -> Int -> Transform -> Vec3 -> Vec3 -> IO (Transform, Vec3, Vec3)
btGImpactMeshShape_getChildAabb a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withTransform a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btGImpactMeshShape_getChildAabb'_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a3'', a4'', a5'')
{-# LINE 1667 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1083>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getChildAabb' :: ( BtGImpactMeshShapeClass bc ) => bc -> Int -> IO (Transform, Vec3, Vec3)
btGImpactMeshShape_getChildAabb' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  btGImpactMeshShape_getChildAabb''_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a3'', a4'', a5'')
{-# LINE 1676 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1060>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getBulletTetrahedron :: ( BtGImpactMeshShapeClass bc , BtTetrahedronShapeExClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactMeshShape_getBulletTetrahedron a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactMeshShape_getBulletTetrahedron'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1683 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1048>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_needsRetrieveTetrahedrons :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (Bool)
btGImpactMeshShape_needsRetrieveTetrahedrons a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_needsRetrieveTetrahedrons'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 1688 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1072>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_unlockChildShapes :: ( BtGImpactMeshShapeClass bc ) => bc -> IO ()
btGImpactMeshShape_unlockChildShapes a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_unlockChildShapes'_ a1' >>= \res ->
  return ()
{-# LINE 1693 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#960>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getMeshPart :: ( BtGImpactMeshShapeClass bc ) => bc -> Int -> IO (BtGImpactMeshShapePart)
btGImpactMeshShape_getMeshPart a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShape_getMeshPart'_ a1' a2' >>= \res ->
  mkBtGImpactMeshShapePart res >>= \res' ->
  return (res')
{-# LINE 1699 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#960>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getMeshPart0 :: ( BtGImpactMeshShapeClass bc ) => bc -> Int -> IO (BtGImpactMeshShapePart)
btGImpactMeshShape_getMeshPart0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShape_getMeshPart0'_ a1' a2' >>= \res ->
  mkBtGImpactMeshShapePart res >>= \res' ->
  return (res')
{-# LINE 1705 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#967>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_getMeshPart1 :: ( BtGImpactMeshShapeClass bc ) => bc -> Int -> IO (BtGImpactMeshShapePart)
btGImpactMeshShape_getMeshPart1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShape_getMeshPart1'_ a1' a2' >>= \res ->
  mkBtGImpactMeshShapePart res >>= \res' ->
  return (res')
{-# LINE 1711 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1002>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_postUpdate :: ( BtGImpactMeshShapeClass bc ) => bc -> IO ()
btGImpactMeshShape_postUpdate a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_postUpdate'_ a1' >>= \res ->
  return ()
{-# LINE 1716 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#901>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_m_meshInterface_set :: ( BtGImpactMeshShapeClass bc , BtStridingMeshInterfaceClass a ) => bc -> a -> IO ()
btGImpactMeshShape_m_meshInterface_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactMeshShape_m_meshInterface_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1720 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#901>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_m_meshInterface_get :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (BtStridingMeshInterface)
btGImpactMeshShape_m_meshInterface_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_m_meshInterface_get'_ a1' >>= \res ->
  mkBtStridingMeshInterface res >>= \res' ->
  return (res')
{-# LINE 1724 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#904>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_m_mesh_parts_set :: ( BtGImpactMeshShapeClass bc , BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class a ) => bc -> a -> IO ()
btGImpactMeshShape_m_mesh_parts_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactMeshShape_m_mesh_parts_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1728 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#904>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShape_m_mesh_parts_get :: ( BtGImpactMeshShapeClass bc ) => bc -> IO (BtAlignedObjectArray_btGImpactMeshShapePart_ptr_)
btGImpactMeshShape_m_mesh_parts_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShape_m_mesh_parts_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btGImpactMeshShapePart_ptr_ res >>= \res' ->
  return (res')
{-# LINE 1732 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btGImpactMeshShapeData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1153>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapeData :: IO (BtGImpactMeshShapeData)
btGImpactMeshShapeData =
  btGImpactMeshShapeData'_ >>= \res ->
  mkBtGImpactMeshShapeData res >>= \res' ->
  return (res')
{-# LINE 1737 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btGImpactMeshShapeData_free :: ( BtGImpactMeshShapeDataClass bc ) => bc -> IO ()
btGImpactMeshShapeData_free a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapeData_free'_ a1' >>= \res ->
  return ()
{-# LINE 1738 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1154>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapeData_m_collisionShapeData_set :: ( BtGImpactMeshShapeDataClass bc , BtCollisionShapeDataClass a ) => bc -> a -> IO ()
btGImpactMeshShapeData_m_collisionShapeData_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactMeshShapeData_m_collisionShapeData_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1742 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1154>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapeData_m_collisionShapeData_get :: ( BtGImpactMeshShapeDataClass bc ) => bc -> IO (BtCollisionShapeData)
btGImpactMeshShapeData_m_collisionShapeData_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapeData_m_collisionShapeData_get'_ a1' >>= \res ->
  mkBtCollisionShapeData res >>= \res' ->
  return (res')
{-# LINE 1746 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1156>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapeData_m_meshInterface_set :: ( BtGImpactMeshShapeDataClass bc , BtStridingMeshInterfaceDataClass a ) => bc -> a -> IO ()
btGImpactMeshShapeData_m_meshInterface_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactMeshShapeData_m_meshInterface_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1750 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1156>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapeData_m_meshInterface_get :: ( BtGImpactMeshShapeDataClass bc ) => bc -> IO (BtStridingMeshInterfaceData)
btGImpactMeshShapeData_m_meshInterface_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapeData_m_meshInterface_get'_ a1' >>= \res ->
  mkBtStridingMeshInterfaceData res >>= \res' ->
  return (res')
{-# LINE 1754 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1158>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapeData_m_localScaling_set :: ( BtGImpactMeshShapeDataClass bc , BtVector3FloatDataClass a ) => bc -> a -> IO ()
btGImpactMeshShapeData_m_localScaling_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactMeshShapeData_m_localScaling_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1758 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1158>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapeData_m_localScaling_get :: ( BtGImpactMeshShapeDataClass bc ) => bc -> IO (BtVector3FloatData)
btGImpactMeshShapeData_m_localScaling_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapeData_m_localScaling_get'_ a1' >>= \res ->
  mkBtVector3FloatData res >>= \res' ->
  return (res')
{-# LINE 1762 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1160>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapeData_m_collisionMargin_set :: ( BtGImpactMeshShapeDataClass bc ) => bc -> Float -> IO ()
btGImpactMeshShapeData_m_collisionMargin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btGImpactMeshShapeData_m_collisionMargin_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1766 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1160>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapeData_m_collisionMargin_get :: ( BtGImpactMeshShapeDataClass bc ) => bc -> IO (Float)
btGImpactMeshShapeData_m_collisionMargin_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapeData_m_collisionMargin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 1770 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1162>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapeData_m_gimpactSubType_set :: ( BtGImpactMeshShapeDataClass bc ) => bc -> Int -> IO ()
btGImpactMeshShapeData_m_gimpactSubType_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShapeData_m_gimpactSubType_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1774 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#1162>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapeData_m_gimpactSubType_get :: ( BtGImpactMeshShapeDataClass bc ) => bc -> IO (Int)
btGImpactMeshShapeData_m_gimpactSubType_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapeData_m_gimpactSubType_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1778 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btGImpactMeshShapePart
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#710>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart0 :: IO (BtGImpactMeshShapePart)
btGImpactMeshShapePart0 =
  btGImpactMeshShapePart0'_ >>= \res ->
  mkBtGImpactMeshShapePart res >>= \res' ->
  return (res')
{-# LINE 1783 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#716>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart1 :: ( BtStridingMeshInterfaceClass p0 ) => p0 -> Int -> IO (BtGImpactMeshShapePart)
btGImpactMeshShapePart1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShapePart1'_ a1' a2' >>= \res ->
  mkBtGImpactMeshShapePart res >>= \res' ->
  return (res')
{-# LINE 1787 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btGImpactMeshShapePart_free :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO ()
btGImpactMeshShapePart_free a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_free'_ a1' >>= \res ->
  return ()
{-# LINE 1788 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#809>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_calculateLocalInertia :: ( BtGImpactMeshShapePartClass bc ) => bc -> Float -> Vec3 -> IO (Vec3)
btGImpactMeshShapePart_calculateLocalInertia a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  withVec3 a3 $ \a3' -> 
  btGImpactMeshShapePart_calculateLocalInertia'_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1795 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#809>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_calculateLocalInertia' :: ( BtGImpactMeshShapePartClass bc ) => bc -> Float -> IO (Vec3)
btGImpactMeshShapePart_calculateLocalInertia' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  allocaVec3 $ \a3' -> 
  btGImpactMeshShapePart_calculateLocalInertia''_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1802 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#786>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_setChildTransform :: ( BtGImpactMeshShapePartClass bc ) => bc -> Int -> Transform -> IO (Transform)
btGImpactMeshShapePart_setChildTransform a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withTransform a3 $ \a3' -> 
  btGImpactMeshShapePart_setChildTransform'_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1809 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#786>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_setChildTransform' :: ( BtGImpactMeshShapePartClass bc ) => bc -> Int -> IO (Transform)
btGImpactMeshShapePart_setChildTransform' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  btGImpactMeshShapePart_setChildTransform''_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1816 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#877>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getLocalScaling :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO (Vec3)
btGImpactMeshShapePart_getLocalScaling a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGImpactMeshShapePart_getLocalScaling'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 1822 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#855>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getVertex :: ( BtGImpactMeshShapePartClass bc ) => bc -> Int -> Vec3 -> IO (Vec3)
btGImpactMeshShapePart_getVertex a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withVec3 a3 $ \a3' -> 
  btGImpactMeshShapePart_getVertex'_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1829 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#855>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getVertex' :: ( BtGImpactMeshShapePartClass bc ) => bc -> Int -> IO (Vec3)
btGImpactMeshShapePart_getVertex' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaVec3 $ \a3' -> 
  btGImpactMeshShapePart_getVertex''_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1836 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#887>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_processAllTriangles :: ( BtGImpactMeshShapePartClass bc , BtTriangleCallbackClass p0 ) => bc -> p0 -> Vec3 -> Vec3 -> IO (Vec3, Vec3)
btGImpactMeshShapePart_processAllTriangles a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btGImpactMeshShapePart_processAllTriangles'_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a3'', a4'')
{-# LINE 1844 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#887>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_processAllTriangles' :: ( BtGImpactMeshShapePartClass bc , BtTriangleCallbackClass p0 ) => bc -> p0 -> IO (Vec3, Vec3)
btGImpactMeshShapePart_processAllTriangles' a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  btGImpactMeshShapePart_processAllTriangles''_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a3'', a4'')
{-# LINE 1852 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#814>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getName :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO (String)
btGImpactMeshShapePart_getName a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_getName'_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')
{-# LINE 1857 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#836>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getBulletTriangle :: ( BtGImpactMeshShapePartClass bc , BtTriangleShapeExClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactMeshShapePart_getBulletTriangle a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactMeshShapePart_getBulletTriangle'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1864 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#871>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_setLocalScaling :: ( BtGImpactMeshShapePartClass bc ) => bc -> Vec3 -> IO (Vec3)
btGImpactMeshShapePart_setLocalScaling a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGImpactMeshShapePart_setLocalScaling'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 1870 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#871>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_setLocalScaling' :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO (Vec3)
btGImpactMeshShapePart_setLocalScaling' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGImpactMeshShapePart_setLocalScaling''_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 1876 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#882>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getPart :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO (Int)
btGImpactMeshShapePart_getPart a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_getPart'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1881 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#728>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_childrenHasTransform :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO (Bool)
btGImpactMeshShapePart_childrenHasTransform a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_childrenHasTransform'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 1886 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#825>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_needsRetrieveTriangles :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO (Bool)
btGImpactMeshShapePart_needsRetrieveTriangles a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_needsRetrieveTriangles'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 1891 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#757>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getChildShape :: ( BtGImpactMeshShapePartClass bc ) => bc -> Int -> IO (BtCollisionShape)
btGImpactMeshShapePart_getChildShape a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShapePart_getChildShape'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 1897 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#757>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getChildShape0 :: ( BtGImpactMeshShapePartClass bc ) => bc -> Int -> IO (BtCollisionShape)
btGImpactMeshShapePart_getChildShape0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShapePart_getChildShape0'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 1903 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#767>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getChildShape1 :: ( BtGImpactMeshShapePartClass bc ) => bc -> Int -> IO (BtCollisionShape)
btGImpactMeshShapePart_getChildShape1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactMeshShapePart_getChildShape1'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 1909 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#775>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getChildTransform :: ( BtGImpactMeshShapePartClass bc ) => bc -> Int -> IO (Transform)
btGImpactMeshShapePart_getChildTransform a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  btGImpactMeshShapePart_getChildTransform'_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 1916 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#735>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_lockChildShapes :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO ()
btGImpactMeshShapePart_lockChildShapes a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_lockChildShapes'_ a1' >>= \res ->
  return ()
{-# LINE 1921 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#866>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getMargin :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO (Float)
btGImpactMeshShapePart_getMargin a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_getMargin'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 1926 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#860>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_setMargin :: ( BtGImpactMeshShapePartClass bc ) => bc -> Float -> IO ()
btGImpactMeshShapePart_setMargin a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btGImpactMeshShapePart_setMargin'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1932 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#795>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getPrimitiveManager :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO (BtPrimitiveManagerBase)
btGImpactMeshShapePart_getPrimitiveManager a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_getPrimitiveManager'_ a1' >>= \res ->
  mkBtPrimitiveManagerBase res >>= \res' ->
  return (res')
{-# LINE 1937 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#750>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getNumChildShapes :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO (Int)
btGImpactMeshShapePart_getNumChildShapes a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_getNumChildShapes'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1942 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#841>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getBulletTetrahedron :: ( BtGImpactMeshShapePartClass bc , BtTetrahedronShapeExClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactMeshShapePart_getBulletTetrahedron a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactMeshShapePart_getBulletTetrahedron'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1949 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#800>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getTrimeshPrimitiveManager :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO (BtGImpactMeshShapePart_TrimeshPrimitiveManager)
btGImpactMeshShapePart_getTrimeshPrimitiveManager a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_getTrimeshPrimitiveManager'_ a1' >>= \res ->
  mkBtGImpactMeshShapePart_TrimeshPrimitiveManager res >>= \res' ->
  return (res')
{-# LINE 1954 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#831>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_needsRetrieveTetrahedrons :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO (Bool)
btGImpactMeshShapePart_needsRetrieveTetrahedrons a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_needsRetrieveTetrahedrons'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 1959 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#742>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_unlockChildShapes :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO ()
btGImpactMeshShapePart_unlockChildShapes a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_unlockChildShapes'_ a1' >>= \res ->
  return ()
{-# LINE 1964 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#850>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_getVertexCount :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO (Int)
btGImpactMeshShapePart_getVertexCount a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_getVertexCount'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1969 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#707>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_m_primitive_manager_set :: ( BtGImpactMeshShapePartClass bc , BtGImpactMeshShapePart_TrimeshPrimitiveManagerClass a ) => bc -> a -> IO ()
btGImpactMeshShapePart_m_primitive_manager_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactMeshShapePart_m_primitive_manager_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1973 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#707>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactMeshShapePart_m_primitive_manager_get :: ( BtGImpactMeshShapePartClass bc ) => bc -> IO (BtGImpactMeshShapePart_TrimeshPrimitiveManager)
btGImpactMeshShapePart_m_primitive_manager_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactMeshShapePart_m_primitive_manager_get'_ a1' >>= \res ->
  mkBtGImpactMeshShapePart_TrimeshPrimitiveManager res >>= \res' ->
  return (res')
{-# LINE 1977 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btGImpactQuantizedBvh
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#238>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh0 :: IO (BtGImpactQuantizedBvh)
btGImpactQuantizedBvh0 =
  btGImpactQuantizedBvh0'_ >>= \res ->
  mkBtGImpactQuantizedBvh res >>= \res' ->
  return (res')
{-# LINE 1982 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#244>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh1 :: ( BtPrimitiveManagerBaseClass p0 ) => p0 -> IO (BtGImpactQuantizedBvh)
btGImpactQuantizedBvh1 a1 =
  withBt a1 $ \a1' -> 
  btGImpactQuantizedBvh1'_ a1' >>= \res ->
  mkBtGImpactQuantizedBvh res >>= \res' ->
  return (res')
{-# LINE 1986 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btGImpactQuantizedBvh_free :: ( BtGImpactQuantizedBvhClass bc ) => bc -> IO ()
btGImpactQuantizedBvh_free a1 =
  withBt a1 $ \a1' -> 
  btGImpactQuantizedBvh_free'_ a1' >>= \res ->
  return ()
{-# LINE 1987 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#330>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_setNodeBound :: ( BtGImpactQuantizedBvhClass bc , BtAABBClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactQuantizedBvh_setNodeBound a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactQuantizedBvh_setNodeBound'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1994 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#346>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_getEscapeNodeIndex :: ( BtGImpactQuantizedBvhClass bc ) => bc -> Int -> IO (Int)
btGImpactQuantizedBvh_getEscapeNodeIndex a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactQuantizedBvh_getEscapeNodeIndex'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2000 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#315>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_isLeafNode :: ( BtGImpactQuantizedBvhClass bc ) => bc -> Int -> IO (Bool)
btGImpactQuantizedBvh_isLeafNode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactQuantizedBvh_isLeafNode'_ a1' a2' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2006 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#261>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_getPrimitiveManager :: ( BtGImpactQuantizedBvhClass bc ) => bc -> IO (BtPrimitiveManagerBase)
btGImpactQuantizedBvh_getPrimitiveManager a1 =
  withBt a1 $ \a1' -> 
  btGImpactQuantizedBvh_getPrimitiveManager'_ a1' >>= \res ->
  mkBtPrimitiveManagerBase res >>= \res' ->
  return (res')
{-# LINE 2011 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#325>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_getNodeBound :: ( BtGImpactQuantizedBvhClass bc , BtAABBClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactQuantizedBvh_getNodeBound a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactQuantizedBvh_getNodeBound'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2018 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#341>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_getRightNode :: ( BtGImpactQuantizedBvhClass bc ) => bc -> Int -> IO (Int)
btGImpactQuantizedBvh_getRightNode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactQuantizedBvh_getRightNode'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2024 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#336>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_getLeftNode :: ( BtGImpactQuantizedBvhClass bc ) => bc -> Int -> IO (Int)
btGImpactQuantizedBvh_getLeftNode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactQuantizedBvh_getLeftNode'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2030 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#256>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_setPrimitiveManager :: ( BtGImpactQuantizedBvhClass bc , BtPrimitiveManagerBaseClass p0 ) => bc -> p0 -> IO ()
btGImpactQuantizedBvh_setPrimitiveManager a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactQuantizedBvh_setPrimitiveManager'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2036 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#277>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_buildSet :: ( BtGImpactQuantizedBvhClass bc ) => bc -> IO ()
btGImpactQuantizedBvh_buildSet a1 =
  withBt a1 $ \a1' -> 
  btGImpactQuantizedBvh_buildSet'_ a1' >>= \res ->
  return ()
{-# LINE 2041 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#351>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_getNodeTriangle :: ( BtGImpactQuantizedBvhClass bc , BtPrimitiveTriangleClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactQuantizedBvh_getNodeTriangle a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactQuantizedBvh_getNodeTriangle'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2048 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#309>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_getNodeCount :: ( BtGImpactQuantizedBvhClass bc ) => bc -> IO (Int)
btGImpactQuantizedBvh_getNodeCount a1 =
  withBt a1 $ \a1' -> 
  btGImpactQuantizedBvh_getNodeCount'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2053 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#297>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_hasHierarchy :: ( BtGImpactQuantizedBvhClass bc ) => bc -> IO (Bool)
btGImpactQuantizedBvh_hasHierarchy a1 =
  withBt a1 $ \a1' -> 
  btGImpactQuantizedBvh_hasHierarchy'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2058 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#294>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_rayQuery :: ( BtGImpactQuantizedBvhClass bc , BtAlignedObjectArray_int_Class p2 ) => bc -> Vec3 -> Vec3 -> p2 -> IO (Bool, Vec3, Vec3)
btGImpactQuantizedBvh_rayQuery a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btGImpactQuantizedBvh_rayQuery'_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  let {res' = toBool res} in
  return (res', a2'', a3'')
{-# LINE 2066 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#294>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_rayQuery' :: ( BtGImpactQuantizedBvhClass bc , BtAlignedObjectArray_int_Class p2 ) => bc -> p2 -> IO (Bool, Vec3, Vec3)
btGImpactQuantizedBvh_rayQuery' a1 a4 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btGImpactQuantizedBvh_rayQuery''_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  let {res' = toBool res} in
  return (res', a2'', a3'')
{-# LINE 2074 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#271>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_update :: ( BtGImpactQuantizedBvhClass bc ) => bc -> IO ()
btGImpactQuantizedBvh_update a1 =
  withBt a1 $ \a1' -> 
  btGImpactQuantizedBvh_update'_ a1' >>= \res ->
  return ()
{-# LINE 2079 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#234>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_refit :: ( BtGImpactQuantizedBvhClass bc ) => bc -> IO ()
btGImpactQuantizedBvh_refit a1 =
  withBt a1 $ \a1' -> 
  btGImpactQuantizedBvh_refit'_ a1' >>= \res ->
  return ()
{-# LINE 2084 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#303>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_isTrimesh :: ( BtGImpactQuantizedBvhClass bc ) => bc -> IO (Bool)
btGImpactQuantizedBvh_isTrimesh a1 =
  withBt a1 $ \a1' -> 
  btGImpactQuantizedBvh_isTrimesh'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2089 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#280>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_boxQuery :: ( BtGImpactQuantizedBvhClass bc , BtAABBClass p0 , BtAlignedObjectArray_int_Class p1 ) => bc -> p0 -> p1 -> IO (Bool)
btGImpactQuantizedBvh_boxQuery a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btGImpactQuantizedBvh_boxQuery'_ a1' a2' a3' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2096 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#368>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_find_collision :: (  BtGImpactQuantizedBvhClass p0 , BtGImpactQuantizedBvhClass p2 , BtPairSetClass p4 ) => p0 -> Transform -> p2 -> Transform -> p4 -> IO (Transform, Transform)
btGImpactQuantizedBvh_find_collision a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  withBt a5 $ \a5' -> 
  btGImpactQuantizedBvh_find_collision'_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a4'>>= \a4'' -> 
  return (a2'', a4'')
{-# LINE 2105 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#368>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_find_collision' :: (  BtGImpactQuantizedBvhClass p0 , BtGImpactQuantizedBvhClass p2 , BtPairSetClass p4 ) => p0 -> p2 -> p4 -> IO (Transform, Transform)
btGImpactQuantizedBvh_find_collision' a1 a3 a5 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  withBt a3 $ \a3' -> 
  allocaTransform $ \a4' -> 
  withBt a5 $ \a5' -> 
  btGImpactQuantizedBvh_find_collision''_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a4'>>= \a4'' -> 
  return (a2'', a4'')
{-# LINE 2114 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#357>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_get_node_pointer :: ( BtGImpactQuantizedBvhClass bc ) => bc -> Int -> IO (BT_QUANTIZED_BVH_NODE)
btGImpactQuantizedBvh_get_node_pointer a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactQuantizedBvh_get_node_pointer'_ a1' a2' >>= \res ->
  mkBT_QUANTIZED_BVH_NODE res >>= \res' ->
  return (res')
{-# LINE 2120 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#284>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_boxQueryTrans :: ( BtGImpactQuantizedBvhClass bc , BtAABBClass p0 , BtAlignedObjectArray_int_Class p2 ) => bc -> p0 -> Transform -> p2 -> IO (Bool, Transform)
btGImpactQuantizedBvh_boxQueryTrans a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btGImpactQuantizedBvh_boxQueryTrans'_ a1' a2' a3' a4' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  let {res' = toBool res} in
  return (res', a3'')
{-# LINE 2128 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#284>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_boxQueryTrans' :: ( BtGImpactQuantizedBvhClass bc , BtAABBClass p0 , BtAlignedObjectArray_int_Class p2 ) => bc -> p0 -> p2 -> IO (Bool, Transform)
btGImpactQuantizedBvh_boxQueryTrans' a1 a2 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaTransform $ \a3' -> 
  withBt a4 $ \a4' -> 
  btGImpactQuantizedBvh_boxQueryTrans''_ a1' a2' a3' a4' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  let {res' = toBool res} in
  return (res', a3'')
{-# LINE 2136 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#320>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_getNodeData :: ( BtGImpactQuantizedBvhClass bc ) => bc -> Int -> IO (Int)
btGImpactQuantizedBvh_getNodeData a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactQuantizedBvh_getNodeData'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2142 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#229>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_m_box_tree_set :: ( BtGImpactQuantizedBvhClass bc , BtQuantizedBvhTreeClass a ) => bc -> a -> IO ()
btGImpactQuantizedBvh_m_box_tree_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactQuantizedBvh_m_box_tree_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2146 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#229>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_m_box_tree_get :: ( BtGImpactQuantizedBvhClass bc ) => bc -> IO (BtQuantizedBvhTree)
btGImpactQuantizedBvh_m_box_tree_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactQuantizedBvh_m_box_tree_get'_ a1' >>= \res ->
  mkBtQuantizedBvhTree res >>= \res' ->
  return (res')
{-# LINE 2150 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_m_primitive_manager_set :: ( BtGImpactQuantizedBvhClass bc , BtPrimitiveManagerBaseClass a ) => bc -> a -> IO ()
btGImpactQuantizedBvh_m_primitive_manager_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactQuantizedBvh_m_primitive_manager_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2154 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btGImpactQuantizedBvh_m_primitive_manager_get :: ( BtGImpactQuantizedBvhClass bc ) => bc -> IO (BtPrimitiveManagerBase)
btGImpactQuantizedBvh_m_primitive_manager_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactQuantizedBvh_m_primitive_manager_get'_ a1' >>= \res ->
  mkBtPrimitiveManagerBase res >>= \res' ->
  return (res')
{-# LINE 2158 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btGImpactShapeInterface
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#239>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getPrimitiveTriangle :: ( BtGImpactShapeInterfaceClass bc , BtPrimitiveTriangleClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactShapeInterface_getPrimitiveTriangle a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactShapeInterface_getPrimitiveTriangle'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2166 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#271>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_setChildTransform :: ( BtGImpactShapeInterfaceClass bc ) => bc -> Int -> Transform -> IO (Transform)
btGImpactShapeInterface_setChildTransform a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withTransform a3 $ \a3' -> 
  btGImpactShapeInterface_setChildTransform'_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 2173 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#271>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_setChildTransform' :: ( BtGImpactShapeInterfaceClass bc ) => bc -> Int -> IO (Transform)
btGImpactShapeInterface_setChildTransform' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  btGImpactShapeInterface_setChildTransform''_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 2180 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#168>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getLocalScaling :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (Vec3)
btGImpactShapeInterface_getLocalScaling a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGImpactShapeInterface_getLocalScaling'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 2186 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getLocalBox :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (BtAABB)
btGImpactShapeInterface_getLocalBox a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_getLocalBox'_ a1' >>= \res ->
  mkBtAABB res >>= \res' ->
  return (res')
{-# LINE 2191 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#208>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getPrimitiveManager :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (BtPrimitiveManagerBase)
btGImpactShapeInterface_getPrimitiveManager a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_getPrimitiveManager'_ a1' >>= \res ->
  mkBtPrimitiveManagerBase res >>= \res' ->
  return (res')
{-# LINE 2196 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#286>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_processAllTriangles :: ( BtGImpactShapeInterfaceClass bc , BtTriangleCallbackClass p0 ) => bc -> p0 -> Vec3 -> Vec3 -> IO (Vec3, Vec3)
btGImpactShapeInterface_processAllTriangles a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btGImpactShapeInterface_processAllTriangles'_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a3'', a4'')
{-# LINE 2204 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#286>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_processAllTriangles' :: ( BtGImpactShapeInterfaceClass bc , BtTriangleCallbackClass p0 ) => bc -> p0 -> IO (Vec3, Vec3)
btGImpactShapeInterface_processAllTriangles' a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  btGImpactShapeInterface_processAllTriangles''_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a3'', a4'')
{-# LINE 2212 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#201>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_hasBoxSet :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (Bool)
btGImpactShapeInterface_hasBoxSet a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_hasBoxSet'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2217 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#277>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_rayTest :: ( BtGImpactShapeInterfaceClass bc , BtCollisionWorld_RayResultCallbackClass p2 ) => bc -> Vec3 -> Vec3 -> p2 -> IO (Vec3, Vec3)
btGImpactShapeInterface_rayTest a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btGImpactShapeInterface_rayTest'_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 2225 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#277>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_rayTest' :: ( BtGImpactShapeInterfaceClass bc , BtCollisionWorld_RayResultCallbackClass p2 ) => bc -> p2 -> IO (Vec3, Vec3)
btGImpactShapeInterface_rayTest' a1 a4 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  withBt a4 $ \a4' -> 
  btGImpactShapeInterface_rayTest''_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 2233 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#195>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getBoxSet :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (BtGImpactQuantizedBvh)
btGImpactShapeInterface_getBoxSet a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_getBoxSet'_ a1' >>= \res ->
  mkBtGImpactQuantizedBvh res >>= \res' ->
  return (res')
{-# LINE 2238 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#223>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getBulletTriangle :: ( BtGImpactShapeInterfaceClass bc , BtTriangleShapeExClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactShapeInterface_getBulletTriangle a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactShapeInterface_getBulletTriangle'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2245 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#162>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_setLocalScaling :: ( BtGImpactShapeInterfaceClass bc ) => bc -> Vec3 -> IO (Vec3)
btGImpactShapeInterface_setLocalScaling a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGImpactShapeInterface_setLocalScaling'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 2251 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#162>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_setLocalScaling' :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (Vec3)
btGImpactShapeInterface_setLocalScaling' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGImpactShapeInterface_setLocalScaling''_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 2257 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#218>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_needsRetrieveTriangles :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (Bool)
btGImpactShapeInterface_needsRetrieveTriangles a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_needsRetrieveTriangles'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2262 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#215>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_childrenHasTransform :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (Bool)
btGImpactShapeInterface_childrenHasTransform a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_childrenHasTransform'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2267 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#133>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getAabb :: ( BtGImpactShapeInterfaceClass bc ) => bc -> Transform -> Vec3 -> Vec3 -> IO (Transform, Vec3, Vec3)
btGImpactShapeInterface_getAabb a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btGImpactShapeInterface_getAabb'_ a1' a2' a3' a4' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 2275 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#133>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getAabb' :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (Transform, Vec3, Vec3)
btGImpactShapeInterface_getAabb' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  btGImpactShapeInterface_getAabb''_ a1' a2' a3' a4' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 2283 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#258>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getChildShape :: ( BtGImpactShapeInterfaceClass bc ) => bc -> Int -> IO (BtCollisionShape)
btGImpactShapeInterface_getChildShape a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactShapeInterface_getChildShape'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 2289 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#258>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getChildShape0 :: ( BtGImpactShapeInterfaceClass bc ) => bc -> Int -> IO (BtCollisionShape)
btGImpactShapeInterface_getChildShape0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactShapeInterface_getChildShape0'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 2295 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#262>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getChildShape1 :: ( BtGImpactShapeInterfaceClass bc ) => bc -> Int -> IO (BtCollisionShape)
btGImpactShapeInterface_getChildShape1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGImpactShapeInterface_getChildShape1'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 2301 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_calcLocalAABB :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO ()
btGImpactShapeInterface_calcLocalAABB a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_calcLocalAABB'_ a1' >>= \res ->
  return ()
{-# LINE 2306 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getChildTransform :: ( BtGImpactShapeInterfaceClass bc ) => bc -> Int -> IO (Transform)
btGImpactShapeInterface_getChildTransform a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  btGImpactShapeInterface_getChildTransform'_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 2313 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_lockChildShapes :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO ()
btGImpactShapeInterface_lockChildShapes a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_lockChildShapes'_ a1' >>= \res ->
  return ()
{-# LINE 2318 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#174>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_setMargin :: ( BtGImpactShapeInterfaceClass bc ) => bc -> Float -> IO ()
btGImpactShapeInterface_setMargin a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btGImpactShapeInterface_setMargin'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2324 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#212>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getNumChildShapes :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (Int)
btGImpactShapeInterface_getNumChildShapes a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_getNumChildShapes'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2329 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#248>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getChildAabb :: ( BtGImpactShapeInterfaceClass bc ) => bc -> Int -> Transform -> Vec3 -> Vec3 -> IO (Transform, Vec3, Vec3)
btGImpactShapeInterface_getChildAabb a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withTransform a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btGImpactShapeInterface_getChildAabb'_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a3'', a4'', a5'')
{-# LINE 2338 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#248>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getChildAabb' :: ( BtGImpactShapeInterfaceClass bc ) => bc -> Int -> IO (Transform, Vec3, Vec3)
btGImpactShapeInterface_getChildAabb' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  btGImpactShapeInterface_getChildAabb''_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a3'', a4'', a5'')
{-# LINE 2347 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#154>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getShapeType :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (Int)
btGImpactShapeInterface_getShapeType a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_getShapeType'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2352 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_getBulletTetrahedron :: ( BtGImpactShapeInterfaceClass bc , BtTetrahedronShapeExClass p1 ) => bc -> Int -> p1 -> IO ()
btGImpactShapeInterface_getBulletTetrahedron a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btGImpactShapeInterface_getBulletTetrahedron'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2359 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#221>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_needsRetrieveTetrahedrons :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (Bool)
btGImpactShapeInterface_needsRetrieveTetrahedrons a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_needsRetrieveTetrahedrons'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2364 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#234>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_unlockChildShapes :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO ()
btGImpactShapeInterface_unlockChildShapes a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_unlockChildShapes'_ a1' >>= \res ->
  return ()
{-# LINE 2369 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#142>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_postUpdate :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO ()
btGImpactShapeInterface_postUpdate a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_postUpdate'_ a1' >>= \res ->
  return ()
{-# LINE 2374 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#122>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_updateBound :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO ()
btGImpactShapeInterface_updateBound a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_updateBound'_ a1' >>= \res ->
  return ()
{-# LINE 2379 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_localScaling_set :: ( BtGImpactShapeInterfaceClass bc ) => bc -> Vec3 -> IO ()
btGImpactShapeInterface_localScaling_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btGImpactShapeInterface_localScaling_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2383 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_localScaling_get :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (Vec3)
btGImpactShapeInterface_localScaling_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btGImpactShapeInterface_localScaling_get'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 2387 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#84>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_m_box_set_set :: ( BtGImpactShapeInterfaceClass bc , BtGImpactQuantizedBvhClass a ) => bc -> a -> IO ()
btGImpactShapeInterface_m_box_set_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactShapeInterface_m_box_set_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2391 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#84>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_m_box_set_get :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (BtGImpactQuantizedBvh)
btGImpactShapeInterface_m_box_set_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_m_box_set_get'_ a1' >>= \res ->
  mkBtGImpactQuantizedBvh res >>= \res' ->
  return (res')
{-# LINE 2395 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_m_localAABB_set :: ( BtGImpactShapeInterfaceClass bc , BtAABBClass a ) => bc -> a -> IO ()
btGImpactShapeInterface_m_localAABB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGImpactShapeInterface_m_localAABB_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2399 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_m_localAABB_get :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (BtAABB)
btGImpactShapeInterface_m_localAABB_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_m_localAABB_get'_ a1' >>= \res ->
  mkBtAABB res >>= \res' ->
  return (res')
{-# LINE 2403 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_m_needs_update_set :: ( BtGImpactShapeInterfaceClass bc ) => bc -> Bool -> IO ()
btGImpactShapeInterface_m_needs_update_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btGImpactShapeInterface_m_needs_update_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2407 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btGImpactShapeInterface_m_needs_update_get :: ( BtGImpactShapeInterfaceClass bc ) => bc -> IO (Bool)
btGImpactShapeInterface_m_needs_update_get a1 =
  withBt a1 $ \a1' -> 
  btGImpactShapeInterface_m_needs_update_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2411 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btPairSet
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btPairSet :: IO (BtPairSet)
btPairSet =
  btPairSet'_ >>= \res ->
  mkBtPairSet res >>= \res' ->
  return (res')
{-# LINE 2416 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btPairSet_free :: ( BtPairSetClass bc ) => bc -> IO ()
btPairSet_free a1 =
  withBt a1 $ \a1' -> 
  btPairSet_free'_ a1' >>= \res ->
  return ()
{-# LINE 2417 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#71>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btPairSet_push_pair_inv :: ( BtPairSetClass bc ) => bc -> Int -> Int -> IO ()
btPairSet_push_pair_inv a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btPairSet_push_pair_inv'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2424 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btPairSet_push_pair :: ( BtPairSetClass bc ) => bc -> Int -> Int -> IO ()
btPairSet_push_pair a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btPairSet_push_pair'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2431 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btPrimitiveManagerBase
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#239>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btPrimitiveManagerBase_get_primitive_box :: ( BtPrimitiveManagerBaseClass bc , BtAABBClass p1 ) => bc -> Int -> p1 -> IO ()
btPrimitiveManagerBase_get_primitive_box a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btPrimitiveManagerBase_get_primitive_box'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2439 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#241>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btPrimitiveManagerBase_get_primitive_triangle :: ( BtPrimitiveManagerBaseClass bc , BtPrimitiveTriangleClass p1 ) => bc -> Int -> p1 -> IO ()
btPrimitiveManagerBase_get_primitive_triangle a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btPrimitiveManagerBase_get_primitive_triangle'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2446 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#237>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btPrimitiveManagerBase_is_trimesh :: ( BtPrimitiveManagerBaseClass bc ) => bc -> IO (Bool)
btPrimitiveManagerBase_is_trimesh a1 =
  withBt a1 $ \a1' -> 
  btPrimitiveManagerBase_is_trimesh'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2451 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.h?r=2223#238>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactBvh.cpp?r=2223>
-}
btPrimitiveManagerBase_get_primitive_count :: ( BtPrimitiveManagerBaseClass bc ) => bc -> IO (Int)
btPrimitiveManagerBase_get_primitive_count a1 =
  withBt a1 $ \a1' -> 
  btPrimitiveManagerBase_get_primitive_count'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2456 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btPrimitiveTriangle
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle :: IO (BtPrimitiveTriangle)
btPrimitiveTriangle =
  btPrimitiveTriangle'_ >>= \res ->
  mkBtPrimitiveTriangle res >>= \res' ->
  return (res')
{-# LINE 2461 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btPrimitiveTriangle_free :: ( BtPrimitiveTriangleClass bc ) => bc -> IO ()
btPrimitiveTriangle_free a1 =
  withBt a1 $ \a1' -> 
  btPrimitiveTriangle_free'_ a1' >>= \res ->
  return ()
{-# LINE 2462 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#101>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle_get_edge_plane :: ( BtPrimitiveTriangleClass bc ) => bc -> Int -> Vec4 -> IO (Vec4)
btPrimitiveTriangle_get_edge_plane a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withVec4 a3 $ \a3' -> 
  btPrimitiveTriangle_get_edge_plane'_ a1' a2' a3' >>= \res ->
  peekVec4  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 2469 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#101>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle_get_edge_plane' :: ( BtPrimitiveTriangleClass bc ) => bc -> Int -> IO (Vec4)
btPrimitiveTriangle_get_edge_plane' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaVec4 $ \a3' -> 
  btPrimitiveTriangle_get_edge_plane''_ a1' a2' a3' >>= \res ->
  peekVec4  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 2476 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#95>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle_overlap_test_conservative :: ( BtPrimitiveTriangleClass bc , BtPrimitiveTriangleClass p0 ) => bc -> p0 -> IO (Bool)
btPrimitiveTriangle_overlap_test_conservative a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btPrimitiveTriangle_overlap_test_conservative'_ a1' a2' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2482 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#87>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle_buildTriPlane :: ( BtPrimitiveTriangleClass bc ) => bc -> IO ()
btPrimitiveTriangle_buildTriPlane a1 =
  withBt a1 $ \a1' -> 
  btPrimitiveTriangle_buildTriPlane'_ a1' >>= \res ->
  return ()
{-# LINE 2487 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#108>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle_applyTransform :: ( BtPrimitiveTriangleClass bc ) => bc -> Transform -> IO (Transform)
btPrimitiveTriangle_applyTransform a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btPrimitiveTriangle_applyTransform'_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 2493 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#108>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle_applyTransform' :: ( BtPrimitiveTriangleClass bc ) => bc -> IO (Transform)
btPrimitiveTriangle_applyTransform' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btPrimitiveTriangle_applyTransform''_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 2499 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#126>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle_find_triangle_collision_clip_method :: ( BtPrimitiveTriangleClass bc , BtPrimitiveTriangleClass p0 , GIM_TRIANGLE_CONTACTClass p1 ) => bc -> p0 -> p1 -> IO (Bool)
btPrimitiveTriangle_find_triangle_collision_clip_method a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btPrimitiveTriangle_find_triangle_collision_clip_method'_ a1' a2' a3' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2506 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle_m_dummy_set :: ( BtPrimitiveTriangleClass bc ) => bc -> Float -> IO ()
btPrimitiveTriangle_m_dummy_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btPrimitiveTriangle_m_dummy_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2510 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle_m_dummy_get :: ( BtPrimitiveTriangleClass bc ) => bc -> IO (Float)
btPrimitiveTriangle_m_dummy_get a1 =
  withBt a1 $ \a1' -> 
  btPrimitiveTriangle_m_dummy_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 2514 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#79>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle_m_margin_set :: ( BtPrimitiveTriangleClass bc ) => bc -> Float -> IO ()
btPrimitiveTriangle_m_margin_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btPrimitiveTriangle_m_margin_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2518 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#79>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle_m_margin_get :: ( BtPrimitiveTriangleClass bc ) => bc -> IO (Float)
btPrimitiveTriangle_m_margin_get a1 =
  withBt a1 $ \a1' -> 
  btPrimitiveTriangle_m_margin_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 2522 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#78>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle_m_plane_set :: ( BtPrimitiveTriangleClass bc ) => bc -> Vec4 -> IO ()
btPrimitiveTriangle_m_plane_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec4 a2 $ \a2' -> 
  btPrimitiveTriangle_m_plane_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2526 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#78>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btPrimitiveTriangle_m_plane_get :: ( BtPrimitiveTriangleClass bc ) => bc -> IO (Vec4)
btPrimitiveTriangle_m_plane_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec4 $ \a2' -> 
  btPrimitiveTriangle_m_plane_get'_ a1' a2' >>= \res ->
  peekVec4  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 2530 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btQuantizedBvhTree
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#123>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree :: IO (BtQuantizedBvhTree)
btQuantizedBvhTree =
  btQuantizedBvhTree'_ >>= \res ->
  mkBtQuantizedBvhTree res >>= \res' ->
  return (res')
{-# LINE 2535 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btQuantizedBvhTree_free :: ( BtQuantizedBvhTreeClass bc ) => bc -> IO ()
btQuantizedBvhTree_free a1 =
  withBt a1 $ \a1' -> 
  btQuantizedBvhTree_free'_ a1' >>= \res ->
  return ()
{-# LINE 2536 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#153>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_getNodeCount :: ( BtQuantizedBvhTreeClass bc ) => bc -> IO (Int)
btQuantizedBvhTree_getNodeCount a1 =
  withBt a1 $ \a1' -> 
  btQuantizedBvhTree_getNodeCount'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2541 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_calc_quantization :: ( BtQuantizedBvhTreeClass bc , GIM_BVH_DATA_ARRAYClass p0 ) => bc -> p0 -> Float -> IO ()
btQuantizedBvhTree_calc_quantization a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btQuantizedBvhTree_calc_quantization'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2548 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#130>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_build_tree :: ( BtQuantizedBvhTreeClass bc , GIM_BVH_DATA_ARRAYClass p0 ) => bc -> p0 -> IO ()
btQuantizedBvhTree_build_tree a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btQuantizedBvhTree_build_tree'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2554 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_setNodeBound :: ( BtQuantizedBvhTreeClass bc , BtAABBClass p1 ) => bc -> Int -> p1 -> IO ()
btQuantizedBvhTree_setNodeBound a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btQuantizedBvhTree_setNodeBound'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2561 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#195>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_getLeftNode :: ( BtQuantizedBvhTreeClass bc ) => bc -> Int -> IO (Int)
btQuantizedBvhTree_getLeftNode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btQuantizedBvhTree_getLeftNode'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2567 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#121>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree__build_sub_tree :: ( BtQuantizedBvhTreeClass bc , GIM_BVH_DATA_ARRAYClass p0 ) => bc -> p0 -> Int -> Int -> IO ()
btQuantizedBvhTree__build_sub_tree a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btQuantizedBvhTree__build_sub_tree'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 2575 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#146>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_clearNodes :: ( BtQuantizedBvhTreeClass bc ) => bc -> IO ()
btQuantizedBvhTree_clearNodes a1 =
  withBt a1 $ \a1' -> 
  btQuantizedBvhTree_clearNodes'_ a1' >>= \res ->
  return ()
{-# LINE 2580 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#117>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree__sort_and_calc_splitting_index :: ( BtQuantizedBvhTreeClass bc , GIM_BVH_DATA_ARRAYClass p0 ) => bc -> p0 -> Int -> Int -> Int -> IO (Int)
btQuantizedBvhTree__sort_and_calc_splitting_index a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  btQuantizedBvhTree__sort_and_calc_splitting_index'_ a1' a2' a3' a4' a5' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2589 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#206>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_getEscapeNodeIndex :: ( BtQuantizedBvhTreeClass bc ) => bc -> Int -> IO (Int)
btQuantizedBvhTree_getEscapeNodeIndex a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btQuantizedBvhTree_getEscapeNodeIndex'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2595 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#159>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_isLeafNode :: ( BtQuantizedBvhTreeClass bc ) => bc -> Int -> IO (Bool)
btQuantizedBvhTree_isLeafNode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btQuantizedBvhTree_isLeafNode'_ a1' a2' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2601 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#211>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_get_node_pointer :: ( BtQuantizedBvhTreeClass bc ) => bc -> Int -> IO (BT_QUANTIZED_BVH_NODE)
btQuantizedBvhTree_get_node_pointer a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btQuantizedBvhTree_get_node_pointer'_ a1' a2' >>= \res ->
  mkBT_QUANTIZED_BVH_NODE res >>= \res' ->
  return (res')
{-# LINE 2607 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#164>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_getNodeData :: ( BtQuantizedBvhTreeClass bc ) => bc -> Int -> IO (Int)
btQuantizedBvhTree_getNodeData a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btQuantizedBvhTree_getNodeData'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2613 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#169>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_getNodeBound :: ( BtQuantizedBvhTreeClass bc , BtAABBClass p1 ) => bc -> Int -> p1 -> IO ()
btQuantizedBvhTree_getNodeBound a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btQuantizedBvhTree_getNodeBound'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2620 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#200>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_getRightNode :: ( BtQuantizedBvhTreeClass bc ) => bc -> Int -> IO (Int)
btQuantizedBvhTree_getRightNode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btQuantizedBvhTree_getRightNode'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2626 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#119>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree__calc_splitting_axis :: ( BtQuantizedBvhTreeClass bc , GIM_BVH_DATA_ARRAYClass p0 ) => bc -> p0 -> Int -> Int -> IO (Int)
btQuantizedBvhTree__calc_splitting_axis a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btQuantizedBvhTree__calc_splitting_axis'_ a1' a2' a3' a4' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2634 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_m_bvhQuantization_set :: ( BtQuantizedBvhTreeClass bc ) => bc -> Vec3 -> IO ()
btQuantizedBvhTree_m_bvhQuantization_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btQuantizedBvhTree_m_bvhQuantization_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2638 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_m_bvhQuantization_get :: ( BtQuantizedBvhTreeClass bc ) => bc -> IO (Vec3)
btQuantizedBvhTree_m_bvhQuantization_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btQuantizedBvhTree_m_bvhQuantization_get'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 2642 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#110>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_m_global_bound_set :: ( BtQuantizedBvhTreeClass bc , BtAABBClass a ) => bc -> a -> IO ()
btQuantizedBvhTree_m_global_bound_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btQuantizedBvhTree_m_global_bound_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2646 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#110>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_m_global_bound_get :: ( BtQuantizedBvhTreeClass bc ) => bc -> IO (BtAABB)
btQuantizedBvhTree_m_global_bound_get a1 =
  withBt a1 $ \a1' -> 
  btQuantizedBvhTree_m_global_bound_get'_ a1' >>= \res ->
  mkBtAABB res >>= \res' ->
  return (res')
{-# LINE 2650 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#109>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_m_node_array_set :: ( BtQuantizedBvhTreeClass bc , GIM_QUANTIZED_BVH_NODE_ARRAYClass a ) => bc -> a -> IO ()
btQuantizedBvhTree_m_node_array_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btQuantizedBvhTree_m_node_array_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2654 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#109>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_m_node_array_get :: ( BtQuantizedBvhTreeClass bc ) => bc -> IO (GIM_QUANTIZED_BVH_NODE_ARRAY)
btQuantizedBvhTree_m_node_array_get a1 =
  withBt a1 $ \a1' -> 
  btQuantizedBvhTree_m_node_array_get'_ a1' >>= \res ->
  mkGIM_QUANTIZED_BVH_NODE_ARRAY res >>= \res' ->
  return (res')
{-# LINE 2658 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#108>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_m_num_nodes_set :: ( BtQuantizedBvhTreeClass bc ) => bc -> Int -> IO ()
btQuantizedBvhTree_m_num_nodes_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btQuantizedBvhTree_m_num_nodes_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2662 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.h?r=2223#108>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactQuantizedBvh.cpp?r=2223>
-}
btQuantizedBvhTree_m_num_nodes_get :: ( BtQuantizedBvhTreeClass bc ) => bc -> IO (Int)
btQuantizedBvhTree_m_num_nodes_get a1 =
  withBt a1 $ \a1' -> 
  btQuantizedBvhTree_m_num_nodes_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2666 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btTetrahedronShapeEx
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#58>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btTetrahedronShapeEx :: IO (BtTetrahedronShapeEx)
btTetrahedronShapeEx =
  btTetrahedronShapeEx'_ >>= \res ->
  mkBtTetrahedronShapeEx res >>= \res' ->
  return (res')
{-# LINE 2671 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btTetrahedronShapeEx_free :: ( BtTetrahedronShapeExClass bc ) => bc -> IO ()
btTetrahedronShapeEx_free a1 =
  withBt a1 $ \a1' -> 
  btTetrahedronShapeEx_free'_ a1' >>= \res ->
  return ()
{-# LINE 2672 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btTetrahedronShapeEx_setVertices :: ( BtTetrahedronShapeExClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> Vec3 -> IO (Vec3, Vec3, Vec3, Vec3)
btTetrahedronShapeEx_setVertices a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btTetrahedronShapeEx_setVertices'_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')
{-# LINE 2681 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btGImpactShape.cpp?r=2223>
-}
btTetrahedronShapeEx_setVertices' :: ( BtTetrahedronShapeExClass bc ) => bc -> IO (Vec3, Vec3, Vec3, Vec3)
btTetrahedronShapeEx_setVertices' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  btTetrahedronShapeEx_setVertices''_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')
{-# LINE 2690 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
-- * btTriangleShapeEx
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#139>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btTriangleShapeEx0 :: IO (BtTriangleShapeEx)
btTriangleShapeEx0 =
  btTriangleShapeEx0'_ >>= \res ->
  mkBtTriangleShapeEx res >>= \res' ->
  return (res')
{-# LINE 2695 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#143>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btTriangleShapeEx1 :: Vec3 -> Vec3 -> Vec3 -> IO (BtTriangleShapeEx)
btTriangleShapeEx1 a1 a2 a3 =
  withVec3 a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  btTriangleShapeEx1'_ a1' a2' a3' >>= \res ->
  mkBtTriangleShapeEx res >>= \res' ->
  return (res')
{-# LINE 2699 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
btTriangleShapeEx_free :: ( BtTriangleShapeExClass bc ) => bc -> IO ()
btTriangleShapeEx_free a1 =
  withBt a1 $ \a1' -> 
  btTriangleShapeEx_free'_ a1' >>= \res ->
  return ()
{-# LINE 2700 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#176>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btTriangleShapeEx_overlap_test_conservative :: ( BtTriangleShapeExClass bc , BtTriangleShapeExClass p0 ) => bc -> p0 -> IO (Bool)
btTriangleShapeEx_overlap_test_conservative a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btTriangleShapeEx_overlap_test_conservative'_ a1' a2' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2706 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#169>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btTriangleShapeEx_buildTriPlane :: ( BtTriangleShapeExClass bc ) => bc -> Vec4 -> IO (Vec4)
btTriangleShapeEx_buildTriPlane a1 a2 =
  withBt a1 $ \a1' -> 
  withVec4 a2 $ \a2' -> 
  btTriangleShapeEx_buildTriPlane'_ a1' a2' >>= \res ->
  peekVec4  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 2712 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#169>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btTriangleShapeEx_buildTriPlane' :: ( BtTriangleShapeExClass bc ) => bc -> IO (Vec4)
btTriangleShapeEx_buildTriPlane' a1 =
  withBt a1 $ \a1' -> 
  allocaVec4 $ \a2' -> 
  btTriangleShapeEx_buildTriPlane''_ a1' a2' >>= \res ->
  peekVec4  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 2718 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#162>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btTriangleShapeEx_applyTransform :: ( BtTriangleShapeExClass bc ) => bc -> Transform -> IO (Transform)
btTriangleShapeEx_applyTransform a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btTriangleShapeEx_applyTransform'_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 2724 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#162>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btTriangleShapeEx_applyTransform' :: ( BtTriangleShapeExClass bc ) => bc -> IO (Transform)
btTriangleShapeEx_applyTransform' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btTriangleShapeEx_applyTransform''_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 2730 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#151>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btTriangleShapeEx_getAabb :: ( BtTriangleShapeExClass bc ) => bc -> Transform -> Vec3 -> Vec3 -> IO (Transform, Vec3, Vec3)
btTriangleShapeEx_getAabb a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btTriangleShapeEx_getAabb'_ a1' a2' a3' a4' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 2738 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.h?r=2223#151>
     <http://code.google.com/p/bullet/source/browse/trunk/src/BulletCollision/Gimpact/btTriangleShapeEx.cpp?r=2223>
-}
btTriangleShapeEx_getAabb' :: ( BtTriangleShapeExClass bc ) => bc -> IO (Transform, Vec3, Vec3)
btTriangleShapeEx_getAabb' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  btTriangleShapeEx_getAabb''_ a1' a2' a3' a4' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 2746 "./Physics/Bullet/Raw/BulletCollision/Gimpact.chs" #-}

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_new"
  bT_BOX_BOX_TRANSFORM_CACHE'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_free"
  bT_BOX_BOX_TRANSFORM_CACHE_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_calc_from_full_invert"
  bT_BOX_BOX_TRANSFORM_CACHE_calc_from_full_invert'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_calc_from_full_invert"
  bT_BOX_BOX_TRANSFORM_CACHE_calc_from_full_invert''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_calc_from_homogenic"
  bT_BOX_BOX_TRANSFORM_CACHE_calc_from_homogenic'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_calc_from_homogenic"
  bT_BOX_BOX_TRANSFORM_CACHE_calc_from_homogenic''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_transform"
  bT_BOX_BOX_TRANSFORM_CACHE_transform'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_transform"
  bT_BOX_BOX_TRANSFORM_CACHE_transform''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_calc_absolute_matrix"
  bT_BOX_BOX_TRANSFORM_CACHE_calc_absolute_matrix'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_m_T1to0_set"
  bT_BOX_BOX_TRANSFORM_CACHE_m_T1to0_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_m_T1to0_get"
  bT_BOX_BOX_TRANSFORM_CACHE_m_T1to0_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_m_R1to0_set"
  bT_BOX_BOX_TRANSFORM_CACHE_m_R1to0_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_m_R1to0_get"
  bT_BOX_BOX_TRANSFORM_CACHE_m_R1to0_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_m_AR_set"
  bT_BOX_BOX_TRANSFORM_CACHE_m_AR_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_BOX_BOX_TRANSFORM_CACHE_m_AR_get"
  bT_BOX_BOX_TRANSFORM_CACHE_m_AR_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_QUANTIZED_BVH_NODE_new"
  bT_QUANTIZED_BVH_NODE'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_QUANTIZED_BVH_NODE_free"
  bT_QUANTIZED_BVH_NODE_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_QUANTIZED_BVH_NODE_getEscapeIndex"
  bT_QUANTIZED_BVH_NODE_getEscapeIndex'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_QUANTIZED_BVH_NODE_getDataIndex"
  bT_QUANTIZED_BVH_NODE_getDataIndex'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_QUANTIZED_BVH_NODE_setEscapeIndex"
  bT_QUANTIZED_BVH_NODE_setEscapeIndex'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_QUANTIZED_BVH_NODE_setDataIndex"
  bT_QUANTIZED_BVH_NODE_setDataIndex'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_QUANTIZED_BVH_NODE_isLeafNode"
  bT_QUANTIZED_BVH_NODE_isLeafNode'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_QUANTIZED_BVH_NODE_m_escapeIndexOrDataIndex_set"
  bT_QUANTIZED_BVH_NODE_m_escapeIndexOrDataIndex_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h bT_QUANTIZED_BVH_NODE_m_escapeIndexOrDataIndex_get"
  bT_QUANTIZED_BVH_NODE_m_escapeIndexOrDataIndex_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_CompoundPrimitiveManager_new0"
  btGImpactCompoundShape_CompoundPrimitiveManager0'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_CompoundPrimitiveManager_new1"
  btGImpactCompoundShape_CompoundPrimitiveManager1'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_CompoundPrimitiveManager_free"
  btGImpactCompoundShape_CompoundPrimitiveManager_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_count"
  btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_count'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_triangle"
  btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_triangle'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_box"
  btGImpactCompoundShape_CompoundPrimitiveManager_get_primitive_box'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_CompoundPrimitiveManager_is_trimesh"
  btGImpactCompoundShape_CompoundPrimitiveManager_is_trimesh'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_CompoundPrimitiveManager_m_compoundShape_set"
  btGImpactCompoundShape_CompoundPrimitiveManager_m_compoundShape_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_CompoundPrimitiveManager_m_compoundShape_get"
  btGImpactCompoundShape_CompoundPrimitiveManager_m_compoundShape_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_CreateFunc_new"
  btGImpactCollisionAlgorithm_CreateFunc'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_CreateFunc_free"
  btGImpactCollisionAlgorithm_CreateFunc_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_CreateFunc_CreateCollisionAlgorithm"
  btGImpactCollisionAlgorithm_CreateFunc_CreateCollisionAlgorithm'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_DATA_new"
  gIM_BVH_DATA'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_DATA_free"
  gIM_BVH_DATA_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_DATA_m_bound_set"
  gIM_BVH_DATA_m_bound_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_DATA_m_bound_get"
  gIM_BVH_DATA_m_bound_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_DATA_m_data_set"
  gIM_BVH_DATA_m_data_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_DATA_m_data_get"
  gIM_BVH_DATA_m_data_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_DATA_ARRAY_new"
  gIM_BVH_DATA_ARRAY'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_DATA_ARRAY_free"
  gIM_BVH_DATA_ARRAY_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_TREE_NODE_new"
  gIM_BVH_TREE_NODE'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_TREE_NODE_free"
  gIM_BVH_TREE_NODE_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_TREE_NODE_setDataIndex"
  gIM_BVH_TREE_NODE_setDataIndex'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_TREE_NODE_getEscapeIndex"
  gIM_BVH_TREE_NODE_getEscapeIndex'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_TREE_NODE_getDataIndex"
  gIM_BVH_TREE_NODE_getDataIndex'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_TREE_NODE_setEscapeIndex"
  gIM_BVH_TREE_NODE_setEscapeIndex'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_TREE_NODE_isLeafNode"
  gIM_BVH_TREE_NODE_isLeafNode'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_TREE_NODE_m_bound_set"
  gIM_BVH_TREE_NODE_m_bound_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_TREE_NODE_m_bound_get"
  gIM_BVH_TREE_NODE_m_bound_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_TREE_NODE_m_escapeIndexOrDataIndex_set"
  gIM_BVH_TREE_NODE_m_escapeIndexOrDataIndex_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_TREE_NODE_m_escapeIndexOrDataIndex_get"
  gIM_BVH_TREE_NODE_m_escapeIndexOrDataIndex_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_TREE_NODE_ARRAY_new"
  gIM_BVH_TREE_NODE_ARRAY'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_BVH_TREE_NODE_ARRAY_free"
  gIM_BVH_TREE_NODE_ARRAY_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_PAIR_new0"
  gIM_PAIR0'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_PAIR_new1"
  gIM_PAIR1'_ :: (CInt -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_PAIR_free"
  gIM_PAIR_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_PAIR_m_index1_set"
  gIM_PAIR_m_index1_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_PAIR_m_index1_get"
  gIM_PAIR_m_index1_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_PAIR_m_index2_set"
  gIM_PAIR_m_index2_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_PAIR_m_index2_get"
  gIM_PAIR_m_index2_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_QUANTIZED_BVH_NODE_ARRAY_new"
  gIM_QUANTIZED_BVH_NODE_ARRAY'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_QUANTIZED_BVH_NODE_ARRAY_free"
  gIM_QUANTIZED_BVH_NODE_ARRAY_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_TRIANGLE_CONTACT_new"
  gIM_TRIANGLE_CONTACT'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_TRIANGLE_CONTACT_free"
  gIM_TRIANGLE_CONTACT_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_TRIANGLE_CONTACT_copy_from"
  gIM_TRIANGLE_CONTACT_copy_from'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_TRIANGLE_CONTACT_m_penetration_depth_set"
  gIM_TRIANGLE_CONTACT_m_penetration_depth_set'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_TRIANGLE_CONTACT_m_penetration_depth_get"
  gIM_TRIANGLE_CONTACT_m_penetration_depth_get'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_TRIANGLE_CONTACT_m_point_count_set"
  gIM_TRIANGLE_CONTACT_m_point_count_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_TRIANGLE_CONTACT_m_point_count_get"
  gIM_TRIANGLE_CONTACT_m_point_count_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_TRIANGLE_CONTACT_m_separating_normal_set"
  gIM_TRIANGLE_CONTACT_m_separating_normal_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h gIM_TRIANGLE_CONTACT_m_separating_normal_get"
  gIM_TRIANGLE_CONTACT_m_separating_normal_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_new0"
  btGImpactMeshShapePart_TrimeshPrimitiveManager0'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_new1"
  btGImpactMeshShapePart_TrimeshPrimitiveManager1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_free"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex_count"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex_count'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_vertex''_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_is_trimesh"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_is_trimesh'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_lock"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_lock'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_box"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_box'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_triangle"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_triangle'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_unlock"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_unlock'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_get_bullet_triangle"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_bullet_triangle'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_count"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_get_primitive_count'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_m_margin_set"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_margin_set'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_m_margin_get"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_margin_get'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_m_meshInterface_set"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_meshInterface_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_m_meshInterface_get"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_meshInterface_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_m_scale_set"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_scale_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_m_scale_get"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_scale_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_m_part_set"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_part_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_m_part_get"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_part_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_m_lock_count_set"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_lock_count_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_m_lock_count_get"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_m_lock_count_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_numverts_set"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_numverts_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_numverts_get"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_numverts_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_stride_set"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_stride_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_stride_get"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_stride_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_indexstride_set"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_indexstride_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_indexstride_get"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_indexstride_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_numfaces_set"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_numfaces_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_TrimeshPrimitiveManager_numfaces_get"
  btGImpactMeshShapePart_TrimeshPrimitiveManager_numfaces_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_new0"
  btAABB0'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_new1"
  btAABB1'_ :: ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO (Ptr ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_new2"
  btAABB2'_ :: ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (IO (Ptr ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_new3"
  btAABB3'_ :: ((Ptr ()) -> (CFloat -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_free"
  btAABB_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_overlapping_trans_conservative"
  btAABB_overlapping_trans_conservative'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> (IO CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_overlapping_trans_conservative"
  btAABB_overlapping_trans_conservative''_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> (IO CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_appy_transform"
  btAABB_appy_transform'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_appy_transform"
  btAABB_appy_transform''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_find_intersection"
  btAABB_find_intersection'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_collide_ray"
  btAABB_collide_ray'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_collide_ray"
  btAABB_collide_ray''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_overlapping_trans_cache"
  btAABB_overlapping_trans_cache'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (CInt -> (IO CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_get_center_extend"
  btAABB_get_center_extend'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_get_center_extend"
  btAABB_get_center_extend''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_invalidate"
  btAABB_invalidate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_has_collision"
  btAABB_has_collision'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_appy_transform_trans_cache"
  btAABB_appy_transform_trans_cache'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_calc_from_triangle_margin"
  btAABB_calc_from_triangle_margin'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_calc_from_triangle_margin"
  btAABB_calc_from_triangle_margin''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_increment_margin"
  btAABB_increment_margin'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_merge"
  btAABB_merge'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_collide_plane"
  btAABB_collide_plane'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_collide_plane"
  btAABB_collide_plane''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_overlapping_trans_conservative2"
  btAABB_overlapping_trans_conservative2'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_copy_with_margin"
  btAABB_copy_with_margin'_ :: ((Ptr ()) -> ((Ptr ()) -> (CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_collide_triangle_exact"
  btAABB_collide_triangle_exact'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO CInt))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_collide_triangle_exact"
  btAABB_collide_triangle_exact''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO CInt))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_m_max_set"
  btAABB_m_max_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_m_max_get"
  btAABB_m_max_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_m_min_set"
  btAABB_m_min_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btAABB_m_min_get"
  btAABB_m_min_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_new"
  btBvhTree'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_free"
  btBvhTree_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_getNodeCount"
  btBvhTree_getNodeCount'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_build_tree"
  btBvhTree_build_tree'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_setNodeBound"
  btBvhTree_setNodeBound'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_getLeftNode"
  btBvhTree_getLeftNode'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree__build_sub_tree"
  btBvhTree__build_sub_tree'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_clearNodes"
  btBvhTree_clearNodes'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree__sort_and_calc_splitting_index"
  btBvhTree__sort_and_calc_splitting_index'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (CInt -> (IO CInt))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_getEscapeNodeIndex"
  btBvhTree_getEscapeNodeIndex'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_isLeafNode"
  btBvhTree_isLeafNode'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_get_node_pointer"
  btBvhTree_get_node_pointer'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_getNodeData"
  btBvhTree_getNodeData'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_getNodeBound"
  btBvhTree_getNodeBound'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_getRightNode"
  btBvhTree_getRightNode'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree__calc_splitting_axis"
  btBvhTree__calc_splitting_axis'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_m_num_nodes_set"
  btBvhTree_m_num_nodes_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_m_num_nodes_get"
  btBvhTree_m_num_nodes_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_m_node_array_set"
  btBvhTree_m_node_array_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btBvhTree_m_node_array_get"
  btBvhTree_m_node_array_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_new0"
  btGImpactBvh0'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_new1"
  btGImpactBvh1'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_free"
  btGImpactBvh_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_setNodeBound"
  btGImpactBvh_setNodeBound'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_getEscapeNodeIndex"
  btGImpactBvh_getEscapeNodeIndex'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_isLeafNode"
  btGImpactBvh_isLeafNode'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_getPrimitiveManager"
  btGImpactBvh_getPrimitiveManager'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_getNodeBound"
  btGImpactBvh_getNodeBound'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_getRightNode"
  btGImpactBvh_getRightNode'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_getLeftNode"
  btGImpactBvh_getLeftNode'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_setPrimitiveManager"
  btGImpactBvh_setPrimitiveManager'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_buildSet"
  btGImpactBvh_buildSet'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_getNodeTriangle"
  btGImpactBvh_getNodeTriangle'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_getNodeCount"
  btGImpactBvh_getNodeCount'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_hasHierarchy"
  btGImpactBvh_hasHierarchy'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_rayQuery"
  btGImpactBvh_rayQuery'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_rayQuery"
  btGImpactBvh_rayQuery''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_update"
  btGImpactBvh_update'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_refit"
  btGImpactBvh_refit'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_isTrimesh"
  btGImpactBvh_isTrimesh'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_boxQuery"
  btGImpactBvh_boxQuery'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_find_collision"
  btGImpactBvh_find_collision'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_find_collision"
  btGImpactBvh_find_collision''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_get_node_pointer"
  btGImpactBvh_get_node_pointer'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_boxQueryTrans"
  btGImpactBvh_boxQueryTrans'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_boxQueryTrans"
  btGImpactBvh_boxQueryTrans''_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_getNodeData"
  btGImpactBvh_getNodeData'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_m_box_tree_set"
  btGImpactBvh_m_box_tree_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_m_box_tree_get"
  btGImpactBvh_m_box_tree_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_m_primitive_manager_set"
  btGImpactBvh_m_primitive_manager_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactBvh_m_primitive_manager_get"
  btGImpactBvh_m_primitive_manager_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_new"
  btGImpactCollisionAlgorithm'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_free"
  btGImpactCollisionAlgorithm_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_getFace1"
  btGImpactCollisionAlgorithm_getFace1'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_getFace0"
  btGImpactCollisionAlgorithm_getFace0'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_gimpact_vs_compoundshape"
  btGImpactCollisionAlgorithm_gimpact_vs_compoundshape'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (CInt -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_gimpact_vs_shape"
  btGImpactCollisionAlgorithm_gimpact_vs_shape'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (CInt -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_convex_vs_convex_collision"
  btGImpactCollisionAlgorithm_convex_vs_convex_collision'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_setFace0"
  btGImpactCollisionAlgorithm_setFace0'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_setFace1"
  btGImpactCollisionAlgorithm_setFace1'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_checkManifold"
  btGImpactCollisionAlgorithm_checkManifold'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_newContactManifold"
  btGImpactCollisionAlgorithm_newContactManifold'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_addContactPoint"
  btGImpactCollisionAlgorithm_addContactPoint'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_addContactPoint"
  btGImpactCollisionAlgorithm_addContactPoint''_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_gimpacttrimeshpart_vs_plane_collision"
  btGImpactCollisionAlgorithm_gimpacttrimeshpart_vs_plane_collision'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (CInt -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_registerAlgorithm"
  btGImpactCollisionAlgorithm_registerAlgorithm'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_processCollision"
  btGImpactCollisionAlgorithm_processCollision'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_destroyContactManifolds"
  btGImpactCollisionAlgorithm_destroyContactManifolds'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_gimpact_vs_gimpact_find_pairs"
  btGImpactCollisionAlgorithm_gimpact_vs_gimpact_find_pairs'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_gimpact_vs_gimpact_find_pairs"
  btGImpactCollisionAlgorithm_gimpact_vs_gimpact_find_pairs''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_getLastManifold"
  btGImpactCollisionAlgorithm_getLastManifold'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_gimpact_vs_shape_find_pairs"
  btGImpactCollisionAlgorithm_gimpact_vs_shape_find_pairs'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_gimpact_vs_shape_find_pairs"
  btGImpactCollisionAlgorithm_gimpact_vs_shape_find_pairs''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_destroyConvexAlgorithm"
  btGImpactCollisionAlgorithm_destroyConvexAlgorithm'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_checkConvexAlgorithm"
  btGImpactCollisionAlgorithm_checkConvexAlgorithm'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_newAlgorithm"
  btGImpactCollisionAlgorithm_newAlgorithm'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_shape_vs_shape_collision"
  btGImpactCollisionAlgorithm_shape_vs_shape_collision'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_setPart1"
  btGImpactCollisionAlgorithm_setPart1'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_setPart0"
  btGImpactCollisionAlgorithm_setPart0'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_clearCache"
  btGImpactCollisionAlgorithm_clearCache'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_getPart1"
  btGImpactCollisionAlgorithm_getPart1'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_getPart0"
  btGImpactCollisionAlgorithm_getPart0'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_gimpact_vs_concave"
  btGImpactCollisionAlgorithm_gimpact_vs_concave'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (CInt -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_calculateTimeOfImpact"
  btGImpactCollisionAlgorithm_calculateTimeOfImpact'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO CFloat))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_gimpact_vs_gimpact"
  btGImpactCollisionAlgorithm_gimpact_vs_gimpact'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_getAllContactManifolds"
  btGImpactCollisionAlgorithm_getAllContactManifolds'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_convex_algorithm_set"
  btGImpactCollisionAlgorithm_m_convex_algorithm_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_convex_algorithm_get"
  btGImpactCollisionAlgorithm_m_convex_algorithm_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_manifoldPtr_set"
  btGImpactCollisionAlgorithm_m_manifoldPtr_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_manifoldPtr_get"
  btGImpactCollisionAlgorithm_m_manifoldPtr_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_resultOut_set"
  btGImpactCollisionAlgorithm_m_resultOut_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_resultOut_get"
  btGImpactCollisionAlgorithm_m_resultOut_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_dispatchInfo_set"
  btGImpactCollisionAlgorithm_m_dispatchInfo_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_dispatchInfo_get"
  btGImpactCollisionAlgorithm_m_dispatchInfo_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_triface0_set"
  btGImpactCollisionAlgorithm_m_triface0_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_triface0_get"
  btGImpactCollisionAlgorithm_m_triface0_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_part0_set"
  btGImpactCollisionAlgorithm_m_part0_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_part0_get"
  btGImpactCollisionAlgorithm_m_part0_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_triface1_set"
  btGImpactCollisionAlgorithm_m_triface1_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_triface1_get"
  btGImpactCollisionAlgorithm_m_triface1_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_part1_set"
  btGImpactCollisionAlgorithm_m_part1_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCollisionAlgorithm_m_part1_get"
  btGImpactCollisionAlgorithm_m_part1_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_new"
  btGImpactCompoundShape'_ :: (CInt -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_free"
  btGImpactCompoundShape_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_calculateLocalInertia"
  btGImpactCompoundShape_calculateLocalInertia'_ :: ((Ptr ()) -> (CFloat -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_calculateLocalInertia"
  btGImpactCompoundShape_calculateLocalInertia''_ :: ((Ptr ()) -> (CFloat -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_addChildShape0"
  btGImpactCompoundShape_addChildShape'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_addChildShape0"
  btGImpactCompoundShape_addChildShape''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_addChildShape0"
  btGImpactCompoundShape_addChildShape0'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_addChildShape0"
  btGImpactCompoundShape_addChildShape0''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_addChildShape1"
  btGImpactCompoundShape_addChildShape1'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_getCompoundPrimitiveManager"
  btGImpactCompoundShape_getCompoundPrimitiveManager'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_setChildTransform"
  btGImpactCompoundShape_setChildTransform'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_setChildTransform"
  btGImpactCompoundShape_setChildTransform''_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_getChildTransform"
  btGImpactCompoundShape_getChildTransform'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_getBulletTetrahedron"
  btGImpactCompoundShape_getBulletTetrahedron'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_getName"
  btGImpactCompoundShape_getName'_ :: ((Ptr ()) -> (IO (Ptr CChar)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_needsRetrieveTetrahedrons"
  btGImpactCompoundShape_needsRetrieveTetrahedrons'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_getChildShape0"
  btGImpactCompoundShape_getChildShape'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_getChildShape0"
  btGImpactCompoundShape_getChildShape0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_getChildShape1"
  btGImpactCompoundShape_getChildShape1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_getBulletTriangle"
  btGImpactCompoundShape_getBulletTriangle'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_needsRetrieveTriangles"
  btGImpactCompoundShape_needsRetrieveTriangles'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_childrenHasTransform"
  btGImpactCompoundShape_childrenHasTransform'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_getNumChildShapes"
  btGImpactCompoundShape_getNumChildShapes'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_getPrimitiveManager"
  btGImpactCompoundShape_getPrimitiveManager'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_getChildAabb"
  btGImpactCompoundShape_getChildAabb'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_getChildAabb"
  btGImpactCompoundShape_getChildAabb''_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_m_childShapes_set"
  btGImpactCompoundShape_m_childShapes_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_m_childShapes_get"
  btGImpactCompoundShape_m_childShapes_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_m_childTransforms_set"
  btGImpactCompoundShape_m_childTransforms_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_m_childTransforms_get"
  btGImpactCompoundShape_m_childTransforms_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_m_primitive_manager_set"
  btGImpactCompoundShape_m_primitive_manager_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactCompoundShape_m_primitive_manager_get"
  btGImpactCompoundShape_m_primitive_manager_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_new"
  btGImpactMeshShape'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_free"
  btGImpactMeshShape_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_calculateLocalInertia"
  btGImpactMeshShape_calculateLocalInertia'_ :: ((Ptr ()) -> (CFloat -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_calculateLocalInertia"
  btGImpactMeshShape_calculateLocalInertia''_ :: ((Ptr ()) -> (CFloat -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_setChildTransform"
  btGImpactMeshShape_setChildTransform'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_setChildTransform"
  btGImpactMeshShape_setChildTransform''_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getMeshInterface0"
  btGImpactMeshShape_getMeshInterface'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getMeshInterface0"
  btGImpactMeshShape_getMeshInterface0'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getMeshInterface1"
  btGImpactMeshShape_getMeshInterface1'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getPrimitiveManager"
  btGImpactMeshShape_getPrimitiveManager'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_processAllTriangles"
  btGImpactMeshShape_processAllTriangles'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_processAllTriangles"
  btGImpactMeshShape_processAllTriangles''_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getMeshPartCount"
  btGImpactMeshShape_getMeshPartCount'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_calculateSerializeBufferSize"
  btGImpactMeshShape_calculateSerializeBufferSize'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_rayTest"
  btGImpactMeshShape_rayTest'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_rayTest"
  btGImpactMeshShape_rayTest''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_buildMeshParts"
  btGImpactMeshShape_buildMeshParts'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getName"
  btGImpactMeshShape_getName'_ :: ((Ptr ()) -> (IO (Ptr CChar)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getBulletTriangle"
  btGImpactMeshShape_getBulletTriangle'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_setLocalScaling"
  btGImpactMeshShape_setLocalScaling'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_setLocalScaling"
  btGImpactMeshShape_setLocalScaling''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_needsRetrieveTriangles"
  btGImpactMeshShape_needsRetrieveTriangles'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_childrenHasTransform"
  btGImpactMeshShape_childrenHasTransform'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getChildShape0"
  btGImpactMeshShape_getChildShape'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getChildShape0"
  btGImpactMeshShape_getChildShape0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getChildShape1"
  btGImpactMeshShape_getChildShape1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_calcLocalAABB"
  btGImpactMeshShape_calcLocalAABB'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getChildTransform"
  btGImpactMeshShape_getChildTransform'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_serialize"
  btGImpactMeshShape_serialize'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr CChar)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_lockChildShapes"
  btGImpactMeshShape_lockChildShapes'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_setMargin"
  btGImpactMeshShape_setMargin'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getNumChildShapes"
  btGImpactMeshShape_getNumChildShapes'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getChildAabb"
  btGImpactMeshShape_getChildAabb'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getChildAabb"
  btGImpactMeshShape_getChildAabb''_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getBulletTetrahedron"
  btGImpactMeshShape_getBulletTetrahedron'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_needsRetrieveTetrahedrons"
  btGImpactMeshShape_needsRetrieveTetrahedrons'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_unlockChildShapes"
  btGImpactMeshShape_unlockChildShapes'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getMeshPart0"
  btGImpactMeshShape_getMeshPart'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getMeshPart0"
  btGImpactMeshShape_getMeshPart0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_getMeshPart1"
  btGImpactMeshShape_getMeshPart1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_postUpdate"
  btGImpactMeshShape_postUpdate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_m_meshInterface_set"
  btGImpactMeshShape_m_meshInterface_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_m_meshInterface_get"
  btGImpactMeshShape_m_meshInterface_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_m_mesh_parts_set"
  btGImpactMeshShape_m_mesh_parts_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShape_m_mesh_parts_get"
  btGImpactMeshShape_m_mesh_parts_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapeData_new"
  btGImpactMeshShapeData'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapeData_free"
  btGImpactMeshShapeData_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapeData_m_collisionShapeData_set"
  btGImpactMeshShapeData_m_collisionShapeData_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapeData_m_collisionShapeData_get"
  btGImpactMeshShapeData_m_collisionShapeData_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapeData_m_meshInterface_set"
  btGImpactMeshShapeData_m_meshInterface_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapeData_m_meshInterface_get"
  btGImpactMeshShapeData_m_meshInterface_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapeData_m_localScaling_set"
  btGImpactMeshShapeData_m_localScaling_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapeData_m_localScaling_get"
  btGImpactMeshShapeData_m_localScaling_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapeData_m_collisionMargin_set"
  btGImpactMeshShapeData_m_collisionMargin_set'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapeData_m_collisionMargin_get"
  btGImpactMeshShapeData_m_collisionMargin_get'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapeData_m_gimpactSubType_set"
  btGImpactMeshShapeData_m_gimpactSubType_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapeData_m_gimpactSubType_get"
  btGImpactMeshShapeData_m_gimpactSubType_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_new0"
  btGImpactMeshShapePart0'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_new1"
  btGImpactMeshShapePart1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_free"
  btGImpactMeshShapePart_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_calculateLocalInertia"
  btGImpactMeshShapePart_calculateLocalInertia'_ :: ((Ptr ()) -> (CFloat -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_calculateLocalInertia"
  btGImpactMeshShapePart_calculateLocalInertia''_ :: ((Ptr ()) -> (CFloat -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_setChildTransform"
  btGImpactMeshShapePart_setChildTransform'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_setChildTransform"
  btGImpactMeshShapePart_setChildTransform''_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getLocalScaling"
  btGImpactMeshShapePart_getLocalScaling'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getVertex"
  btGImpactMeshShapePart_getVertex'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getVertex"
  btGImpactMeshShapePart_getVertex''_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_processAllTriangles"
  btGImpactMeshShapePart_processAllTriangles'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_processAllTriangles"
  btGImpactMeshShapePart_processAllTriangles''_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getName"
  btGImpactMeshShapePart_getName'_ :: ((Ptr ()) -> (IO (Ptr CChar)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getBulletTriangle"
  btGImpactMeshShapePart_getBulletTriangle'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_setLocalScaling"
  btGImpactMeshShapePart_setLocalScaling'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_setLocalScaling"
  btGImpactMeshShapePart_setLocalScaling''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getPart"
  btGImpactMeshShapePart_getPart'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_childrenHasTransform"
  btGImpactMeshShapePart_childrenHasTransform'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_needsRetrieveTriangles"
  btGImpactMeshShapePart_needsRetrieveTriangles'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getChildShape0"
  btGImpactMeshShapePart_getChildShape'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getChildShape0"
  btGImpactMeshShapePart_getChildShape0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getChildShape1"
  btGImpactMeshShapePart_getChildShape1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getChildTransform"
  btGImpactMeshShapePart_getChildTransform'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_lockChildShapes"
  btGImpactMeshShapePart_lockChildShapes'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getMargin"
  btGImpactMeshShapePart_getMargin'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_setMargin"
  btGImpactMeshShapePart_setMargin'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getPrimitiveManager"
  btGImpactMeshShapePart_getPrimitiveManager'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getNumChildShapes"
  btGImpactMeshShapePart_getNumChildShapes'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getBulletTetrahedron"
  btGImpactMeshShapePart_getBulletTetrahedron'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getTrimeshPrimitiveManager"
  btGImpactMeshShapePart_getTrimeshPrimitiveManager'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_needsRetrieveTetrahedrons"
  btGImpactMeshShapePart_needsRetrieveTetrahedrons'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_unlockChildShapes"
  btGImpactMeshShapePart_unlockChildShapes'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_getVertexCount"
  btGImpactMeshShapePart_getVertexCount'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_m_primitive_manager_set"
  btGImpactMeshShapePart_m_primitive_manager_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactMeshShapePart_m_primitive_manager_get"
  btGImpactMeshShapePart_m_primitive_manager_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_new0"
  btGImpactQuantizedBvh0'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_new1"
  btGImpactQuantizedBvh1'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_free"
  btGImpactQuantizedBvh_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_setNodeBound"
  btGImpactQuantizedBvh_setNodeBound'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_getEscapeNodeIndex"
  btGImpactQuantizedBvh_getEscapeNodeIndex'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_isLeafNode"
  btGImpactQuantizedBvh_isLeafNode'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_getPrimitiveManager"
  btGImpactQuantizedBvh_getPrimitiveManager'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_getNodeBound"
  btGImpactQuantizedBvh_getNodeBound'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_getRightNode"
  btGImpactQuantizedBvh_getRightNode'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_getLeftNode"
  btGImpactQuantizedBvh_getLeftNode'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_setPrimitiveManager"
  btGImpactQuantizedBvh_setPrimitiveManager'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_buildSet"
  btGImpactQuantizedBvh_buildSet'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_getNodeTriangle"
  btGImpactQuantizedBvh_getNodeTriangle'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_getNodeCount"
  btGImpactQuantizedBvh_getNodeCount'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_hasHierarchy"
  btGImpactQuantizedBvh_hasHierarchy'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_rayQuery"
  btGImpactQuantizedBvh_rayQuery'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_rayQuery"
  btGImpactQuantizedBvh_rayQuery''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_update"
  btGImpactQuantizedBvh_update'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_refit"
  btGImpactQuantizedBvh_refit'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_isTrimesh"
  btGImpactQuantizedBvh_isTrimesh'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_boxQuery"
  btGImpactQuantizedBvh_boxQuery'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_find_collision"
  btGImpactQuantizedBvh_find_collision'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_find_collision"
  btGImpactQuantizedBvh_find_collision''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_get_node_pointer"
  btGImpactQuantizedBvh_get_node_pointer'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_boxQueryTrans"
  btGImpactQuantizedBvh_boxQueryTrans'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_boxQueryTrans"
  btGImpactQuantizedBvh_boxQueryTrans''_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_getNodeData"
  btGImpactQuantizedBvh_getNodeData'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_m_box_tree_set"
  btGImpactQuantizedBvh_m_box_tree_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_m_box_tree_get"
  btGImpactQuantizedBvh_m_box_tree_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_m_primitive_manager_set"
  btGImpactQuantizedBvh_m_primitive_manager_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactQuantizedBvh_m_primitive_manager_get"
  btGImpactQuantizedBvh_m_primitive_manager_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getPrimitiveTriangle"
  btGImpactShapeInterface_getPrimitiveTriangle'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_setChildTransform"
  btGImpactShapeInterface_setChildTransform'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_setChildTransform"
  btGImpactShapeInterface_setChildTransform''_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getLocalScaling"
  btGImpactShapeInterface_getLocalScaling'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getLocalBox"
  btGImpactShapeInterface_getLocalBox'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getPrimitiveManager"
  btGImpactShapeInterface_getPrimitiveManager'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_processAllTriangles"
  btGImpactShapeInterface_processAllTriangles'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_processAllTriangles"
  btGImpactShapeInterface_processAllTriangles''_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_hasBoxSet"
  btGImpactShapeInterface_hasBoxSet'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_rayTest"
  btGImpactShapeInterface_rayTest'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_rayTest"
  btGImpactShapeInterface_rayTest''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getBoxSet"
  btGImpactShapeInterface_getBoxSet'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getBulletTriangle"
  btGImpactShapeInterface_getBulletTriangle'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_setLocalScaling"
  btGImpactShapeInterface_setLocalScaling'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_setLocalScaling"
  btGImpactShapeInterface_setLocalScaling''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_needsRetrieveTriangles"
  btGImpactShapeInterface_needsRetrieveTriangles'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_childrenHasTransform"
  btGImpactShapeInterface_childrenHasTransform'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getAabb"
  btGImpactShapeInterface_getAabb'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getAabb"
  btGImpactShapeInterface_getAabb''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getChildShape0"
  btGImpactShapeInterface_getChildShape'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getChildShape0"
  btGImpactShapeInterface_getChildShape0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getChildShape1"
  btGImpactShapeInterface_getChildShape1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_calcLocalAABB"
  btGImpactShapeInterface_calcLocalAABB'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getChildTransform"
  btGImpactShapeInterface_getChildTransform'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_lockChildShapes"
  btGImpactShapeInterface_lockChildShapes'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_setMargin"
  btGImpactShapeInterface_setMargin'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getNumChildShapes"
  btGImpactShapeInterface_getNumChildShapes'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getChildAabb"
  btGImpactShapeInterface_getChildAabb'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getChildAabb"
  btGImpactShapeInterface_getChildAabb''_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getShapeType"
  btGImpactShapeInterface_getShapeType'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_getBulletTetrahedron"
  btGImpactShapeInterface_getBulletTetrahedron'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_needsRetrieveTetrahedrons"
  btGImpactShapeInterface_needsRetrieveTetrahedrons'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_unlockChildShapes"
  btGImpactShapeInterface_unlockChildShapes'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_postUpdate"
  btGImpactShapeInterface_postUpdate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_updateBound"
  btGImpactShapeInterface_updateBound'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_localScaling_set"
  btGImpactShapeInterface_localScaling_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_localScaling_get"
  btGImpactShapeInterface_localScaling_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_m_box_set_set"
  btGImpactShapeInterface_m_box_set_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_m_box_set_get"
  btGImpactShapeInterface_m_box_set_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_m_localAABB_set"
  btGImpactShapeInterface_m_localAABB_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_m_localAABB_get"
  btGImpactShapeInterface_m_localAABB_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_m_needs_update_set"
  btGImpactShapeInterface_m_needs_update_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btGImpactShapeInterface_m_needs_update_get"
  btGImpactShapeInterface_m_needs_update_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPairSet_new"
  btPairSet'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPairSet_free"
  btPairSet_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPairSet_push_pair_inv"
  btPairSet_push_pair_inv'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPairSet_push_pair"
  btPairSet_push_pair'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveManagerBase_get_primitive_box"
  btPrimitiveManagerBase_get_primitive_box'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveManagerBase_get_primitive_triangle"
  btPrimitiveManagerBase_get_primitive_triangle'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveManagerBase_is_trimesh"
  btPrimitiveManagerBase_is_trimesh'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveManagerBase_get_primitive_count"
  btPrimitiveManagerBase_get_primitive_count'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_new"
  btPrimitiveTriangle'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_free"
  btPrimitiveTriangle_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_get_edge_plane"
  btPrimitiveTriangle_get_edge_plane'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_get_edge_plane"
  btPrimitiveTriangle_get_edge_plane''_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_overlap_test_conservative"
  btPrimitiveTriangle_overlap_test_conservative'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_buildTriPlane"
  btPrimitiveTriangle_buildTriPlane'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_applyTransform"
  btPrimitiveTriangle_applyTransform'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_applyTransform"
  btPrimitiveTriangle_applyTransform''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_find_triangle_collision_clip_method"
  btPrimitiveTriangle_find_triangle_collision_clip_method'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO CInt))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_m_dummy_set"
  btPrimitiveTriangle_m_dummy_set'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_m_dummy_get"
  btPrimitiveTriangle_m_dummy_get'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_m_margin_set"
  btPrimitiveTriangle_m_margin_set'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_m_margin_get"
  btPrimitiveTriangle_m_margin_get'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_m_plane_set"
  btPrimitiveTriangle_m_plane_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btPrimitiveTriangle_m_plane_get"
  btPrimitiveTriangle_m_plane_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_new"
  btQuantizedBvhTree'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_free"
  btQuantizedBvhTree_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_getNodeCount"
  btQuantizedBvhTree_getNodeCount'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_calc_quantization"
  btQuantizedBvhTree_calc_quantization'_ :: ((Ptr ()) -> ((Ptr ()) -> (CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_build_tree"
  btQuantizedBvhTree_build_tree'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_setNodeBound"
  btQuantizedBvhTree_setNodeBound'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_getLeftNode"
  btQuantizedBvhTree_getLeftNode'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree__build_sub_tree"
  btQuantizedBvhTree__build_sub_tree'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_clearNodes"
  btQuantizedBvhTree_clearNodes'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree__sort_and_calc_splitting_index"
  btQuantizedBvhTree__sort_and_calc_splitting_index'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (CInt -> (IO CInt))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_getEscapeNodeIndex"
  btQuantizedBvhTree_getEscapeNodeIndex'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_isLeafNode"
  btQuantizedBvhTree_isLeafNode'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_get_node_pointer"
  btQuantizedBvhTree_get_node_pointer'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_getNodeData"
  btQuantizedBvhTree_getNodeData'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_getNodeBound"
  btQuantizedBvhTree_getNodeBound'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_getRightNode"
  btQuantizedBvhTree_getRightNode'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree__calc_splitting_axis"
  btQuantizedBvhTree__calc_splitting_axis'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO CInt)))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_m_bvhQuantization_set"
  btQuantizedBvhTree_m_bvhQuantization_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_m_bvhQuantization_get"
  btQuantizedBvhTree_m_bvhQuantization_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_m_global_bound_set"
  btQuantizedBvhTree_m_global_bound_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_m_global_bound_get"
  btQuantizedBvhTree_m_global_bound_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_m_node_array_set"
  btQuantizedBvhTree_m_node_array_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_m_node_array_get"
  btQuantizedBvhTree_m_node_array_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_m_num_nodes_set"
  btQuantizedBvhTree_m_num_nodes_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btQuantizedBvhTree_m_num_nodes_get"
  btQuantizedBvhTree_m_num_nodes_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTetrahedronShapeEx_new"
  btTetrahedronShapeEx'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTetrahedronShapeEx_free"
  btTetrahedronShapeEx_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTetrahedronShapeEx_setVertices"
  btTetrahedronShapeEx_setVertices'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTetrahedronShapeEx_setVertices"
  btTetrahedronShapeEx_setVertices''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTriangleShapeEx_new0"
  btTriangleShapeEx0'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTriangleShapeEx_new1"
  btTriangleShapeEx1'_ :: ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO (Ptr ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTriangleShapeEx_free"
  btTriangleShapeEx_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTriangleShapeEx_overlap_test_conservative"
  btTriangleShapeEx_overlap_test_conservative'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTriangleShapeEx_buildTriPlane"
  btTriangleShapeEx_buildTriPlane'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTriangleShapeEx_buildTriPlane"
  btTriangleShapeEx_buildTriPlane''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTriangleShapeEx_applyTransform"
  btTriangleShapeEx_applyTransform'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTriangleShapeEx_applyTransform"
  btTriangleShapeEx_applyTransform''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTriangleShapeEx_getAabb"
  btTriangleShapeEx_getAabb'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/Gimpact.chs.h btTriangleShapeEx_getAabb"
  btTriangleShapeEx_getAabb''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))