-- 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/LinearMath.chs" #-}{-#LANGUAGE ForeignFunctionInterface#-}
module Physics.Bullet.Raw.LinearMath (
module Physics.Bullet.Raw.LinearMath
) 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
-- * CProfileIterator
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#135>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator :: ( CProfileNodeClass p0 ) => p0 -> IO (CProfileIterator)
cProfileIterator a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator'_ a1' >>= \res ->
  mkCProfileIterator res >>= \res' ->
  return (res')
{-# LINE 17 "./Physics/Bullet/Raw/LinearMath.chs" #-}
cProfileIterator_free :: ( CProfileIteratorClass bc ) => bc -> IO ()
cProfileIterator_free a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_free'_ a1' >>= \res ->
  return ()
{-# LINE 18 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#116>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_Get_Current_Name :: ( CProfileIteratorClass bc ) => bc -> IO (String)
cProfileIterator_Get_Current_Name a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_Get_Current_Name'_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')
{-# LINE 23 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#117>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_Get_Current_Total_Calls :: ( CProfileIteratorClass bc ) => bc -> IO (Int)
cProfileIterator_Get_Current_Total_Calls a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_Get_Current_Total_Calls'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 28 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#118>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_Get_Current_Total_Time :: ( CProfileIteratorClass bc ) => bc -> IO (Float)
cProfileIterator_Get_Current_Total_Time a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_Get_Current_Total_Time'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 33 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_Enter_Child :: ( CProfileIteratorClass bc ) => bc -> Int -> IO ()
cProfileIterator_Enter_Child a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  cProfileIterator_Enter_Child'_ a1' a2' >>= \res ->
  return ()
{-# LINE 39 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#108>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_Is_Done :: ( CProfileIteratorClass bc ) => bc -> IO (Bool)
cProfileIterator_Is_Done a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_Is_Done'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 44 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#107>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_Next :: ( CProfileIteratorClass bc ) => bc -> IO ()
cProfileIterator_Next a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_Next'_ a1' >>= \res ->
  return ()
{-# LINE 49 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#109>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_Is_Root :: ( CProfileIteratorClass bc ) => bc -> IO (Bool)
cProfileIterator_Is_Root a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_Is_Root'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 54 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#123>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_Get_Current_Parent_Name :: ( CProfileIteratorClass bc ) => bc -> IO (String)
cProfileIterator_Get_Current_Parent_Name a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_Get_Current_Parent_Name'_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')
{-# LINE 59 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#120>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_Get_Current_UserPointer :: ( CProfileIteratorClass bc ) => bc -> IO (VoidPtr)
cProfileIterator_Get_Current_UserPointer a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_Get_Current_UserPointer'_ a1' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 64 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#124>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_Get_Current_Parent_Total_Calls :: ( CProfileIteratorClass bc ) => bc -> IO (Int)
cProfileIterator_Get_Current_Parent_Total_Calls a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_Get_Current_Parent_Total_Calls'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 69 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#121>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_Set_Current_UserPointer :: ( CProfileIteratorClass bc ) => bc -> VoidPtr -> IO ()
cProfileIterator_Set_Current_UserPointer a1 a2 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  cProfileIterator_Set_Current_UserPointer'_ a1' a2' >>= \res ->
  return ()
{-# LINE 75 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#125>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_Get_Current_Parent_Total_Time :: ( CProfileIteratorClass bc ) => bc -> IO (Float)
cProfileIterator_Get_Current_Parent_Total_Time a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_Get_Current_Parent_Total_Time'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 80 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_Enter_Parent :: ( CProfileIteratorClass bc ) => bc -> IO ()
cProfileIterator_Enter_Parent a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_Enter_Parent'_ a1' >>= \res ->
  return ()
{-# LINE 85 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#106>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_First :: ( CProfileIteratorClass bc ) => bc -> IO ()
cProfileIterator_First a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_First'_ a1' >>= \res ->
  return ()
{-# LINE 90 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#131>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_CurrentParent_set :: ( CProfileIteratorClass bc , CProfileNodeClass a ) => bc -> a -> IO ()
cProfileIterator_CurrentParent_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  cProfileIterator_CurrentParent_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 94 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#131>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_CurrentParent_get :: ( CProfileIteratorClass bc ) => bc -> IO (CProfileNode)
cProfileIterator_CurrentParent_get a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_CurrentParent_get'_ a1' >>= \res ->
  mkCProfileNode res >>= \res' ->
  return (res')
{-# LINE 98 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#132>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_CurrentChild_set :: ( CProfileIteratorClass bc , CProfileNodeClass a ) => bc -> a -> IO ()
cProfileIterator_CurrentChild_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  cProfileIterator_CurrentChild_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 102 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#132>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileIterator_CurrentChild_get :: ( CProfileIteratorClass bc ) => bc -> IO (CProfileNode)
cProfileIterator_CurrentChild_get a1 =
  withBt a1 $ \a1' -> 
  cProfileIterator_CurrentChild_get'_ a1' >>= \res ->
  mkCProfileNode res >>= \res' ->
  return (res')
{-# LINE 106 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * CProfileManager
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager :: IO (CProfileManager)
cProfileManager =
  cProfileManager'_ >>= \res ->
  mkCProfileManager res >>= \res' ->
  return (res')
{-# LINE 111 "./Physics/Bullet/Raw/LinearMath.chs" #-}
cProfileManager_free :: ( CProfileManagerClass bc ) => bc -> IO ()
cProfileManager_free a1 =
  withBt a1 $ \a1' -> 
  cProfileManager_free'_ a1' >>= \res ->
  return ()
{-# LINE 112 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#151>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_Reset :: ( ) => IO ()
cProfileManager_Reset =
  cProfileManager_Reset'_ >>= \res ->
  return ()
{-# LINE 116 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#165>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_dumpAll :: ( ) => IO ()
cProfileManager_dumpAll =
  cProfileManager_dumpAll'_ >>= \res ->
  return ()
{-# LINE 120 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#153>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_Get_Frame_Count_Since_Reset :: ( ) => IO (Int)
cProfileManager_Get_Frame_Count_Since_Reset =
  cProfileManager_Get_Frame_Count_Since_Reset'_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 124 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#161>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_Release_Iterator :: (  CProfileIteratorClass p0 ) => p0 -> IO ()
cProfileManager_Release_Iterator a1 =
  withBt a1 $ \a1' -> 
  cProfileManager_Release_Iterator'_ a1' >>= \res ->
  return ()
{-# LINE 129 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#144>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_Stop_Profile :: ( ) => IO ()
cProfileManager_Stop_Profile =
  cProfileManager_Stop_Profile'_ >>= \res ->
  return ()
{-# LINE 133 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#146>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_CleanupMemory :: ( ) => IO ()
cProfileManager_CleanupMemory =
  cProfileManager_CleanupMemory'_ >>= \res ->
  return ()
{-# LINE 137 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#154>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_Get_Time_Since_Reset :: ( ) => IO (Float)
cProfileManager_Get_Time_Since_Reset =
  cProfileManager_Get_Time_Since_Reset'_ >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 141 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#143>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_Start_Profile :: ( ) => String -> IO ()
cProfileManager_Start_Profile a1 =
  withCString a1 $ \a1' -> 
  cProfileManager_Start_Profile'_ a1' >>= \res ->
  return ()
{-# LINE 146 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#152>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_Increment_Frame_Counter :: ( ) => IO ()
cProfileManager_Increment_Frame_Counter =
  cProfileManager_Increment_Frame_Counter'_ >>= \res ->
  return ()
{-# LINE 150 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#163>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_dumpRecursive :: (  CProfileIteratorClass p0 ) => p0 -> Int -> IO ()
cProfileManager_dumpRecursive a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  cProfileManager_dumpRecursive'_ a1' a2' >>= \res ->
  return ()
{-# LINE 156 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#156>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_Get_Iterator :: ( ) => IO (CProfileIterator)
cProfileManager_Get_Iterator =
  cProfileManager_Get_Iterator'_ >>= \res ->
  mkCProfileIterator res >>= \res' ->
  return (res')
{-# LINE 160 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#168>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_Root_set :: ( CProfileManagerClass bc , CProfileNodeClass a ) => bc -> a -> IO ()
cProfileManager_Root_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  cProfileManager_Root_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 164 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#168>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_Root_get :: ( CProfileManagerClass bc ) => bc -> IO (CProfileNode)
cProfileManager_Root_get a1 =
  withBt a1 $ \a1' -> 
  cProfileManager_Root_get'_ a1' >>= \res ->
  mkCProfileNode res >>= \res' ->
  return (res')
{-# LINE 168 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#169>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_CurrentNode_set :: ( CProfileManagerClass bc , CProfileNodeClass a ) => bc -> a -> IO ()
cProfileManager_CurrentNode_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  cProfileManager_CurrentNode_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 172 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#169>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_CurrentNode_get :: ( CProfileManagerClass bc ) => bc -> IO (CProfileNode)
cProfileManager_CurrentNode_get a1 =
  withBt a1 $ \a1' -> 
  cProfileManager_CurrentNode_get'_ a1' >>= \res ->
  mkCProfileNode res >>= \res' ->
  return (res')
{-# LINE 176 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#170>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_FrameCounter_set :: ( CProfileManagerClass bc ) => bc -> Int -> IO ()
cProfileManager_FrameCounter_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  cProfileManager_FrameCounter_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 180 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#170>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_FrameCounter_get :: ( CProfileManagerClass bc ) => bc -> IO (Int)
cProfileManager_FrameCounter_get a1 =
  withBt a1 $ \a1' -> 
  cProfileManager_FrameCounter_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 184 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_ResetTime_set :: ( CProfileManagerClass bc ) => bc -> Word64 -> IO ()
cProfileManager_ResetTime_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  cProfileManager_ResetTime_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 188 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileManager_ResetTime_get :: ( CProfileManagerClass bc ) => bc -> IO (Word64)
cProfileManager_ResetTime_get a1 =
  withBt a1 $ \a1' -> 
  cProfileManager_ResetTime_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 192 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * CProfileNode
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode :: ( CProfileNodeClass p1 ) => String -> p1 -> IO (CProfileNode)
cProfileNode a1 a2 =
  withCString a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  cProfileNode'_ a1' a2' >>= \res ->
  mkCProfileNode res >>= \res' ->
  return (res')
{-# LINE 197 "./Physics/Bullet/Raw/LinearMath.chs" #-}
cProfileNode_free :: ( CProfileNodeClass bc ) => bc -> IO ()
cProfileNode_free a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_free'_ a1' >>= \res ->
  return ()
{-# LINE 198 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#78>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Reset :: ( CProfileNodeClass bc ) => bc -> IO ()
cProfileNode_Reset a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_Reset'_ a1' >>= \res ->
  return ()
{-# LINE 203 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Return :: ( CProfileNodeClass bc ) => bc -> IO (Bool)
cProfileNode_Return a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_Return'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 208 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#86>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_SetUserPointer :: ( CProfileNodeClass bc ) => bc -> VoidPtr -> IO ()
cProfileNode_SetUserPointer a1 a2 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  cProfileNode_SetUserPointer'_ a1' a2' >>= \res ->
  return ()
{-# LINE 214 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#71>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Get_Sub_Node :: ( CProfileNodeClass bc ) => bc -> String -> IO (CProfileNode)
cProfileNode_Get_Sub_Node a1 a2 =
  withBt a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  cProfileNode_Get_Sub_Node'_ a1' a2' >>= \res ->
  mkCProfileNode res >>= \res' ->
  return (res')
{-# LINE 220 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#77>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_CleanupMemory :: ( CProfileNodeClass bc ) => bc -> IO ()
cProfileNode_CleanupMemory a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_CleanupMemory'_ a1' >>= \res ->
  return ()
{-# LINE 225 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#73>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Get_Parent :: ( CProfileNodeClass bc ) => bc -> IO (CProfileNode)
cProfileNode_Get_Parent a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_Get_Parent'_ a1' >>= \res ->
  mkCProfileNode res >>= \res' ->
  return (res')
{-# LINE 230 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#85>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_GetUserPointer :: ( CProfileNodeClass bc ) => bc -> IO (VoidPtr)
cProfileNode_GetUserPointer a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_GetUserPointer'_ a1' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 235 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Get_Name :: ( CProfileNodeClass bc ) => bc -> IO (String)
cProfileNode_Get_Name a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_Get_Name'_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')
{-# LINE 240 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#84>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Get_Total_Time :: ( CProfileNodeClass bc ) => bc -> IO (Float)
cProfileNode_Get_Total_Time a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_Get_Total_Time'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 245 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#79>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Call :: ( CProfileNodeClass bc ) => bc -> IO ()
cProfileNode_Call a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_Call'_ a1' >>= \res ->
  return ()
{-# LINE 250 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#74>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Get_Sibling :: ( CProfileNodeClass bc ) => bc -> IO (CProfileNode)
cProfileNode_Get_Sibling a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_Get_Sibling'_ a1' >>= \res ->
  mkCProfileNode res >>= \res' ->
  return (res')
{-# LINE 255 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#75>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Get_Child :: ( CProfileNodeClass bc ) => bc -> IO (CProfileNode)
cProfileNode_Get_Child a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_Get_Child'_ a1' >>= \res ->
  mkCProfileNode res >>= \res' ->
  return (res')
{-# LINE 260 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Get_Total_Calls :: ( CProfileNodeClass bc ) => bc -> IO (Int)
cProfileNode_Get_Total_Calls a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_Get_Total_Calls'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 265 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Child_set :: ( CProfileNodeClass bc , CProfileNodeClass a ) => bc -> a -> IO ()
cProfileNode_Child_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  cProfileNode_Child_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 269 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Child_get :: ( CProfileNodeClass bc ) => bc -> IO (CProfileNode)
cProfileNode_Child_get a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_Child_get'_ a1' >>= \res ->
  mkCProfileNode res >>= \res' ->
  return (res')
{-# LINE 273 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Name_set :: ( CProfileNodeClass bc ) => bc -> String -> IO ()
cProfileNode_Name_set a1 a2 =
  withBt a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  cProfileNode_Name_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 277 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Name_get :: ( CProfileNodeClass bc ) => bc -> IO (String)
cProfileNode_Name_get a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_Name_get'_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')
{-# LINE 281 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#95>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Parent_set :: ( CProfileNodeClass bc , CProfileNodeClass a ) => bc -> a -> IO ()
cProfileNode_Parent_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  cProfileNode_Parent_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 285 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#95>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Parent_get :: ( CProfileNodeClass bc ) => bc -> IO (CProfileNode)
cProfileNode_Parent_get a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_Parent_get'_ a1' >>= \res ->
  mkCProfileNode res >>= \res' ->
  return (res')
{-# LINE 289 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#93>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_RecursionCounter_set :: ( CProfileNodeClass bc ) => bc -> Int -> IO ()
cProfileNode_RecursionCounter_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  cProfileNode_RecursionCounter_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 293 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#93>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_RecursionCounter_get :: ( CProfileNodeClass bc ) => bc -> IO (Int)
cProfileNode_RecursionCounter_get a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_RecursionCounter_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 297 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Sibling_set :: ( CProfileNodeClass bc , CProfileNodeClass a ) => bc -> a -> IO ()
cProfileNode_Sibling_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  cProfileNode_Sibling_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 301 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_Sibling_get :: ( CProfileNodeClass bc ) => bc -> IO (CProfileNode)
cProfileNode_Sibling_get a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_Sibling_get'_ a1' >>= \res ->
  mkCProfileNode res >>= \res' ->
  return (res')
{-# LINE 305 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_StartTime_set :: ( CProfileNodeClass bc ) => bc -> Word64 -> IO ()
cProfileNode_StartTime_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  cProfileNode_StartTime_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 309 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_StartTime_get :: ( CProfileNodeClass bc ) => bc -> IO (Word64)
cProfileNode_StartTime_get a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_StartTime_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 313 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#90>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_TotalCalls_set :: ( CProfileNodeClass bc ) => bc -> Int -> IO ()
cProfileNode_TotalCalls_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  cProfileNode_TotalCalls_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 317 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#90>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_TotalCalls_get :: ( CProfileNodeClass bc ) => bc -> IO (Int)
cProfileNode_TotalCalls_get a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_TotalCalls_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 321 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#91>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_TotalTime_set :: ( CProfileNodeClass bc ) => bc -> Float -> IO ()
cProfileNode_TotalTime_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  cProfileNode_TotalTime_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 325 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#91>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_TotalTime_get :: ( CProfileNodeClass bc ) => bc -> IO (Float)
cProfileNode_TotalTime_get a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_TotalTime_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 329 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#98>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_m_userPtr_set :: ( CProfileNodeClass bc ) => bc -> VoidPtr -> IO ()
cProfileNode_m_userPtr_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  cProfileNode_m_userPtr_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 333 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#98>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileNode_m_userPtr_get :: ( CProfileNodeClass bc ) => bc -> IO (VoidPtr)
cProfileNode_m_userPtr_get a1 =
  withBt a1 $ \a1' -> 
  cProfileNode_m_userPtr_get'_ a1' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 337 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * CProfileSample
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#179>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
cProfileSample :: String -> IO (CProfileSample)
cProfileSample a1 =
  withCString a1 $ \a1' -> 
  cProfileSample'_ a1' >>= \res ->
  mkCProfileSample res >>= \res' ->
  return (res')
{-# LINE 342 "./Physics/Bullet/Raw/LinearMath.chs" #-}
cProfileSample_free :: ( CProfileSampleClass bc ) => bc -> IO ()
cProfileSample_free a1 =
  withBt a1 $ \a1' -> 
  cProfileSample_free'_ a1' >>= \res ->
  return ()
{-# LINE 343 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<BT_QUANTIZED_BVH_NODE, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_ :: IO (BtAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_)
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_ =
  btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_'_ >>= \res ->
  mkBtAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_ res >>= \res' ->
  return (res')
{-# LINE 348 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__free :: ( BtAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 349 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__destroy :: ( BtAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_Class bc , BT_QUANTIZED_BVH_NODEClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 355 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__deallocate :: ( BtAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_Class bc , BT_QUANTIZED_BVH_NODEClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 361 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__construct :: ( BtAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_Class bc , BT_QUANTIZED_BVH_NODEClass p0 , BT_QUANTIZED_BVH_NODEClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 368 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__address :: ( BtAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_Class bc , BT_QUANTIZED_BVH_NODEClass p0 ) => bc -> p0 -> IO (BT_QUANTIZED_BVH_NODE)
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__address'_ a1' a2' >>= \res ->
  mkBT_QUANTIZED_BVH_NODE res >>= \res' ->
  return (res')
{-# LINE 374 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__address0 :: ( BtAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_Class bc , BT_QUANTIZED_BVH_NODEClass p0 ) => bc -> p0 -> IO (BT_QUANTIZED_BVH_NODE)
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__address0'_ a1' a2' >>= \res ->
  mkBT_QUANTIZED_BVH_NODE res >>= \res' ->
  return (res')
{-# LINE 380 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__address1 :: ( BtAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_Class bc , BT_QUANTIZED_BVH_NODEClass p0 ) => bc -> p0 -> IO (BT_QUANTIZED_BVH_NODE)
btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__address1'_ a1' a2' >>= \res ->
  mkBT_QUANTIZED_BVH_NODE res >>= \res' ->
  return (res')
{-# LINE 386 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<GIM_BVH_DATA, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_DATA_16u_ :: IO (BtAlignedAllocator_GIM_BVH_DATA_16u_)
btAlignedAllocator_GIM_BVH_DATA_16u_ =
  btAlignedAllocator_GIM_BVH_DATA_16u_'_ >>= \res ->
  mkBtAlignedAllocator_GIM_BVH_DATA_16u_ res >>= \res' ->
  return (res')
{-# LINE 391 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_GIM_BVH_DATA_16u__free :: ( BtAlignedAllocator_GIM_BVH_DATA_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_GIM_BVH_DATA_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_GIM_BVH_DATA_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 392 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_DATA_16u__destroy :: ( BtAlignedAllocator_GIM_BVH_DATA_16u_Class bc , GIM_BVH_DATAClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_GIM_BVH_DATA_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_BVH_DATA_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 398 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_DATA_16u__deallocate :: ( BtAlignedAllocator_GIM_BVH_DATA_16u_Class bc , GIM_BVH_DATAClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_GIM_BVH_DATA_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_BVH_DATA_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 404 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_DATA_16u__construct :: ( BtAlignedAllocator_GIM_BVH_DATA_16u_Class bc , GIM_BVH_DATAClass p0 , GIM_BVH_DATAClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_GIM_BVH_DATA_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_GIM_BVH_DATA_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 411 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_DATA_16u__address :: ( BtAlignedAllocator_GIM_BVH_DATA_16u_Class bc , GIM_BVH_DATAClass p0 ) => bc -> p0 -> IO (GIM_BVH_DATA)
btAlignedAllocator_GIM_BVH_DATA_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_BVH_DATA_16u__address'_ a1' a2' >>= \res ->
  mkGIM_BVH_DATA res >>= \res' ->
  return (res')
{-# LINE 417 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_DATA_16u__address0 :: ( BtAlignedAllocator_GIM_BVH_DATA_16u_Class bc , GIM_BVH_DATAClass p0 ) => bc -> p0 -> IO (GIM_BVH_DATA)
btAlignedAllocator_GIM_BVH_DATA_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_BVH_DATA_16u__address0'_ a1' a2' >>= \res ->
  mkGIM_BVH_DATA res >>= \res' ->
  return (res')
{-# LINE 423 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_DATA_16u__address1 :: ( BtAlignedAllocator_GIM_BVH_DATA_16u_Class bc , GIM_BVH_DATAClass p0 ) => bc -> p0 -> IO (GIM_BVH_DATA)
btAlignedAllocator_GIM_BVH_DATA_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_BVH_DATA_16u__address1'_ a1' a2' >>= \res ->
  mkGIM_BVH_DATA res >>= \res' ->
  return (res')
{-# LINE 429 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<GIM_BVH_TREE_NODE, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_TREE_NODE_16u_ :: IO (BtAlignedAllocator_GIM_BVH_TREE_NODE_16u_)
btAlignedAllocator_GIM_BVH_TREE_NODE_16u_ =
  btAlignedAllocator_GIM_BVH_TREE_NODE_16u_'_ >>= \res ->
  mkBtAlignedAllocator_GIM_BVH_TREE_NODE_16u_ res >>= \res' ->
  return (res')
{-# LINE 434 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__free :: ( BtAlignedAllocator_GIM_BVH_TREE_NODE_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_GIM_BVH_TREE_NODE_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 435 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__destroy :: ( BtAlignedAllocator_GIM_BVH_TREE_NODE_16u_Class bc , GIM_BVH_TREE_NODEClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_BVH_TREE_NODE_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 441 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__deallocate :: ( BtAlignedAllocator_GIM_BVH_TREE_NODE_16u_Class bc , GIM_BVH_TREE_NODEClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_BVH_TREE_NODE_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 447 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__construct :: ( BtAlignedAllocator_GIM_BVH_TREE_NODE_16u_Class bc , GIM_BVH_TREE_NODEClass p0 , GIM_BVH_TREE_NODEClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_GIM_BVH_TREE_NODE_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 454 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__address :: ( BtAlignedAllocator_GIM_BVH_TREE_NODE_16u_Class bc , GIM_BVH_TREE_NODEClass p0 ) => bc -> p0 -> IO (GIM_BVH_TREE_NODE)
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_BVH_TREE_NODE_16u__address'_ a1' a2' >>= \res ->
  mkGIM_BVH_TREE_NODE res >>= \res' ->
  return (res')
{-# LINE 460 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__address0 :: ( BtAlignedAllocator_GIM_BVH_TREE_NODE_16u_Class bc , GIM_BVH_TREE_NODEClass p0 ) => bc -> p0 -> IO (GIM_BVH_TREE_NODE)
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_BVH_TREE_NODE_16u__address0'_ a1' a2' >>= \res ->
  mkGIM_BVH_TREE_NODE res >>= \res' ->
  return (res')
{-# LINE 466 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__address1 :: ( BtAlignedAllocator_GIM_BVH_TREE_NODE_16u_Class bc , GIM_BVH_TREE_NODEClass p0 ) => bc -> p0 -> IO (GIM_BVH_TREE_NODE)
btAlignedAllocator_GIM_BVH_TREE_NODE_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_BVH_TREE_NODE_16u__address1'_ a1' a2' >>= \res ->
  mkGIM_BVH_TREE_NODE res >>= \res' ->
  return (res')
{-# LINE 472 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<GIM_PAIR, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_PAIR_16u_ :: IO (BtAlignedAllocator_GIM_PAIR_16u_)
btAlignedAllocator_GIM_PAIR_16u_ =
  btAlignedAllocator_GIM_PAIR_16u_'_ >>= \res ->
  mkBtAlignedAllocator_GIM_PAIR_16u_ res >>= \res' ->
  return (res')
{-# LINE 477 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_GIM_PAIR_16u__free :: ( BtAlignedAllocator_GIM_PAIR_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_GIM_PAIR_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_GIM_PAIR_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 478 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_PAIR_16u__destroy :: ( BtAlignedAllocator_GIM_PAIR_16u_Class bc , GIM_PAIRClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_GIM_PAIR_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_PAIR_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 484 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_PAIR_16u__deallocate :: ( BtAlignedAllocator_GIM_PAIR_16u_Class bc , GIM_PAIRClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_GIM_PAIR_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_PAIR_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 490 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_PAIR_16u__construct :: ( BtAlignedAllocator_GIM_PAIR_16u_Class bc , GIM_PAIRClass p0 , GIM_PAIRClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_GIM_PAIR_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_GIM_PAIR_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 497 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_PAIR_16u__address :: ( BtAlignedAllocator_GIM_PAIR_16u_Class bc , GIM_PAIRClass p0 ) => bc -> p0 -> IO (GIM_PAIR)
btAlignedAllocator_GIM_PAIR_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_PAIR_16u__address'_ a1' a2' >>= \res ->
  mkGIM_PAIR res >>= \res' ->
  return (res')
{-# LINE 503 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_PAIR_16u__address0 :: ( BtAlignedAllocator_GIM_PAIR_16u_Class bc , GIM_PAIRClass p0 ) => bc -> p0 -> IO (GIM_PAIR)
btAlignedAllocator_GIM_PAIR_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_PAIR_16u__address0'_ a1' a2' >>= \res ->
  mkGIM_PAIR res >>= \res' ->
  return (res')
{-# LINE 509 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_GIM_PAIR_16u__address1 :: ( BtAlignedAllocator_GIM_PAIR_16u_Class bc , GIM_PAIRClass p0 ) => bc -> p0 -> IO (GIM_PAIR)
btAlignedAllocator_GIM_PAIR_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_GIM_PAIR_16u__address1'_ a1' a2' >>= \res ->
  mkGIM_PAIR res >>= \res' ->
  return (res')
{-# LINE 515 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<bool, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_bool_16u_ :: IO (BtAlignedAllocator_bool_16u_)
btAlignedAllocator_bool_16u_ =
  btAlignedAllocator_bool_16u_'_ >>= \res ->
  mkBtAlignedAllocator_bool_16u_ res >>= \res' ->
  return (res')
{-# LINE 520 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_bool_16u__free :: ( BtAlignedAllocator_bool_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_bool_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_bool_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 521 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btActionInterface*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btActionInterface_ptr_16u_ :: IO (BtAlignedAllocator_btActionInterface_ptr_16u_)
btAlignedAllocator_btActionInterface_ptr_16u_ =
  btAlignedAllocator_btActionInterface_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btActionInterface_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 526 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btActionInterface_ptr_16u__free :: ( BtAlignedAllocator_btActionInterface_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btActionInterface_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btActionInterface_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 527 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btBroadphaseInterface*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBroadphaseInterface_ptr_16u_ :: IO (BtAlignedAllocator_btBroadphaseInterface_ptr_16u_)
btAlignedAllocator_btBroadphaseInterface_ptr_16u_ =
  btAlignedAllocator_btBroadphaseInterface_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btBroadphaseInterface_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 532 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btBroadphaseInterface_ptr_16u__free :: ( BtAlignedAllocator_btBroadphaseInterface_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btBroadphaseInterface_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btBroadphaseInterface_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 533 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btBroadphasePair, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBroadphasePair_16u_ :: IO (BtAlignedAllocator_btBroadphasePair_16u_)
btAlignedAllocator_btBroadphasePair_16u_ =
  btAlignedAllocator_btBroadphasePair_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btBroadphasePair_16u_ res >>= \res' ->
  return (res')
{-# LINE 538 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btBroadphasePair_16u__free :: ( BtAlignedAllocator_btBroadphasePair_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btBroadphasePair_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btBroadphasePair_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 539 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBroadphasePair_16u__destroy :: ( BtAlignedAllocator_btBroadphasePair_16u_Class bc , BtBroadphasePairClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btBroadphasePair_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btBroadphasePair_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 545 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBroadphasePair_16u__deallocate :: ( BtAlignedAllocator_btBroadphasePair_16u_Class bc , BtBroadphasePairClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btBroadphasePair_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btBroadphasePair_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 551 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBroadphasePair_16u__construct :: ( BtAlignedAllocator_btBroadphasePair_16u_Class bc , BtBroadphasePairClass p0 , BtBroadphasePairClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btBroadphasePair_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btBroadphasePair_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 558 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBroadphasePair_16u__address :: ( BtAlignedAllocator_btBroadphasePair_16u_Class bc , BtBroadphasePairClass p0 ) => bc -> p0 -> IO (BtBroadphasePair)
btAlignedAllocator_btBroadphasePair_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btBroadphasePair_16u__address'_ a1' a2' >>= \res ->
  mkBtBroadphasePair res >>= \res' ->
  return (res')
{-# LINE 564 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBroadphasePair_16u__address0 :: ( BtAlignedAllocator_btBroadphasePair_16u_Class bc , BtBroadphasePairClass p0 ) => bc -> p0 -> IO (BtBroadphasePair)
btAlignedAllocator_btBroadphasePair_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btBroadphasePair_16u__address0'_ a1' a2' >>= \res ->
  mkBtBroadphasePair res >>= \res' ->
  return (res')
{-# LINE 570 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBroadphasePair_16u__address1 :: ( BtAlignedAllocator_btBroadphasePair_16u_Class bc , BtBroadphasePairClass p0 ) => bc -> p0 -> IO (BtBroadphasePair)
btAlignedAllocator_btBroadphasePair_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btBroadphasePair_16u__address1'_ a1' a2' >>= \res ->
  mkBtBroadphasePair res >>= \res' ->
  return (res')
{-# LINE 576 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btBvhSubtreeInfo, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBvhSubtreeInfo_16u_ :: IO (BtAlignedAllocator_btBvhSubtreeInfo_16u_)
btAlignedAllocator_btBvhSubtreeInfo_16u_ =
  btAlignedAllocator_btBvhSubtreeInfo_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btBvhSubtreeInfo_16u_ res >>= \res' ->
  return (res')
{-# LINE 581 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btBvhSubtreeInfo_16u__free :: ( BtAlignedAllocator_btBvhSubtreeInfo_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btBvhSubtreeInfo_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btBvhSubtreeInfo_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 582 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBvhSubtreeInfo_16u__destroy :: ( BtAlignedAllocator_btBvhSubtreeInfo_16u_Class bc , BtBvhSubtreeInfoClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btBvhSubtreeInfo_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btBvhSubtreeInfo_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 588 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBvhSubtreeInfo_16u__deallocate :: ( BtAlignedAllocator_btBvhSubtreeInfo_16u_Class bc , BtBvhSubtreeInfoClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btBvhSubtreeInfo_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btBvhSubtreeInfo_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 594 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBvhSubtreeInfo_16u__construct :: ( BtAlignedAllocator_btBvhSubtreeInfo_16u_Class bc , BtBvhSubtreeInfoClass p0 , BtBvhSubtreeInfoClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btBvhSubtreeInfo_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btBvhSubtreeInfo_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 601 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBvhSubtreeInfo_16u__address :: ( BtAlignedAllocator_btBvhSubtreeInfo_16u_Class bc , BtBvhSubtreeInfoClass p0 ) => bc -> p0 -> IO (BtBvhSubtreeInfo)
btAlignedAllocator_btBvhSubtreeInfo_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btBvhSubtreeInfo_16u__address'_ a1' a2' >>= \res ->
  mkBtBvhSubtreeInfo res >>= \res' ->
  return (res')
{-# LINE 607 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBvhSubtreeInfo_16u__address0 :: ( BtAlignedAllocator_btBvhSubtreeInfo_16u_Class bc , BtBvhSubtreeInfoClass p0 ) => bc -> p0 -> IO (BtBvhSubtreeInfo)
btAlignedAllocator_btBvhSubtreeInfo_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btBvhSubtreeInfo_16u__address0'_ a1' a2' >>= \res ->
  mkBtBvhSubtreeInfo res >>= \res' ->
  return (res')
{-# LINE 613 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btBvhSubtreeInfo_16u__address1 :: ( BtAlignedAllocator_btBvhSubtreeInfo_16u_Class bc , BtBvhSubtreeInfoClass p0 ) => bc -> p0 -> IO (BtBvhSubtreeInfo)
btAlignedAllocator_btBvhSubtreeInfo_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btBvhSubtreeInfo_16u__address1'_ a1' a2' >>= \res ->
  mkBtBvhSubtreeInfo res >>= \res' ->
  return (res')
{-# LINE 619 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btChunk*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btChunk_ptr_16u_ :: IO (BtAlignedAllocator_btChunk_ptr_16u_)
btAlignedAllocator_btChunk_ptr_16u_ =
  btAlignedAllocator_btChunk_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btChunk_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 624 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btChunk_ptr_16u__free :: ( BtAlignedAllocator_btChunk_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btChunk_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btChunk_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 625 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btCollisionObject*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btCollisionObject_ptr_16u_ :: IO (BtAlignedAllocator_btCollisionObject_ptr_16u_)
btAlignedAllocator_btCollisionObject_ptr_16u_ =
  btAlignedAllocator_btCollisionObject_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btCollisionObject_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 630 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btCollisionObject_ptr_16u__free :: ( BtAlignedAllocator_btCollisionObject_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btCollisionObject_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btCollisionObject_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 631 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btCollisionShape*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btCollisionShape_ptr_16u_ :: IO (BtAlignedAllocator_btCollisionShape_ptr_16u_)
btAlignedAllocator_btCollisionShape_ptr_16u_ =
  btAlignedAllocator_btCollisionShape_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btCollisionShape_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 636 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btCollisionShape_ptr_16u__free :: ( BtAlignedAllocator_btCollisionShape_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btCollisionShape_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btCollisionShape_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 637 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btCompoundShapeChild, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btCompoundShapeChild_16u_ :: IO (BtAlignedAllocator_btCompoundShapeChild_16u_)
btAlignedAllocator_btCompoundShapeChild_16u_ =
  btAlignedAllocator_btCompoundShapeChild_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btCompoundShapeChild_16u_ res >>= \res' ->
  return (res')
{-# LINE 642 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btCompoundShapeChild_16u__free :: ( BtAlignedAllocator_btCompoundShapeChild_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btCompoundShapeChild_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btCompoundShapeChild_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 643 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btCompoundShapeChild_16u__destroy :: ( BtAlignedAllocator_btCompoundShapeChild_16u_Class bc , BtCompoundShapeChildClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btCompoundShapeChild_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btCompoundShapeChild_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 649 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btCompoundShapeChild_16u__deallocate :: ( BtAlignedAllocator_btCompoundShapeChild_16u_Class bc , BtCompoundShapeChildClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btCompoundShapeChild_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btCompoundShapeChild_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 655 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btCompoundShapeChild_16u__construct :: ( BtAlignedAllocator_btCompoundShapeChild_16u_Class bc , BtCompoundShapeChildClass p0 , BtCompoundShapeChildClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btCompoundShapeChild_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btCompoundShapeChild_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 662 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btCompoundShapeChild_16u__address :: ( BtAlignedAllocator_btCompoundShapeChild_16u_Class bc , BtCompoundShapeChildClass p0 ) => bc -> p0 -> IO (BtCompoundShapeChild)
btAlignedAllocator_btCompoundShapeChild_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btCompoundShapeChild_16u__address'_ a1' a2' >>= \res ->
  mkBtCompoundShapeChild res >>= \res' ->
  return (res')
{-# LINE 668 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btCompoundShapeChild_16u__address0 :: ( BtAlignedAllocator_btCompoundShapeChild_16u_Class bc , BtCompoundShapeChildClass p0 ) => bc -> p0 -> IO (BtCompoundShapeChild)
btAlignedAllocator_btCompoundShapeChild_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btCompoundShapeChild_16u__address0'_ a1' a2' >>= \res ->
  mkBtCompoundShapeChild res >>= \res' ->
  return (res')
{-# LINE 674 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btCompoundShapeChild_16u__address1 :: ( BtAlignedAllocator_btCompoundShapeChild_16u_Class bc , BtCompoundShapeChildClass p0 ) => bc -> p0 -> IO (BtCompoundShapeChild)
btAlignedAllocator_btCompoundShapeChild_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btCompoundShapeChild_16u__address1'_ a1' a2' >>= \res ->
  mkBtCompoundShapeChild res >>= \res' ->
  return (res')
{-# LINE 680 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btDbvt::sStkNN, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNN_16u_ :: IO (BtAlignedAllocator_btDbvt_sStkNN_16u_)
btAlignedAllocator_btDbvt_sStkNN_16u_ =
  btAlignedAllocator_btDbvt_sStkNN_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btDbvt_sStkNN_16u_ res >>= \res' ->
  return (res')
{-# LINE 685 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btDbvt_sStkNN_16u__free :: ( BtAlignedAllocator_btDbvt_sStkNN_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btDbvt_sStkNN_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btDbvt_sStkNN_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 686 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNN_16u__destroy :: ( BtAlignedAllocator_btDbvt_sStkNN_16u_Class bc , BtDbvt_sStkNNClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btDbvt_sStkNN_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNN_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 692 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNN_16u__deallocate :: ( BtAlignedAllocator_btDbvt_sStkNN_16u_Class bc , BtDbvt_sStkNNClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btDbvt_sStkNN_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNN_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 698 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNN_16u__construct :: ( BtAlignedAllocator_btDbvt_sStkNN_16u_Class bc , BtDbvt_sStkNNClass p0 , BtDbvt_sStkNNClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btDbvt_sStkNN_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btDbvt_sStkNN_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 705 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNN_16u__address :: ( BtAlignedAllocator_btDbvt_sStkNN_16u_Class bc , BtDbvt_sStkNNClass p0 ) => bc -> p0 -> IO (BtDbvt_sStkNN)
btAlignedAllocator_btDbvt_sStkNN_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNN_16u__address'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNN res >>= \res' ->
  return (res')
{-# LINE 711 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNN_16u__address0 :: ( BtAlignedAllocator_btDbvt_sStkNN_16u_Class bc , BtDbvt_sStkNNClass p0 ) => bc -> p0 -> IO (BtDbvt_sStkNN)
btAlignedAllocator_btDbvt_sStkNN_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNN_16u__address0'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNN res >>= \res' ->
  return (res')
{-# LINE 717 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNN_16u__address1 :: ( BtAlignedAllocator_btDbvt_sStkNN_16u_Class bc , BtDbvt_sStkNNClass p0 ) => bc -> p0 -> IO (BtDbvt_sStkNN)
btAlignedAllocator_btDbvt_sStkNN_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNN_16u__address1'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNN res >>= \res' ->
  return (res')
{-# LINE 723 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btDbvt::sStkNP, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNP_16u_ :: IO (BtAlignedAllocator_btDbvt_sStkNP_16u_)
btAlignedAllocator_btDbvt_sStkNP_16u_ =
  btAlignedAllocator_btDbvt_sStkNP_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btDbvt_sStkNP_16u_ res >>= \res' ->
  return (res')
{-# LINE 728 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btDbvt_sStkNP_16u__free :: ( BtAlignedAllocator_btDbvt_sStkNP_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btDbvt_sStkNP_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btDbvt_sStkNP_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 729 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNP_16u__destroy :: ( BtAlignedAllocator_btDbvt_sStkNP_16u_Class bc , BtDbvt_sStkNPClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btDbvt_sStkNP_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNP_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 735 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNP_16u__deallocate :: ( BtAlignedAllocator_btDbvt_sStkNP_16u_Class bc , BtDbvt_sStkNPClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btDbvt_sStkNP_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNP_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 741 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNP_16u__construct :: ( BtAlignedAllocator_btDbvt_sStkNP_16u_Class bc , BtDbvt_sStkNPClass p0 , BtDbvt_sStkNPClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btDbvt_sStkNP_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btDbvt_sStkNP_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 748 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNP_16u__address :: ( BtAlignedAllocator_btDbvt_sStkNP_16u_Class bc , BtDbvt_sStkNPClass p0 ) => bc -> p0 -> IO (BtDbvt_sStkNP)
btAlignedAllocator_btDbvt_sStkNP_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNP_16u__address'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNP res >>= \res' ->
  return (res')
{-# LINE 754 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNP_16u__address0 :: ( BtAlignedAllocator_btDbvt_sStkNP_16u_Class bc , BtDbvt_sStkNPClass p0 ) => bc -> p0 -> IO (BtDbvt_sStkNP)
btAlignedAllocator_btDbvt_sStkNP_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNP_16u__address0'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNP res >>= \res' ->
  return (res')
{-# LINE 760 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNP_16u__address1 :: ( BtAlignedAllocator_btDbvt_sStkNP_16u_Class bc , BtDbvt_sStkNPClass p0 ) => bc -> p0 -> IO (BtDbvt_sStkNP)
btAlignedAllocator_btDbvt_sStkNP_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNP_16u__address1'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNP res >>= \res' ->
  return (res')
{-# LINE 766 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btDbvt::sStkNPS, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNPS_16u_ :: IO (BtAlignedAllocator_btDbvt_sStkNPS_16u_)
btAlignedAllocator_btDbvt_sStkNPS_16u_ =
  btAlignedAllocator_btDbvt_sStkNPS_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btDbvt_sStkNPS_16u_ res >>= \res' ->
  return (res')
{-# LINE 771 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btDbvt_sStkNPS_16u__free :: ( BtAlignedAllocator_btDbvt_sStkNPS_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btDbvt_sStkNPS_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btDbvt_sStkNPS_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 772 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNPS_16u__destroy :: ( BtAlignedAllocator_btDbvt_sStkNPS_16u_Class bc , BtDbvt_sStkNPSClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btDbvt_sStkNPS_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNPS_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 778 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNPS_16u__deallocate :: ( BtAlignedAllocator_btDbvt_sStkNPS_16u_Class bc , BtDbvt_sStkNPSClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btDbvt_sStkNPS_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNPS_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 784 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNPS_16u__construct :: ( BtAlignedAllocator_btDbvt_sStkNPS_16u_Class bc , BtDbvt_sStkNPSClass p0 , BtDbvt_sStkNPSClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btDbvt_sStkNPS_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btDbvt_sStkNPS_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 791 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNPS_16u__address :: ( BtAlignedAllocator_btDbvt_sStkNPS_16u_Class bc , BtDbvt_sStkNPSClass p0 ) => bc -> p0 -> IO (BtDbvt_sStkNPS)
btAlignedAllocator_btDbvt_sStkNPS_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNPS_16u__address'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNPS res >>= \res' ->
  return (res')
{-# LINE 797 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNPS_16u__address0 :: ( BtAlignedAllocator_btDbvt_sStkNPS_16u_Class bc , BtDbvt_sStkNPSClass p0 ) => bc -> p0 -> IO (BtDbvt_sStkNPS)
btAlignedAllocator_btDbvt_sStkNPS_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNPS_16u__address0'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNPS res >>= \res' ->
  return (res')
{-# LINE 803 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvt_sStkNPS_16u__address1 :: ( BtAlignedAllocator_btDbvt_sStkNPS_16u_Class bc , BtDbvt_sStkNPSClass p0 ) => bc -> p0 -> IO (BtDbvt_sStkNPS)
btAlignedAllocator_btDbvt_sStkNPS_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btDbvt_sStkNPS_16u__address1'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNPS res >>= \res' ->
  return (res')
{-# LINE 809 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btDbvtNode const*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btDbvtNodeconst_ptr_16u_ :: IO (BtAlignedAllocator_btDbvtNodeconst_ptr_16u_)
btAlignedAllocator_btDbvtNodeconst_ptr_16u_ =
  btAlignedAllocator_btDbvtNodeconst_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btDbvtNodeconst_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 814 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btDbvtNodeconst_ptr_16u__free :: ( BtAlignedAllocator_btDbvtNodeconst_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btDbvtNodeconst_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btDbvtNodeconst_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 815 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btGImpactMeshShapePart*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btGImpactMeshShapePart_ptr_16u_ :: IO (BtAlignedAllocator_btGImpactMeshShapePart_ptr_16u_)
btAlignedAllocator_btGImpactMeshShapePart_ptr_16u_ =
  btAlignedAllocator_btGImpactMeshShapePart_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btGImpactMeshShapePart_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 820 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btGImpactMeshShapePart_ptr_16u__free :: ( BtAlignedAllocator_btGImpactMeshShapePart_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btGImpactMeshShapePart_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btGImpactMeshShapePart_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 821 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btHashInt, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashInt_16u_ :: IO (BtAlignedAllocator_btHashInt_16u_)
btAlignedAllocator_btHashInt_16u_ =
  btAlignedAllocator_btHashInt_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btHashInt_16u_ res >>= \res' ->
  return (res')
{-# LINE 826 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btHashInt_16u__free :: ( BtAlignedAllocator_btHashInt_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btHashInt_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btHashInt_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 827 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashInt_16u__destroy :: ( BtAlignedAllocator_btHashInt_16u_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btHashInt_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashInt_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 833 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashInt_16u__deallocate :: ( BtAlignedAllocator_btHashInt_16u_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btHashInt_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashInt_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 839 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashInt_16u__construct :: ( BtAlignedAllocator_btHashInt_16u_Class bc , BtHashIntClass p0 , BtHashIntClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btHashInt_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btHashInt_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 846 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashInt_16u__address :: ( BtAlignedAllocator_btHashInt_16u_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO (BtHashInt)
btAlignedAllocator_btHashInt_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashInt_16u__address'_ a1' a2' >>= \res ->
  mkBtHashInt res >>= \res' ->
  return (res')
{-# LINE 852 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashInt_16u__address0 :: ( BtAlignedAllocator_btHashInt_16u_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO (BtHashInt)
btAlignedAllocator_btHashInt_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashInt_16u__address0'_ a1' a2' >>= \res ->
  mkBtHashInt res >>= \res' ->
  return (res')
{-# LINE 858 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashInt_16u__address1 :: ( BtAlignedAllocator_btHashInt_16u_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO (BtHashInt)
btAlignedAllocator_btHashInt_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashInt_16u__address1'_ a1' a2' >>= \res ->
  mkBtHashInt res >>= \res' ->
  return (res')
{-# LINE 864 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btHashPtr, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashPtr_16u_ :: IO (BtAlignedAllocator_btHashPtr_16u_)
btAlignedAllocator_btHashPtr_16u_ =
  btAlignedAllocator_btHashPtr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btHashPtr_16u_ res >>= \res' ->
  return (res')
{-# LINE 869 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btHashPtr_16u__free :: ( BtAlignedAllocator_btHashPtr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btHashPtr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btHashPtr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 870 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashPtr_16u__destroy :: ( BtAlignedAllocator_btHashPtr_16u_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btHashPtr_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashPtr_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 876 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashPtr_16u__deallocate :: ( BtAlignedAllocator_btHashPtr_16u_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btHashPtr_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashPtr_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 882 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashPtr_16u__construct :: ( BtAlignedAllocator_btHashPtr_16u_Class bc , BtHashPtrClass p0 , BtHashPtrClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btHashPtr_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btHashPtr_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 889 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashPtr_16u__address :: ( BtAlignedAllocator_btHashPtr_16u_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO (BtHashPtr)
btAlignedAllocator_btHashPtr_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashPtr_16u__address'_ a1' a2' >>= \res ->
  mkBtHashPtr res >>= \res' ->
  return (res')
{-# LINE 895 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashPtr_16u__address0 :: ( BtAlignedAllocator_btHashPtr_16u_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO (BtHashPtr)
btAlignedAllocator_btHashPtr_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashPtr_16u__address0'_ a1' a2' >>= \res ->
  mkBtHashPtr res >>= \res' ->
  return (res')
{-# LINE 901 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashPtr_16u__address1 :: ( BtAlignedAllocator_btHashPtr_16u_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO (BtHashPtr)
btAlignedAllocator_btHashPtr_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashPtr_16u__address1'_ a1' a2' >>= \res ->
  mkBtHashPtr res >>= \res' ->
  return (res')
{-# LINE 907 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btHashString, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashString_16u_ :: IO (BtAlignedAllocator_btHashString_16u_)
btAlignedAllocator_btHashString_16u_ =
  btAlignedAllocator_btHashString_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btHashString_16u_ res >>= \res' ->
  return (res')
{-# LINE 912 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btHashString_16u__free :: ( BtAlignedAllocator_btHashString_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btHashString_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btHashString_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 913 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashString_16u__destroy :: ( BtAlignedAllocator_btHashString_16u_Class bc , BtHashStringClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btHashString_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashString_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 919 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashString_16u__deallocate :: ( BtAlignedAllocator_btHashString_16u_Class bc , BtHashStringClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btHashString_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashString_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 925 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashString_16u__construct :: ( BtAlignedAllocator_btHashString_16u_Class bc , BtHashStringClass p0 , BtHashStringClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btHashString_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btHashString_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 932 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashString_16u__address :: ( BtAlignedAllocator_btHashString_16u_Class bc , BtHashStringClass p0 ) => bc -> p0 -> IO (BtHashString)
btAlignedAllocator_btHashString_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashString_16u__address'_ a1' a2' >>= \res ->
  mkBtHashString res >>= \res' ->
  return (res')
{-# LINE 938 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashString_16u__address0 :: ( BtAlignedAllocator_btHashString_16u_Class bc , BtHashStringClass p0 ) => bc -> p0 -> IO (BtHashString)
btAlignedAllocator_btHashString_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashString_16u__address0'_ a1' a2' >>= \res ->
  mkBtHashString res >>= \res' ->
  return (res')
{-# LINE 944 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btHashString_16u__address1 :: ( BtAlignedAllocator_btHashString_16u_Class bc , BtHashStringClass p0 ) => bc -> p0 -> IO (BtHashString)
btAlignedAllocator_btHashString_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btHashString_16u__address1'_ a1' a2' >>= \res ->
  mkBtHashString res >>= \res' ->
  return (res')
{-# LINE 950 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btIndexedMesh, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btIndexedMesh_16u_ :: IO (BtAlignedAllocator_btIndexedMesh_16u_)
btAlignedAllocator_btIndexedMesh_16u_ =
  btAlignedAllocator_btIndexedMesh_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btIndexedMesh_16u_ res >>= \res' ->
  return (res')
{-# LINE 955 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btIndexedMesh_16u__free :: ( BtAlignedAllocator_btIndexedMesh_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btIndexedMesh_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btIndexedMesh_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 956 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btIndexedMesh_16u__destroy :: ( BtAlignedAllocator_btIndexedMesh_16u_Class bc , BtIndexedMeshClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btIndexedMesh_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btIndexedMesh_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 962 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btIndexedMesh_16u__deallocate :: ( BtAlignedAllocator_btIndexedMesh_16u_Class bc , BtIndexedMeshClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btIndexedMesh_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btIndexedMesh_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 968 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btIndexedMesh_16u__construct :: ( BtAlignedAllocator_btIndexedMesh_16u_Class bc , BtIndexedMeshClass p0 , BtIndexedMeshClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btIndexedMesh_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btIndexedMesh_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 975 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btIndexedMesh_16u__address :: ( BtAlignedAllocator_btIndexedMesh_16u_Class bc , BtIndexedMeshClass p0 ) => bc -> p0 -> IO (BtIndexedMesh)
btAlignedAllocator_btIndexedMesh_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btIndexedMesh_16u__address'_ a1' a2' >>= \res ->
  mkBtIndexedMesh res >>= \res' ->
  return (res')
{-# LINE 981 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btIndexedMesh_16u__address0 :: ( BtAlignedAllocator_btIndexedMesh_16u_Class bc , BtIndexedMeshClass p0 ) => bc -> p0 -> IO (BtIndexedMesh)
btAlignedAllocator_btIndexedMesh_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btIndexedMesh_16u__address0'_ a1' a2' >>= \res ->
  mkBtIndexedMesh res >>= \res' ->
  return (res')
{-# LINE 987 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btIndexedMesh_16u__address1 :: ( BtAlignedAllocator_btIndexedMesh_16u_Class bc , BtIndexedMeshClass p0 ) => bc -> p0 -> IO (BtIndexedMesh)
btAlignedAllocator_btIndexedMesh_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btIndexedMesh_16u__address1'_ a1' a2' >>= \res ->
  mkBtIndexedMesh res >>= \res' ->
  return (res')
{-# LINE 993 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btMultiSapBroadphase::btBridgeProxy*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u_ :: IO (BtAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u_)
btAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u_ =
  btAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 998 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u__free :: ( BtAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 999 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btMultiSapBroadphase::btMultiSapProxy*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u_ :: IO (BtAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u_)
btAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u_ =
  btAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1004 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u__free :: ( BtAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1005 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btOptimizedBvhNode, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btOptimizedBvhNode_16u_ :: IO (BtAlignedAllocator_btOptimizedBvhNode_16u_)
btAlignedAllocator_btOptimizedBvhNode_16u_ =
  btAlignedAllocator_btOptimizedBvhNode_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btOptimizedBvhNode_16u_ res >>= \res' ->
  return (res')
{-# LINE 1010 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btOptimizedBvhNode_16u__free :: ( BtAlignedAllocator_btOptimizedBvhNode_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btOptimizedBvhNode_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btOptimizedBvhNode_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1011 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btOptimizedBvhNode_16u__destroy :: ( BtAlignedAllocator_btOptimizedBvhNode_16u_Class bc , BtOptimizedBvhNodeClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btOptimizedBvhNode_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btOptimizedBvhNode_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1017 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btOptimizedBvhNode_16u__deallocate :: ( BtAlignedAllocator_btOptimizedBvhNode_16u_Class bc , BtOptimizedBvhNodeClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btOptimizedBvhNode_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btOptimizedBvhNode_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1023 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btOptimizedBvhNode_16u__construct :: ( BtAlignedAllocator_btOptimizedBvhNode_16u_Class bc , BtOptimizedBvhNodeClass p0 , BtOptimizedBvhNodeClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btOptimizedBvhNode_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btOptimizedBvhNode_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1030 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btOptimizedBvhNode_16u__address :: ( BtAlignedAllocator_btOptimizedBvhNode_16u_Class bc , BtOptimizedBvhNodeClass p0 ) => bc -> p0 -> IO (BtOptimizedBvhNode)
btAlignedAllocator_btOptimizedBvhNode_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btOptimizedBvhNode_16u__address'_ a1' a2' >>= \res ->
  mkBtOptimizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 1036 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btOptimizedBvhNode_16u__address0 :: ( BtAlignedAllocator_btOptimizedBvhNode_16u_Class bc , BtOptimizedBvhNodeClass p0 ) => bc -> p0 -> IO (BtOptimizedBvhNode)
btAlignedAllocator_btOptimizedBvhNode_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btOptimizedBvhNode_16u__address0'_ a1' a2' >>= \res ->
  mkBtOptimizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 1042 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btOptimizedBvhNode_16u__address1 :: ( BtAlignedAllocator_btOptimizedBvhNode_16u_Class bc , BtOptimizedBvhNodeClass p0 ) => bc -> p0 -> IO (BtOptimizedBvhNode)
btAlignedAllocator_btOptimizedBvhNode_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btOptimizedBvhNode_16u__address1'_ a1' a2' >>= \res ->
  mkBtOptimizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 1048 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btPersistentManifold*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btPersistentManifold_ptr_16u_ :: IO (BtAlignedAllocator_btPersistentManifold_ptr_16u_)
btAlignedAllocator_btPersistentManifold_ptr_16u_ =
  btAlignedAllocator_btPersistentManifold_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btPersistentManifold_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1053 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btPersistentManifold_ptr_16u__free :: ( BtAlignedAllocator_btPersistentManifold_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btPersistentManifold_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btPersistentManifold_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1054 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btPointerUid, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btPointerUid_16u_ :: IO (BtAlignedAllocator_btPointerUid_16u_)
btAlignedAllocator_btPointerUid_16u_ =
  btAlignedAllocator_btPointerUid_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btPointerUid_16u_ res >>= \res' ->
  return (res')
{-# LINE 1059 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btPointerUid_16u__free :: ( BtAlignedAllocator_btPointerUid_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btPointerUid_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btPointerUid_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1060 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btPointerUid_16u__destroy :: ( BtAlignedAllocator_btPointerUid_16u_Class bc , BtPointerUidClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btPointerUid_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btPointerUid_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1066 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btPointerUid_16u__deallocate :: ( BtAlignedAllocator_btPointerUid_16u_Class bc , BtPointerUidClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btPointerUid_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btPointerUid_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1072 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btPointerUid_16u__construct :: ( BtAlignedAllocator_btPointerUid_16u_Class bc , BtPointerUidClass p0 , BtPointerUidClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btPointerUid_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btPointerUid_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1079 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btPointerUid_16u__address :: ( BtAlignedAllocator_btPointerUid_16u_Class bc , BtPointerUidClass p0 ) => bc -> p0 -> IO (BtPointerUid)
btAlignedAllocator_btPointerUid_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btPointerUid_16u__address'_ a1' a2' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 1085 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btPointerUid_16u__address0 :: ( BtAlignedAllocator_btPointerUid_16u_Class bc , BtPointerUidClass p0 ) => bc -> p0 -> IO (BtPointerUid)
btAlignedAllocator_btPointerUid_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btPointerUid_16u__address0'_ a1' a2' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 1091 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btPointerUid_16u__address1 :: ( BtAlignedAllocator_btPointerUid_16u_Class bc , BtPointerUidClass p0 ) => bc -> p0 -> IO (BtPointerUid)
btAlignedAllocator_btPointerUid_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btPointerUid_16u__address1'_ a1' a2' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 1097 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btQuantizedBvhNode, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btQuantizedBvhNode_16u_ :: IO (BtAlignedAllocator_btQuantizedBvhNode_16u_)
btAlignedAllocator_btQuantizedBvhNode_16u_ =
  btAlignedAllocator_btQuantizedBvhNode_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btQuantizedBvhNode_16u_ res >>= \res' ->
  return (res')
{-# LINE 1102 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btQuantizedBvhNode_16u__free :: ( BtAlignedAllocator_btQuantizedBvhNode_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btQuantizedBvhNode_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btQuantizedBvhNode_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1103 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btQuantizedBvhNode_16u__destroy :: ( BtAlignedAllocator_btQuantizedBvhNode_16u_Class bc , BtQuantizedBvhNodeClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btQuantizedBvhNode_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btQuantizedBvhNode_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1109 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btQuantizedBvhNode_16u__deallocate :: ( BtAlignedAllocator_btQuantizedBvhNode_16u_Class bc , BtQuantizedBvhNodeClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btQuantizedBvhNode_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btQuantizedBvhNode_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1115 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btQuantizedBvhNode_16u__construct :: ( BtAlignedAllocator_btQuantizedBvhNode_16u_Class bc , BtQuantizedBvhNodeClass p0 , BtQuantizedBvhNodeClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btQuantizedBvhNode_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btQuantizedBvhNode_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1122 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btQuantizedBvhNode_16u__address :: ( BtAlignedAllocator_btQuantizedBvhNode_16u_Class bc , BtQuantizedBvhNodeClass p0 ) => bc -> p0 -> IO (BtQuantizedBvhNode)
btAlignedAllocator_btQuantizedBvhNode_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btQuantizedBvhNode_16u__address'_ a1' a2' >>= \res ->
  mkBtQuantizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 1128 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btQuantizedBvhNode_16u__address0 :: ( BtAlignedAllocator_btQuantizedBvhNode_16u_Class bc , BtQuantizedBvhNodeClass p0 ) => bc -> p0 -> IO (BtQuantizedBvhNode)
btAlignedAllocator_btQuantizedBvhNode_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btQuantizedBvhNode_16u__address0'_ a1' a2' >>= \res ->
  mkBtQuantizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 1134 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btQuantizedBvhNode_16u__address1 :: ( BtAlignedAllocator_btQuantizedBvhNode_16u_Class bc , BtQuantizedBvhNodeClass p0 ) => bc -> p0 -> IO (BtQuantizedBvhNode)
btAlignedAllocator_btQuantizedBvhNode_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btQuantizedBvhNode_16u__address1'_ a1' a2' >>= \res ->
  mkBtQuantizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 1140 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btRigidBody*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btRigidBody_ptr_16u_ :: IO (BtAlignedAllocator_btRigidBody_ptr_16u_)
btAlignedAllocator_btRigidBody_ptr_16u_ =
  btAlignedAllocator_btRigidBody_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btRigidBody_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1145 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btRigidBody_ptr_16u__free :: ( BtAlignedAllocator_btRigidBody_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btRigidBody_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btRigidBody_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1146 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_ptr_16u_ :: IO (BtAlignedAllocator_btSoftBody_ptr_16u_)
btAlignedAllocator_btSoftBody_ptr_16u_ =
  btAlignedAllocator_btSoftBody_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1151 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_ptr_16u__free :: ( BtAlignedAllocator_btSoftBody_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1152 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::Anchor, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Anchor_16u_ :: IO (BtAlignedAllocator_btSoftBody_Anchor_16u_)
btAlignedAllocator_btSoftBody_Anchor_16u_ =
  btAlignedAllocator_btSoftBody_Anchor_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Anchor_16u_ res >>= \res' ->
  return (res')
{-# LINE 1157 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_Anchor_16u__free :: ( BtAlignedAllocator_btSoftBody_Anchor_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_Anchor_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_Anchor_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1158 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Anchor_16u__destroy :: ( BtAlignedAllocator_btSoftBody_Anchor_16u_Class bc , BtSoftBody_AnchorClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_Anchor_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Anchor_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1164 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Anchor_16u__deallocate :: ( BtAlignedAllocator_btSoftBody_Anchor_16u_Class bc , BtSoftBody_AnchorClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_Anchor_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Anchor_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1170 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Anchor_16u__construct :: ( BtAlignedAllocator_btSoftBody_Anchor_16u_Class bc , BtSoftBody_AnchorClass p0 , BtSoftBody_AnchorClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btSoftBody_Anchor_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btSoftBody_Anchor_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1177 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Anchor_16u__address :: ( BtAlignedAllocator_btSoftBody_Anchor_16u_Class bc , BtSoftBody_AnchorClass p0 ) => bc -> p0 -> IO (BtSoftBody_Anchor)
btAlignedAllocator_btSoftBody_Anchor_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Anchor_16u__address'_ a1' a2' >>= \res ->
  mkBtSoftBody_Anchor res >>= \res' ->
  return (res')
{-# LINE 1183 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Anchor_16u__address0 :: ( BtAlignedAllocator_btSoftBody_Anchor_16u_Class bc , BtSoftBody_AnchorClass p0 ) => bc -> p0 -> IO (BtSoftBody_Anchor)
btAlignedAllocator_btSoftBody_Anchor_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Anchor_16u__address0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Anchor res >>= \res' ->
  return (res')
{-# LINE 1189 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Anchor_16u__address1 :: ( BtAlignedAllocator_btSoftBody_Anchor_16u_Class bc , BtSoftBody_AnchorClass p0 ) => bc -> p0 -> IO (BtSoftBody_Anchor)
btAlignedAllocator_btSoftBody_Anchor_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Anchor_16u__address1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Anchor res >>= \res' ->
  return (res')
{-# LINE 1195 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::Cluster*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Cluster_ptr_16u_ :: IO (BtAlignedAllocator_btSoftBody_Cluster_ptr_16u_)
btAlignedAllocator_btSoftBody_Cluster_ptr_16u_ =
  btAlignedAllocator_btSoftBody_Cluster_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Cluster_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1200 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_Cluster_ptr_16u__free :: ( BtAlignedAllocator_btSoftBody_Cluster_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_Cluster_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_Cluster_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1201 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::Face, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Face_16u_ :: IO (BtAlignedAllocator_btSoftBody_Face_16u_)
btAlignedAllocator_btSoftBody_Face_16u_ =
  btAlignedAllocator_btSoftBody_Face_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Face_16u_ res >>= \res' ->
  return (res')
{-# LINE 1206 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_Face_16u__free :: ( BtAlignedAllocator_btSoftBody_Face_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_Face_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_Face_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1207 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Face_16u__destroy :: ( BtAlignedAllocator_btSoftBody_Face_16u_Class bc , BtSoftBody_FaceClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_Face_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Face_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1213 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Face_16u__deallocate :: ( BtAlignedAllocator_btSoftBody_Face_16u_Class bc , BtSoftBody_FaceClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_Face_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Face_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1219 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Face_16u__construct :: ( BtAlignedAllocator_btSoftBody_Face_16u_Class bc , BtSoftBody_FaceClass p0 , BtSoftBody_FaceClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btSoftBody_Face_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btSoftBody_Face_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1226 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Face_16u__address :: ( BtAlignedAllocator_btSoftBody_Face_16u_Class bc , BtSoftBody_FaceClass p0 ) => bc -> p0 -> IO (BtSoftBody_Face)
btAlignedAllocator_btSoftBody_Face_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Face_16u__address'_ a1' a2' >>= \res ->
  mkBtSoftBody_Face res >>= \res' ->
  return (res')
{-# LINE 1232 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Face_16u__address0 :: ( BtAlignedAllocator_btSoftBody_Face_16u_Class bc , BtSoftBody_FaceClass p0 ) => bc -> p0 -> IO (BtSoftBody_Face)
btAlignedAllocator_btSoftBody_Face_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Face_16u__address0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Face res >>= \res' ->
  return (res')
{-# LINE 1238 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Face_16u__address1 :: ( BtAlignedAllocator_btSoftBody_Face_16u_Class bc , BtSoftBody_FaceClass p0 ) => bc -> p0 -> IO (BtSoftBody_Face)
btAlignedAllocator_btSoftBody_Face_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Face_16u__address1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Face res >>= \res' ->
  return (res')
{-# LINE 1244 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::Joint*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Joint_ptr_16u_ :: IO (BtAlignedAllocator_btSoftBody_Joint_ptr_16u_)
btAlignedAllocator_btSoftBody_Joint_ptr_16u_ =
  btAlignedAllocator_btSoftBody_Joint_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Joint_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1249 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_Joint_ptr_16u__free :: ( BtAlignedAllocator_btSoftBody_Joint_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_Joint_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_Joint_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1250 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::Link, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Link_16u_ :: IO (BtAlignedAllocator_btSoftBody_Link_16u_)
btAlignedAllocator_btSoftBody_Link_16u_ =
  btAlignedAllocator_btSoftBody_Link_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Link_16u_ res >>= \res' ->
  return (res')
{-# LINE 1255 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_Link_16u__free :: ( BtAlignedAllocator_btSoftBody_Link_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_Link_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_Link_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1256 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Link_16u__destroy :: ( BtAlignedAllocator_btSoftBody_Link_16u_Class bc , BtSoftBody_LinkClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_Link_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Link_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1262 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Link_16u__deallocate :: ( BtAlignedAllocator_btSoftBody_Link_16u_Class bc , BtSoftBody_LinkClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_Link_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Link_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1268 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Link_16u__construct :: ( BtAlignedAllocator_btSoftBody_Link_16u_Class bc , BtSoftBody_LinkClass p0 , BtSoftBody_LinkClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btSoftBody_Link_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btSoftBody_Link_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1275 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Link_16u__address :: ( BtAlignedAllocator_btSoftBody_Link_16u_Class bc , BtSoftBody_LinkClass p0 ) => bc -> p0 -> IO (BtSoftBody_Link)
btAlignedAllocator_btSoftBody_Link_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Link_16u__address'_ a1' a2' >>= \res ->
  mkBtSoftBody_Link res >>= \res' ->
  return (res')
{-# LINE 1281 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Link_16u__address0 :: ( BtAlignedAllocator_btSoftBody_Link_16u_Class bc , BtSoftBody_LinkClass p0 ) => bc -> p0 -> IO (BtSoftBody_Link)
btAlignedAllocator_btSoftBody_Link_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Link_16u__address0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Link res >>= \res' ->
  return (res')
{-# LINE 1287 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Link_16u__address1 :: ( BtAlignedAllocator_btSoftBody_Link_16u_Class bc , BtSoftBody_LinkClass p0 ) => bc -> p0 -> IO (BtSoftBody_Link)
btAlignedAllocator_btSoftBody_Link_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Link_16u__address1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Link res >>= \res' ->
  return (res')
{-# LINE 1293 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::Material*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Material_ptr_16u_ :: IO (BtAlignedAllocator_btSoftBody_Material_ptr_16u_)
btAlignedAllocator_btSoftBody_Material_ptr_16u_ =
  btAlignedAllocator_btSoftBody_Material_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Material_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1298 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_Material_ptr_16u__free :: ( BtAlignedAllocator_btSoftBody_Material_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_Material_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_Material_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1299 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::Node*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Node_ptr_16u_ :: IO (BtAlignedAllocator_btSoftBody_Node_ptr_16u_)
btAlignedAllocator_btSoftBody_Node_ptr_16u_ =
  btAlignedAllocator_btSoftBody_Node_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Node_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1304 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_Node_ptr_16u__free :: ( BtAlignedAllocator_btSoftBody_Node_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_Node_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_Node_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1305 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::Node, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Node_16u_ :: IO (BtAlignedAllocator_btSoftBody_Node_16u_)
btAlignedAllocator_btSoftBody_Node_16u_ =
  btAlignedAllocator_btSoftBody_Node_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Node_16u_ res >>= \res' ->
  return (res')
{-# LINE 1310 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_Node_16u__free :: ( BtAlignedAllocator_btSoftBody_Node_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_Node_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_Node_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1311 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Node_16u__destroy :: ( BtAlignedAllocator_btSoftBody_Node_16u_Class bc , BtSoftBody_NodeClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_Node_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Node_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1317 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Node_16u__deallocate :: ( BtAlignedAllocator_btSoftBody_Node_16u_Class bc , BtSoftBody_NodeClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_Node_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Node_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1323 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Node_16u__construct :: ( BtAlignedAllocator_btSoftBody_Node_16u_Class bc , BtSoftBody_NodeClass p0 , BtSoftBody_NodeClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btSoftBody_Node_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btSoftBody_Node_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1330 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Node_16u__address :: ( BtAlignedAllocator_btSoftBody_Node_16u_Class bc , BtSoftBody_NodeClass p0 ) => bc -> p0 -> IO (BtSoftBody_Node)
btAlignedAllocator_btSoftBody_Node_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Node_16u__address'_ a1' a2' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 1336 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Node_16u__address0 :: ( BtAlignedAllocator_btSoftBody_Node_16u_Class bc , BtSoftBody_NodeClass p0 ) => bc -> p0 -> IO (BtSoftBody_Node)
btAlignedAllocator_btSoftBody_Node_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Node_16u__address0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 1342 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Node_16u__address1 :: ( BtAlignedAllocator_btSoftBody_Node_16u_Class bc , BtSoftBody_NodeClass p0 ) => bc -> p0 -> IO (BtSoftBody_Node)
btAlignedAllocator_btSoftBody_Node_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Node_16u__address1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 1348 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::Note, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Note_16u_ :: IO (BtAlignedAllocator_btSoftBody_Note_16u_)
btAlignedAllocator_btSoftBody_Note_16u_ =
  btAlignedAllocator_btSoftBody_Note_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Note_16u_ res >>= \res' ->
  return (res')
{-# LINE 1353 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_Note_16u__free :: ( BtAlignedAllocator_btSoftBody_Note_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_Note_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_Note_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1354 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Note_16u__destroy :: ( BtAlignedAllocator_btSoftBody_Note_16u_Class bc , BtSoftBody_NoteClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_Note_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Note_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1360 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Note_16u__deallocate :: ( BtAlignedAllocator_btSoftBody_Note_16u_Class bc , BtSoftBody_NoteClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_Note_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Note_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1366 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Note_16u__construct :: ( BtAlignedAllocator_btSoftBody_Note_16u_Class bc , BtSoftBody_NoteClass p0 , BtSoftBody_NoteClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btSoftBody_Note_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btSoftBody_Note_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1373 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Note_16u__address :: ( BtAlignedAllocator_btSoftBody_Note_16u_Class bc , BtSoftBody_NoteClass p0 ) => bc -> p0 -> IO (BtSoftBody_Note)
btAlignedAllocator_btSoftBody_Note_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Note_16u__address'_ a1' a2' >>= \res ->
  mkBtSoftBody_Note res >>= \res' ->
  return (res')
{-# LINE 1379 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Note_16u__address0 :: ( BtAlignedAllocator_btSoftBody_Note_16u_Class bc , BtSoftBody_NoteClass p0 ) => bc -> p0 -> IO (BtSoftBody_Note)
btAlignedAllocator_btSoftBody_Note_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Note_16u__address0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Note res >>= \res' ->
  return (res')
{-# LINE 1385 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Note_16u__address1 :: ( BtAlignedAllocator_btSoftBody_Note_16u_Class bc , BtSoftBody_NoteClass p0 ) => bc -> p0 -> IO (BtSoftBody_Note)
btAlignedAllocator_btSoftBody_Note_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Note_16u__address1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Note res >>= \res' ->
  return (res')
{-# LINE 1391 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::RContact, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_RContact_16u_ :: IO (BtAlignedAllocator_btSoftBody_RContact_16u_)
btAlignedAllocator_btSoftBody_RContact_16u_ =
  btAlignedAllocator_btSoftBody_RContact_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_RContact_16u_ res >>= \res' ->
  return (res')
{-# LINE 1396 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_RContact_16u__free :: ( BtAlignedAllocator_btSoftBody_RContact_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_RContact_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_RContact_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1397 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_RContact_16u__destroy :: ( BtAlignedAllocator_btSoftBody_RContact_16u_Class bc , BtSoftBody_RContactClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_RContact_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_RContact_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1403 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_RContact_16u__deallocate :: ( BtAlignedAllocator_btSoftBody_RContact_16u_Class bc , BtSoftBody_RContactClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_RContact_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_RContact_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1409 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_RContact_16u__construct :: ( BtAlignedAllocator_btSoftBody_RContact_16u_Class bc , BtSoftBody_RContactClass p0 , BtSoftBody_RContactClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btSoftBody_RContact_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btSoftBody_RContact_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1416 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_RContact_16u__address :: ( BtAlignedAllocator_btSoftBody_RContact_16u_Class bc , BtSoftBody_RContactClass p0 ) => bc -> p0 -> IO (BtSoftBody_RContact)
btAlignedAllocator_btSoftBody_RContact_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_RContact_16u__address'_ a1' a2' >>= \res ->
  mkBtSoftBody_RContact res >>= \res' ->
  return (res')
{-# LINE 1422 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_RContact_16u__address0 :: ( BtAlignedAllocator_btSoftBody_RContact_16u_Class bc , BtSoftBody_RContactClass p0 ) => bc -> p0 -> IO (BtSoftBody_RContact)
btAlignedAllocator_btSoftBody_RContact_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_RContact_16u__address0'_ a1' a2' >>= \res ->
  mkBtSoftBody_RContact res >>= \res' ->
  return (res')
{-# LINE 1428 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_RContact_16u__address1 :: ( BtAlignedAllocator_btSoftBody_RContact_16u_Class bc , BtSoftBody_RContactClass p0 ) => bc -> p0 -> IO (BtSoftBody_RContact)
btAlignedAllocator_btSoftBody_RContact_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_RContact_16u__address1'_ a1' a2' >>= \res ->
  mkBtSoftBody_RContact res >>= \res' ->
  return (res')
{-# LINE 1434 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::SContact, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_SContact_16u_ :: IO (BtAlignedAllocator_btSoftBody_SContact_16u_)
btAlignedAllocator_btSoftBody_SContact_16u_ =
  btAlignedAllocator_btSoftBody_SContact_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_SContact_16u_ res >>= \res' ->
  return (res')
{-# LINE 1439 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_SContact_16u__free :: ( BtAlignedAllocator_btSoftBody_SContact_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_SContact_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_SContact_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1440 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_SContact_16u__destroy :: ( BtAlignedAllocator_btSoftBody_SContact_16u_Class bc , BtSoftBody_SContactClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_SContact_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_SContact_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1446 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_SContact_16u__deallocate :: ( BtAlignedAllocator_btSoftBody_SContact_16u_Class bc , BtSoftBody_SContactClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_SContact_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_SContact_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1452 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_SContact_16u__construct :: ( BtAlignedAllocator_btSoftBody_SContact_16u_Class bc , BtSoftBody_SContactClass p0 , BtSoftBody_SContactClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btSoftBody_SContact_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btSoftBody_SContact_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1459 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_SContact_16u__address :: ( BtAlignedAllocator_btSoftBody_SContact_16u_Class bc , BtSoftBody_SContactClass p0 ) => bc -> p0 -> IO (BtSoftBody_SContact)
btAlignedAllocator_btSoftBody_SContact_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_SContact_16u__address'_ a1' a2' >>= \res ->
  mkBtSoftBody_SContact res >>= \res' ->
  return (res')
{-# LINE 1465 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_SContact_16u__address0 :: ( BtAlignedAllocator_btSoftBody_SContact_16u_Class bc , BtSoftBody_SContactClass p0 ) => bc -> p0 -> IO (BtSoftBody_SContact)
btAlignedAllocator_btSoftBody_SContact_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_SContact_16u__address0'_ a1' a2' >>= \res ->
  mkBtSoftBody_SContact res >>= \res' ->
  return (res')
{-# LINE 1471 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_SContact_16u__address1 :: ( BtAlignedAllocator_btSoftBody_SContact_16u_Class bc , BtSoftBody_SContactClass p0 ) => bc -> p0 -> IO (BtSoftBody_SContact)
btAlignedAllocator_btSoftBody_SContact_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_SContact_16u__address1'_ a1' a2' >>= \res ->
  mkBtSoftBody_SContact res >>= \res' ->
  return (res')
{-# LINE 1477 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::Tetra, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Tetra_16u_ :: IO (BtAlignedAllocator_btSoftBody_Tetra_16u_)
btAlignedAllocator_btSoftBody_Tetra_16u_ =
  btAlignedAllocator_btSoftBody_Tetra_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Tetra_16u_ res >>= \res' ->
  return (res')
{-# LINE 1482 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_Tetra_16u__free :: ( BtAlignedAllocator_btSoftBody_Tetra_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_Tetra_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_Tetra_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1483 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Tetra_16u__destroy :: ( BtAlignedAllocator_btSoftBody_Tetra_16u_Class bc , BtSoftBody_TetraClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_Tetra_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Tetra_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1489 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Tetra_16u__deallocate :: ( BtAlignedAllocator_btSoftBody_Tetra_16u_Class bc , BtSoftBody_TetraClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSoftBody_Tetra_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Tetra_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1495 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Tetra_16u__construct :: ( BtAlignedAllocator_btSoftBody_Tetra_16u_Class bc , BtSoftBody_TetraClass p0 , BtSoftBody_TetraClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btSoftBody_Tetra_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btSoftBody_Tetra_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1502 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Tetra_16u__address :: ( BtAlignedAllocator_btSoftBody_Tetra_16u_Class bc , BtSoftBody_TetraClass p0 ) => bc -> p0 -> IO (BtSoftBody_Tetra)
btAlignedAllocator_btSoftBody_Tetra_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Tetra_16u__address'_ a1' a2' >>= \res ->
  mkBtSoftBody_Tetra res >>= \res' ->
  return (res')
{-# LINE 1508 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Tetra_16u__address0 :: ( BtAlignedAllocator_btSoftBody_Tetra_16u_Class bc , BtSoftBody_TetraClass p0 ) => bc -> p0 -> IO (BtSoftBody_Tetra)
btAlignedAllocator_btSoftBody_Tetra_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Tetra_16u__address0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Tetra res >>= \res' ->
  return (res')
{-# LINE 1514 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_Tetra_16u__address1 :: ( BtAlignedAllocator_btSoftBody_Tetra_16u_Class bc , BtSoftBody_TetraClass p0 ) => bc -> p0 -> IO (BtSoftBody_Tetra)
btAlignedAllocator_btSoftBody_Tetra_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSoftBody_Tetra_16u__address1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Tetra res >>= \res' ->
  return (res')
{-# LINE 1520 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::ePSolver::_, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_ePSolver___16u_ :: IO (BtAlignedAllocator_btSoftBody_ePSolver___16u_)
btAlignedAllocator_btSoftBody_ePSolver___16u_ =
  btAlignedAllocator_btSoftBody_ePSolver___16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_ePSolver___16u_ res >>= \res' ->
  return (res')
{-# LINE 1525 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_ePSolver___16u__free :: ( BtAlignedAllocator_btSoftBody_ePSolver___16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_ePSolver___16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_ePSolver___16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1526 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSoftBody::eVSolver::_, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSoftBody_eVSolver___16u_ :: IO (BtAlignedAllocator_btSoftBody_eVSolver___16u_)
btAlignedAllocator_btSoftBody_eVSolver___16u_ =
  btAlignedAllocator_btSoftBody_eVSolver___16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSoftBody_eVSolver___16u_ res >>= \res' ->
  return (res')
{-# LINE 1531 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSoftBody_eVSolver___16u__free :: ( BtAlignedAllocator_btSoftBody_eVSolver___16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSoftBody_eVSolver___16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSoftBody_eVSolver___16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1532 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSolverConstraint, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSolverConstraint_16u_ :: IO (BtAlignedAllocator_btSolverConstraint_16u_)
btAlignedAllocator_btSolverConstraint_16u_ =
  btAlignedAllocator_btSolverConstraint_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSolverConstraint_16u_ res >>= \res' ->
  return (res')
{-# LINE 1537 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSolverConstraint_16u__free :: ( BtAlignedAllocator_btSolverConstraint_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSolverConstraint_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSolverConstraint_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1538 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSolverConstraint_16u__destroy :: ( BtAlignedAllocator_btSolverConstraint_16u_Class bc , BtSolverConstraintClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSolverConstraint_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSolverConstraint_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1544 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSolverConstraint_16u__deallocate :: ( BtAlignedAllocator_btSolverConstraint_16u_Class bc , BtSolverConstraintClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btSolverConstraint_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSolverConstraint_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1550 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSolverConstraint_16u__construct :: ( BtAlignedAllocator_btSolverConstraint_16u_Class bc , BtSolverConstraintClass p0 , BtSolverConstraintClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btSolverConstraint_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btSolverConstraint_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1557 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSolverConstraint_16u__address :: ( BtAlignedAllocator_btSolverConstraint_16u_Class bc , BtSolverConstraintClass p0 ) => bc -> p0 -> IO (BtSolverConstraint)
btAlignedAllocator_btSolverConstraint_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSolverConstraint_16u__address'_ a1' a2' >>= \res ->
  mkBtSolverConstraint res >>= \res' ->
  return (res')
{-# LINE 1563 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSolverConstraint_16u__address0 :: ( BtAlignedAllocator_btSolverConstraint_16u_Class bc , BtSolverConstraintClass p0 ) => bc -> p0 -> IO (BtSolverConstraint)
btAlignedAllocator_btSolverConstraint_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSolverConstraint_16u__address0'_ a1' a2' >>= \res ->
  mkBtSolverConstraint res >>= \res' ->
  return (res')
{-# LINE 1569 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSolverConstraint_16u__address1 :: ( BtAlignedAllocator_btSolverConstraint_16u_Class bc , BtSolverConstraintClass p0 ) => bc -> p0 -> IO (BtSolverConstraint)
btAlignedAllocator_btSolverConstraint_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btSolverConstraint_16u__address1'_ a1' a2' >>= \res ->
  mkBtSolverConstraint res >>= \res' ->
  return (res')
{-# LINE 1575 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btSparseSdf<3>::Cell*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btSparseSdf_3__Cell_ptr_16u_ :: IO (BtAlignedAllocator_btSparseSdf_3__Cell_ptr_16u_)
btAlignedAllocator_btSparseSdf_3__Cell_ptr_16u_ =
  btAlignedAllocator_btSparseSdf_3__Cell_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btSparseSdf_3__Cell_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1580 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btSparseSdf_3__Cell_ptr_16u__free :: ( BtAlignedAllocator_btSparseSdf_3__Cell_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btSparseSdf_3__Cell_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btSparseSdf_3__Cell_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1581 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btTransform, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTransform_16u_ :: IO (BtAlignedAllocator_btTransform_16u_)
btAlignedAllocator_btTransform_16u_ =
  btAlignedAllocator_btTransform_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btTransform_16u_ res >>= \res' ->
  return (res')
{-# LINE 1586 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btTransform_16u__free :: ( BtAlignedAllocator_btTransform_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btTransform_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btTransform_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1587 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btTriangleInfo, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTriangleInfo_16u_ :: IO (BtAlignedAllocator_btTriangleInfo_16u_)
btAlignedAllocator_btTriangleInfo_16u_ =
  btAlignedAllocator_btTriangleInfo_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btTriangleInfo_16u_ res >>= \res' ->
  return (res')
{-# LINE 1592 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btTriangleInfo_16u__free :: ( BtAlignedAllocator_btTriangleInfo_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btTriangleInfo_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btTriangleInfo_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1593 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTriangleInfo_16u__destroy :: ( BtAlignedAllocator_btTriangleInfo_16u_Class bc , BtTriangleInfoClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btTriangleInfo_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btTriangleInfo_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1599 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTriangleInfo_16u__deallocate :: ( BtAlignedAllocator_btTriangleInfo_16u_Class bc , BtTriangleInfoClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btTriangleInfo_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btTriangleInfo_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1605 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTriangleInfo_16u__construct :: ( BtAlignedAllocator_btTriangleInfo_16u_Class bc , BtTriangleInfoClass p0 , BtTriangleInfoClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btTriangleInfo_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btTriangleInfo_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1612 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTriangleInfo_16u__address :: ( BtAlignedAllocator_btTriangleInfo_16u_Class bc , BtTriangleInfoClass p0 ) => bc -> p0 -> IO (BtTriangleInfo)
btAlignedAllocator_btTriangleInfo_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btTriangleInfo_16u__address'_ a1' a2' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 1618 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTriangleInfo_16u__address0 :: ( BtAlignedAllocator_btTriangleInfo_16u_Class bc , BtTriangleInfoClass p0 ) => bc -> p0 -> IO (BtTriangleInfo)
btAlignedAllocator_btTriangleInfo_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btTriangleInfo_16u__address0'_ a1' a2' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 1624 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTriangleInfo_16u__address1 :: ( BtAlignedAllocator_btTriangleInfo_16u_Class bc , BtTriangleInfoClass p0 ) => bc -> p0 -> IO (BtTriangleInfo)
btAlignedAllocator_btTriangleInfo_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btTriangleInfo_16u__address1'_ a1' a2' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 1630 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btTypedConstraint*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTypedConstraint_ptr_16u_ :: IO (BtAlignedAllocator_btTypedConstraint_ptr_16u_)
btAlignedAllocator_btTypedConstraint_ptr_16u_ =
  btAlignedAllocator_btTypedConstraint_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btTypedConstraint_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1635 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btTypedConstraint_ptr_16u__free :: ( BtAlignedAllocator_btTypedConstraint_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btTypedConstraint_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btTypedConstraint_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1636 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btTypedConstraint::btConstraintInfo1, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_ :: IO (BtAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_)
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_ =
  btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_ res >>= \res' ->
  return (res')
{-# LINE 1641 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__free :: ( BtAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1642 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__destroy :: ( BtAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_Class bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1648 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__deallocate :: ( BtAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_Class bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1654 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__construct :: ( BtAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_Class bc , BtTypedConstraint_btConstraintInfo1Class p0 , BtTypedConstraint_btConstraintInfo1Class p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1661 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__address :: ( BtAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_Class bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => bc -> p0 -> IO (BtTypedConstraint_btConstraintInfo1)
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__address'_ a1' a2' >>= \res ->
  mkBtTypedConstraint_btConstraintInfo1 res >>= \res' ->
  return (res')
{-# LINE 1667 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__address0 :: ( BtAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_Class bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => bc -> p0 -> IO (BtTypedConstraint_btConstraintInfo1)
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__address0'_ a1' a2' >>= \res ->
  mkBtTypedConstraint_btConstraintInfo1 res >>= \res' ->
  return (res')
{-# LINE 1673 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__address1 :: ( BtAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_Class bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => bc -> p0 -> IO (BtTypedConstraint_btConstraintInfo1)
btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__address1'_ a1' a2' >>= \res ->
  mkBtTypedConstraint_btConstraintInfo1 res >>= \res' ->
  return (res')
{-# LINE 1679 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btVector3, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btVector3_16u_ :: IO (BtAlignedAllocator_btVector3_16u_)
btAlignedAllocator_btVector3_16u_ =
  btAlignedAllocator_btVector3_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btVector3_16u_ res >>= \res' ->
  return (res')
{-# LINE 1684 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btVector3_16u__free :: ( BtAlignedAllocator_btVector3_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btVector3_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btVector3_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1685 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<btWheelInfo, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btWheelInfo_16u_ :: IO (BtAlignedAllocator_btWheelInfo_16u_)
btAlignedAllocator_btWheelInfo_16u_ =
  btAlignedAllocator_btWheelInfo_16u_'_ >>= \res ->
  mkBtAlignedAllocator_btWheelInfo_16u_ res >>= \res' ->
  return (res')
{-# LINE 1690 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_btWheelInfo_16u__free :: ( BtAlignedAllocator_btWheelInfo_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_btWheelInfo_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_btWheelInfo_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1691 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#92>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btWheelInfo_16u__destroy :: ( BtAlignedAllocator_btWheelInfo_16u_Class bc , BtWheelInfoClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btWheelInfo_16u__destroy a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btWheelInfo_16u__destroy'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1697 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btWheelInfo_16u__deallocate :: ( BtAlignedAllocator_btWheelInfo_16u_Class bc , BtWheelInfoClass p0 ) => bc -> p0 -> IO ()
btAlignedAllocator_btWheelInfo_16u__deallocate a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btWheelInfo_16u__deallocate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1703 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btWheelInfo_16u__construct :: ( BtAlignedAllocator_btWheelInfo_16u_Class bc , BtWheelInfoClass p0 , BtWheelInfoClass p1 ) => bc -> p0 -> p1 -> IO ()
btAlignedAllocator_btWheelInfo_16u__construct a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btAlignedAllocator_btWheelInfo_16u__construct'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1710 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btWheelInfo_16u__address :: ( BtAlignedAllocator_btWheelInfo_16u_Class bc , BtWheelInfoClass p0 ) => bc -> p0 -> IO (BtWheelInfo)
btAlignedAllocator_btWheelInfo_16u__address a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btWheelInfo_16u__address'_ a1' a2' >>= \res ->
  mkBtWheelInfo res >>= \res' ->
  return (res')
{-# LINE 1716 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btWheelInfo_16u__address0 :: ( BtAlignedAllocator_btWheelInfo_16u_Class bc , BtWheelInfoClass p0 ) => bc -> p0 -> IO (BtWheelInfo)
btAlignedAllocator_btWheelInfo_16u__address0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btWheelInfo_16u__address0'_ a1' a2' >>= \res ->
  mkBtWheelInfo res >>= \res' ->
  return (res')
{-# LINE 1722 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#83>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_btWheelInfo_16u__address1 :: ( BtAlignedAllocator_btWheelInfo_16u_Class bc , BtWheelInfoClass p0 ) => bc -> p0 -> IO (BtWheelInfo)
btAlignedAllocator_btWheelInfo_16u__address1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedAllocator_btWheelInfo_16u__address1'_ a1' a2' >>= \res ->
  mkBtWheelInfo res >>= \res' ->
  return (res')
{-# LINE 1728 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<char const*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_charconst_ptr_16u_ :: IO (BtAlignedAllocator_charconst_ptr_16u_)
btAlignedAllocator_charconst_ptr_16u_ =
  btAlignedAllocator_charconst_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_charconst_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1733 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_charconst_ptr_16u__free :: ( BtAlignedAllocator_charconst_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_charconst_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_charconst_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1734 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<char*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_char_ptr_16u_ :: IO (BtAlignedAllocator_char_ptr_16u_)
btAlignedAllocator_char_ptr_16u_ =
  btAlignedAllocator_char_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_char_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1739 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_char_ptr_16u__free :: ( BtAlignedAllocator_char_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_char_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_char_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1740 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<float, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_float_16u_ :: IO (BtAlignedAllocator_float_16u_)
btAlignedAllocator_float_16u_ =
  btAlignedAllocator_float_16u_'_ >>= \res ->
  mkBtAlignedAllocator_float_16u_ res >>= \res' ->
  return (res')
{-# LINE 1745 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_float_16u__free :: ( BtAlignedAllocator_float_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_float_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_float_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1746 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<int, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_int_16u_ :: IO (BtAlignedAllocator_int_16u_)
btAlignedAllocator_int_16u_ =
  btAlignedAllocator_int_16u_'_ >>= \res ->
  mkBtAlignedAllocator_int_16u_ res >>= \res' ->
  return (res')
{-# LINE 1751 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_int_16u__free :: ( BtAlignedAllocator_int_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_int_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_int_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1752 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<short*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_short_ptr_16u_ :: IO (BtAlignedAllocator_short_ptr_16u_)
btAlignedAllocator_short_ptr_16u_ =
  btAlignedAllocator_short_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_short_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1757 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_short_ptr_16u__free :: ( BtAlignedAllocator_short_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_short_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_short_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1758 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<short, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_short_16u_ :: IO (BtAlignedAllocator_short_16u_)
btAlignedAllocator_short_16u_ =
  btAlignedAllocator_short_16u_'_ >>= \res ->
  mkBtAlignedAllocator_short_16u_ res >>= \res' ->
  return (res')
{-# LINE 1763 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_short_16u__free :: ( BtAlignedAllocator_short_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_short_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_short_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1764 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<unsigned int, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_unsignedint_16u_ :: IO (BtAlignedAllocator_unsignedint_16u_)
btAlignedAllocator_unsignedint_16u_ =
  btAlignedAllocator_unsignedint_16u_'_ >>= \res ->
  mkBtAlignedAllocator_unsignedint_16u_ res >>= \res' ->
  return (res')
{-# LINE 1769 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_unsignedint_16u__free :: ( BtAlignedAllocator_unsignedint_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_unsignedint_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_unsignedint_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1770 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<unsigned short, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_unsignedshort_16u_ :: IO (BtAlignedAllocator_unsignedshort_16u_)
btAlignedAllocator_unsignedshort_16u_ =
  btAlignedAllocator_unsignedshort_16u_'_ >>= \res ->
  mkBtAlignedAllocator_unsignedshort_16u_ res >>= \res' ->
  return (res')
{-# LINE 1775 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_unsignedshort_16u__free :: ( BtAlignedAllocator_unsignedshort_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_unsignedshort_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_unsignedshort_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1776 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedAllocator<void*, 16u>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.h?r=2223#68>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedAllocator.cpp?r=2223>
-}
btAlignedAllocator_void_ptr_16u_ :: IO (BtAlignedAllocator_void_ptr_16u_)
btAlignedAllocator_void_ptr_16u_ =
  btAlignedAllocator_void_ptr_16u_'_ >>= \res ->
  mkBtAlignedAllocator_void_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 1781 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedAllocator_void_ptr_16u__free :: ( BtAlignedAllocator_void_ptr_16u_Class bc ) => bc -> IO ()
btAlignedAllocator_void_ptr_16u__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedAllocator_void_ptr_16u__free'_ a1' >>= \res ->
  return ()
{-# LINE 1782 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<BT_QUANTIZED_BVH_NODE>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE_ :: IO (BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE_ =
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE_'_ >>= \res ->
  mkBtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_ res >>= \res' ->
  return (res')
{-# LINE 1787 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__free :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__free'_ a1' >>= \res ->
  return ()
{-# LINE 1788 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__push_back :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc , BT_QUANTIZED_BVH_NODEClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1794 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__at :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> Int -> IO (BT_QUANTIZED_BVH_NODE)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__at'_ a1' a2' >>= \res ->
  mkBT_QUANTIZED_BVH_NODE res >>= \res' ->
  return (res')
{-# LINE 1800 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__at0 :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> Int -> IO (BT_QUANTIZED_BVH_NODE)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__at0'_ a1' a2' >>= \res ->
  mkBT_QUANTIZED_BVH_NODE res >>= \res' ->
  return (res')
{-# LINE 1806 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__at1 :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> Int -> IO (BT_QUANTIZED_BVH_NODE)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__at1'_ a1' a2' >>= \res ->
  mkBT_QUANTIZED_BVH_NODE res >>= \res' ->
  return (res')
{-# LINE 1812 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__size :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1817 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__capacity :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1822 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__init :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__init'_ a1' >>= \res ->
  return ()
{-# LINE 1827 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__allocate :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 1833 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__pop_back :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 1838 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__deallocate :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 1843 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__swap :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1850 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__initializeFromBuffer :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 1858 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__expandNonInitializing :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> IO (BT_QUANTIZED_BVH_NODE)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__expandNonInitializing'_ a1' >>= \res ->
  mkBT_QUANTIZED_BVH_NODE res >>= \res' ->
  return (res')
{-# LINE 1863 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__resize :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc , BT_QUANTIZED_BVH_NODEClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1870 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__destroy :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 1877 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__copy :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc , BT_QUANTIZED_BVH_NODEClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 1885 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__expand :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc , BT_QUANTIZED_BVH_NODEClass p0 ) => bc -> p0 -> IO (BT_QUANTIZED_BVH_NODE)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__expand'_ a1' a2' >>= \res ->
  mkBT_QUANTIZED_BVH_NODE res >>= \res' ->
  return (res')
{-# LINE 1891 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__clear :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__clear'_ a1' >>= \res ->
  return ()
{-# LINE 1896 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__allocSize :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1902 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__reserve :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1908 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_allocator_set :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc , BtAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1912 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_allocator_get :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> IO (BtAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_ res >>= \res' ->
  return (res')
{-# LINE 1916 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_size_set :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1920 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_size_get :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1924 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_capacity_set :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1928 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_capacity_get :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1932 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_data_set :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc , BT_QUANTIZED_BVH_NODEClass a ) => bc -> a -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1936 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_data_get :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> IO (BT_QUANTIZED_BVH_NODE)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_data_get'_ a1' >>= \res ->
  mkBT_QUANTIZED_BVH_NODE res >>= \res' ->
  return (res')
{-# LINE 1940 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_ownsMemory_set :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1944 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_ownsMemory_get :: ( BtAlignedObjectArray_BT_QUANTIZED_BVH_NODE_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 1948 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<GIM_BVH_DATA>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA_ :: IO (BtAlignedObjectArray_GIM_BVH_DATA_)
btAlignedObjectArray_GIM_BVH_DATA_ =
  btAlignedObjectArray_GIM_BVH_DATA_'_ >>= \res ->
  mkBtAlignedObjectArray_GIM_BVH_DATA_ res >>= \res' ->
  return (res')
{-# LINE 1953 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_GIM_BVH_DATA__free :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_DATA__free'_ a1' >>= \res ->
  return ()
{-# LINE 1954 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__push_back :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc , GIM_BVH_DATAClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_GIM_BVH_DATA__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 1960 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__at :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> Int -> IO (GIM_BVH_DATA)
btAlignedObjectArray_GIM_BVH_DATA__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_DATA__at'_ a1' a2' >>= \res ->
  mkGIM_BVH_DATA res >>= \res' ->
  return (res')
{-# LINE 1966 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__at0 :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> Int -> IO (GIM_BVH_DATA)
btAlignedObjectArray_GIM_BVH_DATA__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_DATA__at0'_ a1' a2' >>= \res ->
  mkGIM_BVH_DATA res >>= \res' ->
  return (res')
{-# LINE 1972 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__at1 :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> Int -> IO (GIM_BVH_DATA)
btAlignedObjectArray_GIM_BVH_DATA__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_DATA__at1'_ a1' a2' >>= \res ->
  mkGIM_BVH_DATA res >>= \res' ->
  return (res')
{-# LINE 1978 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__size :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_GIM_BVH_DATA__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_DATA__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1983 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__capacity :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_GIM_BVH_DATA__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_DATA__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 1988 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__init :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_DATA__init'_ a1' >>= \res ->
  return ()
{-# LINE 1993 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__allocate :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_GIM_BVH_DATA__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_DATA__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 1999 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__pop_back :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_DATA__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 2004 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__deallocate :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_DATA__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 2009 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__swap :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_GIM_BVH_DATA__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2016 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__initializeFromBuffer :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_GIM_BVH_DATA__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 2024 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__expandNonInitializing :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> IO (GIM_BVH_DATA)
btAlignedObjectArray_GIM_BVH_DATA__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_DATA__expandNonInitializing'_ a1' >>= \res ->
  mkGIM_BVH_DATA res >>= \res' ->
  return (res')
{-# LINE 2029 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__resize :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc , GIM_BVH_DATAClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_GIM_BVH_DATA__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2036 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__destroy :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_GIM_BVH_DATA__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2043 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__copy :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc , GIM_BVH_DATAClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_GIM_BVH_DATA__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 2051 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__expand :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc , GIM_BVH_DATAClass p0 ) => bc -> p0 -> IO (GIM_BVH_DATA)
btAlignedObjectArray_GIM_BVH_DATA__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_GIM_BVH_DATA__expand'_ a1' a2' >>= \res ->
  mkGIM_BVH_DATA res >>= \res' ->
  return (res')
{-# LINE 2057 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__clear :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_DATA__clear'_ a1' >>= \res ->
  return ()
{-# LINE 2062 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__allocSize :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_GIM_BVH_DATA__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_DATA__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2068 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__reserve :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_DATA__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2074 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__m_allocator_set :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc , BtAlignedAllocator_GIM_BVH_DATA_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_GIM_BVH_DATA__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2078 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__m_allocator_get :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> IO (BtAlignedAllocator_GIM_BVH_DATA_16u_)
btAlignedObjectArray_GIM_BVH_DATA__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_DATA__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_GIM_BVH_DATA_16u_ res >>= \res' ->
  return (res')
{-# LINE 2082 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__m_size_set :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_DATA__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2086 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__m_size_get :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_GIM_BVH_DATA__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_DATA__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2090 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__m_capacity_set :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_DATA__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2094 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__m_capacity_get :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_GIM_BVH_DATA__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_DATA__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2098 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__m_data_set :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc , GIM_BVH_DATAClass a ) => bc -> a -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_GIM_BVH_DATA__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2102 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__m_data_get :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> IO (GIM_BVH_DATA)
btAlignedObjectArray_GIM_BVH_DATA__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_DATA__m_data_get'_ a1' >>= \res ->
  mkGIM_BVH_DATA res >>= \res' ->
  return (res')
{-# LINE 2106 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__m_ownsMemory_set :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_GIM_BVH_DATA__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_GIM_BVH_DATA__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2110 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_DATA__m_ownsMemory_get :: ( BtAlignedObjectArray_GIM_BVH_DATA_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_GIM_BVH_DATA__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_DATA__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2114 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<GIM_BVH_TREE_NODE>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE_ :: IO (BtAlignedObjectArray_GIM_BVH_TREE_NODE_)
btAlignedObjectArray_GIM_BVH_TREE_NODE_ =
  btAlignedObjectArray_GIM_BVH_TREE_NODE_'_ >>= \res ->
  mkBtAlignedObjectArray_GIM_BVH_TREE_NODE_ res >>= \res' ->
  return (res')
{-# LINE 2119 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__free :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__free'_ a1' >>= \res ->
  return ()
{-# LINE 2120 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__push_back :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc , GIM_BVH_TREE_NODEClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2126 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__at :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> Int -> IO (GIM_BVH_TREE_NODE)
btAlignedObjectArray_GIM_BVH_TREE_NODE__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__at'_ a1' a2' >>= \res ->
  mkGIM_BVH_TREE_NODE res >>= \res' ->
  return (res')
{-# LINE 2132 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__at0 :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> Int -> IO (GIM_BVH_TREE_NODE)
btAlignedObjectArray_GIM_BVH_TREE_NODE__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__at0'_ a1' a2' >>= \res ->
  mkGIM_BVH_TREE_NODE res >>= \res' ->
  return (res')
{-# LINE 2138 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__at1 :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> Int -> IO (GIM_BVH_TREE_NODE)
btAlignedObjectArray_GIM_BVH_TREE_NODE__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__at1'_ a1' a2' >>= \res ->
  mkGIM_BVH_TREE_NODE res >>= \res' ->
  return (res')
{-# LINE 2144 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__size :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_GIM_BVH_TREE_NODE__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2149 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__capacity :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_GIM_BVH_TREE_NODE__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2154 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__init :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__init'_ a1' >>= \res ->
  return ()
{-# LINE 2159 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__allocate :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_GIM_BVH_TREE_NODE__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 2165 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__pop_back :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 2170 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__deallocate :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 2175 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__swap :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2182 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__initializeFromBuffer :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 2190 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__expandNonInitializing :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> IO (GIM_BVH_TREE_NODE)
btAlignedObjectArray_GIM_BVH_TREE_NODE__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__expandNonInitializing'_ a1' >>= \res ->
  mkGIM_BVH_TREE_NODE res >>= \res' ->
  return (res')
{-# LINE 2195 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__resize :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc , GIM_BVH_TREE_NODEClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2202 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__destroy :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2209 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__copy :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc , GIM_BVH_TREE_NODEClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 2217 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__expand :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc , GIM_BVH_TREE_NODEClass p0 ) => bc -> p0 -> IO (GIM_BVH_TREE_NODE)
btAlignedObjectArray_GIM_BVH_TREE_NODE__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__expand'_ a1' a2' >>= \res ->
  mkGIM_BVH_TREE_NODE res >>= \res' ->
  return (res')
{-# LINE 2223 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__clear :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__clear'_ a1' >>= \res ->
  return ()
{-# LINE 2228 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__allocSize :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_GIM_BVH_TREE_NODE__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2234 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__reserve :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2240 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_allocator_set :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc , BtAlignedAllocator_GIM_BVH_TREE_NODE_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2244 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_allocator_get :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> IO (BtAlignedAllocator_GIM_BVH_TREE_NODE_16u_)
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_GIM_BVH_TREE_NODE_16u_ res >>= \res' ->
  return (res')
{-# LINE 2248 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_size_set :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2252 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_size_get :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2256 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_capacity_set :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2260 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_capacity_get :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2264 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_data_set :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc , GIM_BVH_TREE_NODEClass a ) => bc -> a -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2268 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_data_get :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> IO (GIM_BVH_TREE_NODE)
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__m_data_get'_ a1' >>= \res ->
  mkGIM_BVH_TREE_NODE res >>= \res' ->
  return (res')
{-# LINE 2272 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_ownsMemory_set :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2276 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_ownsMemory_get :: ( BtAlignedObjectArray_GIM_BVH_TREE_NODE_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_GIM_BVH_TREE_NODE__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_BVH_TREE_NODE__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2280 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<GIM_PAIR>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR_ :: IO (BtAlignedObjectArray_GIM_PAIR_)
btAlignedObjectArray_GIM_PAIR_ =
  btAlignedObjectArray_GIM_PAIR_'_ >>= \res ->
  mkBtAlignedObjectArray_GIM_PAIR_ res >>= \res' ->
  return (res')
{-# LINE 2285 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_GIM_PAIR__free :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_PAIR__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_PAIR__free'_ a1' >>= \res ->
  return ()
{-# LINE 2286 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__push_back :: ( BtAlignedObjectArray_GIM_PAIR_Class bc , GIM_PAIRClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_GIM_PAIR__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_GIM_PAIR__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2292 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__at :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> Int -> IO (GIM_PAIR)
btAlignedObjectArray_GIM_PAIR__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_PAIR__at'_ a1' a2' >>= \res ->
  mkGIM_PAIR res >>= \res' ->
  return (res')
{-# LINE 2298 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__at0 :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> Int -> IO (GIM_PAIR)
btAlignedObjectArray_GIM_PAIR__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_PAIR__at0'_ a1' a2' >>= \res ->
  mkGIM_PAIR res >>= \res' ->
  return (res')
{-# LINE 2304 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__at1 :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> Int -> IO (GIM_PAIR)
btAlignedObjectArray_GIM_PAIR__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_PAIR__at1'_ a1' a2' >>= \res ->
  mkGIM_PAIR res >>= \res' ->
  return (res')
{-# LINE 2310 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__size :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_GIM_PAIR__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_PAIR__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2315 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__capacity :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_GIM_PAIR__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_PAIR__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2320 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__init :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_PAIR__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_PAIR__init'_ a1' >>= \res ->
  return ()
{-# LINE 2325 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__allocate :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_GIM_PAIR__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_PAIR__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 2331 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__pop_back :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_PAIR__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_PAIR__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 2336 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__deallocate :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_PAIR__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_PAIR__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 2341 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__swap :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_GIM_PAIR__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_GIM_PAIR__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2348 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__initializeFromBuffer :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_GIM_PAIR__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_GIM_PAIR__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 2356 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__expandNonInitializing :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> IO (GIM_PAIR)
btAlignedObjectArray_GIM_PAIR__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_PAIR__expandNonInitializing'_ a1' >>= \res ->
  mkGIM_PAIR res >>= \res' ->
  return (res')
{-# LINE 2361 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__resize :: ( BtAlignedObjectArray_GIM_PAIR_Class bc , GIM_PAIRClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_GIM_PAIR__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_GIM_PAIR__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2368 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__destroy :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_GIM_PAIR__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_GIM_PAIR__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2375 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__copy :: ( BtAlignedObjectArray_GIM_PAIR_Class bc , GIM_PAIRClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_GIM_PAIR__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_GIM_PAIR__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 2383 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__expand :: ( BtAlignedObjectArray_GIM_PAIR_Class bc , GIM_PAIRClass p0 ) => bc -> p0 -> IO (GIM_PAIR)
btAlignedObjectArray_GIM_PAIR__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_GIM_PAIR__expand'_ a1' a2' >>= \res ->
  mkGIM_PAIR res >>= \res' ->
  return (res')
{-# LINE 2389 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__clear :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> IO ()
btAlignedObjectArray_GIM_PAIR__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_PAIR__clear'_ a1' >>= \res ->
  return ()
{-# LINE 2394 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__allocSize :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_GIM_PAIR__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_PAIR__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2400 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__reserve :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_GIM_PAIR__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_PAIR__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2406 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__m_allocator_set :: ( BtAlignedObjectArray_GIM_PAIR_Class bc , BtAlignedAllocator_GIM_PAIR_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_GIM_PAIR__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_GIM_PAIR__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2410 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__m_allocator_get :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> IO (BtAlignedAllocator_GIM_PAIR_16u_)
btAlignedObjectArray_GIM_PAIR__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_PAIR__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_GIM_PAIR_16u_ res >>= \res' ->
  return (res')
{-# LINE 2414 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__m_size_set :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_GIM_PAIR__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_PAIR__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2418 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__m_size_get :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_GIM_PAIR__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_PAIR__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2422 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__m_capacity_set :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_GIM_PAIR__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_GIM_PAIR__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2426 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__m_capacity_get :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_GIM_PAIR__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_PAIR__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2430 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__m_data_set :: ( BtAlignedObjectArray_GIM_PAIR_Class bc , GIM_PAIRClass a ) => bc -> a -> IO ()
btAlignedObjectArray_GIM_PAIR__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_GIM_PAIR__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2434 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__m_data_get :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> IO (GIM_PAIR)
btAlignedObjectArray_GIM_PAIR__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_PAIR__m_data_get'_ a1' >>= \res ->
  mkGIM_PAIR res >>= \res' ->
  return (res')
{-# LINE 2438 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__m_ownsMemory_set :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_GIM_PAIR__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_GIM_PAIR__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2442 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_GIM_PAIR__m_ownsMemory_get :: ( BtAlignedObjectArray_GIM_PAIR_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_GIM_PAIR__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_GIM_PAIR__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2446 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<bool>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool_ :: IO (BtAlignedObjectArray_bool_)
btAlignedObjectArray_bool_ =
  btAlignedObjectArray_bool_'_ >>= \res ->
  mkBtAlignedObjectArray_bool_ res >>= \res' ->
  return (res')
{-# LINE 2451 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_bool__free :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> IO ()
btAlignedObjectArray_bool__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_bool__free'_ a1' >>= \res ->
  return ()
{-# LINE 2452 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__size :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_bool__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_bool__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2457 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__capacity :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_bool__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_bool__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2462 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__init :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> IO ()
btAlignedObjectArray_bool__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_bool__init'_ a1' >>= \res ->
  return ()
{-# LINE 2467 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__swap :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_bool__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_bool__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2474 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__pop_back :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> IO ()
btAlignedObjectArray_bool__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_bool__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 2479 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__deallocate :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> IO ()
btAlignedObjectArray_bool__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_bool__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 2484 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__allocate :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_bool__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_bool__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 2490 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__initializeFromBuffer :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_bool__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_bool__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 2498 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__destroy :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_bool__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_bool__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2505 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__clear :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> IO ()
btAlignedObjectArray_bool__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_bool__clear'_ a1' >>= \res ->
  return ()
{-# LINE 2510 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__allocSize :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_bool__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_bool__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2516 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__reserve :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_bool__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_bool__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2522 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__m_allocator_set :: ( BtAlignedObjectArray_bool_Class bc , BtAlignedAllocator_bool_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_bool__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_bool__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2526 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__m_allocator_get :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> IO (BtAlignedAllocator_bool_16u_)
btAlignedObjectArray_bool__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_bool__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_bool_16u_ res >>= \res' ->
  return (res')
{-# LINE 2530 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__m_capacity_set :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_bool__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_bool__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2534 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__m_capacity_get :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_bool__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_bool__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2538 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__m_ownsMemory_set :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_bool__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_bool__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2542 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__m_ownsMemory_get :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_bool__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_bool__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2546 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__m_size_set :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_bool__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_bool__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2550 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_bool__m_size_get :: ( BtAlignedObjectArray_bool_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_bool__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_bool__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2554 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btActionInterface*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr_ :: IO (BtAlignedObjectArray_btActionInterface_ptr_)
btAlignedObjectArray_btActionInterface_ptr_ =
  btAlignedObjectArray_btActionInterface_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btActionInterface_ptr_ res >>= \res' ->
  return (res')
{-# LINE 2559 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btActionInterface_ptr__free :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btActionInterface_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btActionInterface_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 2560 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__push_back :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc , BtActionInterfaceClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btActionInterface_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btActionInterface_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2566 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__at :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> Int -> IO (BtActionInterface)
btAlignedObjectArray_btActionInterface_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btActionInterface_ptr__at'_ a1' a2' >>= \res ->
  mkBtActionInterface res >>= \res' ->
  return (res')
{-# LINE 2572 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__at0 :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> Int -> IO (BtActionInterface)
btAlignedObjectArray_btActionInterface_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btActionInterface_ptr__at0'_ a1' a2' >>= \res ->
  mkBtActionInterface res >>= \res' ->
  return (res')
{-# LINE 2578 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__at1 :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> Int -> IO (BtActionInterface)
btAlignedObjectArray_btActionInterface_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btActionInterface_ptr__at1'_ a1' a2' >>= \res ->
  mkBtActionInterface res >>= \res' ->
  return (res')
{-# LINE 2584 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__size :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btActionInterface_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btActionInterface_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2589 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__capacity :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btActionInterface_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btActionInterface_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2594 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__init :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btActionInterface_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btActionInterface_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 2599 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__allocate :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btActionInterface_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btActionInterface_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 2605 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__pop_back :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btActionInterface_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btActionInterface_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 2610 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__deallocate :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btActionInterface_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btActionInterface_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 2615 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__swap :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btActionInterface_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btActionInterface_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2622 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btActionInterface_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btActionInterface_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 2630 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> IO (BtActionInterface)
btAlignedObjectArray_btActionInterface_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btActionInterface_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtActionInterface res >>= \res' ->
  return (res')
{-# LINE 2635 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__resize :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc , BtActionInterfaceClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btActionInterface_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btActionInterface_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2642 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__destroy :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btActionInterface_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btActionInterface_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2649 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__expand :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc , BtActionInterfaceClass p0 ) => bc -> p0 -> IO (BtActionInterface)
btAlignedObjectArray_btActionInterface_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btActionInterface_ptr__expand'_ a1' a2' >>= \res ->
  mkBtActionInterface res >>= \res' ->
  return (res')
{-# LINE 2655 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__clear :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btActionInterface_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btActionInterface_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 2660 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__allocSize :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btActionInterface_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btActionInterface_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2666 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__reserve :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btActionInterface_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btActionInterface_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2672 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__m_allocator_set :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc , BtAlignedAllocator_btActionInterface_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btActionInterface_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btActionInterface_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2676 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__m_allocator_get :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btActionInterface_ptr_16u_)
btAlignedObjectArray_btActionInterface_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btActionInterface_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btActionInterface_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 2680 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__m_size_set :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btActionInterface_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btActionInterface_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2684 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__m_size_get :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btActionInterface_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btActionInterface_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2688 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__m_capacity_set :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btActionInterface_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btActionInterface_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2692 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__m_capacity_get :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btActionInterface_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btActionInterface_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2696 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btActionInterface_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btActionInterface_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2700 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btActionInterface_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btActionInterface_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btActionInterface_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btActionInterface_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2704 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btBroadphaseInterface*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr_ :: IO (BtAlignedObjectArray_btBroadphaseInterface_ptr_)
btAlignedObjectArray_btBroadphaseInterface_ptr_ =
  btAlignedObjectArray_btBroadphaseInterface_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btBroadphaseInterface_ptr_ res >>= \res' ->
  return (res')
{-# LINE 2709 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btBroadphaseInterface_ptr__free :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 2710 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__push_back :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc , BtBroadphaseInterfaceClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2716 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__at :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> Int -> IO (BtBroadphaseInterface)
btAlignedObjectArray_btBroadphaseInterface_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphaseInterface_ptr__at'_ a1' a2' >>= \res ->
  mkBtBroadphaseInterface res >>= \res' ->
  return (res')
{-# LINE 2722 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__at0 :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> Int -> IO (BtBroadphaseInterface)
btAlignedObjectArray_btBroadphaseInterface_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphaseInterface_ptr__at0'_ a1' a2' >>= \res ->
  mkBtBroadphaseInterface res >>= \res' ->
  return (res')
{-# LINE 2728 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__at1 :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> Int -> IO (BtBroadphaseInterface)
btAlignedObjectArray_btBroadphaseInterface_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphaseInterface_ptr__at1'_ a1' a2' >>= \res ->
  mkBtBroadphaseInterface res >>= \res' ->
  return (res')
{-# LINE 2734 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__size :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btBroadphaseInterface_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2739 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__capacity :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btBroadphaseInterface_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2744 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__init :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 2749 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__allocate :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btBroadphaseInterface_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphaseInterface_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 2755 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__pop_back :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 2760 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__deallocate :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 2765 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__swap :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btBroadphaseInterface_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2772 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btBroadphaseInterface_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 2780 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> IO (BtBroadphaseInterface)
btAlignedObjectArray_btBroadphaseInterface_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtBroadphaseInterface res >>= \res' ->
  return (res')
{-# LINE 2785 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__resize :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc , BtBroadphaseInterfaceClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2792 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__destroy :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btBroadphaseInterface_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2799 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__expand :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc , BtBroadphaseInterfaceClass p0 ) => bc -> p0 -> IO (BtBroadphaseInterface)
btAlignedObjectArray_btBroadphaseInterface_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__expand'_ a1' a2' >>= \res ->
  mkBtBroadphaseInterface res >>= \res' ->
  return (res')
{-# LINE 2805 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__clear :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 2810 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__allocSize :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btBroadphaseInterface_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphaseInterface_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2816 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__reserve :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphaseInterface_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2822 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__m_allocator_set :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc , BtAlignedAllocator_btBroadphaseInterface_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2826 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__m_allocator_get :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btBroadphaseInterface_ptr_16u_)
btAlignedObjectArray_btBroadphaseInterface_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btBroadphaseInterface_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 2830 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__m_size_set :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphaseInterface_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2834 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__m_size_get :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btBroadphaseInterface_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2838 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__m_capacity_set :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphaseInterface_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2842 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__m_capacity_get :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btBroadphaseInterface_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2846 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btBroadphaseInterface_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btBroadphaseInterface_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2850 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphaseInterface_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btBroadphaseInterface_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btBroadphaseInterface_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphaseInterface_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 2854 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btBroadphasePair>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair_ :: IO (BtAlignedObjectArray_btBroadphasePair_)
btAlignedObjectArray_btBroadphasePair_ =
  btAlignedObjectArray_btBroadphasePair_'_ >>= \res ->
  mkBtAlignedObjectArray_btBroadphasePair_ res >>= \res' ->
  return (res')
{-# LINE 2859 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btBroadphasePair__free :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBroadphasePair__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphasePair__free'_ a1' >>= \res ->
  return ()
{-# LINE 2860 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__push_back :: ( BtAlignedObjectArray_btBroadphasePair_Class bc , BtBroadphasePairClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btBroadphasePair__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btBroadphasePair__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2866 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__at :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> Int -> IO (BtBroadphasePair)
btAlignedObjectArray_btBroadphasePair__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphasePair__at'_ a1' a2' >>= \res ->
  mkBtBroadphasePair res >>= \res' ->
  return (res')
{-# LINE 2872 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__at0 :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> Int -> IO (BtBroadphasePair)
btAlignedObjectArray_btBroadphasePair__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphasePair__at0'_ a1' a2' >>= \res ->
  mkBtBroadphasePair res >>= \res' ->
  return (res')
{-# LINE 2878 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__at1 :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> Int -> IO (BtBroadphasePair)
btAlignedObjectArray_btBroadphasePair__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphasePair__at1'_ a1' a2' >>= \res ->
  mkBtBroadphasePair res >>= \res' ->
  return (res')
{-# LINE 2884 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__size :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btBroadphasePair__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphasePair__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2889 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__capacity :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btBroadphasePair__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphasePair__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2894 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__init :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBroadphasePair__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphasePair__init'_ a1' >>= \res ->
  return ()
{-# LINE 2899 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__allocate :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btBroadphasePair__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphasePair__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 2905 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__pop_back :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBroadphasePair__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphasePair__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 2910 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__deallocate :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBroadphasePair__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphasePair__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 2915 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__swap :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btBroadphasePair__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btBroadphasePair__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2922 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__initializeFromBuffer :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btBroadphasePair__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btBroadphasePair__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 2930 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__expandNonInitializing :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> IO (BtBroadphasePair)
btAlignedObjectArray_btBroadphasePair__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphasePair__expandNonInitializing'_ a1' >>= \res ->
  mkBtBroadphasePair res >>= \res' ->
  return (res')
{-# LINE 2935 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__resize :: ( BtAlignedObjectArray_btBroadphasePair_Class bc , BtBroadphasePairClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btBroadphasePair__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btBroadphasePair__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2942 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__destroy :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btBroadphasePair__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btBroadphasePair__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 2949 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__copy :: ( BtAlignedObjectArray_btBroadphasePair_Class bc , BtBroadphasePairClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btBroadphasePair__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btBroadphasePair__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 2957 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__expand :: ( BtAlignedObjectArray_btBroadphasePair_Class bc , BtBroadphasePairClass p0 ) => bc -> p0 -> IO (BtBroadphasePair)
btAlignedObjectArray_btBroadphasePair__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btBroadphasePair__expand'_ a1' a2' >>= \res ->
  mkBtBroadphasePair res >>= \res' ->
  return (res')
{-# LINE 2963 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__clear :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBroadphasePair__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphasePair__clear'_ a1' >>= \res ->
  return ()
{-# LINE 2968 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__allocSize :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btBroadphasePair__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphasePair__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2974 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__reserve :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btBroadphasePair__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphasePair__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2980 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__m_allocator_set :: ( BtAlignedObjectArray_btBroadphasePair_Class bc , BtAlignedAllocator_btBroadphasePair_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btBroadphasePair__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btBroadphasePair__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2984 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__m_allocator_get :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> IO (BtAlignedAllocator_btBroadphasePair_16u_)
btAlignedObjectArray_btBroadphasePair__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphasePair__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btBroadphasePair_16u_ res >>= \res' ->
  return (res')
{-# LINE 2988 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__m_size_set :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btBroadphasePair__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphasePair__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 2992 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__m_size_get :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btBroadphasePair__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphasePair__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 2996 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__m_capacity_set :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btBroadphasePair__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBroadphasePair__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3000 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__m_capacity_get :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btBroadphasePair__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphasePair__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3004 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__m_data_set :: ( BtAlignedObjectArray_btBroadphasePair_Class bc , BtBroadphasePairClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btBroadphasePair__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btBroadphasePair__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3008 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__m_data_get :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> IO (BtBroadphasePair)
btAlignedObjectArray_btBroadphasePair__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphasePair__m_data_get'_ a1' >>= \res ->
  mkBtBroadphasePair res >>= \res' ->
  return (res')
{-# LINE 3012 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__m_ownsMemory_set :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btBroadphasePair__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btBroadphasePair__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3016 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBroadphasePair__m_ownsMemory_get :: ( BtAlignedObjectArray_btBroadphasePair_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btBroadphasePair__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBroadphasePair__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 3020 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btBvhSubtreeInfo>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo_ :: IO (BtAlignedObjectArray_btBvhSubtreeInfo_)
btAlignedObjectArray_btBvhSubtreeInfo_ =
  btAlignedObjectArray_btBvhSubtreeInfo_'_ >>= \res ->
  mkBtAlignedObjectArray_btBvhSubtreeInfo_ res >>= \res' ->
  return (res')
{-# LINE 3025 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btBvhSubtreeInfo__free :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__free'_ a1' >>= \res ->
  return ()
{-# LINE 3026 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__push_back :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc , BtBvhSubtreeInfoClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3032 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__at :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> Int -> IO (BtBvhSubtreeInfo)
btAlignedObjectArray_btBvhSubtreeInfo__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBvhSubtreeInfo__at'_ a1' a2' >>= \res ->
  mkBtBvhSubtreeInfo res >>= \res' ->
  return (res')
{-# LINE 3038 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__at0 :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> Int -> IO (BtBvhSubtreeInfo)
btAlignedObjectArray_btBvhSubtreeInfo__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBvhSubtreeInfo__at0'_ a1' a2' >>= \res ->
  mkBtBvhSubtreeInfo res >>= \res' ->
  return (res')
{-# LINE 3044 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__at1 :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> Int -> IO (BtBvhSubtreeInfo)
btAlignedObjectArray_btBvhSubtreeInfo__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBvhSubtreeInfo__at1'_ a1' a2' >>= \res ->
  mkBtBvhSubtreeInfo res >>= \res' ->
  return (res')
{-# LINE 3050 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__size :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btBvhSubtreeInfo__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3055 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__capacity :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btBvhSubtreeInfo__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3060 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__init :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__init'_ a1' >>= \res ->
  return ()
{-# LINE 3065 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__allocate :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btBvhSubtreeInfo__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBvhSubtreeInfo__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 3071 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__pop_back :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 3076 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__deallocate :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 3081 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__swap :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btBvhSubtreeInfo__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3088 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__initializeFromBuffer :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btBvhSubtreeInfo__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 3096 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__expandNonInitializing :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> IO (BtBvhSubtreeInfo)
btAlignedObjectArray_btBvhSubtreeInfo__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__expandNonInitializing'_ a1' >>= \res ->
  mkBtBvhSubtreeInfo res >>= \res' ->
  return (res')
{-# LINE 3101 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__resize :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc , BtBvhSubtreeInfoClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3108 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__destroy :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btBvhSubtreeInfo__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3115 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__copy :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc , BtBvhSubtreeInfoClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 3123 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__expand :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc , BtBvhSubtreeInfoClass p0 ) => bc -> p0 -> IO (BtBvhSubtreeInfo)
btAlignedObjectArray_btBvhSubtreeInfo__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__expand'_ a1' a2' >>= \res ->
  mkBtBvhSubtreeInfo res >>= \res' ->
  return (res')
{-# LINE 3129 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__clear :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__clear'_ a1' >>= \res ->
  return ()
{-# LINE 3134 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__allocSize :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btBvhSubtreeInfo__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBvhSubtreeInfo__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3140 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__reserve :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBvhSubtreeInfo__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3146 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__m_allocator_set :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc , BtAlignedAllocator_btBvhSubtreeInfo_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3150 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__m_allocator_get :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> IO (BtAlignedAllocator_btBvhSubtreeInfo_16u_)
btAlignedObjectArray_btBvhSubtreeInfo__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btBvhSubtreeInfo_16u_ res >>= \res' ->
  return (res')
{-# LINE 3154 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__m_size_set :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBvhSubtreeInfo__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3158 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__m_size_get :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btBvhSubtreeInfo__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3162 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__m_capacity_set :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btBvhSubtreeInfo__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3166 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__m_capacity_get :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btBvhSubtreeInfo__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3170 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__m_data_set :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc , BtBvhSubtreeInfoClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3174 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__m_data_get :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> IO (BtBvhSubtreeInfo)
btAlignedObjectArray_btBvhSubtreeInfo__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__m_data_get'_ a1' >>= \res ->
  mkBtBvhSubtreeInfo res >>= \res' ->
  return (res')
{-# LINE 3178 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__m_ownsMemory_set :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btBvhSubtreeInfo__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btBvhSubtreeInfo__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3182 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btBvhSubtreeInfo__m_ownsMemory_get :: ( BtAlignedObjectArray_btBvhSubtreeInfo_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btBvhSubtreeInfo__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btBvhSubtreeInfo__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 3186 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btChunk*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr_ :: IO (BtAlignedObjectArray_btChunk_ptr_)
btAlignedObjectArray_btChunk_ptr_ =
  btAlignedObjectArray_btChunk_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btChunk_ptr_ res >>= \res' ->
  return (res')
{-# LINE 3191 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btChunk_ptr__free :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btChunk_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btChunk_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 3192 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__push_back :: ( BtAlignedObjectArray_btChunk_ptr_Class bc , BtChunkClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btChunk_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btChunk_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3198 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__at :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> Int -> IO (BtChunk)
btAlignedObjectArray_btChunk_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btChunk_ptr__at'_ a1' a2' >>= \res ->
  mkBtChunk res >>= \res' ->
  return (res')
{-# LINE 3204 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__at0 :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> Int -> IO (BtChunk)
btAlignedObjectArray_btChunk_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btChunk_ptr__at0'_ a1' a2' >>= \res ->
  mkBtChunk res >>= \res' ->
  return (res')
{-# LINE 3210 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__at1 :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> Int -> IO (BtChunk)
btAlignedObjectArray_btChunk_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btChunk_ptr__at1'_ a1' a2' >>= \res ->
  mkBtChunk res >>= \res' ->
  return (res')
{-# LINE 3216 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__size :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btChunk_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btChunk_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3221 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__capacity :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btChunk_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btChunk_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3226 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__init :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btChunk_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btChunk_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 3231 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__allocate :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btChunk_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btChunk_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 3237 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__pop_back :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btChunk_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btChunk_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 3242 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__deallocate :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btChunk_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btChunk_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 3247 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__swap :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btChunk_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btChunk_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3254 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btChunk_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btChunk_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 3262 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> IO (BtChunk)
btAlignedObjectArray_btChunk_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btChunk_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtChunk res >>= \res' ->
  return (res')
{-# LINE 3267 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__resize :: ( BtAlignedObjectArray_btChunk_ptr_Class bc , BtChunkClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btChunk_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btChunk_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3274 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__destroy :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btChunk_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btChunk_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3281 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__expand :: ( BtAlignedObjectArray_btChunk_ptr_Class bc , BtChunkClass p0 ) => bc -> p0 -> IO (BtChunk)
btAlignedObjectArray_btChunk_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btChunk_ptr__expand'_ a1' a2' >>= \res ->
  mkBtChunk res >>= \res' ->
  return (res')
{-# LINE 3287 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__clear :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btChunk_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btChunk_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 3292 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__allocSize :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btChunk_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btChunk_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3298 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__reserve :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btChunk_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btChunk_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3304 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__m_allocator_set :: ( BtAlignedObjectArray_btChunk_ptr_Class bc , BtAlignedAllocator_btChunk_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btChunk_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btChunk_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3308 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__m_allocator_get :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btChunk_ptr_16u_)
btAlignedObjectArray_btChunk_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btChunk_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btChunk_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 3312 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__m_size_set :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btChunk_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btChunk_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3316 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__m_size_get :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btChunk_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btChunk_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3320 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__m_capacity_set :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btChunk_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btChunk_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3324 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__m_capacity_get :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btChunk_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btChunk_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3328 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btChunk_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btChunk_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3332 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btChunk_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btChunk_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btChunk_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btChunk_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 3336 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btCollisionObject*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr_ :: IO (BtAlignedObjectArray_btCollisionObject_ptr_)
btAlignedObjectArray_btCollisionObject_ptr_ =
  btAlignedObjectArray_btCollisionObject_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btCollisionObject_ptr_ res >>= \res' ->
  return (res')
{-# LINE 3341 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btCollisionObject_ptr__free :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionObject_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 3342 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__push_back :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc , BtCollisionObjectClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btCollisionObject_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3348 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__at :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> Int -> IO (BtCollisionObject)
btAlignedObjectArray_btCollisionObject_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionObject_ptr__at'_ a1' a2' >>= \res ->
  mkBtCollisionObject res >>= \res' ->
  return (res')
{-# LINE 3354 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__at0 :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> Int -> IO (BtCollisionObject)
btAlignedObjectArray_btCollisionObject_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionObject_ptr__at0'_ a1' a2' >>= \res ->
  mkBtCollisionObject res >>= \res' ->
  return (res')
{-# LINE 3360 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__at1 :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> Int -> IO (BtCollisionObject)
btAlignedObjectArray_btCollisionObject_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionObject_ptr__at1'_ a1' a2' >>= \res ->
  mkBtCollisionObject res >>= \res' ->
  return (res')
{-# LINE 3366 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__size :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btCollisionObject_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionObject_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3371 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__capacity :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btCollisionObject_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionObject_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3376 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__init :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionObject_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 3381 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__swap :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btCollisionObject_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3388 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__pop_back :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionObject_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 3393 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__deallocate :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionObject_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 3398 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__allocate :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btCollisionObject_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionObject_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 3404 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btCollisionObject_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 3412 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> IO (BtCollisionObject)
btAlignedObjectArray_btCollisionObject_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionObject_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtCollisionObject res >>= \res' ->
  return (res')
{-# LINE 3417 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__destroy :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btCollisionObject_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3424 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__resize :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc , BtCollisionObjectClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btCollisionObject_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3431 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__clear :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionObject_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 3436 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__allocSize :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btCollisionObject_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionObject_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3442 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__expand :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc , BtCollisionObjectClass p0 ) => bc -> p0 -> IO (BtCollisionObject)
btAlignedObjectArray_btCollisionObject_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btCollisionObject_ptr__expand'_ a1' a2' >>= \res ->
  mkBtCollisionObject res >>= \res' ->
  return (res')
{-# LINE 3448 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__reserve :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionObject_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3454 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__m_allocator_set :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc , BtAlignedAllocator_btCollisionObject_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btCollisionObject_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3458 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__m_allocator_get :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btCollisionObject_ptr_16u_)
btAlignedObjectArray_btCollisionObject_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionObject_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btCollisionObject_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 3462 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__m_capacity_set :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionObject_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3466 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__m_capacity_get :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btCollisionObject_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionObject_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3470 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btCollisionObject_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3474 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btCollisionObject_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionObject_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 3478 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__m_size_set :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btCollisionObject_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionObject_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3482 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionObject_ptr__m_size_get :: ( BtAlignedObjectArray_btCollisionObject_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btCollisionObject_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionObject_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3486 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btCollisionShape*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr_ :: IO (BtAlignedObjectArray_btCollisionShape_ptr_)
btAlignedObjectArray_btCollisionShape_ptr_ =
  btAlignedObjectArray_btCollisionShape_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btCollisionShape_ptr_ res >>= \res' ->
  return (res')
{-# LINE 3491 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btCollisionShape_ptr__free :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionShape_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 3492 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__push_back :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc , BtCollisionShapeClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btCollisionShape_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3498 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__at :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> Int -> IO (BtCollisionShape)
btAlignedObjectArray_btCollisionShape_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionShape_ptr__at'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 3504 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__at0 :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> Int -> IO (BtCollisionShape)
btAlignedObjectArray_btCollisionShape_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionShape_ptr__at0'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 3510 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__at1 :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> Int -> IO (BtCollisionShape)
btAlignedObjectArray_btCollisionShape_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionShape_ptr__at1'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 3516 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__size :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btCollisionShape_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionShape_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3521 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__capacity :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btCollisionShape_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionShape_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3526 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__init :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionShape_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 3531 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__allocate :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btCollisionShape_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionShape_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 3537 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__pop_back :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionShape_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 3542 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__deallocate :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionShape_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 3547 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__swap :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btCollisionShape_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3554 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btCollisionShape_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 3562 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> IO (BtCollisionShape)
btAlignedObjectArray_btCollisionShape_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionShape_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 3567 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__resize :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc , BtCollisionShapeClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btCollisionShape_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3574 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__destroy :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btCollisionShape_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3581 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__expand :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc , BtCollisionShapeClass p0 ) => bc -> p0 -> IO (BtCollisionShape)
btAlignedObjectArray_btCollisionShape_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btCollisionShape_ptr__expand'_ a1' a2' >>= \res ->
  mkBtCollisionShape res >>= \res' ->
  return (res')
{-# LINE 3587 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__clear :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionShape_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 3592 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__allocSize :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btCollisionShape_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionShape_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3598 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__reserve :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionShape_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3604 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__m_allocator_set :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc , BtAlignedAllocator_btCollisionShape_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btCollisionShape_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3608 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__m_allocator_get :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btCollisionShape_ptr_16u_)
btAlignedObjectArray_btCollisionShape_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionShape_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btCollisionShape_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 3612 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__m_size_set :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionShape_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3616 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__m_size_get :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btCollisionShape_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionShape_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3620 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__m_capacity_set :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCollisionShape_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3624 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__m_capacity_get :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btCollisionShape_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionShape_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3628 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btCollisionShape_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btCollisionShape_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3632 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCollisionShape_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btCollisionShape_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btCollisionShape_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCollisionShape_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 3636 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btCompoundShapeChild>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild_ :: IO (BtAlignedObjectArray_btCompoundShapeChild_)
btAlignedObjectArray_btCompoundShapeChild_ =
  btAlignedObjectArray_btCompoundShapeChild_'_ >>= \res ->
  mkBtAlignedObjectArray_btCompoundShapeChild_ res >>= \res' ->
  return (res')
{-# LINE 3641 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btCompoundShapeChild__free :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCompoundShapeChild__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCompoundShapeChild__free'_ a1' >>= \res ->
  return ()
{-# LINE 3642 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__push_back :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc , BtCompoundShapeChildClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btCompoundShapeChild__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btCompoundShapeChild__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3648 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__at :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> Int -> IO (BtCompoundShapeChild)
btAlignedObjectArray_btCompoundShapeChild__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCompoundShapeChild__at'_ a1' a2' >>= \res ->
  mkBtCompoundShapeChild res >>= \res' ->
  return (res')
{-# LINE 3654 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__at0 :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> Int -> IO (BtCompoundShapeChild)
btAlignedObjectArray_btCompoundShapeChild__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCompoundShapeChild__at0'_ a1' a2' >>= \res ->
  mkBtCompoundShapeChild res >>= \res' ->
  return (res')
{-# LINE 3660 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__at1 :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> Int -> IO (BtCompoundShapeChild)
btAlignedObjectArray_btCompoundShapeChild__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCompoundShapeChild__at1'_ a1' a2' >>= \res ->
  mkBtCompoundShapeChild res >>= \res' ->
  return (res')
{-# LINE 3666 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__size :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btCompoundShapeChild__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCompoundShapeChild__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3671 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__capacity :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btCompoundShapeChild__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCompoundShapeChild__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3676 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__init :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCompoundShapeChild__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCompoundShapeChild__init'_ a1' >>= \res ->
  return ()
{-# LINE 3681 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__allocate :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btCompoundShapeChild__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCompoundShapeChild__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 3687 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__pop_back :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCompoundShapeChild__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCompoundShapeChild__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 3692 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__deallocate :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCompoundShapeChild__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCompoundShapeChild__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 3697 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__swap :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btCompoundShapeChild__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btCompoundShapeChild__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3704 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__initializeFromBuffer :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btCompoundShapeChild__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btCompoundShapeChild__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 3712 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__expandNonInitializing :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> IO (BtCompoundShapeChild)
btAlignedObjectArray_btCompoundShapeChild__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCompoundShapeChild__expandNonInitializing'_ a1' >>= \res ->
  mkBtCompoundShapeChild res >>= \res' ->
  return (res')
{-# LINE 3717 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__resize :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc , BtCompoundShapeChildClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btCompoundShapeChild__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btCompoundShapeChild__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3724 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__destroy :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btCompoundShapeChild__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btCompoundShapeChild__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3731 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__copy :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc , BtCompoundShapeChildClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btCompoundShapeChild__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btCompoundShapeChild__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 3739 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__expand :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc , BtCompoundShapeChildClass p0 ) => bc -> p0 -> IO (BtCompoundShapeChild)
btAlignedObjectArray_btCompoundShapeChild__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btCompoundShapeChild__expand'_ a1' a2' >>= \res ->
  mkBtCompoundShapeChild res >>= \res' ->
  return (res')
{-# LINE 3745 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__clear :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> IO ()
btAlignedObjectArray_btCompoundShapeChild__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCompoundShapeChild__clear'_ a1' >>= \res ->
  return ()
{-# LINE 3750 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__allocSize :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btCompoundShapeChild__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCompoundShapeChild__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3756 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__reserve :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btCompoundShapeChild__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCompoundShapeChild__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3762 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__m_allocator_set :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc , BtAlignedAllocator_btCompoundShapeChild_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btCompoundShapeChild__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btCompoundShapeChild__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3766 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__m_allocator_get :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> IO (BtAlignedAllocator_btCompoundShapeChild_16u_)
btAlignedObjectArray_btCompoundShapeChild__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCompoundShapeChild__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btCompoundShapeChild_16u_ res >>= \res' ->
  return (res')
{-# LINE 3770 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__m_size_set :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btCompoundShapeChild__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCompoundShapeChild__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3774 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__m_size_get :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btCompoundShapeChild__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCompoundShapeChild__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3778 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__m_capacity_set :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btCompoundShapeChild__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btCompoundShapeChild__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3782 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__m_capacity_get :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btCompoundShapeChild__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCompoundShapeChild__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3786 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__m_data_set :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc , BtCompoundShapeChildClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btCompoundShapeChild__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btCompoundShapeChild__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3790 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__m_data_get :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> IO (BtCompoundShapeChild)
btAlignedObjectArray_btCompoundShapeChild__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCompoundShapeChild__m_data_get'_ a1' >>= \res ->
  mkBtCompoundShapeChild res >>= \res' ->
  return (res')
{-# LINE 3794 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__m_ownsMemory_set :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btCompoundShapeChild__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btCompoundShapeChild__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3798 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btCompoundShapeChild__m_ownsMemory_get :: ( BtAlignedObjectArray_btCompoundShapeChild_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btCompoundShapeChild__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btCompoundShapeChild__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 3802 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btDbvt::sStkNN>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN_ :: IO (BtAlignedObjectArray_btDbvt_sStkNN_)
btAlignedObjectArray_btDbvt_sStkNN_ =
  btAlignedObjectArray_btDbvt_sStkNN_'_ >>= \res ->
  mkBtAlignedObjectArray_btDbvt_sStkNN_ res >>= \res' ->
  return (res')
{-# LINE 3807 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btDbvt_sStkNN__free :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNN__free'_ a1' >>= \res ->
  return ()
{-# LINE 3808 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__push_back :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc , BtDbvt_sStkNNClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvt_sStkNN__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3814 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__at :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> Int -> IO (BtDbvt_sStkNN)
btAlignedObjectArray_btDbvt_sStkNN__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNN__at'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNN res >>= \res' ->
  return (res')
{-# LINE 3820 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__at0 :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> Int -> IO (BtDbvt_sStkNN)
btAlignedObjectArray_btDbvt_sStkNN__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNN__at0'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNN res >>= \res' ->
  return (res')
{-# LINE 3826 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__at1 :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> Int -> IO (BtDbvt_sStkNN)
btAlignedObjectArray_btDbvt_sStkNN__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNN__at1'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNN res >>= \res' ->
  return (res')
{-# LINE 3832 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__size :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNN__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNN__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3837 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__capacity :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNN__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNN__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3842 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__init :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNN__init'_ a1' >>= \res ->
  return ()
{-# LINE 3847 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__allocate :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btDbvt_sStkNN__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNN__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 3853 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__pop_back :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNN__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 3858 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__deallocate :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNN__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 3863 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__swap :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btDbvt_sStkNN__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3870 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__initializeFromBuffer :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btDbvt_sStkNN__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 3878 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__expandNonInitializing :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> IO (BtDbvt_sStkNN)
btAlignedObjectArray_btDbvt_sStkNN__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNN__expandNonInitializing'_ a1' >>= \res ->
  mkBtDbvt_sStkNN res >>= \res' ->
  return (res')
{-# LINE 3883 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__resize :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc , BtDbvt_sStkNNClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btDbvt_sStkNN__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3890 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__destroy :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btDbvt_sStkNN__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 3897 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__copy :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc , BtDbvt_sStkNNClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btDbvt_sStkNN__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 3905 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__expand :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc , BtDbvt_sStkNNClass p0 ) => bc -> p0 -> IO (BtDbvt_sStkNN)
btAlignedObjectArray_btDbvt_sStkNN__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvt_sStkNN__expand'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNN res >>= \res' ->
  return (res')
{-# LINE 3911 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__clear :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNN__clear'_ a1' >>= \res ->
  return ()
{-# LINE 3916 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__allocSize :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNN__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNN__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3922 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__reserve :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNN__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3928 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__m_allocator_set :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc , BtAlignedAllocator_btDbvt_sStkNN_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvt_sStkNN__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3932 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__m_allocator_get :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> IO (BtAlignedAllocator_btDbvt_sStkNN_16u_)
btAlignedObjectArray_btDbvt_sStkNN__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNN__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btDbvt_sStkNN_16u_ res >>= \res' ->
  return (res')
{-# LINE 3936 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__m_size_set :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNN__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3940 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__m_size_get :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNN__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNN__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3944 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__m_capacity_set :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNN__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3948 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__m_capacity_get :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNN__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNN__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 3952 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__m_data_set :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc , BtDbvt_sStkNNClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvt_sStkNN__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3956 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__m_data_get :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> IO (BtDbvt_sStkNN)
btAlignedObjectArray_btDbvt_sStkNN__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNN__m_data_get'_ a1' >>= \res ->
  mkBtDbvt_sStkNN res >>= \res' ->
  return (res')
{-# LINE 3960 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__m_ownsMemory_set :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btDbvt_sStkNN__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btDbvt_sStkNN__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3964 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNN__m_ownsMemory_get :: ( BtAlignedObjectArray_btDbvt_sStkNN_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btDbvt_sStkNN__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNN__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 3968 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btDbvt::sStkNP>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP_ :: IO (BtAlignedObjectArray_btDbvt_sStkNP_)
btAlignedObjectArray_btDbvt_sStkNP_ =
  btAlignedObjectArray_btDbvt_sStkNP_'_ >>= \res ->
  mkBtAlignedObjectArray_btDbvt_sStkNP_ res >>= \res' ->
  return (res')
{-# LINE 3973 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btDbvt_sStkNP__free :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNP__free'_ a1' >>= \res ->
  return ()
{-# LINE 3974 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__push_back :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc , BtDbvt_sStkNPClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvt_sStkNP__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 3980 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__at :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> Int -> IO (BtDbvt_sStkNP)
btAlignedObjectArray_btDbvt_sStkNP__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNP__at'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNP res >>= \res' ->
  return (res')
{-# LINE 3986 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__at0 :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> Int -> IO (BtDbvt_sStkNP)
btAlignedObjectArray_btDbvt_sStkNP__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNP__at0'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNP res >>= \res' ->
  return (res')
{-# LINE 3992 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__at1 :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> Int -> IO (BtDbvt_sStkNP)
btAlignedObjectArray_btDbvt_sStkNP__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNP__at1'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNP res >>= \res' ->
  return (res')
{-# LINE 3998 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__size :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNP__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNP__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4003 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__capacity :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNP__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNP__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4008 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__init :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNP__init'_ a1' >>= \res ->
  return ()
{-# LINE 4013 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__allocate :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btDbvt_sStkNP__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNP__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 4019 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__pop_back :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNP__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 4024 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__deallocate :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNP__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 4029 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__swap :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btDbvt_sStkNP__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4036 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__initializeFromBuffer :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btDbvt_sStkNP__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 4044 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__expandNonInitializing :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> IO (BtDbvt_sStkNP)
btAlignedObjectArray_btDbvt_sStkNP__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNP__expandNonInitializing'_ a1' >>= \res ->
  mkBtDbvt_sStkNP res >>= \res' ->
  return (res')
{-# LINE 4049 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__resize :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc , BtDbvt_sStkNPClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btDbvt_sStkNP__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4056 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__destroy :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btDbvt_sStkNP__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4063 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__copy :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc , BtDbvt_sStkNPClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btDbvt_sStkNP__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 4071 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__expand :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc , BtDbvt_sStkNPClass p0 ) => bc -> p0 -> IO (BtDbvt_sStkNP)
btAlignedObjectArray_btDbvt_sStkNP__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvt_sStkNP__expand'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNP res >>= \res' ->
  return (res')
{-# LINE 4077 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__clear :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNP__clear'_ a1' >>= \res ->
  return ()
{-# LINE 4082 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__allocSize :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNP__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNP__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4088 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__reserve :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNP__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4094 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__m_allocator_set :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc , BtAlignedAllocator_btDbvt_sStkNP_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvt_sStkNP__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4098 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__m_allocator_get :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> IO (BtAlignedAllocator_btDbvt_sStkNP_16u_)
btAlignedObjectArray_btDbvt_sStkNP__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNP__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btDbvt_sStkNP_16u_ res >>= \res' ->
  return (res')
{-# LINE 4102 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__m_size_set :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNP__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4106 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__m_size_get :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNP__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNP__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4110 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__m_capacity_set :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNP__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4114 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__m_capacity_get :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNP__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNP__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4118 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__m_data_set :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc , BtDbvt_sStkNPClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvt_sStkNP__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4122 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__m_data_get :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> IO (BtDbvt_sStkNP)
btAlignedObjectArray_btDbvt_sStkNP__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNP__m_data_get'_ a1' >>= \res ->
  mkBtDbvt_sStkNP res >>= \res' ->
  return (res')
{-# LINE 4126 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__m_ownsMemory_set :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btDbvt_sStkNP__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btDbvt_sStkNP__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4130 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNP__m_ownsMemory_get :: ( BtAlignedObjectArray_btDbvt_sStkNP_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btDbvt_sStkNP__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNP__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 4134 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btDbvt::sStkNPS>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS_ :: IO (BtAlignedObjectArray_btDbvt_sStkNPS_)
btAlignedObjectArray_btDbvt_sStkNPS_ =
  btAlignedObjectArray_btDbvt_sStkNPS_'_ >>= \res ->
  mkBtAlignedObjectArray_btDbvt_sStkNPS_ res >>= \res' ->
  return (res')
{-# LINE 4139 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btDbvt_sStkNPS__free :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__free'_ a1' >>= \res ->
  return ()
{-# LINE 4140 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__push_back :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc , BtDbvt_sStkNPSClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4146 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__at :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> Int -> IO (BtDbvt_sStkNPS)
btAlignedObjectArray_btDbvt_sStkNPS__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNPS__at'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNPS res >>= \res' ->
  return (res')
{-# LINE 4152 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__at0 :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> Int -> IO (BtDbvt_sStkNPS)
btAlignedObjectArray_btDbvt_sStkNPS__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNPS__at0'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNPS res >>= \res' ->
  return (res')
{-# LINE 4158 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__at1 :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> Int -> IO (BtDbvt_sStkNPS)
btAlignedObjectArray_btDbvt_sStkNPS__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNPS__at1'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNPS res >>= \res' ->
  return (res')
{-# LINE 4164 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__size :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNPS__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4169 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__capacity :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNPS__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4174 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__init :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__init'_ a1' >>= \res ->
  return ()
{-# LINE 4179 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__allocate :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btDbvt_sStkNPS__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNPS__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 4185 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__pop_back :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 4190 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__deallocate :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 4195 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__swap :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btDbvt_sStkNPS__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4202 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__initializeFromBuffer :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btDbvt_sStkNPS__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 4210 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__expandNonInitializing :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> IO (BtDbvt_sStkNPS)
btAlignedObjectArray_btDbvt_sStkNPS__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__expandNonInitializing'_ a1' >>= \res ->
  mkBtDbvt_sStkNPS res >>= \res' ->
  return (res')
{-# LINE 4215 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__resize :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc , BtDbvt_sStkNPSClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4222 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__destroy :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btDbvt_sStkNPS__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4229 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__copy :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc , BtDbvt_sStkNPSClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 4237 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__expand :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc , BtDbvt_sStkNPSClass p0 ) => bc -> p0 -> IO (BtDbvt_sStkNPS)
btAlignedObjectArray_btDbvt_sStkNPS__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__expand'_ a1' a2' >>= \res ->
  mkBtDbvt_sStkNPS res >>= \res' ->
  return (res')
{-# LINE 4243 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__clear :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__clear'_ a1' >>= \res ->
  return ()
{-# LINE 4248 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__allocSize :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNPS__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNPS__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4254 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__reserve :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNPS__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4260 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__m_allocator_set :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc , BtAlignedAllocator_btDbvt_sStkNPS_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4264 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__m_allocator_get :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> IO (BtAlignedAllocator_btDbvt_sStkNPS_16u_)
btAlignedObjectArray_btDbvt_sStkNPS__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btDbvt_sStkNPS_16u_ res >>= \res' ->
  return (res')
{-# LINE 4268 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__m_size_set :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNPS__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4272 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__m_size_get :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNPS__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4276 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__m_capacity_set :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvt_sStkNPS__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4280 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__m_capacity_get :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvt_sStkNPS__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4284 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__m_data_set :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc , BtDbvt_sStkNPSClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4288 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__m_data_get :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> IO (BtDbvt_sStkNPS)
btAlignedObjectArray_btDbvt_sStkNPS__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__m_data_get'_ a1' >>= \res ->
  mkBtDbvt_sStkNPS res >>= \res' ->
  return (res')
{-# LINE 4292 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__m_ownsMemory_set :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btDbvt_sStkNPS__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btDbvt_sStkNPS__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4296 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvt_sStkNPS__m_ownsMemory_get :: ( BtAlignedObjectArray_btDbvt_sStkNPS_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btDbvt_sStkNPS__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvt_sStkNPS__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 4300 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btDbvtNode const*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr_ :: IO (BtAlignedObjectArray_btDbvtNodeconst_ptr_)
btAlignedObjectArray_btDbvtNodeconst_ptr_ =
  btAlignedObjectArray_btDbvtNodeconst_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btDbvtNodeconst_ptr_ res >>= \res' ->
  return (res')
{-# LINE 4305 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btDbvtNodeconst_ptr__free :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 4306 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__push_back :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc , BtDbvtNodeClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4312 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__at :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> Int -> IO (BtDbvtNode)
btAlignedObjectArray_btDbvtNodeconst_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvtNodeconst_ptr__at'_ a1' a2' >>= \res ->
  mkBtDbvtNode res >>= \res' ->
  return (res')
{-# LINE 4318 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__at0 :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> Int -> IO (BtDbvtNode)
btAlignedObjectArray_btDbvtNodeconst_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvtNodeconst_ptr__at0'_ a1' a2' >>= \res ->
  mkBtDbvtNode res >>= \res' ->
  return (res')
{-# LINE 4324 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__at1 :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> Int -> IO (BtDbvtNode)
btAlignedObjectArray_btDbvtNodeconst_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvtNodeconst_ptr__at1'_ a1' a2' >>= \res ->
  mkBtDbvtNode res >>= \res' ->
  return (res')
{-# LINE 4330 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__size :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvtNodeconst_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4335 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__capacity :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvtNodeconst_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4340 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__init :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 4345 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__allocate :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btDbvtNodeconst_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvtNodeconst_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 4351 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__pop_back :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 4356 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__deallocate :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 4361 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__swap :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btDbvtNodeconst_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4368 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btDbvtNodeconst_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 4376 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> IO (BtDbvtNode)
btAlignedObjectArray_btDbvtNodeconst_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtDbvtNode res >>= \res' ->
  return (res')
{-# LINE 4381 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__resize :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc , BtDbvtNodeClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4388 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__destroy :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btDbvtNodeconst_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4395 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__expand :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc , BtDbvtNodeClass p0 ) => bc -> p0 -> IO (BtDbvtNode)
btAlignedObjectArray_btDbvtNodeconst_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__expand'_ a1' a2' >>= \res ->
  mkBtDbvtNode res >>= \res' ->
  return (res')
{-# LINE 4401 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__clear :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 4406 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__allocSize :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btDbvtNodeconst_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvtNodeconst_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4412 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__reserve :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvtNodeconst_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4418 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__m_allocator_set :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc , BtAlignedAllocator_btDbvtNodeconst_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4422 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__m_allocator_get :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btDbvtNodeconst_ptr_16u_)
btAlignedObjectArray_btDbvtNodeconst_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btDbvtNodeconst_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 4426 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__m_size_set :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvtNodeconst_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4430 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__m_size_get :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvtNodeconst_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4434 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__m_capacity_set :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btDbvtNodeconst_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4438 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__m_capacity_get :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btDbvtNodeconst_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4442 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btDbvtNodeconst_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btDbvtNodeconst_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4446 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btDbvtNodeconst_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btDbvtNodeconst_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btDbvtNodeconst_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btDbvtNodeconst_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 4450 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btGImpactMeshShapePart*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr_ :: IO (BtAlignedObjectArray_btGImpactMeshShapePart_ptr_)
btAlignedObjectArray_btGImpactMeshShapePart_ptr_ =
  btAlignedObjectArray_btGImpactMeshShapePart_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btGImpactMeshShapePart_ptr_ res >>= \res' ->
  return (res')
{-# LINE 4455 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__free :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 4456 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__push_back :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc , BtGImpactMeshShapePartClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4462 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__at :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> Int -> IO (BtGImpactMeshShapePart)
btAlignedObjectArray_btGImpactMeshShapePart_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__at'_ a1' a2' >>= \res ->
  mkBtGImpactMeshShapePart res >>= \res' ->
  return (res')
{-# LINE 4468 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__at0 :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> Int -> IO (BtGImpactMeshShapePart)
btAlignedObjectArray_btGImpactMeshShapePart_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__at0'_ a1' a2' >>= \res ->
  mkBtGImpactMeshShapePart res >>= \res' ->
  return (res')
{-# LINE 4474 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__at1 :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> Int -> IO (BtGImpactMeshShapePart)
btAlignedObjectArray_btGImpactMeshShapePart_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__at1'_ a1' a2' >>= \res ->
  mkBtGImpactMeshShapePart res >>= \res' ->
  return (res')
{-# LINE 4480 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__size :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btGImpactMeshShapePart_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4485 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__capacity :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btGImpactMeshShapePart_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4490 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__init :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 4495 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__allocate :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btGImpactMeshShapePart_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 4501 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__pop_back :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 4506 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__deallocate :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 4511 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__swap :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4518 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 4526 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> IO (BtGImpactMeshShapePart)
btAlignedObjectArray_btGImpactMeshShapePart_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtGImpactMeshShapePart res >>= \res' ->
  return (res')
{-# LINE 4531 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__resize :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc , BtGImpactMeshShapePartClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4538 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__destroy :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4545 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__expand :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc , BtGImpactMeshShapePartClass p0 ) => bc -> p0 -> IO (BtGImpactMeshShapePart)
btAlignedObjectArray_btGImpactMeshShapePart_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__expand'_ a1' a2' >>= \res ->
  mkBtGImpactMeshShapePart res >>= \res' ->
  return (res')
{-# LINE 4551 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__clear :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 4556 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__allocSize :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btGImpactMeshShapePart_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4562 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__reserve :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4568 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_allocator_set :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc , BtAlignedAllocator_btGImpactMeshShapePart_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4572 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_allocator_get :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btGImpactMeshShapePart_ptr_16u_)
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btGImpactMeshShapePart_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 4576 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_size_set :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4580 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_size_get :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4584 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_capacity_set :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4588 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_capacity_get :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4592 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4596 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btGImpactMeshShapePart_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 4600 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btHashInt>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt_ :: IO (BtAlignedObjectArray_btHashInt_)
btAlignedObjectArray_btHashInt_ =
  btAlignedObjectArray_btHashInt_'_ >>= \res ->
  mkBtAlignedObjectArray_btHashInt_ res >>= \res' ->
  return (res')
{-# LINE 4605 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btHashInt__free :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashInt__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashInt__free'_ a1' >>= \res ->
  return ()
{-# LINE 4606 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__push_back :: ( BtAlignedObjectArray_btHashInt_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btHashInt__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btHashInt__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4612 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__at :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> Int -> IO (BtHashInt)
btAlignedObjectArray_btHashInt__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashInt__at'_ a1' a2' >>= \res ->
  mkBtHashInt res >>= \res' ->
  return (res')
{-# LINE 4618 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__at0 :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> Int -> IO (BtHashInt)
btAlignedObjectArray_btHashInt__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashInt__at0'_ a1' a2' >>= \res ->
  mkBtHashInt res >>= \res' ->
  return (res')
{-# LINE 4624 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__at1 :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> Int -> IO (BtHashInt)
btAlignedObjectArray_btHashInt__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashInt__at1'_ a1' a2' >>= \res ->
  mkBtHashInt res >>= \res' ->
  return (res')
{-# LINE 4630 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__size :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btHashInt__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashInt__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4635 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__capacity :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btHashInt__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashInt__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4640 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__init :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashInt__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashInt__init'_ a1' >>= \res ->
  return ()
{-# LINE 4645 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__allocate :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btHashInt__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashInt__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 4651 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__pop_back :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashInt__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashInt__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 4656 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__deallocate :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashInt__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashInt__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 4661 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__swap :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btHashInt__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btHashInt__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4668 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__initializeFromBuffer :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btHashInt__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btHashInt__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 4676 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__expandNonInitializing :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> IO (BtHashInt)
btAlignedObjectArray_btHashInt__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashInt__expandNonInitializing'_ a1' >>= \res ->
  mkBtHashInt res >>= \res' ->
  return (res')
{-# LINE 4681 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__resize :: ( BtAlignedObjectArray_btHashInt_Class bc , BtHashIntClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btHashInt__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btHashInt__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4688 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__destroy :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btHashInt__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btHashInt__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4695 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__copy :: ( BtAlignedObjectArray_btHashInt_Class bc , BtHashIntClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btHashInt__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btHashInt__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 4703 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__expand :: ( BtAlignedObjectArray_btHashInt_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO (BtHashInt)
btAlignedObjectArray_btHashInt__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btHashInt__expand'_ a1' a2' >>= \res ->
  mkBtHashInt res >>= \res' ->
  return (res')
{-# LINE 4709 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__clear :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashInt__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashInt__clear'_ a1' >>= \res ->
  return ()
{-# LINE 4714 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__allocSize :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btHashInt__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashInt__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4720 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__reserve :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btHashInt__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashInt__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4726 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__m_allocator_set :: ( BtAlignedObjectArray_btHashInt_Class bc , BtAlignedAllocator_btHashInt_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btHashInt__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btHashInt__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4730 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__m_allocator_get :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> IO (BtAlignedAllocator_btHashInt_16u_)
btAlignedObjectArray_btHashInt__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashInt__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btHashInt_16u_ res >>= \res' ->
  return (res')
{-# LINE 4734 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__m_size_set :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btHashInt__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashInt__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4738 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__m_size_get :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btHashInt__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashInt__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4742 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__m_capacity_set :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btHashInt__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashInt__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4746 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__m_capacity_get :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btHashInt__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashInt__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4750 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__m_data_set :: ( BtAlignedObjectArray_btHashInt_Class bc , BtHashIntClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btHashInt__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btHashInt__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4754 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__m_data_get :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> IO (BtHashInt)
btAlignedObjectArray_btHashInt__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashInt__m_data_get'_ a1' >>= \res ->
  mkBtHashInt res >>= \res' ->
  return (res')
{-# LINE 4758 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__m_ownsMemory_set :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btHashInt__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btHashInt__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4762 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashInt__m_ownsMemory_get :: ( BtAlignedObjectArray_btHashInt_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btHashInt__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashInt__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 4766 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btHashPtr>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr_ :: IO (BtAlignedObjectArray_btHashPtr_)
btAlignedObjectArray_btHashPtr_ =
  btAlignedObjectArray_btHashPtr_'_ >>= \res ->
  mkBtAlignedObjectArray_btHashPtr_ res >>= \res' ->
  return (res')
{-# LINE 4771 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btHashPtr__free :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashPtr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashPtr__free'_ a1' >>= \res ->
  return ()
{-# LINE 4772 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__push_back :: ( BtAlignedObjectArray_btHashPtr_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btHashPtr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btHashPtr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4778 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__at :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> Int -> IO (BtHashPtr)
btAlignedObjectArray_btHashPtr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashPtr__at'_ a1' a2' >>= \res ->
  mkBtHashPtr res >>= \res' ->
  return (res')
{-# LINE 4784 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__at0 :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> Int -> IO (BtHashPtr)
btAlignedObjectArray_btHashPtr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashPtr__at0'_ a1' a2' >>= \res ->
  mkBtHashPtr res >>= \res' ->
  return (res')
{-# LINE 4790 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__at1 :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> Int -> IO (BtHashPtr)
btAlignedObjectArray_btHashPtr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashPtr__at1'_ a1' a2' >>= \res ->
  mkBtHashPtr res >>= \res' ->
  return (res')
{-# LINE 4796 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__size :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btHashPtr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashPtr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4801 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__capacity :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btHashPtr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashPtr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4806 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__init :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashPtr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashPtr__init'_ a1' >>= \res ->
  return ()
{-# LINE 4811 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__allocate :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btHashPtr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashPtr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 4817 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__pop_back :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashPtr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashPtr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 4822 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__deallocate :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashPtr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashPtr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 4827 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__swap :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btHashPtr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btHashPtr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4834 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__initializeFromBuffer :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btHashPtr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btHashPtr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 4842 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__expandNonInitializing :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> IO (BtHashPtr)
btAlignedObjectArray_btHashPtr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashPtr__expandNonInitializing'_ a1' >>= \res ->
  mkBtHashPtr res >>= \res' ->
  return (res')
{-# LINE 4847 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__resize :: ( BtAlignedObjectArray_btHashPtr_Class bc , BtHashPtrClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btHashPtr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btHashPtr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4854 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__destroy :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btHashPtr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btHashPtr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 4861 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__copy :: ( BtAlignedObjectArray_btHashPtr_Class bc , BtHashPtrClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btHashPtr__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btHashPtr__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 4869 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__expand :: ( BtAlignedObjectArray_btHashPtr_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO (BtHashPtr)
btAlignedObjectArray_btHashPtr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btHashPtr__expand'_ a1' a2' >>= \res ->
  mkBtHashPtr res >>= \res' ->
  return (res')
{-# LINE 4875 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__clear :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashPtr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashPtr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 4880 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__allocSize :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btHashPtr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashPtr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4886 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__reserve :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btHashPtr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashPtr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4892 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__m_allocator_set :: ( BtAlignedObjectArray_btHashPtr_Class bc , BtAlignedAllocator_btHashPtr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btHashPtr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btHashPtr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4896 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__m_allocator_get :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> IO (BtAlignedAllocator_btHashPtr_16u_)
btAlignedObjectArray_btHashPtr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashPtr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btHashPtr_16u_ res >>= \res' ->
  return (res')
{-# LINE 4900 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__m_size_set :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btHashPtr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashPtr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4904 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__m_size_get :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btHashPtr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashPtr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4908 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__m_capacity_set :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btHashPtr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashPtr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4912 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__m_capacity_get :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btHashPtr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashPtr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4916 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__m_data_set :: ( BtAlignedObjectArray_btHashPtr_Class bc , BtHashPtrClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btHashPtr__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btHashPtr__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4920 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__m_data_get :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> IO (BtHashPtr)
btAlignedObjectArray_btHashPtr__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashPtr__m_data_get'_ a1' >>= \res ->
  mkBtHashPtr res >>= \res' ->
  return (res')
{-# LINE 4924 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__m_ownsMemory_set :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btHashPtr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btHashPtr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4928 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashPtr__m_ownsMemory_get :: ( BtAlignedObjectArray_btHashPtr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btHashPtr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashPtr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 4932 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btHashString>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString_ :: IO (BtAlignedObjectArray_btHashString_)
btAlignedObjectArray_btHashString_ =
  btAlignedObjectArray_btHashString_'_ >>= \res ->
  mkBtAlignedObjectArray_btHashString_ res >>= \res' ->
  return (res')
{-# LINE 4937 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btHashString__free :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashString__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashString__free'_ a1' >>= \res ->
  return ()
{-# LINE 4938 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__push_back :: ( BtAlignedObjectArray_btHashString_Class bc , BtHashStringClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btHashString__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btHashString__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 4944 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__at :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> Int -> IO (BtHashString)
btAlignedObjectArray_btHashString__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashString__at'_ a1' a2' >>= \res ->
  mkBtHashString res >>= \res' ->
  return (res')
{-# LINE 4950 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__at0 :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> Int -> IO (BtHashString)
btAlignedObjectArray_btHashString__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashString__at0'_ a1' a2' >>= \res ->
  mkBtHashString res >>= \res' ->
  return (res')
{-# LINE 4956 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__at1 :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> Int -> IO (BtHashString)
btAlignedObjectArray_btHashString__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashString__at1'_ a1' a2' >>= \res ->
  mkBtHashString res >>= \res' ->
  return (res')
{-# LINE 4962 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__size :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btHashString__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashString__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4967 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__capacity :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btHashString__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashString__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 4972 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__init :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashString__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashString__init'_ a1' >>= \res ->
  return ()
{-# LINE 4977 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__allocate :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btHashString__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashString__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 4983 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__pop_back :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashString__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashString__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 4988 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__deallocate :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashString__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashString__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 4993 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__swap :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btHashString__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btHashString__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5000 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__initializeFromBuffer :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btHashString__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btHashString__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 5008 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__expandNonInitializing :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> IO (BtHashString)
btAlignedObjectArray_btHashString__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashString__expandNonInitializing'_ a1' >>= \res ->
  mkBtHashString res >>= \res' ->
  return (res')
{-# LINE 5013 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__resize :: ( BtAlignedObjectArray_btHashString_Class bc , BtHashStringClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btHashString__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btHashString__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5020 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__destroy :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btHashString__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btHashString__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5027 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__copy :: ( BtAlignedObjectArray_btHashString_Class bc , BtHashStringClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btHashString__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btHashString__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 5035 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__expand :: ( BtAlignedObjectArray_btHashString_Class bc , BtHashStringClass p0 ) => bc -> p0 -> IO (BtHashString)
btAlignedObjectArray_btHashString__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btHashString__expand'_ a1' a2' >>= \res ->
  mkBtHashString res >>= \res' ->
  return (res')
{-# LINE 5041 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__clear :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> IO ()
btAlignedObjectArray_btHashString__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashString__clear'_ a1' >>= \res ->
  return ()
{-# LINE 5046 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__allocSize :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btHashString__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashString__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5052 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__reserve :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btHashString__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashString__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5058 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__m_allocator_set :: ( BtAlignedObjectArray_btHashString_Class bc , BtAlignedAllocator_btHashString_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btHashString__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btHashString__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5062 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__m_allocator_get :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> IO (BtAlignedAllocator_btHashString_16u_)
btAlignedObjectArray_btHashString__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashString__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btHashString_16u_ res >>= \res' ->
  return (res')
{-# LINE 5066 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__m_size_set :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btHashString__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashString__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5070 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__m_size_get :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btHashString__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashString__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5074 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__m_capacity_set :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btHashString__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btHashString__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5078 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__m_capacity_get :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btHashString__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashString__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5082 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__m_data_set :: ( BtAlignedObjectArray_btHashString_Class bc , BtHashStringClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btHashString__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btHashString__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5086 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__m_data_get :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> IO (BtHashString)
btAlignedObjectArray_btHashString__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashString__m_data_get'_ a1' >>= \res ->
  mkBtHashString res >>= \res' ->
  return (res')
{-# LINE 5090 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__m_ownsMemory_set :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btHashString__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btHashString__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5094 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btHashString__m_ownsMemory_get :: ( BtAlignedObjectArray_btHashString_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btHashString__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btHashString__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 5098 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btIndexedMesh>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh_ :: IO (BtAlignedObjectArray_btIndexedMesh_)
btAlignedObjectArray_btIndexedMesh_ =
  btAlignedObjectArray_btIndexedMesh_'_ >>= \res ->
  mkBtAlignedObjectArray_btIndexedMesh_ res >>= \res' ->
  return (res')
{-# LINE 5103 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btIndexedMesh__free :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> IO ()
btAlignedObjectArray_btIndexedMesh__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btIndexedMesh__free'_ a1' >>= \res ->
  return ()
{-# LINE 5104 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__push_back :: ( BtAlignedObjectArray_btIndexedMesh_Class bc , BtIndexedMeshClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btIndexedMesh__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btIndexedMesh__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5110 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__at :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> Int -> IO (BtIndexedMesh)
btAlignedObjectArray_btIndexedMesh__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btIndexedMesh__at'_ a1' a2' >>= \res ->
  mkBtIndexedMesh res >>= \res' ->
  return (res')
{-# LINE 5116 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__at0 :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> Int -> IO (BtIndexedMesh)
btAlignedObjectArray_btIndexedMesh__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btIndexedMesh__at0'_ a1' a2' >>= \res ->
  mkBtIndexedMesh res >>= \res' ->
  return (res')
{-# LINE 5122 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__at1 :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> Int -> IO (BtIndexedMesh)
btAlignedObjectArray_btIndexedMesh__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btIndexedMesh__at1'_ a1' a2' >>= \res ->
  mkBtIndexedMesh res >>= \res' ->
  return (res')
{-# LINE 5128 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__size :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btIndexedMesh__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btIndexedMesh__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5133 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__capacity :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btIndexedMesh__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btIndexedMesh__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5138 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__init :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> IO ()
btAlignedObjectArray_btIndexedMesh__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btIndexedMesh__init'_ a1' >>= \res ->
  return ()
{-# LINE 5143 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__allocate :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btIndexedMesh__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btIndexedMesh__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 5149 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__pop_back :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> IO ()
btAlignedObjectArray_btIndexedMesh__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btIndexedMesh__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 5154 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__deallocate :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> IO ()
btAlignedObjectArray_btIndexedMesh__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btIndexedMesh__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 5159 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__swap :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btIndexedMesh__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btIndexedMesh__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5166 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__initializeFromBuffer :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btIndexedMesh__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btIndexedMesh__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 5174 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__expandNonInitializing :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> IO (BtIndexedMesh)
btAlignedObjectArray_btIndexedMesh__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btIndexedMesh__expandNonInitializing'_ a1' >>= \res ->
  mkBtIndexedMesh res >>= \res' ->
  return (res')
{-# LINE 5179 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__resize :: ( BtAlignedObjectArray_btIndexedMesh_Class bc , BtIndexedMeshClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btIndexedMesh__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btIndexedMesh__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5186 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__destroy :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btIndexedMesh__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btIndexedMesh__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5193 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__copy :: ( BtAlignedObjectArray_btIndexedMesh_Class bc , BtIndexedMeshClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btIndexedMesh__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btIndexedMesh__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 5201 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__expand :: ( BtAlignedObjectArray_btIndexedMesh_Class bc , BtIndexedMeshClass p0 ) => bc -> p0 -> IO (BtIndexedMesh)
btAlignedObjectArray_btIndexedMesh__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btIndexedMesh__expand'_ a1' a2' >>= \res ->
  mkBtIndexedMesh res >>= \res' ->
  return (res')
{-# LINE 5207 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__clear :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> IO ()
btAlignedObjectArray_btIndexedMesh__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btIndexedMesh__clear'_ a1' >>= \res ->
  return ()
{-# LINE 5212 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__allocSize :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btIndexedMesh__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btIndexedMesh__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5218 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__reserve :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btIndexedMesh__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btIndexedMesh__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5224 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__m_allocator_set :: ( BtAlignedObjectArray_btIndexedMesh_Class bc , BtAlignedAllocator_btIndexedMesh_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btIndexedMesh__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btIndexedMesh__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5228 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__m_allocator_get :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> IO (BtAlignedAllocator_btIndexedMesh_16u_)
btAlignedObjectArray_btIndexedMesh__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btIndexedMesh__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btIndexedMesh_16u_ res >>= \res' ->
  return (res')
{-# LINE 5232 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__m_size_set :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btIndexedMesh__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btIndexedMesh__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5236 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__m_size_get :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btIndexedMesh__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btIndexedMesh__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5240 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__m_capacity_set :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btIndexedMesh__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btIndexedMesh__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5244 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__m_capacity_get :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btIndexedMesh__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btIndexedMesh__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5248 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__m_data_set :: ( BtAlignedObjectArray_btIndexedMesh_Class bc , BtIndexedMeshClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btIndexedMesh__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btIndexedMesh__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5252 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__m_data_get :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> IO (BtIndexedMesh)
btAlignedObjectArray_btIndexedMesh__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btIndexedMesh__m_data_get'_ a1' >>= \res ->
  mkBtIndexedMesh res >>= \res' ->
  return (res')
{-# LINE 5256 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__m_ownsMemory_set :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btIndexedMesh__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btIndexedMesh__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5260 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btIndexedMesh__m_ownsMemory_get :: ( BtAlignedObjectArray_btIndexedMesh_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btIndexedMesh__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btIndexedMesh__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 5264 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btMultiSapBroadphase::btBridgeProxy*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_ :: IO (BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_ =
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_ res >>= \res' ->
  return (res')
{-# LINE 5269 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__free :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 5270 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__push_back :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc , BtMultiSapBroadphase_btBridgeProxyClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5276 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> Int -> IO (BtMultiSapBroadphase_btBridgeProxy)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at'_ a1' a2' >>= \res ->
  mkBtMultiSapBroadphase_btBridgeProxy res >>= \res' ->
  return (res')
{-# LINE 5282 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at0 :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> Int -> IO (BtMultiSapBroadphase_btBridgeProxy)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at0'_ a1' a2' >>= \res ->
  mkBtMultiSapBroadphase_btBridgeProxy res >>= \res' ->
  return (res')
{-# LINE 5288 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at1 :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> Int -> IO (BtMultiSapBroadphase_btBridgeProxy)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at1'_ a1' a2' >>= \res ->
  mkBtMultiSapBroadphase_btBridgeProxy res >>= \res' ->
  return (res')
{-# LINE 5294 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__size :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5299 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__capacity :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5304 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__init :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 5309 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__allocate :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 5315 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__pop_back :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 5320 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__deallocate :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 5325 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__swap :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5332 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 5340 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> IO (BtMultiSapBroadphase_btBridgeProxy)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtMultiSapBroadphase_btBridgeProxy res >>= \res' ->
  return (res')
{-# LINE 5345 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__resize :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc , BtMultiSapBroadphase_btBridgeProxyClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5352 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__destroy :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5359 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__expand :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc , BtMultiSapBroadphase_btBridgeProxyClass p0 ) => bc -> p0 -> IO (BtMultiSapBroadphase_btBridgeProxy)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__expand'_ a1' a2' >>= \res ->
  mkBtMultiSapBroadphase_btBridgeProxy res >>= \res' ->
  return (res')
{-# LINE 5365 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__clear :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 5370 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__allocSize :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5376 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__reserve :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5382 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_allocator_set :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc , BtAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5386 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_allocator_get :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u_)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 5390 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_size_set :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5394 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_size_get :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5398 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_capacity_set :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5402 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_capacity_get :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5406 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5410 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 5414 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btMultiSapBroadphase::btMultiSapProxy*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_ :: IO (BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_ =
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_ res >>= \res' ->
  return (res')
{-# LINE 5419 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__free :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 5420 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__push_back :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc , BtMultiSapBroadphase_btMultiSapProxyClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5426 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> Int -> IO (BtMultiSapBroadphase_btMultiSapProxy)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at'_ a1' a2' >>= \res ->
  mkBtMultiSapBroadphase_btMultiSapProxy res >>= \res' ->
  return (res')
{-# LINE 5432 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at0 :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> Int -> IO (BtMultiSapBroadphase_btMultiSapProxy)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at0'_ a1' a2' >>= \res ->
  mkBtMultiSapBroadphase_btMultiSapProxy res >>= \res' ->
  return (res')
{-# LINE 5438 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at1 :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> Int -> IO (BtMultiSapBroadphase_btMultiSapProxy)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at1'_ a1' a2' >>= \res ->
  mkBtMultiSapBroadphase_btMultiSapProxy res >>= \res' ->
  return (res')
{-# LINE 5444 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__size :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5449 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__capacity :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5454 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__init :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 5459 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__allocate :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 5465 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__pop_back :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 5470 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__deallocate :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 5475 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__swap :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5482 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 5490 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> IO (BtMultiSapBroadphase_btMultiSapProxy)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtMultiSapBroadphase_btMultiSapProxy res >>= \res' ->
  return (res')
{-# LINE 5495 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__resize :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc , BtMultiSapBroadphase_btMultiSapProxyClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5502 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__destroy :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5509 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__expand :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc , BtMultiSapBroadphase_btMultiSapProxyClass p0 ) => bc -> p0 -> IO (BtMultiSapBroadphase_btMultiSapProxy)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__expand'_ a1' a2' >>= \res ->
  mkBtMultiSapBroadphase_btMultiSapProxy res >>= \res' ->
  return (res')
{-# LINE 5515 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__clear :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 5520 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__allocSize :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5526 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__reserve :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5532 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_allocator_set :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc , BtAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5536 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_allocator_get :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u_)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 5540 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_size_set :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5544 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_size_get :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5548 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_capacity_set :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5552 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_capacity_get :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5556 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5560 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 5564 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btOptimizedBvhNode>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode_ :: IO (BtAlignedObjectArray_btOptimizedBvhNode_)
btAlignedObjectArray_btOptimizedBvhNode_ =
  btAlignedObjectArray_btOptimizedBvhNode_'_ >>= \res ->
  mkBtAlignedObjectArray_btOptimizedBvhNode_ res >>= \res' ->
  return (res')
{-# LINE 5569 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btOptimizedBvhNode__free :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btOptimizedBvhNode__free'_ a1' >>= \res ->
  return ()
{-# LINE 5570 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__push_back :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc , BtOptimizedBvhNodeClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btOptimizedBvhNode__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5576 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__at :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> Int -> IO (BtOptimizedBvhNode)
btAlignedObjectArray_btOptimizedBvhNode__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btOptimizedBvhNode__at'_ a1' a2' >>= \res ->
  mkBtOptimizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 5582 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__at0 :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> Int -> IO (BtOptimizedBvhNode)
btAlignedObjectArray_btOptimizedBvhNode__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btOptimizedBvhNode__at0'_ a1' a2' >>= \res ->
  mkBtOptimizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 5588 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__at1 :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> Int -> IO (BtOptimizedBvhNode)
btAlignedObjectArray_btOptimizedBvhNode__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btOptimizedBvhNode__at1'_ a1' a2' >>= \res ->
  mkBtOptimizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 5594 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__size :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btOptimizedBvhNode__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btOptimizedBvhNode__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5599 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__capacity :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btOptimizedBvhNode__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btOptimizedBvhNode__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5604 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__init :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btOptimizedBvhNode__init'_ a1' >>= \res ->
  return ()
{-# LINE 5609 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__allocate :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btOptimizedBvhNode__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btOptimizedBvhNode__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 5615 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__pop_back :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btOptimizedBvhNode__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 5620 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__deallocate :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btOptimizedBvhNode__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 5625 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__swap :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btOptimizedBvhNode__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5632 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__initializeFromBuffer :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btOptimizedBvhNode__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 5640 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__expandNonInitializing :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> IO (BtOptimizedBvhNode)
btAlignedObjectArray_btOptimizedBvhNode__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btOptimizedBvhNode__expandNonInitializing'_ a1' >>= \res ->
  mkBtOptimizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 5645 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__resize :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc , BtOptimizedBvhNodeClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btOptimizedBvhNode__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5652 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__destroy :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btOptimizedBvhNode__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5659 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__copy :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc , BtOptimizedBvhNodeClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btOptimizedBvhNode__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 5667 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__expand :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc , BtOptimizedBvhNodeClass p0 ) => bc -> p0 -> IO (BtOptimizedBvhNode)
btAlignedObjectArray_btOptimizedBvhNode__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btOptimizedBvhNode__expand'_ a1' a2' >>= \res ->
  mkBtOptimizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 5673 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__clear :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btOptimizedBvhNode__clear'_ a1' >>= \res ->
  return ()
{-# LINE 5678 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__allocSize :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btOptimizedBvhNode__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btOptimizedBvhNode__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5684 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__reserve :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btOptimizedBvhNode__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5690 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__m_allocator_set :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc , BtAlignedAllocator_btOptimizedBvhNode_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btOptimizedBvhNode__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5694 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__m_allocator_get :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> IO (BtAlignedAllocator_btOptimizedBvhNode_16u_)
btAlignedObjectArray_btOptimizedBvhNode__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btOptimizedBvhNode__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btOptimizedBvhNode_16u_ res >>= \res' ->
  return (res')
{-# LINE 5698 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__m_size_set :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btOptimizedBvhNode__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5702 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__m_size_get :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btOptimizedBvhNode__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btOptimizedBvhNode__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5706 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__m_capacity_set :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btOptimizedBvhNode__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5710 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__m_capacity_get :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btOptimizedBvhNode__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btOptimizedBvhNode__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5714 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__m_data_set :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc , BtOptimizedBvhNodeClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btOptimizedBvhNode__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5718 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__m_data_get :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> IO (BtOptimizedBvhNode)
btAlignedObjectArray_btOptimizedBvhNode__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btOptimizedBvhNode__m_data_get'_ a1' >>= \res ->
  mkBtOptimizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 5722 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__m_ownsMemory_set :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btOptimizedBvhNode__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btOptimizedBvhNode__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5726 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btOptimizedBvhNode__m_ownsMemory_get :: ( BtAlignedObjectArray_btOptimizedBvhNode_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btOptimizedBvhNode__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btOptimizedBvhNode__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 5730 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btPersistentManifold*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr_ :: IO (BtAlignedObjectArray_btPersistentManifold_ptr_)
btAlignedObjectArray_btPersistentManifold_ptr_ =
  btAlignedObjectArray_btPersistentManifold_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btPersistentManifold_ptr_ res >>= \res' ->
  return (res')
{-# LINE 5735 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btPersistentManifold_ptr__free :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 5736 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__push_back :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc , BtPersistentManifoldClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5742 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__at :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> Int -> IO (BtPersistentManifold)
btAlignedObjectArray_btPersistentManifold_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPersistentManifold_ptr__at'_ a1' a2' >>= \res ->
  mkBtPersistentManifold res >>= \res' ->
  return (res')
{-# LINE 5748 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__at0 :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> Int -> IO (BtPersistentManifold)
btAlignedObjectArray_btPersistentManifold_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPersistentManifold_ptr__at0'_ a1' a2' >>= \res ->
  mkBtPersistentManifold res >>= \res' ->
  return (res')
{-# LINE 5754 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__at1 :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> Int -> IO (BtPersistentManifold)
btAlignedObjectArray_btPersistentManifold_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPersistentManifold_ptr__at1'_ a1' a2' >>= \res ->
  mkBtPersistentManifold res >>= \res' ->
  return (res')
{-# LINE 5760 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__size :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btPersistentManifold_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5765 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__capacity :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btPersistentManifold_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5770 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__init :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 5775 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__allocate :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btPersistentManifold_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPersistentManifold_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 5781 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__pop_back :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 5786 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__deallocate :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 5791 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__swap :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btPersistentManifold_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5798 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btPersistentManifold_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 5806 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> IO (BtPersistentManifold)
btAlignedObjectArray_btPersistentManifold_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtPersistentManifold res >>= \res' ->
  return (res')
{-# LINE 5811 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__resize :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc , BtPersistentManifoldClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5818 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__destroy :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btPersistentManifold_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5825 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__expand :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc , BtPersistentManifoldClass p0 ) => bc -> p0 -> IO (BtPersistentManifold)
btAlignedObjectArray_btPersistentManifold_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__expand'_ a1' a2' >>= \res ->
  mkBtPersistentManifold res >>= \res' ->
  return (res')
{-# LINE 5831 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__clear :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 5836 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__allocSize :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btPersistentManifold_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPersistentManifold_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5842 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__reserve :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPersistentManifold_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5848 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__m_allocator_set :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc , BtAlignedAllocator_btPersistentManifold_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5852 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__m_allocator_get :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btPersistentManifold_ptr_16u_)
btAlignedObjectArray_btPersistentManifold_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btPersistentManifold_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 5856 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__m_size_set :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPersistentManifold_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5860 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__m_size_get :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btPersistentManifold_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5864 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__m_capacity_set :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPersistentManifold_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5868 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__m_capacity_get :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btPersistentManifold_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5872 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btPersistentManifold_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btPersistentManifold_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5876 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPersistentManifold_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btPersistentManifold_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btPersistentManifold_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPersistentManifold_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 5880 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btPointerUid>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid_ :: IO (BtAlignedObjectArray_btPointerUid_)
btAlignedObjectArray_btPointerUid_ =
  btAlignedObjectArray_btPointerUid_'_ >>= \res ->
  mkBtAlignedObjectArray_btPointerUid_ res >>= \res' ->
  return (res')
{-# LINE 5885 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btPointerUid__free :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> IO ()
btAlignedObjectArray_btPointerUid__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPointerUid__free'_ a1' >>= \res ->
  return ()
{-# LINE 5886 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__push_back :: ( BtAlignedObjectArray_btPointerUid_Class bc , BtPointerUidClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btPointerUid__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btPointerUid__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 5892 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__at :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> Int -> IO (BtPointerUid)
btAlignedObjectArray_btPointerUid__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPointerUid__at'_ a1' a2' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 5898 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__at0 :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> Int -> IO (BtPointerUid)
btAlignedObjectArray_btPointerUid__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPointerUid__at0'_ a1' a2' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 5904 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__at1 :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> Int -> IO (BtPointerUid)
btAlignedObjectArray_btPointerUid__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPointerUid__at1'_ a1' a2' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 5910 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__size :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btPointerUid__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPointerUid__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5915 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__capacity :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btPointerUid__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPointerUid__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 5920 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__init :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> IO ()
btAlignedObjectArray_btPointerUid__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPointerUid__init'_ a1' >>= \res ->
  return ()
{-# LINE 5925 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__allocate :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btPointerUid__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPointerUid__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 5931 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__pop_back :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> IO ()
btAlignedObjectArray_btPointerUid__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPointerUid__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 5936 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__deallocate :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> IO ()
btAlignedObjectArray_btPointerUid__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPointerUid__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 5941 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__swap :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btPointerUid__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btPointerUid__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5948 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__initializeFromBuffer :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btPointerUid__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btPointerUid__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 5956 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__expandNonInitializing :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> IO (BtPointerUid)
btAlignedObjectArray_btPointerUid__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPointerUid__expandNonInitializing'_ a1' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 5961 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__resize :: ( BtAlignedObjectArray_btPointerUid_Class bc , BtPointerUidClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btPointerUid__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btPointerUid__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5968 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__destroy :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btPointerUid__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btPointerUid__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 5975 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__copy :: ( BtAlignedObjectArray_btPointerUid_Class bc , BtPointerUidClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btPointerUid__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btPointerUid__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 5983 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__expand :: ( BtAlignedObjectArray_btPointerUid_Class bc , BtPointerUidClass p0 ) => bc -> p0 -> IO (BtPointerUid)
btAlignedObjectArray_btPointerUid__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btPointerUid__expand'_ a1' a2' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 5989 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__clear :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> IO ()
btAlignedObjectArray_btPointerUid__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPointerUid__clear'_ a1' >>= \res ->
  return ()
{-# LINE 5994 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__allocSize :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btPointerUid__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPointerUid__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6000 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__reserve :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btPointerUid__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPointerUid__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6006 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__m_allocator_set :: ( BtAlignedObjectArray_btPointerUid_Class bc , BtAlignedAllocator_btPointerUid_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btPointerUid__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btPointerUid__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6010 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__m_allocator_get :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> IO (BtAlignedAllocator_btPointerUid_16u_)
btAlignedObjectArray_btPointerUid__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPointerUid__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btPointerUid_16u_ res >>= \res' ->
  return (res')
{-# LINE 6014 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__m_size_set :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btPointerUid__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPointerUid__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6018 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__m_size_get :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btPointerUid__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPointerUid__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6022 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__m_capacity_set :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btPointerUid__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btPointerUid__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6026 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__m_capacity_get :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btPointerUid__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPointerUid__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6030 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__m_data_set :: ( BtAlignedObjectArray_btPointerUid_Class bc , BtPointerUidClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btPointerUid__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btPointerUid__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6034 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__m_data_get :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> IO (BtPointerUid)
btAlignedObjectArray_btPointerUid__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPointerUid__m_data_get'_ a1' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 6038 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__m_ownsMemory_set :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btPointerUid__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btPointerUid__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6042 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btPointerUid__m_ownsMemory_get :: ( BtAlignedObjectArray_btPointerUid_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btPointerUid__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btPointerUid__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 6046 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btQuantizedBvhNode>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode_ :: IO (BtAlignedObjectArray_btQuantizedBvhNode_)
btAlignedObjectArray_btQuantizedBvhNode_ =
  btAlignedObjectArray_btQuantizedBvhNode_'_ >>= \res ->
  mkBtAlignedObjectArray_btQuantizedBvhNode_ res >>= \res' ->
  return (res')
{-# LINE 6051 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btQuantizedBvhNode__free :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btQuantizedBvhNode__free'_ a1' >>= \res ->
  return ()
{-# LINE 6052 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__push_back :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc , BtQuantizedBvhNodeClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btQuantizedBvhNode__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6058 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__at :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> Int -> IO (BtQuantizedBvhNode)
btAlignedObjectArray_btQuantizedBvhNode__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btQuantizedBvhNode__at'_ a1' a2' >>= \res ->
  mkBtQuantizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 6064 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__at0 :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> Int -> IO (BtQuantizedBvhNode)
btAlignedObjectArray_btQuantizedBvhNode__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btQuantizedBvhNode__at0'_ a1' a2' >>= \res ->
  mkBtQuantizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 6070 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__at1 :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> Int -> IO (BtQuantizedBvhNode)
btAlignedObjectArray_btQuantizedBvhNode__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btQuantizedBvhNode__at1'_ a1' a2' >>= \res ->
  mkBtQuantizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 6076 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__size :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btQuantizedBvhNode__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btQuantizedBvhNode__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6081 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__capacity :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btQuantizedBvhNode__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btQuantizedBvhNode__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6086 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__init :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btQuantizedBvhNode__init'_ a1' >>= \res ->
  return ()
{-# LINE 6091 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__allocate :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btQuantizedBvhNode__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btQuantizedBvhNode__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 6097 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__pop_back :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btQuantizedBvhNode__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 6102 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__deallocate :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btQuantizedBvhNode__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 6107 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__swap :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btQuantizedBvhNode__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6114 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__initializeFromBuffer :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btQuantizedBvhNode__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 6122 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__expandNonInitializing :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> IO (BtQuantizedBvhNode)
btAlignedObjectArray_btQuantizedBvhNode__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btQuantizedBvhNode__expandNonInitializing'_ a1' >>= \res ->
  mkBtQuantizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 6127 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__resize :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc , BtQuantizedBvhNodeClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btQuantizedBvhNode__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6134 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__destroy :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btQuantizedBvhNode__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6141 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__copy :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc , BtQuantizedBvhNodeClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btQuantizedBvhNode__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 6149 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__expand :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc , BtQuantizedBvhNodeClass p0 ) => bc -> p0 -> IO (BtQuantizedBvhNode)
btAlignedObjectArray_btQuantizedBvhNode__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btQuantizedBvhNode__expand'_ a1' a2' >>= \res ->
  mkBtQuantizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 6155 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__clear :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btQuantizedBvhNode__clear'_ a1' >>= \res ->
  return ()
{-# LINE 6160 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__allocSize :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btQuantizedBvhNode__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btQuantizedBvhNode__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6166 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__reserve :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btQuantizedBvhNode__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6172 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__m_allocator_set :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc , BtAlignedAllocator_btQuantizedBvhNode_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btQuantizedBvhNode__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6176 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__m_allocator_get :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> IO (BtAlignedAllocator_btQuantizedBvhNode_16u_)
btAlignedObjectArray_btQuantizedBvhNode__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btQuantizedBvhNode__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btQuantizedBvhNode_16u_ res >>= \res' ->
  return (res')
{-# LINE 6180 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__m_size_set :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btQuantizedBvhNode__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6184 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__m_size_get :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btQuantizedBvhNode__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btQuantizedBvhNode__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6188 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__m_capacity_set :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btQuantizedBvhNode__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6192 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__m_capacity_get :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btQuantizedBvhNode__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btQuantizedBvhNode__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6196 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__m_data_set :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc , BtQuantizedBvhNodeClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btQuantizedBvhNode__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6200 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__m_data_get :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> IO (BtQuantizedBvhNode)
btAlignedObjectArray_btQuantizedBvhNode__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btQuantizedBvhNode__m_data_get'_ a1' >>= \res ->
  mkBtQuantizedBvhNode res >>= \res' ->
  return (res')
{-# LINE 6204 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__m_ownsMemory_set :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btQuantizedBvhNode__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btQuantizedBvhNode__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6208 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btQuantizedBvhNode__m_ownsMemory_get :: ( BtAlignedObjectArray_btQuantizedBvhNode_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btQuantizedBvhNode__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btQuantizedBvhNode__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 6212 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btRigidBody*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr_ :: IO (BtAlignedObjectArray_btRigidBody_ptr_)
btAlignedObjectArray_btRigidBody_ptr_ =
  btAlignedObjectArray_btRigidBody_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btRigidBody_ptr_ res >>= \res' ->
  return (res')
{-# LINE 6217 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btRigidBody_ptr__free :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btRigidBody_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btRigidBody_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 6218 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__push_back :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc , BtRigidBodyClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btRigidBody_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btRigidBody_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6224 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__at :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> Int -> IO (BtRigidBody)
btAlignedObjectArray_btRigidBody_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btRigidBody_ptr__at'_ a1' a2' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')
{-# LINE 6230 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__at0 :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> Int -> IO (BtRigidBody)
btAlignedObjectArray_btRigidBody_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btRigidBody_ptr__at0'_ a1' a2' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')
{-# LINE 6236 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__at1 :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> Int -> IO (BtRigidBody)
btAlignedObjectArray_btRigidBody_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btRigidBody_ptr__at1'_ a1' a2' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')
{-# LINE 6242 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__size :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btRigidBody_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btRigidBody_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6247 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__capacity :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btRigidBody_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btRigidBody_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6252 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__init :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btRigidBody_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btRigidBody_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 6257 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__allocate :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btRigidBody_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btRigidBody_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 6263 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__pop_back :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btRigidBody_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btRigidBody_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 6268 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__deallocate :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btRigidBody_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btRigidBody_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 6273 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__swap :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btRigidBody_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btRigidBody_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6280 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btRigidBody_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btRigidBody_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 6288 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> IO (BtRigidBody)
btAlignedObjectArray_btRigidBody_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btRigidBody_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')
{-# LINE 6293 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__resize :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc , BtRigidBodyClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btRigidBody_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btRigidBody_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6300 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__destroy :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btRigidBody_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btRigidBody_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6307 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__expand :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc , BtRigidBodyClass p0 ) => bc -> p0 -> IO (BtRigidBody)
btAlignedObjectArray_btRigidBody_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btRigidBody_ptr__expand'_ a1' a2' >>= \res ->
  mkBtRigidBody res >>= \res' ->
  return (res')
{-# LINE 6313 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__clear :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btRigidBody_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btRigidBody_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 6318 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__allocSize :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btRigidBody_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btRigidBody_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6324 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__reserve :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btRigidBody_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btRigidBody_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6330 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__m_allocator_set :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc , BtAlignedAllocator_btRigidBody_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btRigidBody_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btRigidBody_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6334 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__m_allocator_get :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btRigidBody_ptr_16u_)
btAlignedObjectArray_btRigidBody_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btRigidBody_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btRigidBody_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 6338 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__m_size_set :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btRigidBody_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btRigidBody_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6342 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__m_size_get :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btRigidBody_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btRigidBody_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6346 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__m_capacity_set :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btRigidBody_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btRigidBody_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6350 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__m_capacity_get :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btRigidBody_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btRigidBody_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6354 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btRigidBody_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btRigidBody_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6358 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btRigidBody_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btRigidBody_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btRigidBody_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btRigidBody_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 6362 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr_ :: IO (BtAlignedObjectArray_btSoftBody_ptr_)
btAlignedObjectArray_btSoftBody_ptr_ =
  btAlignedObjectArray_btSoftBody_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_ptr_ res >>= \res' ->
  return (res')
{-# LINE 6367 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_ptr__free :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 6368 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__push_back :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc , BtSoftBodyClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSoftBody_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6374 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__at :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody)
btAlignedObjectArray_btSoftBody_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_ptr__at'_ a1' a2' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  return (res')
{-# LINE 6380 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__at0 :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody)
btAlignedObjectArray_btSoftBody_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_ptr__at0'_ a1' a2' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  return (res')
{-# LINE 6386 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__at1 :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody)
btAlignedObjectArray_btSoftBody_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_ptr__at1'_ a1' a2' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  return (res')
{-# LINE 6392 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__size :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6397 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__capacity :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6402 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__init :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 6407 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__swap :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6414 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__pop_back :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 6419 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__deallocate :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 6424 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__allocate :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 6430 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 6438 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> IO (BtSoftBody)
btAlignedObjectArray_btSoftBody_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  return (res')
{-# LINE 6443 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__destroy :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6450 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__resize :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc , BtSoftBodyClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSoftBody_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSoftBody_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6457 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__clear :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 6462 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__allocSize :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6468 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__expand :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc , BtSoftBodyClass p0 ) => bc -> p0 -> IO (BtSoftBody)
btAlignedObjectArray_btSoftBody_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_ptr__expand'_ a1' a2' >>= \res ->
  mkBtSoftBody res >>= \res' ->
  return (res')
{-# LINE 6474 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__reserve :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6480 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc , BtAlignedAllocator_btSoftBody_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6484 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_ptr_16u_)
btAlignedObjectArray_btSoftBody_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 6488 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6492 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6496 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6500 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 6504 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__m_size_set :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6508 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ptr__m_size_get :: ( BtAlignedObjectArray_btSoftBody_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6512 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::Anchor>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor_ :: IO (BtAlignedObjectArray_btSoftBody_Anchor_)
btAlignedObjectArray_btSoftBody_Anchor_ =
  btAlignedObjectArray_btSoftBody_Anchor_'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Anchor_ res >>= \res' ->
  return (res')
{-# LINE 6517 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_Anchor__free :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Anchor__free'_ a1' >>= \res ->
  return ()
{-# LINE 6518 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__push_back :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc , BtSoftBody_AnchorClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Anchor__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6524 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__at :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> Int -> IO (BtSoftBody_Anchor)
btAlignedObjectArray_btSoftBody_Anchor__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Anchor__at'_ a1' a2' >>= \res ->
  mkBtSoftBody_Anchor res >>= \res' ->
  return (res')
{-# LINE 6530 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__at0 :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> Int -> IO (BtSoftBody_Anchor)
btAlignedObjectArray_btSoftBody_Anchor__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Anchor__at0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Anchor res >>= \res' ->
  return (res')
{-# LINE 6536 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__at1 :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> Int -> IO (BtSoftBody_Anchor)
btAlignedObjectArray_btSoftBody_Anchor__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Anchor__at1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Anchor res >>= \res' ->
  return (res')
{-# LINE 6542 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__size :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Anchor__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Anchor__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6547 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__capacity :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Anchor__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Anchor__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6552 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__init :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Anchor__init'_ a1' >>= \res ->
  return ()
{-# LINE 6557 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__swap :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Anchor__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6564 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__pop_back :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Anchor__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 6569 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__deallocate :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Anchor__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 6574 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__allocate :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_Anchor__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Anchor__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 6580 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_Anchor__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 6588 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__expandNonInitializing :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> IO (BtSoftBody_Anchor)
btAlignedObjectArray_btSoftBody_Anchor__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Anchor__expandNonInitializing'_ a1' >>= \res ->
  mkBtSoftBody_Anchor res >>= \res' ->
  return (res')
{-# LINE 6593 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__destroy :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Anchor__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6600 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__copy :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc , BtSoftBody_AnchorClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btSoftBody_Anchor__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 6608 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__resize :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc , BtSoftBody_AnchorClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSoftBody_Anchor__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6615 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__clear :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Anchor__clear'_ a1' >>= \res ->
  return ()
{-# LINE 6620 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__allocSize :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_Anchor__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Anchor__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6626 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__expand :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc , BtSoftBody_AnchorClass p0 ) => bc -> p0 -> IO (BtSoftBody_Anchor)
btAlignedObjectArray_btSoftBody_Anchor__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Anchor__expand'_ a1' a2' >>= \res ->
  mkBtSoftBody_Anchor res >>= \res' ->
  return (res')
{-# LINE 6632 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__reserve :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Anchor__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6638 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc , BtAlignedAllocator_btSoftBody_Anchor_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Anchor__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6642 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_Anchor_16u_)
btAlignedObjectArray_btSoftBody_Anchor__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Anchor__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Anchor_16u_ res >>= \res' ->
  return (res')
{-# LINE 6646 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Anchor__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6650 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Anchor__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Anchor__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6654 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__m_data_set :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc , BtSoftBody_AnchorClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Anchor__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6658 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__m_data_get :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> IO (BtSoftBody_Anchor)
btAlignedObjectArray_btSoftBody_Anchor__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Anchor__m_data_get'_ a1' >>= \res ->
  mkBtSoftBody_Anchor res >>= \res' ->
  return (res')
{-# LINE 6662 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_Anchor__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6666 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_Anchor__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Anchor__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 6670 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__m_size_set :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Anchor__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Anchor__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6674 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Anchor__m_size_get :: ( BtAlignedObjectArray_btSoftBody_Anchor_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Anchor__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Anchor__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6678 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::Cluster*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr_ :: IO (BtAlignedObjectArray_btSoftBody_Cluster_ptr_)
btAlignedObjectArray_btSoftBody_Cluster_ptr_ =
  btAlignedObjectArray_btSoftBody_Cluster_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Cluster_ptr_ res >>= \res' ->
  return (res')
{-# LINE 6683 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__free :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 6684 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__push_back :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc , BtSoftBody_ClusterClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6690 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__at :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody_Cluster)
btAlignedObjectArray_btSoftBody_Cluster_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__at'_ a1' a2' >>= \res ->
  mkBtSoftBody_Cluster res >>= \res' ->
  return (res')
{-# LINE 6696 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__at0 :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody_Cluster)
btAlignedObjectArray_btSoftBody_Cluster_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__at0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Cluster res >>= \res' ->
  return (res')
{-# LINE 6702 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__at1 :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody_Cluster)
btAlignedObjectArray_btSoftBody_Cluster_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__at1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Cluster res >>= \res' ->
  return (res')
{-# LINE 6708 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__size :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Cluster_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6713 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__capacity :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Cluster_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6718 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__init :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 6723 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__swap :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6730 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__pop_back :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 6735 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__deallocate :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 6740 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__allocate :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_Cluster_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 6746 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 6754 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> IO (BtSoftBody_Cluster)
btAlignedObjectArray_btSoftBody_Cluster_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtSoftBody_Cluster res >>= \res' ->
  return (res')
{-# LINE 6759 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__destroy :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6766 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__resize :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc , BtSoftBody_ClusterClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6773 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__clear :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 6778 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__allocSize :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_Cluster_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6784 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__expand :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc , BtSoftBody_ClusterClass p0 ) => bc -> p0 -> IO (BtSoftBody_Cluster)
btAlignedObjectArray_btSoftBody_Cluster_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__expand'_ a1' a2' >>= \res ->
  mkBtSoftBody_Cluster res >>= \res' ->
  return (res')
{-# LINE 6790 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__reserve :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6796 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc , BtAlignedAllocator_btSoftBody_Cluster_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6800 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_Cluster_ptr_16u_)
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Cluster_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 6804 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6808 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6812 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6816 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 6820 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_size_set :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6824 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_size_get :: ( BtAlignedObjectArray_btSoftBody_Cluster_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Cluster_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6828 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::Face>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face_ :: IO (BtAlignedObjectArray_btSoftBody_Face_)
btAlignedObjectArray_btSoftBody_Face_ =
  btAlignedObjectArray_btSoftBody_Face_'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Face_ res >>= \res' ->
  return (res')
{-# LINE 6833 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_Face__free :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Face__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Face__free'_ a1' >>= \res ->
  return ()
{-# LINE 6834 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__push_back :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc , BtSoftBody_FaceClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSoftBody_Face__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Face__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6840 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__at :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> Int -> IO (BtSoftBody_Face)
btAlignedObjectArray_btSoftBody_Face__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Face__at'_ a1' a2' >>= \res ->
  mkBtSoftBody_Face res >>= \res' ->
  return (res')
{-# LINE 6846 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__at0 :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> Int -> IO (BtSoftBody_Face)
btAlignedObjectArray_btSoftBody_Face__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Face__at0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Face res >>= \res' ->
  return (res')
{-# LINE 6852 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__at1 :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> Int -> IO (BtSoftBody_Face)
btAlignedObjectArray_btSoftBody_Face__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Face__at1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Face res >>= \res' ->
  return (res')
{-# LINE 6858 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__size :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Face__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Face__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6863 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__capacity :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Face__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Face__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6868 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__init :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Face__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Face__init'_ a1' >>= \res ->
  return ()
{-# LINE 6873 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__swap :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Face__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Face__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6880 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__pop_back :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Face__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Face__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 6885 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__deallocate :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Face__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Face__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 6890 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__allocate :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_Face__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Face__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 6896 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Face__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_Face__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 6904 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__expandNonInitializing :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> IO (BtSoftBody_Face)
btAlignedObjectArray_btSoftBody_Face__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Face__expandNonInitializing'_ a1' >>= \res ->
  mkBtSoftBody_Face res >>= \res' ->
  return (res')
{-# LINE 6909 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__destroy :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Face__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Face__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6916 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__copy :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc , BtSoftBody_FaceClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btSoftBody_Face__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btSoftBody_Face__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 6924 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__resize :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc , BtSoftBody_FaceClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSoftBody_Face__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSoftBody_Face__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 6931 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__clear :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Face__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Face__clear'_ a1' >>= \res ->
  return ()
{-# LINE 6936 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__allocSize :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_Face__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Face__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6942 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__expand :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc , BtSoftBody_FaceClass p0 ) => bc -> p0 -> IO (BtSoftBody_Face)
btAlignedObjectArray_btSoftBody_Face__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Face__expand'_ a1' a2' >>= \res ->
  mkBtSoftBody_Face res >>= \res' ->
  return (res')
{-# LINE 6948 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__reserve :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Face__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Face__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6954 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc , BtAlignedAllocator_btSoftBody_Face_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Face__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Face__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6958 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_Face_16u_)
btAlignedObjectArray_btSoftBody_Face__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Face__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Face_16u_ res >>= \res' ->
  return (res')
{-# LINE 6962 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Face__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Face__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6966 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Face__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Face__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6970 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__m_data_set :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc , BtSoftBody_FaceClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Face__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Face__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6974 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__m_data_get :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> IO (BtSoftBody_Face)
btAlignedObjectArray_btSoftBody_Face__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Face__m_data_get'_ a1' >>= \res ->
  mkBtSoftBody_Face res >>= \res' ->
  return (res')
{-# LINE 6978 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_Face__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_Face__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6982 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_Face__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Face__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 6986 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__m_size_set :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Face__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Face__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 6990 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Face__m_size_get :: ( BtAlignedObjectArray_btSoftBody_Face_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Face__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Face__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 6994 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::Joint*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr_ :: IO (BtAlignedObjectArray_btSoftBody_Joint_ptr_)
btAlignedObjectArray_btSoftBody_Joint_ptr_ =
  btAlignedObjectArray_btSoftBody_Joint_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Joint_ptr_ res >>= \res' ->
  return (res')
{-# LINE 6999 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_Joint_ptr__free :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 7000 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__push_back :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc , BtSoftBody_JointClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7006 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__at :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody_Joint)
btAlignedObjectArray_btSoftBody_Joint_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Joint_ptr__at'_ a1' a2' >>= \res ->
  mkBtSoftBody_Joint res >>= \res' ->
  return (res')
{-# LINE 7012 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__at0 :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody_Joint)
btAlignedObjectArray_btSoftBody_Joint_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Joint_ptr__at0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Joint res >>= \res' ->
  return (res')
{-# LINE 7018 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__at1 :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody_Joint)
btAlignedObjectArray_btSoftBody_Joint_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Joint_ptr__at1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Joint res >>= \res' ->
  return (res')
{-# LINE 7024 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__size :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Joint_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7029 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__capacity :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Joint_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7034 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__init :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 7039 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__swap :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Joint_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7046 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__pop_back :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 7051 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__deallocate :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 7056 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__allocate :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_Joint_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Joint_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 7062 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_Joint_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 7070 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> IO (BtSoftBody_Joint)
btAlignedObjectArray_btSoftBody_Joint_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtSoftBody_Joint res >>= \res' ->
  return (res')
{-# LINE 7075 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__destroy :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Joint_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7082 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__resize :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc , BtSoftBody_JointClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7089 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__clear :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 7094 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__allocSize :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_Joint_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Joint_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7100 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__expand :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc , BtSoftBody_JointClass p0 ) => bc -> p0 -> IO (BtSoftBody_Joint)
btAlignedObjectArray_btSoftBody_Joint_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__expand'_ a1' a2' >>= \res ->
  mkBtSoftBody_Joint res >>= \res' ->
  return (res')
{-# LINE 7106 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__reserve :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Joint_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7112 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc , BtAlignedAllocator_btSoftBody_Joint_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7116 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_Joint_ptr_16u_)
btAlignedObjectArray_btSoftBody_Joint_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Joint_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 7120 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7124 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Joint_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7128 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7132 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_Joint_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 7136 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__m_size_set :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Joint_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7140 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Joint_ptr__m_size_get :: ( BtAlignedObjectArray_btSoftBody_Joint_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Joint_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7144 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::Link>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link_ :: IO (BtAlignedObjectArray_btSoftBody_Link_)
btAlignedObjectArray_btSoftBody_Link_ =
  btAlignedObjectArray_btSoftBody_Link_'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Link_ res >>= \res' ->
  return (res')
{-# LINE 7149 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_Link__free :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Link__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Link__free'_ a1' >>= \res ->
  return ()
{-# LINE 7150 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__push_back :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc , BtSoftBody_LinkClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSoftBody_Link__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Link__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7156 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__at :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> Int -> IO (BtSoftBody_Link)
btAlignedObjectArray_btSoftBody_Link__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Link__at'_ a1' a2' >>= \res ->
  mkBtSoftBody_Link res >>= \res' ->
  return (res')
{-# LINE 7162 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__at0 :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> Int -> IO (BtSoftBody_Link)
btAlignedObjectArray_btSoftBody_Link__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Link__at0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Link res >>= \res' ->
  return (res')
{-# LINE 7168 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__at1 :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> Int -> IO (BtSoftBody_Link)
btAlignedObjectArray_btSoftBody_Link__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Link__at1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Link res >>= \res' ->
  return (res')
{-# LINE 7174 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__size :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Link__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Link__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7179 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__capacity :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Link__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Link__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7184 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__init :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Link__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Link__init'_ a1' >>= \res ->
  return ()
{-# LINE 7189 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__swap :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Link__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Link__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7196 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__pop_back :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Link__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Link__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 7201 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__deallocate :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Link__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Link__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 7206 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__allocate :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_Link__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Link__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 7212 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Link__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_Link__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 7220 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__expandNonInitializing :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> IO (BtSoftBody_Link)
btAlignedObjectArray_btSoftBody_Link__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Link__expandNonInitializing'_ a1' >>= \res ->
  mkBtSoftBody_Link res >>= \res' ->
  return (res')
{-# LINE 7225 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__destroy :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Link__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Link__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7232 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__copy :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc , BtSoftBody_LinkClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btSoftBody_Link__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btSoftBody_Link__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 7240 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__resize :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc , BtSoftBody_LinkClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSoftBody_Link__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSoftBody_Link__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7247 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__clear :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Link__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Link__clear'_ a1' >>= \res ->
  return ()
{-# LINE 7252 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__allocSize :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_Link__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Link__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7258 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__expand :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc , BtSoftBody_LinkClass p0 ) => bc -> p0 -> IO (BtSoftBody_Link)
btAlignedObjectArray_btSoftBody_Link__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Link__expand'_ a1' a2' >>= \res ->
  mkBtSoftBody_Link res >>= \res' ->
  return (res')
{-# LINE 7264 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__reserve :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Link__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Link__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7270 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc , BtAlignedAllocator_btSoftBody_Link_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Link__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Link__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7274 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_Link_16u_)
btAlignedObjectArray_btSoftBody_Link__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Link__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Link_16u_ res >>= \res' ->
  return (res')
{-# LINE 7278 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Link__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Link__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7282 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Link__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Link__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7286 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__m_data_set :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc , BtSoftBody_LinkClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Link__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Link__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7290 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__m_data_get :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> IO (BtSoftBody_Link)
btAlignedObjectArray_btSoftBody_Link__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Link__m_data_get'_ a1' >>= \res ->
  mkBtSoftBody_Link res >>= \res' ->
  return (res')
{-# LINE 7294 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_Link__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_Link__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7298 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_Link__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Link__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 7302 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__m_size_set :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Link__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Link__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7306 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Link__m_size_get :: ( BtAlignedObjectArray_btSoftBody_Link_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Link__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Link__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7310 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::Material*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr_ :: IO (BtAlignedObjectArray_btSoftBody_Material_ptr_)
btAlignedObjectArray_btSoftBody_Material_ptr_ =
  btAlignedObjectArray_btSoftBody_Material_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Material_ptr_ res >>= \res' ->
  return (res')
{-# LINE 7315 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_Material_ptr__free :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 7316 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__push_back :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc , BtSoftBody_MaterialClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7322 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__at :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody_Material)
btAlignedObjectArray_btSoftBody_Material_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Material_ptr__at'_ a1' a2' >>= \res ->
  mkBtSoftBody_Material res >>= \res' ->
  return (res')
{-# LINE 7328 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__at0 :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody_Material)
btAlignedObjectArray_btSoftBody_Material_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Material_ptr__at0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Material res >>= \res' ->
  return (res')
{-# LINE 7334 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__at1 :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody_Material)
btAlignedObjectArray_btSoftBody_Material_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Material_ptr__at1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Material res >>= \res' ->
  return (res')
{-# LINE 7340 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__size :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Material_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7345 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__capacity :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Material_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7350 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__init :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 7355 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__swap :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Material_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7362 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__pop_back :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 7367 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__deallocate :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 7372 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__allocate :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_Material_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Material_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 7378 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_Material_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 7386 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> IO (BtSoftBody_Material)
btAlignedObjectArray_btSoftBody_Material_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtSoftBody_Material res >>= \res' ->
  return (res')
{-# LINE 7391 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__destroy :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Material_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7398 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__resize :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc , BtSoftBody_MaterialClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7405 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__clear :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 7410 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__allocSize :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_Material_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Material_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7416 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__expand :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc , BtSoftBody_MaterialClass p0 ) => bc -> p0 -> IO (BtSoftBody_Material)
btAlignedObjectArray_btSoftBody_Material_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__expand'_ a1' a2' >>= \res ->
  mkBtSoftBody_Material res >>= \res' ->
  return (res')
{-# LINE 7422 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__reserve :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Material_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7428 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc , BtAlignedAllocator_btSoftBody_Material_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7432 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_Material_ptr_16u_)
btAlignedObjectArray_btSoftBody_Material_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Material_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 7436 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Material_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7440 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Material_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7444 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_Material_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7448 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_Material_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 7452 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__m_size_set :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Material_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Material_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7456 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Material_ptr__m_size_get :: ( BtAlignedObjectArray_btSoftBody_Material_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Material_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Material_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7460 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::Node*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr_ :: IO (BtAlignedObjectArray_btSoftBody_Node_ptr_)
btAlignedObjectArray_btSoftBody_Node_ptr_ =
  btAlignedObjectArray_btSoftBody_Node_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Node_ptr_ res >>= \res' ->
  return (res')
{-# LINE 7465 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_Node_ptr__free :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 7466 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__push_back :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc , BtSoftBody_NodeClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7472 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__at :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody_Node)
btAlignedObjectArray_btSoftBody_Node_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node_ptr__at'_ a1' a2' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 7478 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__at0 :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody_Node)
btAlignedObjectArray_btSoftBody_Node_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node_ptr__at0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 7484 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__at1 :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> Int -> IO (BtSoftBody_Node)
btAlignedObjectArray_btSoftBody_Node_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node_ptr__at1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 7490 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__size :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Node_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7495 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__capacity :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Node_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7500 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__init :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 7505 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__swap :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Node_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7512 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__pop_back :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 7517 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__deallocate :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 7522 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__allocate :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_Node_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 7528 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_Node_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 7536 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> IO (BtSoftBody_Node)
btAlignedObjectArray_btSoftBody_Node_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 7541 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__destroy :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Node_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7548 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__resize :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc , BtSoftBody_NodeClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7555 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__clear :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 7560 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__allocSize :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_Node_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7566 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__expand :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc , BtSoftBody_NodeClass p0 ) => bc -> p0 -> IO (BtSoftBody_Node)
btAlignedObjectArray_btSoftBody_Node_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__expand'_ a1' a2' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 7572 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__reserve :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7578 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc , BtAlignedAllocator_btSoftBody_Node_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7582 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_Node_ptr_16u_)
btAlignedObjectArray_btSoftBody_Node_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Node_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 7586 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7590 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Node_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7594 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_Node_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7598 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_Node_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 7602 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__m_size_set :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Node_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7606 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ptr__m_size_get :: ( BtAlignedObjectArray_btSoftBody_Node_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Node_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7610 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::Node>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node_ :: IO (BtAlignedObjectArray_btSoftBody_Node_)
btAlignedObjectArray_btSoftBody_Node_ =
  btAlignedObjectArray_btSoftBody_Node_'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Node_ res >>= \res' ->
  return (res')
{-# LINE 7615 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_Node__free :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Node__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node__free'_ a1' >>= \res ->
  return ()
{-# LINE 7616 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__push_back :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc , BtSoftBody_NodeClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSoftBody_Node__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Node__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7622 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__at :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> Int -> IO (BtSoftBody_Node)
btAlignedObjectArray_btSoftBody_Node__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node__at'_ a1' a2' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 7628 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__at0 :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> Int -> IO (BtSoftBody_Node)
btAlignedObjectArray_btSoftBody_Node__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node__at0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 7634 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__at1 :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> Int -> IO (BtSoftBody_Node)
btAlignedObjectArray_btSoftBody_Node__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node__at1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 7640 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__size :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Node__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7645 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__capacity :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Node__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7650 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__init :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Node__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node__init'_ a1' >>= \res ->
  return ()
{-# LINE 7655 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__swap :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Node__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Node__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7662 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__pop_back :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Node__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 7667 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__deallocate :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Node__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 7672 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__allocate :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_Node__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 7678 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Node__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_Node__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 7686 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__expandNonInitializing :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> IO (BtSoftBody_Node)
btAlignedObjectArray_btSoftBody_Node__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node__expandNonInitializing'_ a1' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 7691 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__destroy :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Node__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Node__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7698 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__copy :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc , BtSoftBody_NodeClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btSoftBody_Node__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btSoftBody_Node__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 7706 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__resize :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc , BtSoftBody_NodeClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSoftBody_Node__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSoftBody_Node__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7713 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__clear :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Node__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node__clear'_ a1' >>= \res ->
  return ()
{-# LINE 7718 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__allocSize :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_Node__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7724 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__expand :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc , BtSoftBody_NodeClass p0 ) => bc -> p0 -> IO (BtSoftBody_Node)
btAlignedObjectArray_btSoftBody_Node__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Node__expand'_ a1' a2' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 7730 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__reserve :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Node__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7736 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc , BtAlignedAllocator_btSoftBody_Node_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Node__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Node__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7740 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_Node_16u_)
btAlignedObjectArray_btSoftBody_Node__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Node_16u_ res >>= \res' ->
  return (res')
{-# LINE 7744 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Node__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7748 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Node__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7752 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__m_data_set :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc , BtSoftBody_NodeClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Node__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Node__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7756 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__m_data_get :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> IO (BtSoftBody_Node)
btAlignedObjectArray_btSoftBody_Node__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node__m_data_get'_ a1' >>= \res ->
  mkBtSoftBody_Node res >>= \res' ->
  return (res')
{-# LINE 7760 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_Node__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_Node__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7764 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_Node__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 7768 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__m_size_set :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Node__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Node__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7772 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Node__m_size_get :: ( BtAlignedObjectArray_btSoftBody_Node_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Node__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Node__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7776 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::Note>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note_ :: IO (BtAlignedObjectArray_btSoftBody_Note_)
btAlignedObjectArray_btSoftBody_Note_ =
  btAlignedObjectArray_btSoftBody_Note_'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Note_ res >>= \res' ->
  return (res')
{-# LINE 7781 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_Note__free :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Note__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Note__free'_ a1' >>= \res ->
  return ()
{-# LINE 7782 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__push_back :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc , BtSoftBody_NoteClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSoftBody_Note__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Note__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7788 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__at :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> Int -> IO (BtSoftBody_Note)
btAlignedObjectArray_btSoftBody_Note__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Note__at'_ a1' a2' >>= \res ->
  mkBtSoftBody_Note res >>= \res' ->
  return (res')
{-# LINE 7794 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__at0 :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> Int -> IO (BtSoftBody_Note)
btAlignedObjectArray_btSoftBody_Note__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Note__at0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Note res >>= \res' ->
  return (res')
{-# LINE 7800 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__at1 :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> Int -> IO (BtSoftBody_Note)
btAlignedObjectArray_btSoftBody_Note__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Note__at1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Note res >>= \res' ->
  return (res')
{-# LINE 7806 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__size :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Note__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Note__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7811 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__capacity :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Note__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Note__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7816 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__init :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Note__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Note__init'_ a1' >>= \res ->
  return ()
{-# LINE 7821 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__swap :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Note__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Note__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7828 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__pop_back :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Note__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Note__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 7833 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__deallocate :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Note__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Note__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 7838 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__allocate :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_Note__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Note__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 7844 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Note__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_Note__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 7852 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__expandNonInitializing :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> IO (BtSoftBody_Note)
btAlignedObjectArray_btSoftBody_Note__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Note__expandNonInitializing'_ a1' >>= \res ->
  mkBtSoftBody_Note res >>= \res' ->
  return (res')
{-# LINE 7857 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__destroy :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Note__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Note__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7864 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__copy :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc , BtSoftBody_NoteClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btSoftBody_Note__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btSoftBody_Note__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 7872 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__resize :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc , BtSoftBody_NoteClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSoftBody_Note__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSoftBody_Note__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7879 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__clear :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Note__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Note__clear'_ a1' >>= \res ->
  return ()
{-# LINE 7884 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__allocSize :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_Note__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Note__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7890 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__expand :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc , BtSoftBody_NoteClass p0 ) => bc -> p0 -> IO (BtSoftBody_Note)
btAlignedObjectArray_btSoftBody_Note__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Note__expand'_ a1' a2' >>= \res ->
  mkBtSoftBody_Note res >>= \res' ->
  return (res')
{-# LINE 7896 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__reserve :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Note__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Note__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7902 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc , BtAlignedAllocator_btSoftBody_Note_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Note__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Note__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7906 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_Note_16u_)
btAlignedObjectArray_btSoftBody_Note__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Note__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Note_16u_ res >>= \res' ->
  return (res')
{-# LINE 7910 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Note__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Note__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7914 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Note__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Note__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7918 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__m_data_set :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc , BtSoftBody_NoteClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Note__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Note__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7922 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__m_data_get :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> IO (BtSoftBody_Note)
btAlignedObjectArray_btSoftBody_Note__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Note__m_data_get'_ a1' >>= \res ->
  mkBtSoftBody_Note res >>= \res' ->
  return (res')
{-# LINE 7926 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_Note__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_Note__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7930 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_Note__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Note__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 7934 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__m_size_set :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Note__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Note__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7938 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Note__m_size_get :: ( BtAlignedObjectArray_btSoftBody_Note_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Note__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Note__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7942 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::RContact>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact_ :: IO (BtAlignedObjectArray_btSoftBody_RContact_)
btAlignedObjectArray_btSoftBody_RContact_ =
  btAlignedObjectArray_btSoftBody_RContact_'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_RContact_ res >>= \res' ->
  return (res')
{-# LINE 7947 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_RContact__free :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_RContact__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_RContact__free'_ a1' >>= \res ->
  return ()
{-# LINE 7948 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__push_back :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc , BtSoftBody_RContactClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSoftBody_RContact__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_RContact__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 7954 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__at :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> Int -> IO (BtSoftBody_RContact)
btAlignedObjectArray_btSoftBody_RContact__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_RContact__at'_ a1' a2' >>= \res ->
  mkBtSoftBody_RContact res >>= \res' ->
  return (res')
{-# LINE 7960 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__at0 :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> Int -> IO (BtSoftBody_RContact)
btAlignedObjectArray_btSoftBody_RContact__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_RContact__at0'_ a1' a2' >>= \res ->
  mkBtSoftBody_RContact res >>= \res' ->
  return (res')
{-# LINE 7966 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__at1 :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> Int -> IO (BtSoftBody_RContact)
btAlignedObjectArray_btSoftBody_RContact__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_RContact__at1'_ a1' a2' >>= \res ->
  mkBtSoftBody_RContact res >>= \res' ->
  return (res')
{-# LINE 7972 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__size :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_RContact__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_RContact__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7977 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__capacity :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_RContact__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_RContact__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 7982 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__init :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_RContact__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_RContact__init'_ a1' >>= \res ->
  return ()
{-# LINE 7987 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__swap :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_RContact__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_RContact__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 7994 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__pop_back :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_RContact__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_RContact__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 7999 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__deallocate :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_RContact__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_RContact__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 8004 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__allocate :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_RContact__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_RContact__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 8010 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_RContact__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_RContact__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 8018 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__expandNonInitializing :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> IO (BtSoftBody_RContact)
btAlignedObjectArray_btSoftBody_RContact__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_RContact__expandNonInitializing'_ a1' >>= \res ->
  mkBtSoftBody_RContact res >>= \res' ->
  return (res')
{-# LINE 8023 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__destroy :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_RContact__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_RContact__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8030 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__copy :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc , BtSoftBody_RContactClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btSoftBody_RContact__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btSoftBody_RContact__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 8038 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__resize :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc , BtSoftBody_RContactClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSoftBody_RContact__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSoftBody_RContact__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8045 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__clear :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_RContact__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_RContact__clear'_ a1' >>= \res ->
  return ()
{-# LINE 8050 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__allocSize :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_RContact__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_RContact__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8056 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__expand :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc , BtSoftBody_RContactClass p0 ) => bc -> p0 -> IO (BtSoftBody_RContact)
btAlignedObjectArray_btSoftBody_RContact__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_RContact__expand'_ a1' a2' >>= \res ->
  mkBtSoftBody_RContact res >>= \res' ->
  return (res')
{-# LINE 8062 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__reserve :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_RContact__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_RContact__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8068 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc , BtAlignedAllocator_btSoftBody_RContact_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_RContact__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_RContact__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8072 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_RContact_16u_)
btAlignedObjectArray_btSoftBody_RContact__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_RContact__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_RContact_16u_ res >>= \res' ->
  return (res')
{-# LINE 8076 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_RContact__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_RContact__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8080 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_RContact__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_RContact__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8084 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__m_data_set :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc , BtSoftBody_RContactClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_RContact__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_RContact__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8088 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__m_data_get :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> IO (BtSoftBody_RContact)
btAlignedObjectArray_btSoftBody_RContact__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_RContact__m_data_get'_ a1' >>= \res ->
  mkBtSoftBody_RContact res >>= \res' ->
  return (res')
{-# LINE 8092 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_RContact__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_RContact__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8096 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_RContact__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_RContact__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 8100 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__m_size_set :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_RContact__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_RContact__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8104 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_RContact__m_size_get :: ( BtAlignedObjectArray_btSoftBody_RContact_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_RContact__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_RContact__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8108 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::SContact>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact_ :: IO (BtAlignedObjectArray_btSoftBody_SContact_)
btAlignedObjectArray_btSoftBody_SContact_ =
  btAlignedObjectArray_btSoftBody_SContact_'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_SContact_ res >>= \res' ->
  return (res')
{-# LINE 8113 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_SContact__free :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_SContact__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_SContact__free'_ a1' >>= \res ->
  return ()
{-# LINE 8114 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__push_back :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc , BtSoftBody_SContactClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSoftBody_SContact__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_SContact__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8120 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__at :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> Int -> IO (BtSoftBody_SContact)
btAlignedObjectArray_btSoftBody_SContact__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_SContact__at'_ a1' a2' >>= \res ->
  mkBtSoftBody_SContact res >>= \res' ->
  return (res')
{-# LINE 8126 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__at0 :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> Int -> IO (BtSoftBody_SContact)
btAlignedObjectArray_btSoftBody_SContact__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_SContact__at0'_ a1' a2' >>= \res ->
  mkBtSoftBody_SContact res >>= \res' ->
  return (res')
{-# LINE 8132 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__at1 :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> Int -> IO (BtSoftBody_SContact)
btAlignedObjectArray_btSoftBody_SContact__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_SContact__at1'_ a1' a2' >>= \res ->
  mkBtSoftBody_SContact res >>= \res' ->
  return (res')
{-# LINE 8138 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__size :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_SContact__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_SContact__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8143 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__capacity :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_SContact__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_SContact__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8148 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__init :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_SContact__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_SContact__init'_ a1' >>= \res ->
  return ()
{-# LINE 8153 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__swap :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_SContact__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_SContact__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8160 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__pop_back :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_SContact__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_SContact__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 8165 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__deallocate :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_SContact__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_SContact__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 8170 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__allocate :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_SContact__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_SContact__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 8176 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_SContact__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_SContact__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 8184 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__expandNonInitializing :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> IO (BtSoftBody_SContact)
btAlignedObjectArray_btSoftBody_SContact__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_SContact__expandNonInitializing'_ a1' >>= \res ->
  mkBtSoftBody_SContact res >>= \res' ->
  return (res')
{-# LINE 8189 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__destroy :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_SContact__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_SContact__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8196 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__copy :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc , BtSoftBody_SContactClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btSoftBody_SContact__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btSoftBody_SContact__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 8204 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__resize :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc , BtSoftBody_SContactClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSoftBody_SContact__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSoftBody_SContact__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8211 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__clear :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_SContact__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_SContact__clear'_ a1' >>= \res ->
  return ()
{-# LINE 8216 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__allocSize :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_SContact__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_SContact__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8222 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__expand :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc , BtSoftBody_SContactClass p0 ) => bc -> p0 -> IO (BtSoftBody_SContact)
btAlignedObjectArray_btSoftBody_SContact__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_SContact__expand'_ a1' a2' >>= \res ->
  mkBtSoftBody_SContact res >>= \res' ->
  return (res')
{-# LINE 8228 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__reserve :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_SContact__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_SContact__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8234 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc , BtAlignedAllocator_btSoftBody_SContact_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_SContact__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_SContact__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8238 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_SContact_16u_)
btAlignedObjectArray_btSoftBody_SContact__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_SContact__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_SContact_16u_ res >>= \res' ->
  return (res')
{-# LINE 8242 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_SContact__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_SContact__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8246 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_SContact__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_SContact__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8250 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__m_data_set :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc , BtSoftBody_SContactClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_SContact__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_SContact__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8254 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__m_data_get :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> IO (BtSoftBody_SContact)
btAlignedObjectArray_btSoftBody_SContact__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_SContact__m_data_get'_ a1' >>= \res ->
  mkBtSoftBody_SContact res >>= \res' ->
  return (res')
{-# LINE 8258 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_SContact__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_SContact__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8262 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_SContact__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_SContact__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 8266 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__m_size_set :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_SContact__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_SContact__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8270 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_SContact__m_size_get :: ( BtAlignedObjectArray_btSoftBody_SContact_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_SContact__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_SContact__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8274 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::Tetra>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra_ :: IO (BtAlignedObjectArray_btSoftBody_Tetra_)
btAlignedObjectArray_btSoftBody_Tetra_ =
  btAlignedObjectArray_btSoftBody_Tetra_'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_Tetra_ res >>= \res' ->
  return (res')
{-# LINE 8279 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_Tetra__free :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Tetra__free'_ a1' >>= \res ->
  return ()
{-# LINE 8280 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__push_back :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc , BtSoftBody_TetraClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Tetra__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8286 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__at :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> Int -> IO (BtSoftBody_Tetra)
btAlignedObjectArray_btSoftBody_Tetra__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Tetra__at'_ a1' a2' >>= \res ->
  mkBtSoftBody_Tetra res >>= \res' ->
  return (res')
{-# LINE 8292 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__at0 :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> Int -> IO (BtSoftBody_Tetra)
btAlignedObjectArray_btSoftBody_Tetra__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Tetra__at0'_ a1' a2' >>= \res ->
  mkBtSoftBody_Tetra res >>= \res' ->
  return (res')
{-# LINE 8298 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__at1 :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> Int -> IO (BtSoftBody_Tetra)
btAlignedObjectArray_btSoftBody_Tetra__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Tetra__at1'_ a1' a2' >>= \res ->
  mkBtSoftBody_Tetra res >>= \res' ->
  return (res')
{-# LINE 8304 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__size :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Tetra__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Tetra__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8309 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__capacity :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Tetra__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Tetra__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8314 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__init :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Tetra__init'_ a1' >>= \res ->
  return ()
{-# LINE 8319 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__swap :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Tetra__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8326 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__pop_back :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Tetra__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 8331 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__deallocate :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Tetra__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 8336 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__allocate :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_Tetra__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Tetra__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 8342 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_Tetra__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 8350 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__expandNonInitializing :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> IO (BtSoftBody_Tetra)
btAlignedObjectArray_btSoftBody_Tetra__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Tetra__expandNonInitializing'_ a1' >>= \res ->
  mkBtSoftBody_Tetra res >>= \res' ->
  return (res')
{-# LINE 8355 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__destroy :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_Tetra__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8362 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__copy :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc , BtSoftBody_TetraClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btSoftBody_Tetra__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 8370 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__resize :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc , BtSoftBody_TetraClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSoftBody_Tetra__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8377 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__clear :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Tetra__clear'_ a1' >>= \res ->
  return ()
{-# LINE 8382 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__allocSize :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_Tetra__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Tetra__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8388 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__expand :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc , BtSoftBody_TetraClass p0 ) => bc -> p0 -> IO (BtSoftBody_Tetra)
btAlignedObjectArray_btSoftBody_Tetra__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Tetra__expand'_ a1' a2' >>= \res ->
  mkBtSoftBody_Tetra res >>= \res' ->
  return (res')
{-# LINE 8394 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__reserve :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Tetra__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8400 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc , BtAlignedAllocator_btSoftBody_Tetra_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Tetra__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8404 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_Tetra_16u_)
btAlignedObjectArray_btSoftBody_Tetra__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Tetra__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_Tetra_16u_ res >>= \res' ->
  return (res')
{-# LINE 8408 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Tetra__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8412 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Tetra__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Tetra__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8416 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__m_data_set :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc , BtSoftBody_TetraClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_Tetra__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8420 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__m_data_get :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> IO (BtSoftBody_Tetra)
btAlignedObjectArray_btSoftBody_Tetra__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Tetra__m_data_get'_ a1' >>= \res ->
  mkBtSoftBody_Tetra res >>= \res' ->
  return (res')
{-# LINE 8424 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_Tetra__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8428 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_Tetra__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Tetra__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 8432 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__m_size_set :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_Tetra__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_Tetra__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8436 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_Tetra__m_size_get :: ( BtAlignedObjectArray_btSoftBody_Tetra_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_Tetra__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_Tetra__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8440 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::ePSolver::_>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver___ :: IO (BtAlignedObjectArray_btSoftBody_ePSolver___)
btAlignedObjectArray_btSoftBody_ePSolver___ =
  btAlignedObjectArray_btSoftBody_ePSolver___'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_ePSolver___ res >>= \res' ->
  return (res')
{-# LINE 8445 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_ePSolver____free :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_ePSolver____free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ePSolver____free'_ a1' >>= \res ->
  return ()
{-# LINE 8446 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____size :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_ePSolver____size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ePSolver____size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8451 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____capacity :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_ePSolver____capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ePSolver____capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8456 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____init :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_ePSolver____init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ePSolver____init'_ a1' >>= \res ->
  return ()
{-# LINE 8461 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____swap :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_ePSolver____swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_ePSolver____swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8468 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____pop_back :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_ePSolver____pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ePSolver____pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 8473 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____deallocate :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_ePSolver____deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ePSolver____deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 8478 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____allocate :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_ePSolver____allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_ePSolver____allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 8484 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_ePSolver____initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_ePSolver____initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 8492 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____destroy :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_ePSolver____destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_ePSolver____destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8499 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____clear :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_ePSolver____clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ePSolver____clear'_ a1' >>= \res ->
  return ()
{-# LINE 8504 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____allocSize :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_ePSolver____allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_ePSolver____allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8510 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____reserve :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_ePSolver____reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_ePSolver____reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8516 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc , BtAlignedAllocator_btSoftBody_ePSolver___16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_ePSolver____m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_ePSolver____m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8520 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_ePSolver___16u_)
btAlignedObjectArray_btSoftBody_ePSolver____m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ePSolver____m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_ePSolver___16u_ res >>= \res' ->
  return (res')
{-# LINE 8524 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_ePSolver____m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_ePSolver____m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8528 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_ePSolver____m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ePSolver____m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8532 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_ePSolver____m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_ePSolver____m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8536 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_ePSolver____m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ePSolver____m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 8540 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____m_size_set :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_ePSolver____m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_ePSolver____m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8544 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_ePSolver____m_size_get :: ( BtAlignedObjectArray_btSoftBody_ePSolver___Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_ePSolver____m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_ePSolver____m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8548 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSoftBody::eVSolver::_>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver___ :: IO (BtAlignedObjectArray_btSoftBody_eVSolver___)
btAlignedObjectArray_btSoftBody_eVSolver___ =
  btAlignedObjectArray_btSoftBody_eVSolver___'_ >>= \res ->
  mkBtAlignedObjectArray_btSoftBody_eVSolver___ res >>= \res' ->
  return (res')
{-# LINE 8553 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSoftBody_eVSolver____free :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_eVSolver____free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_eVSolver____free'_ a1' >>= \res ->
  return ()
{-# LINE 8554 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____size :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_eVSolver____size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_eVSolver____size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8559 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____capacity :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_eVSolver____capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_eVSolver____capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8564 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____init :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_eVSolver____init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_eVSolver____init'_ a1' >>= \res ->
  return ()
{-# LINE 8569 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____swap :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_eVSolver____swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_eVSolver____swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8576 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____pop_back :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_eVSolver____pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_eVSolver____pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 8581 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____deallocate :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_eVSolver____deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_eVSolver____deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 8586 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____allocate :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSoftBody_eVSolver____allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_eVSolver____allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 8592 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____initializeFromBuffer :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_eVSolver____initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSoftBody_eVSolver____initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 8600 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____destroy :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSoftBody_eVSolver____destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSoftBody_eVSolver____destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8607 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____clear :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> IO ()
btAlignedObjectArray_btSoftBody_eVSolver____clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_eVSolver____clear'_ a1' >>= \res ->
  return ()
{-# LINE 8612 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____allocSize :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSoftBody_eVSolver____allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_eVSolver____allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8618 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____reserve :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_eVSolver____reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_eVSolver____reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8624 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____m_allocator_set :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc , BtAlignedAllocator_btSoftBody_eVSolver___16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSoftBody_eVSolver____m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSoftBody_eVSolver____m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8628 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____m_allocator_get :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> IO (BtAlignedAllocator_btSoftBody_eVSolver___16u_)
btAlignedObjectArray_btSoftBody_eVSolver____m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_eVSolver____m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSoftBody_eVSolver___16u_ res >>= \res' ->
  return (res')
{-# LINE 8632 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____m_capacity_set :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_eVSolver____m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_eVSolver____m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8636 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____m_capacity_get :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_eVSolver____m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_eVSolver____m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8640 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____m_ownsMemory_set :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSoftBody_eVSolver____m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSoftBody_eVSolver____m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8644 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____m_ownsMemory_get :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSoftBody_eVSolver____m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_eVSolver____m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 8648 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____m_size_set :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSoftBody_eVSolver____m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSoftBody_eVSolver____m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8652 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSoftBody_eVSolver____m_size_get :: ( BtAlignedObjectArray_btSoftBody_eVSolver___Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSoftBody_eVSolver____m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSoftBody_eVSolver____m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8656 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSolverConstraint>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint_ :: IO (BtAlignedObjectArray_btSolverConstraint_)
btAlignedObjectArray_btSolverConstraint_ =
  btAlignedObjectArray_btSolverConstraint_'_ >>= \res ->
  mkBtAlignedObjectArray_btSolverConstraint_ res >>= \res' ->
  return (res')
{-# LINE 8661 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSolverConstraint__free :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSolverConstraint__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSolverConstraint__free'_ a1' >>= \res ->
  return ()
{-# LINE 8662 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__push_back :: ( BtAlignedObjectArray_btSolverConstraint_Class bc , BtSolverConstraintClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btSolverConstraint__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSolverConstraint__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8668 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__at :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> Int -> IO (BtSolverConstraint)
btAlignedObjectArray_btSolverConstraint__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSolverConstraint__at'_ a1' a2' >>= \res ->
  mkBtSolverConstraint res >>= \res' ->
  return (res')
{-# LINE 8674 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__at0 :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> Int -> IO (BtSolverConstraint)
btAlignedObjectArray_btSolverConstraint__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSolverConstraint__at0'_ a1' a2' >>= \res ->
  mkBtSolverConstraint res >>= \res' ->
  return (res')
{-# LINE 8680 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__at1 :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> Int -> IO (BtSolverConstraint)
btAlignedObjectArray_btSolverConstraint__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSolverConstraint__at1'_ a1' a2' >>= \res ->
  mkBtSolverConstraint res >>= \res' ->
  return (res')
{-# LINE 8686 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__size :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSolverConstraint__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSolverConstraint__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8691 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__capacity :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSolverConstraint__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSolverConstraint__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8696 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__init :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSolverConstraint__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSolverConstraint__init'_ a1' >>= \res ->
  return ()
{-# LINE 8701 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__allocate :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSolverConstraint__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSolverConstraint__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 8707 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__pop_back :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSolverConstraint__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSolverConstraint__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 8712 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__deallocate :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSolverConstraint__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSolverConstraint__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 8717 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__swap :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSolverConstraint__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSolverConstraint__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8724 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__initializeFromBuffer :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSolverConstraint__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSolverConstraint__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 8732 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__expandNonInitializing :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> IO (BtSolverConstraint)
btAlignedObjectArray_btSolverConstraint__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSolverConstraint__expandNonInitializing'_ a1' >>= \res ->
  mkBtSolverConstraint res >>= \res' ->
  return (res')
{-# LINE 8737 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__resize :: ( BtAlignedObjectArray_btSolverConstraint_Class bc , BtSolverConstraintClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btSolverConstraint__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btSolverConstraint__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8744 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__destroy :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSolverConstraint__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSolverConstraint__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8751 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__copy :: ( BtAlignedObjectArray_btSolverConstraint_Class bc , BtSolverConstraintClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btSolverConstraint__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btSolverConstraint__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 8759 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__expand :: ( BtAlignedObjectArray_btSolverConstraint_Class bc , BtSolverConstraintClass p0 ) => bc -> p0 -> IO (BtSolverConstraint)
btAlignedObjectArray_btSolverConstraint__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSolverConstraint__expand'_ a1' a2' >>= \res ->
  mkBtSolverConstraint res >>= \res' ->
  return (res')
{-# LINE 8765 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__clear :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSolverConstraint__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSolverConstraint__clear'_ a1' >>= \res ->
  return ()
{-# LINE 8770 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__allocSize :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSolverConstraint__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSolverConstraint__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8776 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__reserve :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSolverConstraint__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSolverConstraint__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8782 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__m_allocator_set :: ( BtAlignedObjectArray_btSolverConstraint_Class bc , BtAlignedAllocator_btSolverConstraint_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSolverConstraint__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSolverConstraint__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8786 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__m_allocator_get :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> IO (BtAlignedAllocator_btSolverConstraint_16u_)
btAlignedObjectArray_btSolverConstraint__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSolverConstraint__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSolverConstraint_16u_ res >>= \res' ->
  return (res')
{-# LINE 8790 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__m_size_set :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSolverConstraint__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSolverConstraint__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8794 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__m_size_get :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSolverConstraint__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSolverConstraint__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8798 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__m_capacity_set :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSolverConstraint__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSolverConstraint__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8802 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__m_capacity_get :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSolverConstraint__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSolverConstraint__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8806 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__m_data_set :: ( BtAlignedObjectArray_btSolverConstraint_Class bc , BtSolverConstraintClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btSolverConstraint__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSolverConstraint__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8810 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__m_data_get :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> IO (BtSolverConstraint)
btAlignedObjectArray_btSolverConstraint__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSolverConstraint__m_data_get'_ a1' >>= \res ->
  mkBtSolverConstraint res >>= \res' ->
  return (res')
{-# LINE 8814 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__m_ownsMemory_set :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSolverConstraint__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSolverConstraint__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8818 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSolverConstraint__m_ownsMemory_get :: ( BtAlignedObjectArray_btSolverConstraint_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSolverConstraint__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSolverConstraint__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 8822 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btSparseSdf<3>::Cell*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr_ :: IO (BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_)
btAlignedObjectArray_btSparseSdf_3__Cell_ptr_ =
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btSparseSdf_3__Cell_ptr_ res >>= \res' ->
  return (res')
{-# LINE 8827 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__free :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 8828 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__size :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8833 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__capacity :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8838 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__init :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 8843 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__swap :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8850 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__pop_back :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 8855 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__deallocate :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 8860 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__allocate :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 8866 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 8874 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__destroy :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 8881 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__clear :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 8886 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__allocSize :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8892 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__reserve :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8898 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_allocator_set :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc , BtAlignedAllocator_btSparseSdf_3__Cell_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8902 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_allocator_get :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btSparseSdf_3__Cell_ptr_16u_)
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btSparseSdf_3__Cell_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 8906 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_capacity_set :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8910 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_capacity_get :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8914 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8918 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 8922 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_size_set :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 8926 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_size_get :: ( BtAlignedObjectArray_btSparseSdf_3__Cell_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8930 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btTransform>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform_ :: IO (BtAlignedObjectArray_btTransform_)
btAlignedObjectArray_btTransform_ =
  btAlignedObjectArray_btTransform_'_ >>= \res ->
  mkBtAlignedObjectArray_btTransform_ res >>= \res' ->
  return (res')
{-# LINE 8935 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btTransform__free :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTransform__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTransform__free'_ a1' >>= \res ->
  return ()
{-# LINE 8936 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__push_back :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Transform -> IO (Transform)
btAlignedObjectArray_btTransform__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btAlignedObjectArray_btTransform__push_back'_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 8942 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__push_back' :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO (Transform)
btAlignedObjectArray_btTransform__push_back' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btAlignedObjectArray_btTransform__push_back''_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 8948 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__at :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Int -> IO (Transform)
btAlignedObjectArray_btTransform__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  btAlignedObjectArray_btTransform__at'_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 8955 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__at0 :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Int -> IO (Transform)
btAlignedObjectArray_btTransform__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  btAlignedObjectArray_btTransform__at0'_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 8962 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__at1 :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Int -> IO (Transform)
btAlignedObjectArray_btTransform__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  btAlignedObjectArray_btTransform__at1'_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 8969 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__size :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTransform__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTransform__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8974 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__capacity :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTransform__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTransform__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 8979 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__init :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTransform__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTransform__init'_ a1' >>= \res ->
  return ()
{-# LINE 8984 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__allocate :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btTransform__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTransform__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 8990 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__pop_back :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTransform__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTransform__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 8995 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__deallocate :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTransform__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTransform__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 9000 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__swap :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btTransform__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btTransform__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9007 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__initializeFromBuffer :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btTransform__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btTransform__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 9015 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__expandNonInitializing :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO (Transform)
btAlignedObjectArray_btTransform__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btAlignedObjectArray_btTransform__expandNonInitializing'_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 9021 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__resize :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Int -> Transform -> IO (Transform)
btAlignedObjectArray_btTransform__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withTransform a3 $ \a3' -> 
  btAlignedObjectArray_btTransform__resize'_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 9028 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__resize' :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Int -> IO (Transform)
btAlignedObjectArray_btTransform__resize' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaTransform $ \a3' -> 
  btAlignedObjectArray_btTransform__resize''_ a1' a2' a3' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 9035 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__destroy :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btTransform__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btTransform__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9042 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__expand :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Transform -> IO (Transform, Transform)
btAlignedObjectArray_btTransform__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  allocaTransform $ \a3' -> 
  btAlignedObjectArray_btTransform__expand'_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 9049 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__expand' :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO (Transform, Transform)
btAlignedObjectArray_btTransform__expand' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  btAlignedObjectArray_btTransform__expand''_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 9056 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__clear :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTransform__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTransform__clear'_ a1' >>= \res ->
  return ()
{-# LINE 9061 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__allocSize :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btTransform__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTransform__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9067 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__reserve :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btTransform__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTransform__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9073 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__m_allocator_set :: ( BtAlignedObjectArray_btTransform_Class bc , BtAlignedAllocator_btTransform_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btTransform__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btTransform__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9077 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__m_allocator_get :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO (BtAlignedAllocator_btTransform_16u_)
btAlignedObjectArray_btTransform__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTransform__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btTransform_16u_ res >>= \res' ->
  return (res')
{-# LINE 9081 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__m_size_set :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btTransform__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTransform__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9085 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__m_size_get :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTransform__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTransform__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9089 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__m_capacity_set :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btTransform__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTransform__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9093 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__m_capacity_get :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTransform__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTransform__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9097 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__m_ownsMemory_set :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btTransform__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btTransform__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9101 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTransform__m_ownsMemory_get :: ( BtAlignedObjectArray_btTransform_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btTransform__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTransform__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 9105 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btTriangleInfo>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo_ :: IO (BtAlignedObjectArray_btTriangleInfo_)
btAlignedObjectArray_btTriangleInfo_ =
  btAlignedObjectArray_btTriangleInfo_'_ >>= \res ->
  mkBtAlignedObjectArray_btTriangleInfo_ res >>= \res' ->
  return (res')
{-# LINE 9110 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btTriangleInfo__free :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTriangleInfo__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTriangleInfo__free'_ a1' >>= \res ->
  return ()
{-# LINE 9111 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__push_back :: ( BtAlignedObjectArray_btTriangleInfo_Class bc , BtTriangleInfoClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btTriangleInfo__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btTriangleInfo__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9117 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__at :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> Int -> IO (BtTriangleInfo)
btAlignedObjectArray_btTriangleInfo__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTriangleInfo__at'_ a1' a2' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 9123 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__at0 :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> Int -> IO (BtTriangleInfo)
btAlignedObjectArray_btTriangleInfo__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTriangleInfo__at0'_ a1' a2' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 9129 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__at1 :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> Int -> IO (BtTriangleInfo)
btAlignedObjectArray_btTriangleInfo__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTriangleInfo__at1'_ a1' a2' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 9135 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__size :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTriangleInfo__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTriangleInfo__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9140 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__capacity :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTriangleInfo__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTriangleInfo__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9145 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__init :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTriangleInfo__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTriangleInfo__init'_ a1' >>= \res ->
  return ()
{-# LINE 9150 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__allocate :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btTriangleInfo__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTriangleInfo__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 9156 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__pop_back :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTriangleInfo__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTriangleInfo__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 9161 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__deallocate :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTriangleInfo__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTriangleInfo__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 9166 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__swap :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btTriangleInfo__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btTriangleInfo__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9173 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__initializeFromBuffer :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btTriangleInfo__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btTriangleInfo__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 9181 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__expandNonInitializing :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> IO (BtTriangleInfo)
btAlignedObjectArray_btTriangleInfo__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTriangleInfo__expandNonInitializing'_ a1' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 9186 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__resize :: ( BtAlignedObjectArray_btTriangleInfo_Class bc , BtTriangleInfoClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btTriangleInfo__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btTriangleInfo__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9193 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__destroy :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btTriangleInfo__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btTriangleInfo__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9200 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__copy :: ( BtAlignedObjectArray_btTriangleInfo_Class bc , BtTriangleInfoClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btTriangleInfo__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btTriangleInfo__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 9208 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__expand :: ( BtAlignedObjectArray_btTriangleInfo_Class bc , BtTriangleInfoClass p0 ) => bc -> p0 -> IO (BtTriangleInfo)
btAlignedObjectArray_btTriangleInfo__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btTriangleInfo__expand'_ a1' a2' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 9214 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__clear :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTriangleInfo__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTriangleInfo__clear'_ a1' >>= \res ->
  return ()
{-# LINE 9219 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__allocSize :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btTriangleInfo__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTriangleInfo__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9225 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__reserve :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btTriangleInfo__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTriangleInfo__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9231 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__m_allocator_set :: ( BtAlignedObjectArray_btTriangleInfo_Class bc , BtAlignedAllocator_btTriangleInfo_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btTriangleInfo__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btTriangleInfo__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9235 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__m_allocator_get :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> IO (BtAlignedAllocator_btTriangleInfo_16u_)
btAlignedObjectArray_btTriangleInfo__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTriangleInfo__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btTriangleInfo_16u_ res >>= \res' ->
  return (res')
{-# LINE 9239 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__m_size_set :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btTriangleInfo__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTriangleInfo__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9243 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__m_size_get :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTriangleInfo__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTriangleInfo__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9247 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__m_capacity_set :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btTriangleInfo__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTriangleInfo__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9251 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__m_capacity_get :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTriangleInfo__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTriangleInfo__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9255 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__m_data_set :: ( BtAlignedObjectArray_btTriangleInfo_Class bc , BtTriangleInfoClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btTriangleInfo__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btTriangleInfo__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9259 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__m_data_get :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> IO (BtTriangleInfo)
btAlignedObjectArray_btTriangleInfo__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTriangleInfo__m_data_get'_ a1' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 9263 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__m_ownsMemory_set :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btTriangleInfo__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btTriangleInfo__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9267 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTriangleInfo__m_ownsMemory_get :: ( BtAlignedObjectArray_btTriangleInfo_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btTriangleInfo__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTriangleInfo__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 9271 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btTypedConstraint*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr_ :: IO (BtAlignedObjectArray_btTypedConstraint_ptr_)
btAlignedObjectArray_btTypedConstraint_ptr_ =
  btAlignedObjectArray_btTypedConstraint_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_btTypedConstraint_ptr_ res >>= \res' ->
  return (res')
{-# LINE 9276 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btTypedConstraint_ptr__free :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 9277 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__push_back :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc , BtTypedConstraintClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9283 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__at :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> Int -> IO (BtTypedConstraint)
btAlignedObjectArray_btTypedConstraint_ptr__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_ptr__at'_ a1' a2' >>= \res ->
  mkBtTypedConstraint res >>= \res' ->
  return (res')
{-# LINE 9289 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__at0 :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> Int -> IO (BtTypedConstraint)
btAlignedObjectArray_btTypedConstraint_ptr__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_ptr__at0'_ a1' a2' >>= \res ->
  mkBtTypedConstraint res >>= \res' ->
  return (res')
{-# LINE 9295 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__at1 :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> Int -> IO (BtTypedConstraint)
btAlignedObjectArray_btTypedConstraint_ptr__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_ptr__at1'_ a1' a2' >>= \res ->
  mkBtTypedConstraint res >>= \res' ->
  return (res')
{-# LINE 9301 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__size :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTypedConstraint_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9306 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__capacity :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTypedConstraint_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9311 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__init :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 9316 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__allocate :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btTypedConstraint_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 9322 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__pop_back :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 9327 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__deallocate :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 9332 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__swap :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btTypedConstraint_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9339 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btTypedConstraint_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 9347 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__expandNonInitializing :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> IO (BtTypedConstraint)
btAlignedObjectArray_btTypedConstraint_ptr__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__expandNonInitializing'_ a1' >>= \res ->
  mkBtTypedConstraint res >>= \res' ->
  return (res')
{-# LINE 9352 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__resize :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc , BtTypedConstraintClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9359 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__destroy :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btTypedConstraint_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9366 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__expand :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc , BtTypedConstraintClass p0 ) => bc -> p0 -> IO (BtTypedConstraint)
btAlignedObjectArray_btTypedConstraint_ptr__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__expand'_ a1' a2' >>= \res ->
  mkBtTypedConstraint res >>= \res' ->
  return (res')
{-# LINE 9372 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__clear :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 9377 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__allocSize :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btTypedConstraint_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9383 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__reserve :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9389 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__m_allocator_set :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc , BtAlignedAllocator_btTypedConstraint_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9393 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__m_allocator_get :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_btTypedConstraint_ptr_16u_)
btAlignedObjectArray_btTypedConstraint_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btTypedConstraint_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 9397 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__m_size_set :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9401 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__m_size_get :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTypedConstraint_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9405 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__m_capacity_set :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9409 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__m_capacity_get :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTypedConstraint_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9413 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btTypedConstraint_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btTypedConstraint_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9417 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_btTypedConstraint_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btTypedConstraint_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 9421 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btTypedConstraint::btConstraintInfo1>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1_ :: IO (BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1_ =
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1_'_ >>= \res ->
  mkBtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_ res >>= \res' ->
  return (res')
{-# LINE 9426 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__free :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__free'_ a1' >>= \res ->
  return ()
{-# LINE 9427 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__push_back :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9433 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> Int -> IO (BtTypedConstraint_btConstraintInfo1)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at'_ a1' a2' >>= \res ->
  mkBtTypedConstraint_btConstraintInfo1 res >>= \res' ->
  return (res')
{-# LINE 9439 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at0 :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> Int -> IO (BtTypedConstraint_btConstraintInfo1)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at0'_ a1' a2' >>= \res ->
  mkBtTypedConstraint_btConstraintInfo1 res >>= \res' ->
  return (res')
{-# LINE 9445 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at1 :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> Int -> IO (BtTypedConstraint_btConstraintInfo1)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at1'_ a1' a2' >>= \res ->
  mkBtTypedConstraint_btConstraintInfo1 res >>= \res' ->
  return (res')
{-# LINE 9451 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__size :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9456 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__capacity :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9461 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__init :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__init'_ a1' >>= \res ->
  return ()
{-# LINE 9466 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__allocate :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 9472 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__pop_back :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 9477 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__deallocate :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 9482 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__swap :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9489 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__initializeFromBuffer :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 9497 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__expandNonInitializing :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> IO (BtTypedConstraint_btConstraintInfo1)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__expandNonInitializing'_ a1' >>= \res ->
  mkBtTypedConstraint_btConstraintInfo1 res >>= \res' ->
  return (res')
{-# LINE 9502 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__resize :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc , BtTypedConstraint_btConstraintInfo1Class p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9509 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__destroy :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9516 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__copy :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc , BtTypedConstraint_btConstraintInfo1Class p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 9524 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__expand :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc , BtTypedConstraint_btConstraintInfo1Class p0 ) => bc -> p0 -> IO (BtTypedConstraint_btConstraintInfo1)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__expand'_ a1' a2' >>= \res ->
  mkBtTypedConstraint_btConstraintInfo1 res >>= \res' ->
  return (res')
{-# LINE 9530 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__clear :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__clear'_ a1' >>= \res ->
  return ()
{-# LINE 9535 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__allocSize :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9541 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__reserve :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9547 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_allocator_set :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc , BtAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9551 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_allocator_get :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> IO (BtAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_ res >>= \res' ->
  return (res')
{-# LINE 9555 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_size_set :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9559 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_size_get :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9563 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_capacity_set :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9567 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_capacity_get :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9571 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_data_set :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc , BtTypedConstraint_btConstraintInfo1Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9575 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_data_get :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> IO (BtTypedConstraint_btConstraintInfo1)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_data_get'_ a1' >>= \res ->
  mkBtTypedConstraint_btConstraintInfo1 res >>= \res' ->
  return (res')
{-# LINE 9579 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_ownsMemory_set :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9583 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_ownsMemory_get :: ( BtAlignedObjectArray_btTypedConstraint_btConstraintInfo1_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 9587 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btVector3>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3_ :: IO (BtAlignedObjectArray_btVector3_)
btAlignedObjectArray_btVector3_ =
  btAlignedObjectArray_btVector3_'_ >>= \res ->
  mkBtAlignedObjectArray_btVector3_ res >>= \res' ->
  return (res')
{-# LINE 9592 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btVector3__free :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO ()
btAlignedObjectArray_btVector3__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btVector3__free'_ a1' >>= \res ->
  return ()
{-# LINE 9593 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__push_back :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Vec3 -> IO (Vec3)
btAlignedObjectArray_btVector3__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btAlignedObjectArray_btVector3__push_back'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 9599 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__push_back' :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO (Vec3)
btAlignedObjectArray_btVector3__push_back' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btAlignedObjectArray_btVector3__push_back''_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 9605 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__at :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Int -> IO (Vec3)
btAlignedObjectArray_btVector3__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaVec3 $ \a3' -> 
  btAlignedObjectArray_btVector3__at'_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 9612 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__at0 :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Int -> IO (Vec3)
btAlignedObjectArray_btVector3__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaVec3 $ \a3' -> 
  btAlignedObjectArray_btVector3__at0'_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 9619 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__at1 :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Int -> IO (Vec3)
btAlignedObjectArray_btVector3__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaVec3 $ \a3' -> 
  btAlignedObjectArray_btVector3__at1'_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 9626 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__size :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btVector3__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btVector3__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9631 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__capacity :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btVector3__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btVector3__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9636 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__init :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO ()
btAlignedObjectArray_btVector3__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btVector3__init'_ a1' >>= \res ->
  return ()
{-# LINE 9641 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__swap :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btVector3__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btVector3__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9648 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__pop_back :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO ()
btAlignedObjectArray_btVector3__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btVector3__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 9653 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__deallocate :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO ()
btAlignedObjectArray_btVector3__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btVector3__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 9658 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__allocate :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btVector3__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btVector3__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 9664 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__initializeFromBuffer :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btVector3__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btVector3__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 9672 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__expandNonInitializing :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO (Vec3)
btAlignedObjectArray_btVector3__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btAlignedObjectArray_btVector3__expandNonInitializing'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 9678 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__destroy :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btVector3__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btVector3__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9685 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__resize :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Int -> Vec3 -> IO (Vec3)
btAlignedObjectArray_btVector3__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withVec3 a3 $ \a3' -> 
  btAlignedObjectArray_btVector3__resize'_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 9692 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__resize' :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Int -> IO (Vec3)
btAlignedObjectArray_btVector3__resize' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  allocaVec3 $ \a3' -> 
  btAlignedObjectArray_btVector3__resize''_ a1' a2' a3' >>= \res ->
  peekVec3  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 9699 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__clear :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO ()
btAlignedObjectArray_btVector3__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btVector3__clear'_ a1' >>= \res ->
  return ()
{-# LINE 9704 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__allocSize :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btVector3__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btVector3__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9710 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__expand :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Vec3 -> IO (Vec3, Vec3)
btAlignedObjectArray_btVector3__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btAlignedObjectArray_btVector3__expand'_ a1' a2' a3' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 9717 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__expand' :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO (Vec3, Vec3)
btAlignedObjectArray_btVector3__expand' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  btAlignedObjectArray_btVector3__expand''_ a1' a2' a3' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 9724 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__reserve :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btVector3__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btVector3__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9730 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__m_allocator_set :: ( BtAlignedObjectArray_btVector3_Class bc , BtAlignedAllocator_btVector3_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btVector3__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btVector3__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9734 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__m_allocator_get :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO (BtAlignedAllocator_btVector3_16u_)
btAlignedObjectArray_btVector3__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btVector3__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btVector3_16u_ res >>= \res' ->
  return (res')
{-# LINE 9738 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__m_capacity_set :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btVector3__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btVector3__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9742 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__m_capacity_get :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btVector3__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btVector3__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9746 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__m_ownsMemory_set :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btVector3__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btVector3__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9750 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__m_ownsMemory_get :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btVector3__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btVector3__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 9754 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__m_size_set :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btVector3__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btVector3__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9758 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btVector3__m_size_get :: ( BtAlignedObjectArray_btVector3_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btVector3__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btVector3__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9762 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<btWheelInfo>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo_ :: IO (BtAlignedObjectArray_btWheelInfo_)
btAlignedObjectArray_btWheelInfo_ =
  btAlignedObjectArray_btWheelInfo_'_ >>= \res ->
  mkBtAlignedObjectArray_btWheelInfo_ res >>= \res' ->
  return (res')
{-# LINE 9767 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_btWheelInfo__free :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btWheelInfo__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btWheelInfo__free'_ a1' >>= \res ->
  return ()
{-# LINE 9768 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#246>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__push_back :: ( BtAlignedObjectArray_btWheelInfo_Class bc , BtWheelInfoClass p0 ) => bc -> p0 -> IO ()
btAlignedObjectArray_btWheelInfo__push_back a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btWheelInfo__push_back'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9774 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__at :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> Int -> IO (BtWheelInfo)
btAlignedObjectArray_btWheelInfo__at a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btWheelInfo__at'_ a1' a2' >>= \res ->
  mkBtWheelInfo res >>= \res' ->
  return (res')
{-# LINE 9780 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#141>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__at0 :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> Int -> IO (BtWheelInfo)
btAlignedObjectArray_btWheelInfo__at0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btWheelInfo__at0'_ a1' a2' >>= \res ->
  mkBtWheelInfo res >>= \res' ->
  return (res')
{-# LINE 9786 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__at1 :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> Int -> IO (BtWheelInfo)
btAlignedObjectArray_btWheelInfo__at1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btWheelInfo__at1'_ a1' a2' >>= \res ->
  mkBtWheelInfo res >>= \res' ->
  return (res')
{-# LINE 9792 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__size :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btWheelInfo__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btWheelInfo__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9797 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__capacity :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btWheelInfo__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btWheelInfo__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9802 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__init :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btWheelInfo__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btWheelInfo__init'_ a1' >>= \res ->
  return ()
{-# LINE 9807 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__allocate :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_btWheelInfo__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btWheelInfo__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 9813 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__pop_back :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btWheelInfo__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btWheelInfo__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 9818 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__deallocate :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btWheelInfo__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btWheelInfo__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 9823 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__swap :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btWheelInfo__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btWheelInfo__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9830 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__initializeFromBuffer :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_btWheelInfo__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_btWheelInfo__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 9838 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#217>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__expandNonInitializing :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> IO (BtWheelInfo)
btAlignedObjectArray_btWheelInfo__expandNonInitializing a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btWheelInfo__expandNonInitializing'_ a1' >>= \res ->
  mkBtWheelInfo res >>= \res' ->
  return (res')
{-# LINE 9843 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__resize :: ( BtAlignedObjectArray_btWheelInfo_Class bc , BtWheelInfoClass p1 ) => bc -> Int -> p1 -> IO ()
btAlignedObjectArray_btWheelInfo__resize a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withBt a3 $ \a3' -> 
  btAlignedObjectArray_btWheelInfo__resize'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9850 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__destroy :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_btWheelInfo__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_btWheelInfo__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9857 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__copy :: ( BtAlignedObjectArray_btWheelInfo_Class bc , BtWheelInfoClass p2 ) => bc -> Int -> Int -> p2 -> IO ()
btAlignedObjectArray_btWheelInfo__copy a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  withBt a4 $ \a4' -> 
  btAlignedObjectArray_btWheelInfo__copy'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 9865 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__expand :: ( BtAlignedObjectArray_btWheelInfo_Class bc , BtWheelInfoClass p0 ) => bc -> p0 -> IO (BtWheelInfo)
btAlignedObjectArray_btWheelInfo__expand a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btWheelInfo__expand'_ a1' a2' >>= \res ->
  mkBtWheelInfo res >>= \res' ->
  return (res')
{-# LINE 9871 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__clear :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> IO ()
btAlignedObjectArray_btWheelInfo__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btWheelInfo__clear'_ a1' >>= \res ->
  return ()
{-# LINE 9876 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__allocSize :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_btWheelInfo__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btWheelInfo__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9882 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__reserve :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btWheelInfo__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btWheelInfo__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9888 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__m_allocator_set :: ( BtAlignedObjectArray_btWheelInfo_Class bc , BtAlignedAllocator_btWheelInfo_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_btWheelInfo__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btWheelInfo__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9892 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__m_allocator_get :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> IO (BtAlignedAllocator_btWheelInfo_16u_)
btAlignedObjectArray_btWheelInfo__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btWheelInfo__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_btWheelInfo_16u_ res >>= \res' ->
  return (res')
{-# LINE 9896 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__m_size_set :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btWheelInfo__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btWheelInfo__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9900 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__m_size_get :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btWheelInfo__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btWheelInfo__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9904 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__m_capacity_set :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_btWheelInfo__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_btWheelInfo__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9908 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__m_capacity_get :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_btWheelInfo__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btWheelInfo__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9912 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__m_data_set :: ( BtAlignedObjectArray_btWheelInfo_Class bc , BtWheelInfoClass a ) => bc -> a -> IO ()
btAlignedObjectArray_btWheelInfo__m_data_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_btWheelInfo__m_data_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9916 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#52>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__m_data_get :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> IO (BtWheelInfo)
btAlignedObjectArray_btWheelInfo__m_data_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btWheelInfo__m_data_get'_ a1' >>= \res ->
  mkBtWheelInfo res >>= \res' ->
  return (res')
{-# LINE 9920 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__m_ownsMemory_set :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_btWheelInfo__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_btWheelInfo__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 9924 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_btWheelInfo__m_ownsMemory_get :: ( BtAlignedObjectArray_btWheelInfo_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_btWheelInfo__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_btWheelInfo__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 9928 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<char const*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr_ :: IO (BtAlignedObjectArray_charconst_ptr_)
btAlignedObjectArray_charconst_ptr_ =
  btAlignedObjectArray_charconst_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_charconst_ptr_ res >>= \res' ->
  return (res')
{-# LINE 9933 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_charconst_ptr__free :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_charconst_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_charconst_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 9934 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__size :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_charconst_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_charconst_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9939 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__capacity :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_charconst_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_charconst_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9944 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__init :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_charconst_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_charconst_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 9949 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__allocate :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_charconst_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_charconst_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 9955 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__pop_back :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_charconst_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_charconst_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 9960 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__deallocate :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_charconst_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_charconst_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 9965 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__swap :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_charconst_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_charconst_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9972 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_charconst_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_charconst_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 9980 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__destroy :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_charconst_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_charconst_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 9987 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__clear :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_charconst_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_charconst_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 9992 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__allocSize :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_charconst_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_charconst_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 9998 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__reserve :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_charconst_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_charconst_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10004 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__m_allocator_set :: ( BtAlignedObjectArray_charconst_ptr_Class bc , BtAlignedAllocator_charconst_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_charconst_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_charconst_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10008 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__m_allocator_get :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_charconst_ptr_16u_)
btAlignedObjectArray_charconst_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_charconst_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_charconst_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 10012 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__m_size_set :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_charconst_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_charconst_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10016 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__m_size_get :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_charconst_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_charconst_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10020 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__m_capacity_set :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_charconst_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_charconst_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10024 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__m_capacity_get :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_charconst_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_charconst_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10028 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_charconst_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_charconst_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10032 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_charconst_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_charconst_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_charconst_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_charconst_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 10036 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<char*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr_ :: IO (BtAlignedObjectArray_char_ptr_)
btAlignedObjectArray_char_ptr_ =
  btAlignedObjectArray_char_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_char_ptr_ res >>= \res' ->
  return (res')
{-# LINE 10041 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_char_ptr__free :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_char_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_char_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 10042 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__size :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_char_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_char_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10047 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__capacity :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_char_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_char_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10052 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__init :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_char_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_char_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 10057 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__allocate :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_char_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_char_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 10063 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__pop_back :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_char_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_char_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 10068 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__deallocate :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_char_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_char_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 10073 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__swap :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_char_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_char_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10080 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_char_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_char_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 10088 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__destroy :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_char_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_char_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10095 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__clear :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_char_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_char_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 10100 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__allocSize :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_char_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_char_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10106 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__reserve :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_char_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_char_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10112 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__m_allocator_set :: ( BtAlignedObjectArray_char_ptr_Class bc , BtAlignedAllocator_char_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_char_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_char_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10116 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__m_allocator_get :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_char_ptr_16u_)
btAlignedObjectArray_char_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_char_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_char_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 10120 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__m_size_set :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_char_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_char_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10124 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__m_size_get :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_char_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_char_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10128 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__m_capacity_set :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_char_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_char_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10132 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__m_capacity_get :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_char_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_char_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10136 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_char_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_char_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10140 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_char_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_char_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_char_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_char_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 10144 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<float>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float_ :: IO (BtAlignedObjectArray_float_)
btAlignedObjectArray_float_ =
  btAlignedObjectArray_float_'_ >>= \res ->
  mkBtAlignedObjectArray_float_ res >>= \res' ->
  return (res')
{-# LINE 10149 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_float__free :: ( BtAlignedObjectArray_float_Class bc ) => bc -> IO ()
btAlignedObjectArray_float__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_float__free'_ a1' >>= \res ->
  return ()
{-# LINE 10150 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__size :: ( BtAlignedObjectArray_float_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_float__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_float__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10155 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__capacity :: ( BtAlignedObjectArray_float_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_float__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_float__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10160 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__init :: ( BtAlignedObjectArray_float_Class bc ) => bc -> IO ()
btAlignedObjectArray_float__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_float__init'_ a1' >>= \res ->
  return ()
{-# LINE 10165 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__swap :: ( BtAlignedObjectArray_float_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_float__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_float__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10172 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__pop_back :: ( BtAlignedObjectArray_float_Class bc ) => bc -> IO ()
btAlignedObjectArray_float__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_float__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 10177 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__deallocate :: ( BtAlignedObjectArray_float_Class bc ) => bc -> IO ()
btAlignedObjectArray_float__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_float__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 10182 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__allocate :: ( BtAlignedObjectArray_float_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_float__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_float__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 10188 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__initializeFromBuffer :: ( BtAlignedObjectArray_float_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_float__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_float__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 10196 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__destroy :: ( BtAlignedObjectArray_float_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_float__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_float__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10203 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__clear :: ( BtAlignedObjectArray_float_Class bc ) => bc -> IO ()
btAlignedObjectArray_float__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_float__clear'_ a1' >>= \res ->
  return ()
{-# LINE 10208 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__allocSize :: ( BtAlignedObjectArray_float_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_float__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_float__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10214 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__reserve :: ( BtAlignedObjectArray_float_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_float__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_float__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10220 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__m_allocator_set :: ( BtAlignedObjectArray_float_Class bc , BtAlignedAllocator_float_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_float__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_float__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10224 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__m_allocator_get :: ( BtAlignedObjectArray_float_Class bc ) => bc -> IO (BtAlignedAllocator_float_16u_)
btAlignedObjectArray_float__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_float__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_float_16u_ res >>= \res' ->
  return (res')
{-# LINE 10228 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__m_capacity_set :: ( BtAlignedObjectArray_float_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_float__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_float__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10232 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__m_capacity_get :: ( BtAlignedObjectArray_float_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_float__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_float__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10236 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__m_ownsMemory_set :: ( BtAlignedObjectArray_float_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_float__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_float__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10240 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__m_ownsMemory_get :: ( BtAlignedObjectArray_float_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_float__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_float__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 10244 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__m_size_set :: ( BtAlignedObjectArray_float_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_float__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_float__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10248 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_float__m_size_get :: ( BtAlignedObjectArray_float_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_float__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_float__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10252 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<int>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int_ :: IO (BtAlignedObjectArray_int_)
btAlignedObjectArray_int_ =
  btAlignedObjectArray_int_'_ >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 10257 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_int__free :: ( BtAlignedObjectArray_int_Class bc ) => bc -> IO ()
btAlignedObjectArray_int__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_int__free'_ a1' >>= \res ->
  return ()
{-# LINE 10258 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__size :: ( BtAlignedObjectArray_int_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_int__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_int__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10263 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__capacity :: ( BtAlignedObjectArray_int_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_int__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_int__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10268 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__init :: ( BtAlignedObjectArray_int_Class bc ) => bc -> IO ()
btAlignedObjectArray_int__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_int__init'_ a1' >>= \res ->
  return ()
{-# LINE 10273 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__swap :: ( BtAlignedObjectArray_int_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_int__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_int__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10280 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__pop_back :: ( BtAlignedObjectArray_int_Class bc ) => bc -> IO ()
btAlignedObjectArray_int__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_int__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 10285 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__deallocate :: ( BtAlignedObjectArray_int_Class bc ) => bc -> IO ()
btAlignedObjectArray_int__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_int__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 10290 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__allocate :: ( BtAlignedObjectArray_int_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_int__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_int__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 10296 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__initializeFromBuffer :: ( BtAlignedObjectArray_int_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_int__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_int__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 10304 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__destroy :: ( BtAlignedObjectArray_int_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_int__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_int__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10311 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__clear :: ( BtAlignedObjectArray_int_Class bc ) => bc -> IO ()
btAlignedObjectArray_int__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_int__clear'_ a1' >>= \res ->
  return ()
{-# LINE 10316 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__allocSize :: ( BtAlignedObjectArray_int_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_int__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_int__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10322 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__reserve :: ( BtAlignedObjectArray_int_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_int__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_int__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10328 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__m_allocator_set :: ( BtAlignedObjectArray_int_Class bc , BtAlignedAllocator_int_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_int__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_int__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10332 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__m_allocator_get :: ( BtAlignedObjectArray_int_Class bc ) => bc -> IO (BtAlignedAllocator_int_16u_)
btAlignedObjectArray_int__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_int__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_int_16u_ res >>= \res' ->
  return (res')
{-# LINE 10336 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__m_capacity_set :: ( BtAlignedObjectArray_int_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_int__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_int__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10340 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__m_capacity_get :: ( BtAlignedObjectArray_int_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_int__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_int__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10344 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__m_ownsMemory_set :: ( BtAlignedObjectArray_int_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_int__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_int__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10348 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__m_ownsMemory_get :: ( BtAlignedObjectArray_int_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_int__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_int__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 10352 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__m_size_set :: ( BtAlignedObjectArray_int_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_int__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_int__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10356 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_int__m_size_get :: ( BtAlignedObjectArray_int_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_int__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_int__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10360 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<short*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr_ :: IO (BtAlignedObjectArray_short_ptr_)
btAlignedObjectArray_short_ptr_ =
  btAlignedObjectArray_short_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_short_ptr_ res >>= \res' ->
  return (res')
{-# LINE 10365 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_short_ptr__free :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_short_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 10366 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__size :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_short_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10371 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__capacity :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_short_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10376 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__init :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_short_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 10381 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__allocate :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_short_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_short_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 10387 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__pop_back :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_short_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 10392 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__deallocate :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_short_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 10397 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__swap :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_short_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_short_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10404 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_short_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_short_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 10412 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__destroy :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_short_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_short_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10419 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__clear :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_short_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 10424 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__allocSize :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_short_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_short_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10430 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__reserve :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_short_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_short_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10436 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__m_allocator_set :: ( BtAlignedObjectArray_short_ptr_Class bc , BtAlignedAllocator_short_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_short_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_short_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10440 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__m_allocator_get :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_short_ptr_16u_)
btAlignedObjectArray_short_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_short_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 10444 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__m_size_set :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_short_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_short_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10448 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__m_size_get :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_short_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10452 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__m_capacity_set :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_short_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_short_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10456 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__m_capacity_get :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_short_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10460 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_short_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_short_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10464 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_short_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_short_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 10468 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<short>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short_ :: IO (BtAlignedObjectArray_short_)
btAlignedObjectArray_short_ =
  btAlignedObjectArray_short_'_ >>= \res ->
  mkBtAlignedObjectArray_short_ res >>= \res' ->
  return (res')
{-# LINE 10473 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_short__free :: ( BtAlignedObjectArray_short_Class bc ) => bc -> IO ()
btAlignedObjectArray_short__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short__free'_ a1' >>= \res ->
  return ()
{-# LINE 10474 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__size :: ( BtAlignedObjectArray_short_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_short__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10479 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__capacity :: ( BtAlignedObjectArray_short_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_short__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10484 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__init :: ( BtAlignedObjectArray_short_Class bc ) => bc -> IO ()
btAlignedObjectArray_short__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short__init'_ a1' >>= \res ->
  return ()
{-# LINE 10489 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__allocate :: ( BtAlignedObjectArray_short_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_short__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_short__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 10495 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__pop_back :: ( BtAlignedObjectArray_short_Class bc ) => bc -> IO ()
btAlignedObjectArray_short__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 10500 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__deallocate :: ( BtAlignedObjectArray_short_Class bc ) => bc -> IO ()
btAlignedObjectArray_short__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 10505 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__swap :: ( BtAlignedObjectArray_short_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_short__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_short__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10512 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__initializeFromBuffer :: ( BtAlignedObjectArray_short_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_short__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_short__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 10520 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__destroy :: ( BtAlignedObjectArray_short_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_short__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_short__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10527 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__clear :: ( BtAlignedObjectArray_short_Class bc ) => bc -> IO ()
btAlignedObjectArray_short__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short__clear'_ a1' >>= \res ->
  return ()
{-# LINE 10532 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__allocSize :: ( BtAlignedObjectArray_short_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_short__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_short__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10538 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__reserve :: ( BtAlignedObjectArray_short_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_short__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_short__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10544 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__m_allocator_set :: ( BtAlignedObjectArray_short_Class bc , BtAlignedAllocator_short_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_short__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_short__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10548 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__m_allocator_get :: ( BtAlignedObjectArray_short_Class bc ) => bc -> IO (BtAlignedAllocator_short_16u_)
btAlignedObjectArray_short__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_short_16u_ res >>= \res' ->
  return (res')
{-# LINE 10552 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__m_size_set :: ( BtAlignedObjectArray_short_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_short__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_short__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10556 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__m_size_get :: ( BtAlignedObjectArray_short_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_short__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10560 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__m_capacity_set :: ( BtAlignedObjectArray_short_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_short__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_short__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10564 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__m_capacity_get :: ( BtAlignedObjectArray_short_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_short__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10568 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__m_ownsMemory_set :: ( BtAlignedObjectArray_short_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_short__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_short__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10572 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_short__m_ownsMemory_get :: ( BtAlignedObjectArray_short_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_short__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_short__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 10576 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<unsigned int>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint_ :: IO (BtAlignedObjectArray_unsignedint_)
btAlignedObjectArray_unsignedint_ =
  btAlignedObjectArray_unsignedint_'_ >>= \res ->
  mkBtAlignedObjectArray_unsignedint_ res >>= \res' ->
  return (res')
{-# LINE 10581 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_unsignedint__free :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> IO ()
btAlignedObjectArray_unsignedint__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedint__free'_ a1' >>= \res ->
  return ()
{-# LINE 10582 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__size :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_unsignedint__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedint__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10587 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__capacity :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_unsignedint__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedint__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10592 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__init :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> IO ()
btAlignedObjectArray_unsignedint__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedint__init'_ a1' >>= \res ->
  return ()
{-# LINE 10597 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__allocate :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_unsignedint__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_unsignedint__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 10603 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__pop_back :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> IO ()
btAlignedObjectArray_unsignedint__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedint__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 10608 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__deallocate :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> IO ()
btAlignedObjectArray_unsignedint__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedint__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 10613 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__swap :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_unsignedint__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_unsignedint__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10620 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__initializeFromBuffer :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_unsignedint__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_unsignedint__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 10628 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__destroy :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_unsignedint__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_unsignedint__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10635 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__clear :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> IO ()
btAlignedObjectArray_unsignedint__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedint__clear'_ a1' >>= \res ->
  return ()
{-# LINE 10640 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__allocSize :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_unsignedint__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_unsignedint__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10646 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__reserve :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_unsignedint__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_unsignedint__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10652 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__m_allocator_set :: ( BtAlignedObjectArray_unsignedint_Class bc , BtAlignedAllocator_unsignedint_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_unsignedint__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_unsignedint__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10656 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__m_allocator_get :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> IO (BtAlignedAllocator_unsignedint_16u_)
btAlignedObjectArray_unsignedint__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedint__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_unsignedint_16u_ res >>= \res' ->
  return (res')
{-# LINE 10660 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__m_size_set :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_unsignedint__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_unsignedint__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10664 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__m_size_get :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_unsignedint__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedint__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10668 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__m_capacity_set :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_unsignedint__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_unsignedint__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10672 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__m_capacity_get :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_unsignedint__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedint__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10676 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__m_ownsMemory_set :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_unsignedint__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_unsignedint__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10680 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedint__m_ownsMemory_get :: ( BtAlignedObjectArray_unsignedint_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_unsignedint__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedint__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 10684 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<unsigned short>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort_ :: IO (BtAlignedObjectArray_unsignedshort_)
btAlignedObjectArray_unsignedshort_ =
  btAlignedObjectArray_unsignedshort_'_ >>= \res ->
  mkBtAlignedObjectArray_unsignedshort_ res >>= \res' ->
  return (res')
{-# LINE 10689 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_unsignedshort__free :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> IO ()
btAlignedObjectArray_unsignedshort__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedshort__free'_ a1' >>= \res ->
  return ()
{-# LINE 10690 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__size :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_unsignedshort__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedshort__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10695 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__capacity :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_unsignedshort__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedshort__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10700 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__init :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> IO ()
btAlignedObjectArray_unsignedshort__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedshort__init'_ a1' >>= \res ->
  return ()
{-# LINE 10705 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__allocate :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_unsignedshort__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_unsignedshort__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 10711 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__pop_back :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> IO ()
btAlignedObjectArray_unsignedshort__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedshort__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 10716 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__deallocate :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> IO ()
btAlignedObjectArray_unsignedshort__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedshort__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 10721 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__swap :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_unsignedshort__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_unsignedshort__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10728 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__initializeFromBuffer :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_unsignedshort__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_unsignedshort__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 10736 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__destroy :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_unsignedshort__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_unsignedshort__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10743 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__clear :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> IO ()
btAlignedObjectArray_unsignedshort__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedshort__clear'_ a1' >>= \res ->
  return ()
{-# LINE 10748 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__allocSize :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_unsignedshort__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_unsignedshort__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10754 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__reserve :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_unsignedshort__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_unsignedshort__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10760 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__m_allocator_set :: ( BtAlignedObjectArray_unsignedshort_Class bc , BtAlignedAllocator_unsignedshort_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_unsignedshort__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_unsignedshort__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10764 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__m_allocator_get :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> IO (BtAlignedAllocator_unsignedshort_16u_)
btAlignedObjectArray_unsignedshort__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedshort__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_unsignedshort_16u_ res >>= \res' ->
  return (res')
{-# LINE 10768 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__m_size_set :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_unsignedshort__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_unsignedshort__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10772 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__m_size_get :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_unsignedshort__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedshort__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10776 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__m_capacity_set :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_unsignedshort__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_unsignedshort__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10780 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__m_capacity_get :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_unsignedshort__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedshort__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10784 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__m_ownsMemory_set :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_unsignedshort__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_unsignedshort__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10788 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_unsignedshort__m_ownsMemory_get :: ( BtAlignedObjectArray_unsignedshort_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_unsignedshort__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_unsignedshort__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 10792 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btAlignedObjectArray<void*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr_ :: IO (BtAlignedObjectArray_void_ptr_)
btAlignedObjectArray_void_ptr_ =
  btAlignedObjectArray_void_ptr_'_ >>= \res ->
  mkBtAlignedObjectArray_void_ptr_ res >>= \res' ->
  return (res')
{-# LINE 10797 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btAlignedObjectArray_void_ptr__free :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_void_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_void_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 10798 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#136>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__size :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_void_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_void_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10803 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#265>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__capacity :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_void_ptr__capacity a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_void_ptr__capacity'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10808 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#72>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__init :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_void_ptr__init a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_void_ptr__init'_ a1' >>= \res ->
  return ()
{-# LINE 10813 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__allocate :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> Int -> IO (VoidPtr)
btAlignedObjectArray_void_ptr__allocate a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_void_ptr__allocate'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 10819 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#180>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__pop_back :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_void_ptr__pop_back a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_void_ptr__pop_back'_ a1' >>= \res ->
  return ()
{-# LINE 10824 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__deallocate :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_void_ptr__deallocate a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_void_ptr__deallocate'_ a1' >>= \res ->
  return ()
{-# LINE 10829 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#376>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__swap :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_void_ptr__swap a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_void_ptr__swap'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10836 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#462>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__initializeFromBuffer :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> VoidPtr -> Int -> Int -> IO ()
btAlignedObjectArray_void_ptr__initializeFromBuffer a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  btAlignedObjectArray_void_ptr__initializeFromBuffer'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 10844 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__destroy :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> Int -> Int -> IO ()
btAlignedObjectArray_void_ptr__destroy a1 a2 a3 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  btAlignedObjectArray_void_ptr__destroy'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 10851 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#171>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__clear :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> IO ()
btAlignedObjectArray_void_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_void_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 10856 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__allocSize :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> Int -> IO (Int)
btAlignedObjectArray_void_ptr__allocSize a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_void_ptr__allocSize'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10862 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#270>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__reserve :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_void_ptr__reserve a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_void_ptr__reserve'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10868 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__m_allocator_set :: ( BtAlignedObjectArray_void_ptr_Class bc , BtAlignedAllocator_void_ptr_16u_Class a ) => bc -> a -> IO ()
btAlignedObjectArray_void_ptr__m_allocator_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btAlignedObjectArray_void_ptr__m_allocator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10872 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#48>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__m_allocator_get :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> IO (BtAlignedAllocator_void_ptr_16u_)
btAlignedObjectArray_void_ptr__m_allocator_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_void_ptr__m_allocator_get'_ a1' >>= \res ->
  mkBtAlignedAllocator_void_ptr_16u_ res >>= \res' ->
  return (res')
{-# LINE 10876 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__m_size_set :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_void_ptr__m_size_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_void_ptr__m_size_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10880 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__m_size_get :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_void_ptr__m_size_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_void_ptr__m_size_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10884 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__m_capacity_set :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> Int -> IO ()
btAlignedObjectArray_void_ptr__m_capacity_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btAlignedObjectArray_void_ptr__m_capacity_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10888 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__m_capacity_get :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> IO (Int)
btAlignedObjectArray_void_ptr__m_capacity_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_void_ptr__m_capacity_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10892 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__m_ownsMemory_set :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> Bool -> IO ()
btAlignedObjectArray_void_ptr__m_ownsMemory_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btAlignedObjectArray_void_ptr__m_ownsMemory_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10896 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btAlignedObjectArray.cpp?r=2223>
-}
btAlignedObjectArray_void_ptr__m_ownsMemory_get :: ( BtAlignedObjectArray_void_ptr_Class bc ) => bc -> IO (Bool)
btAlignedObjectArray_void_ptr__m_ownsMemory_get a1 =
  withBt a1 $ \a1' -> 
  btAlignedObjectArray_void_ptr__m_ownsMemory_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 10900 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btBlock
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#28>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btBlock :: IO (BtBlock)
btBlock =
  btBlock'_ >>= \res ->
  mkBtBlock res >>= \res' ->
  return (res')
{-# LINE 10905 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btBlock_free :: ( BtBlockClass bc ) => bc -> IO ()
btBlock_free a1 =
  withBt a1 $ \a1' -> 
  btBlock_free'_ a1' >>= \res ->
  return ()
{-# LINE 10906 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#29>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btBlock_previous_set :: ( BtBlockClass bc , BtBlockClass a ) => bc -> a -> IO ()
btBlock_previous_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btBlock_previous_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10910 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#29>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btBlock_previous_get :: ( BtBlockClass bc ) => bc -> IO (BtBlock)
btBlock_previous_get a1 =
  withBt a1 $ \a1' -> 
  btBlock_previous_get'_ a1' >>= \res ->
  mkBtBlock res >>= \res' ->
  return (res')
{-# LINE 10914 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btChunk
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#53>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btChunk :: IO (BtChunk)
btChunk =
  btChunk'_ >>= \res ->
  mkBtChunk res >>= \res' ->
  return (res')
{-# LINE 10919 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btChunk_free :: ( BtChunkClass bc ) => bc -> IO ()
btChunk_free a1 =
  withBt a1 $ \a1' -> 
  btChunk_free'_ a1' >>= \res ->
  return ()
{-# LINE 10920 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#55>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btChunk_m_chunkCode_set :: ( BtChunkClass bc ) => bc -> Int -> IO ()
btChunk_m_chunkCode_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btChunk_m_chunkCode_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10924 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#55>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btChunk_m_chunkCode_get :: ( BtChunkClass bc ) => bc -> IO (Int)
btChunk_m_chunkCode_get a1 =
  withBt a1 $ \a1' -> 
  btChunk_m_chunkCode_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10928 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#58>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btChunk_m_dna_nr_set :: ( BtChunkClass bc ) => bc -> Int -> IO ()
btChunk_m_dna_nr_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btChunk_m_dna_nr_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10932 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#58>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btChunk_m_dna_nr_get :: ( BtChunkClass bc ) => bc -> IO (Int)
btChunk_m_dna_nr_get a1 =
  withBt a1 $ \a1' -> 
  btChunk_m_dna_nr_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10936 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#56>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btChunk_m_length_set :: ( BtChunkClass bc ) => bc -> Int -> IO ()
btChunk_m_length_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btChunk_m_length_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10940 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#56>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btChunk_m_length_get :: ( BtChunkClass bc ) => bc -> IO (Int)
btChunk_m_length_get a1 =
  withBt a1 $ \a1' -> 
  btChunk_m_length_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10944 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#59>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btChunk_m_number_set :: ( BtChunkClass bc ) => bc -> Int -> IO ()
btChunk_m_number_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btChunk_m_number_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10948 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#59>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btChunk_m_number_get :: ( BtChunkClass bc ) => bc -> IO (Int)
btChunk_m_number_get a1 =
  withBt a1 $ \a1' -> 
  btChunk_m_number_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10952 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btChunk_m_oldPtr_set :: ( BtChunkClass bc ) => bc -> VoidPtr -> IO ()
btChunk_m_oldPtr_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  btChunk_m_oldPtr_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 10956 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btChunk_m_oldPtr_get :: ( BtChunkClass bc ) => bc -> IO (VoidPtr)
btChunk_m_oldPtr_get a1 =
  withBt a1 $ \a1' -> 
  btChunk_m_oldPtr_get'_ a1' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 10960 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btClock
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#38>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
btClock :: IO (BtClock)
btClock =
  btClock'_ >>= \res ->
  mkBtClock res >>= \res' ->
  return (res')
{-# LINE 10965 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btClock_free :: ( BtClockClass bc ) => bc -> IO ()
btClock_free a1 =
  withBt a1 $ \a1' -> 
  btClock_free'_ a1' >>= \res ->
  return ()
{-# LINE 10966 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#46>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
btClock_reset :: ( BtClockClass bc ) => bc -> IO ()
btClock_reset a1 =
  withBt a1 $ \a1' -> 
  btClock_reset'_ a1' >>= \res ->
  return ()
{-# LINE 10971 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#50>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
btClock_getTimeMilliseconds :: ( BtClockClass bc ) => bc -> IO (Word64)
btClock_getTimeMilliseconds a1 =
  withBt a1 $ \a1' -> 
  btClock_getTimeMilliseconds'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10976 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuickprof.cpp?r=2223>
-}
btClock_getTimeMicroseconds :: ( BtClockClass bc ) => bc -> IO (Word64)
btClock_getTimeMicroseconds a1 =
  withBt a1 $ \a1' -> 
  btClock_getTimeMicroseconds'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 10981 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btConvexSeparatingDistanceUtil
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#161>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil :: Float -> Float -> IO (BtConvexSeparatingDistanceUtil)
btConvexSeparatingDistanceUtil a1 a2 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  btConvexSeparatingDistanceUtil'_ a1' a2' >>= \res ->
  mkBtConvexSeparatingDistanceUtil res >>= \res' ->
  return (res')
{-# LINE 10986 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btConvexSeparatingDistanceUtil_free :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> IO ()
btConvexSeparatingDistanceUtil_free a1 =
  withBt a1 $ \a1' -> 
  btConvexSeparatingDistanceUtil_free'_ a1' >>= \res ->
  return ()
{-# LINE 10987 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#173>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_updateSeparatingDistance :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> Transform -> Transform -> IO (Transform, Transform)
btConvexSeparatingDistanceUtil_updateSeparatingDistance a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  withTransform a3 $ \a3' -> 
  btConvexSeparatingDistanceUtil_updateSeparatingDistance'_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 10994 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#173>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_updateSeparatingDistance' :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> IO (Transform, Transform)
btConvexSeparatingDistanceUtil_updateSeparatingDistance' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  allocaTransform $ \a3' -> 
  btConvexSeparatingDistanceUtil_updateSeparatingDistance''_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  peekTransform  a3'>>= \a3'' -> 
  return (a2'', a3'')
{-# LINE 11001 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#168>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_getConservativeSeparatingDistance :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> IO (Float)
btConvexSeparatingDistanceUtil_getConservativeSeparatingDistance a1 =
  withBt a1 $ \a1' -> 
  btConvexSeparatingDistanceUtil_getConservativeSeparatingDistance'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 11006 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#205>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_initSeparatingDistance :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> Vec3 -> Float -> Transform -> Transform -> IO (Vec3, Transform, Transform)
btConvexSeparatingDistanceUtil_initSeparatingDistance a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  withTransform a4 $ \a4' -> 
  withTransform a5 $ \a5' -> 
  btConvexSeparatingDistanceUtil_initSeparatingDistance'_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekTransform  a5'>>= \a5'' -> 
  return (a2'', a4'', a5'')
{-# LINE 11015 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#205>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_initSeparatingDistance' :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> Float -> IO (Vec3, Transform, Transform)
btConvexSeparatingDistanceUtil_initSeparatingDistance' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  allocaTransform $ \a4' -> 
  allocaTransform $ \a5' -> 
  btConvexSeparatingDistanceUtil_initSeparatingDistance''_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekTransform  a5'>>= \a5'' -> 
  return (a2'', a4'', a5'')
{-# LINE 11024 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_ornA_set :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> UnitQuaternion -> IO ()
btConvexSeparatingDistanceUtil_m_ornA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withUnitQuaternion a2 $ \a2' -> 
  btConvexSeparatingDistanceUtil_m_ornA_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11028 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#148>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_ornA_get :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> IO (UnitQuaternion)
btConvexSeparatingDistanceUtil_m_ornA_get a1 =
  withBt a1 $ \a1' -> 
  allocaUnitQuaternion $ \a2' -> 
  btConvexSeparatingDistanceUtil_m_ornA_get'_ a1' a2' >>= \res ->
  peekUnitQuaternion  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11032 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#149>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_ornB_set :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> UnitQuaternion -> IO ()
btConvexSeparatingDistanceUtil_m_ornB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withUnitQuaternion a2 $ \a2' -> 
  btConvexSeparatingDistanceUtil_m_ornB_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11036 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#149>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_ornB_get :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> IO (UnitQuaternion)
btConvexSeparatingDistanceUtil_m_ornB_get a1 =
  withBt a1 $ \a1' -> 
  allocaUnitQuaternion $ \a2' -> 
  btConvexSeparatingDistanceUtil_m_ornB_get'_ a1' a2' >>= \res ->
  peekUnitQuaternion  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11040 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#150>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_posA_set :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> Vec3 -> IO ()
btConvexSeparatingDistanceUtil_m_posA_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btConvexSeparatingDistanceUtil_m_posA_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11044 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#150>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_posA_get :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> IO (Vec3)
btConvexSeparatingDistanceUtil_m_posA_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btConvexSeparatingDistanceUtil_m_posA_get'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11048 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#151>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_posB_set :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> Vec3 -> IO ()
btConvexSeparatingDistanceUtil_m_posB_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btConvexSeparatingDistanceUtil_m_posB_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11052 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#151>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_posB_get :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> IO (Vec3)
btConvexSeparatingDistanceUtil_m_posB_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btConvexSeparatingDistanceUtil_m_posB_get'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11056 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#153>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_separatingNormal_set :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> Vec3 -> IO ()
btConvexSeparatingDistanceUtil_m_separatingNormal_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  btConvexSeparatingDistanceUtil_m_separatingNormal_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11060 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#153>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_separatingNormal_get :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> IO (Vec3)
btConvexSeparatingDistanceUtil_m_separatingNormal_get a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  btConvexSeparatingDistanceUtil_m_separatingNormal_get'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11064 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#155>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_boundingRadiusA_set :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> Float -> IO ()
btConvexSeparatingDistanceUtil_m_boundingRadiusA_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConvexSeparatingDistanceUtil_m_boundingRadiusA_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11068 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#155>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_boundingRadiusA_get :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> IO (Float)
btConvexSeparatingDistanceUtil_m_boundingRadiusA_get a1 =
  withBt a1 $ \a1' -> 
  btConvexSeparatingDistanceUtil_m_boundingRadiusA_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 11072 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#156>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_boundingRadiusB_set :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> Float -> IO ()
btConvexSeparatingDistanceUtil_m_boundingRadiusB_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConvexSeparatingDistanceUtil_m_boundingRadiusB_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11076 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#156>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_boundingRadiusB_get :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> IO (Float)
btConvexSeparatingDistanceUtil_m_boundingRadiusB_get a1 =
  withBt a1 $ \a1' -> 
  btConvexSeparatingDistanceUtil_m_boundingRadiusB_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 11080 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#157>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_separatingDistance_set :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> Float -> IO ()
btConvexSeparatingDistanceUtil_m_separatingDistance_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btConvexSeparatingDistanceUtil_m_separatingDistance_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11084 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#157>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btConvexSeparatingDistanceUtil_m_separatingDistance_get :: ( BtConvexSeparatingDistanceUtilClass bc ) => bc -> IO (Float)
btConvexSeparatingDistanceUtil_m_separatingDistance_get a1 =
  withBt a1 $ \a1' -> 
  btConvexSeparatingDistanceUtil_m_separatingDistance_get'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 11088 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btDefaultMotionState
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.h?r=2223#14>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.cpp?r=2223>
-}
btDefaultMotionState :: Transform -> Transform -> IO (BtDefaultMotionState)
btDefaultMotionState a1 a2 =
  withTransform a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btDefaultMotionState'_ a1' a2' >>= \res ->
  mkBtDefaultMotionState res >>= \res' ->
  return (res')
{-# LINE 11093 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btDefaultMotionState_free :: ( BtDefaultMotionStateClass bc ) => bc -> IO ()
btDefaultMotionState_free a1 =
  withBt a1 $ \a1' -> 
  btDefaultMotionState_free'_ a1' >>= \res ->
  return ()
{-# LINE 11094 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.h?r=2223#31>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.cpp?r=2223>
-}
btDefaultMotionState_setWorldTransform :: ( BtDefaultMotionStateClass bc ) => bc -> Transform -> IO (Transform)
btDefaultMotionState_setWorldTransform a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btDefaultMotionState_setWorldTransform'_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11100 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.h?r=2223#31>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.cpp?r=2223>
-}
btDefaultMotionState_setWorldTransform' :: ( BtDefaultMotionStateClass bc ) => bc -> IO (Transform)
btDefaultMotionState_setWorldTransform' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btDefaultMotionState_setWorldTransform''_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11106 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.h?r=2223#24>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.cpp?r=2223>
-}
btDefaultMotionState_getWorldTransform :: ( BtDefaultMotionStateClass bc ) => bc -> Transform -> IO (Transform)
btDefaultMotionState_getWorldTransform a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btDefaultMotionState_getWorldTransform'_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11112 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.h?r=2223#24>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.cpp?r=2223>
-}
btDefaultMotionState_getWorldTransform' :: ( BtDefaultMotionStateClass bc ) => bc -> IO (Transform)
btDefaultMotionState_getWorldTransform' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btDefaultMotionState_getWorldTransform''_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11118 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.h?r=2223#9>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.cpp?r=2223>
-}
btDefaultMotionState_m_graphicsWorldTrans_set :: ( BtDefaultMotionStateClass bc ) => bc -> Transform -> IO ()
btDefaultMotionState_m_graphicsWorldTrans_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btDefaultMotionState_m_graphicsWorldTrans_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11122 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.h?r=2223#9>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.cpp?r=2223>
-}
btDefaultMotionState_m_graphicsWorldTrans_get :: ( BtDefaultMotionStateClass bc ) => bc -> IO (Transform)
btDefaultMotionState_m_graphicsWorldTrans_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btDefaultMotionState_m_graphicsWorldTrans_get'_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11126 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.h?r=2223#10>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.cpp?r=2223>
-}
btDefaultMotionState_m_centerOfMassOffset_set :: ( BtDefaultMotionStateClass bc ) => bc -> Transform -> IO ()
btDefaultMotionState_m_centerOfMassOffset_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btDefaultMotionState_m_centerOfMassOffset_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11130 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.h?r=2223#10>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.cpp?r=2223>
-}
btDefaultMotionState_m_centerOfMassOffset_get :: ( BtDefaultMotionStateClass bc ) => bc -> IO (Transform)
btDefaultMotionState_m_centerOfMassOffset_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btDefaultMotionState_m_centerOfMassOffset_get'_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11134 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.h?r=2223#11>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.cpp?r=2223>
-}
btDefaultMotionState_m_startWorldTrans_set :: ( BtDefaultMotionStateClass bc ) => bc -> Transform -> IO ()
btDefaultMotionState_m_startWorldTrans_set a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btDefaultMotionState_m_startWorldTrans_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11138 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.h?r=2223#11>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.cpp?r=2223>
-}
btDefaultMotionState_m_startWorldTrans_get :: ( BtDefaultMotionStateClass bc ) => bc -> IO (Transform)
btDefaultMotionState_m_startWorldTrans_get a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btDefaultMotionState_m_startWorldTrans_get'_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11142 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.h?r=2223#12>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.cpp?r=2223>
-}
btDefaultMotionState_m_userPointer_set :: ( BtDefaultMotionStateClass bc ) => bc -> VoidPtr -> IO ()
btDefaultMotionState_m_userPointer_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  btDefaultMotionState_m_userPointer_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11146 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.h?r=2223#12>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btDefaultMotionState.cpp?r=2223>
-}
btDefaultMotionState_m_userPointer_get :: ( BtDefaultMotionStateClass bc ) => bc -> IO (VoidPtr)
btDefaultMotionState_m_userPointer_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultMotionState_m_userPointer_get'_ a1' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 11150 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btDefaultSerializer
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#377>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer :: Int -> IO (BtDefaultSerializer)
btDefaultSerializer a1 =
  let {a1' = fromIntegral a1} in 
  btDefaultSerializer'_ a1' >>= \res ->
  mkBtDefaultSerializer res >>= \res' ->
  return (res')
{-# LINE 11155 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btDefaultSerializer_free :: ( BtDefaultSerializerClass bc ) => bc -> IO ()
btDefaultSerializer_free a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_free'_ a1' >>= \res ->
  return ()
{-# LINE 11156 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#472>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_finishSerialization :: ( BtDefaultSerializerClass bc ) => bc -> IO ()
btDefaultSerializer_finishSerialization a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_finishSerialization'_ a1' >>= \res ->
  return ()
{-# LINE 11161 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#461>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_startSerialization :: ( BtDefaultSerializerClass bc ) => bc -> IO ()
btDefaultSerializer_startSerialization a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_startSerialization'_ a1' >>= \res ->
  return ()
{-# LINE 11166 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#641>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_getSerializationFlags :: ( BtDefaultSerializerClass bc ) => bc -> IO (Int)
btDefaultSerializer_getSerializationFlags a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_getSerializationFlags'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11171 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#646>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_setSerializationFlags :: ( BtDefaultSerializerClass bc ) => bc -> Int -> IO ()
btDefaultSerializer_setSerializationFlags a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btDefaultSerializer_setSerializationFlags'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11177 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#189>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_getReverseType :: ( BtDefaultSerializerClass bc ) => bc -> String -> IO (Int)
btDefaultSerializer_getReverseType a1 a2 =
  withBt a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  btDefaultSerializer_getReverseType'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11183 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#541>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_finalizeChunk :: ( BtDefaultSerializerClass bc , BtChunkClass p0 ) => bc -> p0 -> String -> Int -> VoidPtr -> IO ()
btDefaultSerializer_finalizeChunk a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  let {a4' = fromIntegral a4} in 
  withVoidPtr a5 $ \a5' -> 
  btDefaultSerializer_finalizeChunk'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 11192 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#200>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_initDNA :: ( BtDefaultSerializerClass bc ) => bc -> String -> Int -> IO ()
btDefaultSerializer_initDNA a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  btDefaultSerializer_initDNA'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 11199 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#182>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_writeDNA :: ( BtDefaultSerializerClass bc ) => bc -> IO ()
btDefaultSerializer_writeDNA a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_writeDNA'_ a1' >>= \res ->
  return ()
{-# LINE 11204 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#536>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_getCurrentBufferSize :: ( BtDefaultSerializerClass bc ) => bc -> IO (Int)
btDefaultSerializer_getCurrentBufferSize a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_getCurrentBufferSize'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11209 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#511>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_getUniquePointer :: ( BtDefaultSerializerClass bc ) => bc -> VoidPtr -> IO (VoidPtr)
btDefaultSerializer_getUniquePointer a1 a2 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  btDefaultSerializer_getUniquePointer'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 11215 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#612>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_serializeName :: ( BtDefaultSerializerClass bc ) => bc -> String -> IO ()
btDefaultSerializer_serializeName a1 a2 =
  withBt a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  btDefaultSerializer_serializeName'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11221 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#170>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_findPointer :: ( BtDefaultSerializerClass bc ) => bc -> VoidPtr -> IO (VoidPtr)
btDefaultSerializer_findPointer a1 a2 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  btDefaultSerializer_findPointer'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 11227 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#143>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_mTypes_set :: ( BtDefaultSerializerClass bc , BtAlignedObjectArray_char_ptr_Class a ) => bc -> a -> IO ()
btDefaultSerializer_mTypes_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btDefaultSerializer_mTypes_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11231 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#143>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_mTypes_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (BtAlignedObjectArray_char_ptr_)
btDefaultSerializer_mTypes_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_mTypes_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_char_ptr_ res >>= \res' ->
  return (res')
{-# LINE 11235 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#144>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_mStructs_set :: ( BtDefaultSerializerClass bc , BtAlignedObjectArray_short_ptr_Class a ) => bc -> a -> IO ()
btDefaultSerializer_mStructs_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btDefaultSerializer_mStructs_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11239 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#144>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_mStructs_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (BtAlignedObjectArray_short_ptr_)
btDefaultSerializer_mStructs_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_mStructs_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_short_ptr_ res >>= \res' ->
  return (res')
{-# LINE 11243 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#145>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_mTlens_set :: ( BtDefaultSerializerClass bc , BtAlignedObjectArray_short_Class a ) => bc -> a -> IO ()
btDefaultSerializer_mTlens_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btDefaultSerializer_mTlens_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11247 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#145>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_mTlens_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (BtAlignedObjectArray_short_)
btDefaultSerializer_mTlens_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_mTlens_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_short_ res >>= \res' ->
  return (res')
{-# LINE 11251 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#146>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_mStructReverse_set :: ( BtDefaultSerializerClass bc , BtHashMap_btHashInt_int_Class a ) => bc -> a -> IO ()
btDefaultSerializer_mStructReverse_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btDefaultSerializer_mStructReverse_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11255 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#146>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_mStructReverse_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (BtHashMap_btHashInt_int_)
btDefaultSerializer_mStructReverse_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_mStructReverse_get'_ a1' >>= \res ->
  mkBtHashMap_btHashInt_int_ res >>= \res' ->
  return (res')
{-# LINE 11259 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_mTypeLookup_set :: ( BtDefaultSerializerClass bc , BtHashMap_btHashString_int_Class a ) => bc -> a -> IO ()
btDefaultSerializer_mTypeLookup_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btDefaultSerializer_mTypeLookup_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11263 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_mTypeLookup_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (BtHashMap_btHashString_int_)
btDefaultSerializer_mTypeLookup_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_mTypeLookup_get'_ a1' >>= \res ->
  mkBtHashMap_btHashString_int_ res >>= \res' ->
  return (res')
{-# LINE 11267 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#150>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_chunkP_set :: ( BtDefaultSerializerClass bc , BtHashMap_btHashPtr_void_ptr_Class a ) => bc -> a -> IO ()
btDefaultSerializer_m_chunkP_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btDefaultSerializer_m_chunkP_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11271 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#150>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_chunkP_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (BtHashMap_btHashPtr_void_ptr_)
btDefaultSerializer_m_chunkP_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_m_chunkP_get'_ a1' >>= \res ->
  mkBtHashMap_btHashPtr_void_ptr_ res >>= \res' ->
  return (res')
{-# LINE 11275 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#152>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_nameMap_set :: ( BtDefaultSerializerClass bc , BtHashMap_btHashPtr_charconst_ptr_Class a ) => bc -> a -> IO ()
btDefaultSerializer_m_nameMap_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btDefaultSerializer_m_nameMap_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11279 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#152>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_nameMap_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (BtHashMap_btHashPtr_charconst_ptr_)
btDefaultSerializer_m_nameMap_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_m_nameMap_get'_ a1' >>= \res ->
  mkBtHashMap_btHashPtr_charconst_ptr_ res >>= \res' ->
  return (res')
{-# LINE 11283 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#154>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_uniquePointers_set :: ( BtDefaultSerializerClass bc , BtHashMap_btHashPtr_btPointerUid_Class a ) => bc -> a -> IO ()
btDefaultSerializer_m_uniquePointers_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btDefaultSerializer_m_uniquePointers_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11287 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#154>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_uniquePointers_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (BtHashMap_btHashPtr_btPointerUid_)
btDefaultSerializer_m_uniquePointers_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_m_uniquePointers_get'_ a1' >>= \res ->
  mkBtHashMap_btHashPtr_btPointerUid_ res >>= \res' ->
  return (res')
{-# LINE 11291 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#155>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_uniqueIdGenerator_set :: ( BtDefaultSerializerClass bc ) => bc -> Int -> IO ()
btDefaultSerializer_m_uniqueIdGenerator_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btDefaultSerializer_m_uniqueIdGenerator_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11295 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#155>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_uniqueIdGenerator_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (Int)
btDefaultSerializer_m_uniqueIdGenerator_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_m_uniqueIdGenerator_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11299 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#157>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_totalSize_set :: ( BtDefaultSerializerClass bc ) => bc -> Int -> IO ()
btDefaultSerializer_m_totalSize_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btDefaultSerializer_m_totalSize_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11303 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#157>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_totalSize_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (Int)
btDefaultSerializer_m_totalSize_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_m_totalSize_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11307 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#159>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_currentSize_set :: ( BtDefaultSerializerClass bc ) => bc -> Int -> IO ()
btDefaultSerializer_m_currentSize_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btDefaultSerializer_m_currentSize_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11311 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#159>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_currentSize_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (Int)
btDefaultSerializer_m_currentSize_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_m_currentSize_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11315 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#160>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_dna_set :: ( BtDefaultSerializerClass bc ) => bc -> VoidPtr -> IO ()
btDefaultSerializer_m_dna_set a1 a2 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  btDefaultSerializer_m_dna_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11319 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#160>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_dna_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (VoidPtr)
btDefaultSerializer_m_dna_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_m_dna_get'_ a1' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 11323 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#161>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_dnaLength_set :: ( BtDefaultSerializerClass bc ) => bc -> Int -> IO ()
btDefaultSerializer_m_dnaLength_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btDefaultSerializer_m_dnaLength_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11327 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#161>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_dnaLength_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (Int)
btDefaultSerializer_m_dnaLength_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_m_dnaLength_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11331 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#163>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_serializationFlags_set :: ( BtDefaultSerializerClass bc ) => bc -> Int -> IO ()
btDefaultSerializer_m_serializationFlags_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btDefaultSerializer_m_serializationFlags_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11335 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#163>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_serializationFlags_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (Int)
btDefaultSerializer_m_serializationFlags_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_m_serializationFlags_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11339 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#166>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_chunkPtrs_set :: ( BtDefaultSerializerClass bc , BtAlignedObjectArray_btChunk_ptr_Class a ) => bc -> a -> IO ()
btDefaultSerializer_m_chunkPtrs_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btDefaultSerializer_m_chunkPtrs_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11343 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#166>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btDefaultSerializer_m_chunkPtrs_get :: ( BtDefaultSerializerClass bc ) => bc -> IO (BtAlignedObjectArray_btChunk_ptr_)
btDefaultSerializer_m_chunkPtrs_get a1 =
  withBt a1 $ \a1' -> 
  btDefaultSerializer_m_chunkPtrs_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btChunk_ptr_ res >>= \res' ->
  return (res')
{-# LINE 11347 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btGeometryUtil
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.h?r=2223#24>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.cpp?r=2223>
-}
btGeometryUtil :: IO (BtGeometryUtil)
btGeometryUtil =
  btGeometryUtil'_ >>= \res ->
  mkBtGeometryUtil res >>= \res' ->
  return (res')
{-# LINE 11352 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btGeometryUtil_free :: ( BtGeometryUtilClass bc ) => bc -> IO ()
btGeometryUtil_free a1 =
  withBt a1 $ \a1' -> 
  btGeometryUtil_free'_ a1' >>= \res ->
  return ()
{-# LINE 11353 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.h?r=2223#34>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.cpp?r=2223>
-}
btGeometryUtil_isPointInsidePlanes :: (  BtAlignedObjectArray_btVector3_Class p0 ) => p0 -> Vec3 -> Float -> IO (Bool, Vec3)
btGeometryUtil_isPointInsidePlanes a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btGeometryUtil_isPointInsidePlanes'_ a1' a2' a3' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  let {res' = toBool res} in
  return (res', a2'')
{-# LINE 11360 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.h?r=2223#34>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.cpp?r=2223>
-}
btGeometryUtil_isPointInsidePlanes' :: (  BtAlignedObjectArray_btVector3_Class p0 ) => p0 -> Float -> IO (Bool, Vec3)
btGeometryUtil_isPointInsidePlanes' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btGeometryUtil_isPointInsidePlanes''_ a1' a2' a3' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  let {res' = toBool res} in
  return (res', a2'')
{-# LINE 11367 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.h?r=2223#30>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.cpp?r=2223>
-}
btGeometryUtil_getVerticesFromPlaneEquations :: (  BtAlignedObjectArray_btVector3_Class p0 , BtAlignedObjectArray_btVector3_Class p1 ) => p0 -> p1 -> IO ()
btGeometryUtil_getVerticesFromPlaneEquations a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeometryUtil_getVerticesFromPlaneEquations'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11373 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.h?r=2223#36>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.cpp?r=2223>
-}
btGeometryUtil_areVerticesBehindPlane :: (  BtAlignedObjectArray_btVector3_Class p1 ) => Vec3 -> p1 -> Float -> IO (Bool, Vec3)
btGeometryUtil_areVerticesBehindPlane a1 a2 a3 =
  withVec3 a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btGeometryUtil_areVerticesBehindPlane'_ a1' a2' a3' >>= \res ->
  peekVec3  a1'>>= \a1'' -> 
  let {res' = toBool res} in
  return (res', a1'')
{-# LINE 11380 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.h?r=2223#36>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.cpp?r=2223>
-}
btGeometryUtil_areVerticesBehindPlane' :: (  BtAlignedObjectArray_btVector3_Class p1 ) => p1 -> Float -> IO (Bool, Vec3)
btGeometryUtil_areVerticesBehindPlane' a2 a3 =
  allocaVec3 $ \a1' -> 
  withBt a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btGeometryUtil_areVerticesBehindPlane''_ a1' a2' a3' >>= \res ->
  peekVec3  a1'>>= \a1'' -> 
  let {res' = toBool res} in
  return (res', a1'')
{-# LINE 11387 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.h?r=2223#28>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btGeometryUtil.cpp?r=2223>
-}
btGeometryUtil_getPlaneEquationsFromVertices :: (  BtAlignedObjectArray_btVector3_Class p0 , BtAlignedObjectArray_btVector3_Class p1 ) => p0 -> p1 -> IO ()
btGeometryUtil_getPlaneEquationsFromVertices a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btGeometryUtil_getPlaneEquationsFromVertices'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11393 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btHashInt
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashInt :: Int -> IO (BtHashInt)
btHashInt a1 =
  let {a1' = fromIntegral a1} in 
  btHashInt'_ a1' >>= \res ->
  mkBtHashInt res >>= \res' ->
  return (res')
{-# LINE 11398 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btHashInt_free :: ( BtHashIntClass bc ) => bc -> IO ()
btHashInt_free a1 =
  withBt a1 $ \a1' -> 
  btHashInt_free'_ a1' >>= \res ->
  return ()
{-# LINE 11399 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#86>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashInt_getUid1 :: ( BtHashIntClass bc ) => bc -> IO (Int)
btHashInt_getUid1 a1 =
  withBt a1 $ \a1' -> 
  btHashInt_getUid1'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11404 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#101>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashInt_getHash :: ( BtHashIntClass bc ) => bc -> IO (Word32)
btHashInt_getHash a1 =
  withBt a1 $ \a1' -> 
  btHashInt_getHash'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11409 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#91>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashInt_setUid1 :: ( BtHashIntClass bc ) => bc -> Int -> IO ()
btHashInt_setUid1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHashInt_setUid1'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11415 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashInt_equals :: ( BtHashIntClass bc , BtHashIntClass p0 ) => bc -> p0 -> IO (Bool)
btHashInt_equals a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashInt_equals'_ a1' a2' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 11421 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashInt_m_uid_set :: ( BtHashIntClass bc ) => bc -> Int -> IO ()
btHashInt_m_uid_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHashInt_m_uid_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11425 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#80>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashInt_m_uid_get :: ( BtHashIntClass bc ) => bc -> IO (Int)
btHashInt_m_uid_get a1 =
  withBt a1 $ \a1' -> 
  btHashInt_m_uid_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11429 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btHashMap<btHashInt, btTriangleInfo>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#221>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo_ :: IO (BtHashMap_btHashInt_btTriangleInfo_)
btHashMap_btHashInt_btTriangleInfo_ =
  btHashMap_btHashInt_btTriangleInfo_'_ >>= \res ->
  mkBtHashMap_btHashInt_btTriangleInfo_ res >>= \res' ->
  return (res')
{-# LINE 11434 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btHashMap_btHashInt_btTriangleInfo__free :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc ) => bc -> IO ()
btHashMap_btHashInt_btTriangleInfo__free a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_btTriangleInfo__free'_ a1' >>= \res ->
  return ()
{-# LINE 11435 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#269>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__insert :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc , BtHashIntClass p0 , BtTriangleInfoClass p1 ) => bc -> p0 -> p1 -> IO ()
btHashMap_btHashInt_btTriangleInfo__insert a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btHashMap_btHashInt_btTriangleInfo__insert'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 11442 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#423>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__findIndex :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO (Int)
btHashMap_btHashInt_btTriangleInfo__findIndex a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_btTriangleInfo__findIndex'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11448 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#440>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__clear :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc ) => bc -> IO ()
btHashMap_btHashInt_btTriangleInfo__clear a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_btTriangleInfo__clear'_ a1' >>= \res ->
  return ()
{-# LINE 11453 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#384>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__getAtIndex :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc ) => bc -> Int -> IO (BtTriangleInfo)
btHashMap_btHashInt_btTriangleInfo__getAtIndex a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHashMap_btHashInt_btTriangleInfo__getAtIndex'_ a1' a2' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 11459 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#384>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__getAtIndex0 :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc ) => bc -> Int -> IO (BtTriangleInfo)
btHashMap_btHashInt_btTriangleInfo__getAtIndex0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHashMap_btHashInt_btTriangleInfo__getAtIndex0'_ a1' a2' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 11465 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#391>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__getAtIndex1 :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc ) => bc -> Int -> IO (BtTriangleInfo)
btHashMap_btHashInt_btTriangleInfo__getAtIndex1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHashMap_btHashInt_btTriangleInfo__getAtIndex1'_ a1' a2' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 11471 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__growTables :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO ()
btHashMap_btHashInt_btTriangleInfo__growTables a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_btTriangleInfo__growTables'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11477 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#402>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__find :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO (BtTriangleInfo)
btHashMap_btHashInt_btTriangleInfo__find a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_btTriangleInfo__find'_ a1' a2' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 11483 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#402>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__find0 :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO (BtTriangleInfo)
btHashMap_btHashInt_btTriangleInfo__find0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_btTriangleInfo__find0'_ a1' a2' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 11489 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#412>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__find1 :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO (BtTriangleInfo)
btHashMap_btHashInt_btTriangleInfo__find1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_btTriangleInfo__find1'_ a1' a2' >>= \res ->
  mkBtTriangleInfo res >>= \res' ->
  return (res')
{-# LINE 11495 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#379>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__size :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc ) => bc -> IO (Int)
btHashMap_btHashInt_btTriangleInfo__size a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_btTriangleInfo__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11500 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__m_hashTable_set :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashInt_btTriangleInfo__m_hashTable_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_btTriangleInfo__m_hashTable_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11504 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__m_hashTable_get :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashInt_btTriangleInfo__m_hashTable_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_btTriangleInfo__m_hashTable_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11508 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__m_next_set :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashInt_btTriangleInfo__m_next_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_btTriangleInfo__m_next_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11512 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__m_next_get :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashInt_btTriangleInfo__m_next_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_btTriangleInfo__m_next_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11516 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__m_valueArray_set :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc , BtAlignedObjectArray_btTriangleInfo_Class a ) => bc -> a -> IO ()
btHashMap_btHashInt_btTriangleInfo__m_valueArray_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_btTriangleInfo__m_valueArray_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11520 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__m_valueArray_get :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc ) => bc -> IO (BtAlignedObjectArray_btTriangleInfo_)
btHashMap_btHashInt_btTriangleInfo__m_valueArray_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_btTriangleInfo__m_valueArray_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btTriangleInfo_ res >>= \res' ->
  return (res')
{-# LINE 11524 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__m_keyArray_set :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc , BtAlignedObjectArray_btHashInt_Class a ) => bc -> a -> IO ()
btHashMap_btHashInt_btTriangleInfo__m_keyArray_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_btTriangleInfo__m_keyArray_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11528 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_btTriangleInfo__m_keyArray_get :: ( BtHashMap_btHashInt_btTriangleInfo_Class bc ) => bc -> IO (BtAlignedObjectArray_btHashInt_)
btHashMap_btHashInt_btTriangleInfo__m_keyArray_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_btTriangleInfo__m_keyArray_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btHashInt_ res >>= \res' ->
  return (res')
{-# LINE 11532 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btHashMap<btHashInt, int>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#221>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_int_ :: IO (BtHashMap_btHashInt_int_)
btHashMap_btHashInt_int_ =
  btHashMap_btHashInt_int_'_ >>= \res ->
  mkBtHashMap_btHashInt_int_ res >>= \res' ->
  return (res')
{-# LINE 11537 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btHashMap_btHashInt_int__free :: ( BtHashMap_btHashInt_int_Class bc ) => bc -> IO ()
btHashMap_btHashInt_int__free a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_int__free'_ a1' >>= \res ->
  return ()
{-# LINE 11538 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#423>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_int__findIndex :: ( BtHashMap_btHashInt_int_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO (Int)
btHashMap_btHashInt_int__findIndex a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_int__findIndex'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11544 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#440>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_int__clear :: ( BtHashMap_btHashInt_int_Class bc ) => bc -> IO ()
btHashMap_btHashInt_int__clear a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_int__clear'_ a1' >>= \res ->
  return ()
{-# LINE 11549 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_int__growTables :: ( BtHashMap_btHashInt_int_Class bc , BtHashIntClass p0 ) => bc -> p0 -> IO ()
btHashMap_btHashInt_int__growTables a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_int__growTables'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11555 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#379>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_int__size :: ( BtHashMap_btHashInt_int_Class bc ) => bc -> IO (Int)
btHashMap_btHashInt_int__size a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_int__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11560 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_int__m_hashTable_set :: ( BtHashMap_btHashInt_int_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashInt_int__m_hashTable_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_int__m_hashTable_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11564 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_int__m_hashTable_get :: ( BtHashMap_btHashInt_int_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashInt_int__m_hashTable_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_int__m_hashTable_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11568 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_int__m_keyArray_set :: ( BtHashMap_btHashInt_int_Class bc , BtAlignedObjectArray_btHashInt_Class a ) => bc -> a -> IO ()
btHashMap_btHashInt_int__m_keyArray_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_int__m_keyArray_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11572 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_int__m_keyArray_get :: ( BtHashMap_btHashInt_int_Class bc ) => bc -> IO (BtAlignedObjectArray_btHashInt_)
btHashMap_btHashInt_int__m_keyArray_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_int__m_keyArray_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btHashInt_ res >>= \res' ->
  return (res')
{-# LINE 11576 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_int__m_next_set :: ( BtHashMap_btHashInt_int_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashInt_int__m_next_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_int__m_next_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11580 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_int__m_next_get :: ( BtHashMap_btHashInt_int_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashInt_int__m_next_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_int__m_next_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11584 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_int__m_valueArray_set :: ( BtHashMap_btHashInt_int_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashInt_int__m_valueArray_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashInt_int__m_valueArray_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11588 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashInt_int__m_valueArray_get :: ( BtHashMap_btHashInt_int_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashInt_int__m_valueArray_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashInt_int__m_valueArray_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11592 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btHashMap<btHashPtr, btPointerUid>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#221>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid_ :: IO (BtHashMap_btHashPtr_btPointerUid_)
btHashMap_btHashPtr_btPointerUid_ =
  btHashMap_btHashPtr_btPointerUid_'_ >>= \res ->
  mkBtHashMap_btHashPtr_btPointerUid_ res >>= \res' ->
  return (res')
{-# LINE 11597 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btHashMap_btHashPtr_btPointerUid__free :: ( BtHashMap_btHashPtr_btPointerUid_Class bc ) => bc -> IO ()
btHashMap_btHashPtr_btPointerUid__free a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_btPointerUid__free'_ a1' >>= \res ->
  return ()
{-# LINE 11598 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#269>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__insert :: ( BtHashMap_btHashPtr_btPointerUid_Class bc , BtHashPtrClass p0 , BtPointerUidClass p1 ) => bc -> p0 -> p1 -> IO ()
btHashMap_btHashPtr_btPointerUid__insert a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withBt a3 $ \a3' -> 
  btHashMap_btHashPtr_btPointerUid__insert'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 11605 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#423>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__findIndex :: ( BtHashMap_btHashPtr_btPointerUid_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO (Int)
btHashMap_btHashPtr_btPointerUid__findIndex a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_btPointerUid__findIndex'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11611 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#440>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__clear :: ( BtHashMap_btHashPtr_btPointerUid_Class bc ) => bc -> IO ()
btHashMap_btHashPtr_btPointerUid__clear a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_btPointerUid__clear'_ a1' >>= \res ->
  return ()
{-# LINE 11616 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#384>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__getAtIndex :: ( BtHashMap_btHashPtr_btPointerUid_Class bc ) => bc -> Int -> IO (BtPointerUid)
btHashMap_btHashPtr_btPointerUid__getAtIndex a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHashMap_btHashPtr_btPointerUid__getAtIndex'_ a1' a2' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 11622 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#384>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__getAtIndex0 :: ( BtHashMap_btHashPtr_btPointerUid_Class bc ) => bc -> Int -> IO (BtPointerUid)
btHashMap_btHashPtr_btPointerUid__getAtIndex0 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHashMap_btHashPtr_btPointerUid__getAtIndex0'_ a1' a2' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 11628 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#391>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__getAtIndex1 :: ( BtHashMap_btHashPtr_btPointerUid_Class bc ) => bc -> Int -> IO (BtPointerUid)
btHashMap_btHashPtr_btPointerUid__getAtIndex1 a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHashMap_btHashPtr_btPointerUid__getAtIndex1'_ a1' a2' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 11634 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__growTables :: ( BtHashMap_btHashPtr_btPointerUid_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO ()
btHashMap_btHashPtr_btPointerUid__growTables a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_btPointerUid__growTables'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11640 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#402>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__find :: ( BtHashMap_btHashPtr_btPointerUid_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO (BtPointerUid)
btHashMap_btHashPtr_btPointerUid__find a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_btPointerUid__find'_ a1' a2' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 11646 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#402>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__find0 :: ( BtHashMap_btHashPtr_btPointerUid_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO (BtPointerUid)
btHashMap_btHashPtr_btPointerUid__find0 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_btPointerUid__find0'_ a1' a2' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 11652 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#412>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__find1 :: ( BtHashMap_btHashPtr_btPointerUid_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO (BtPointerUid)
btHashMap_btHashPtr_btPointerUid__find1 a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_btPointerUid__find1'_ a1' a2' >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 11658 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#379>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__size :: ( BtHashMap_btHashPtr_btPointerUid_Class bc ) => bc -> IO (Int)
btHashMap_btHashPtr_btPointerUid__size a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_btPointerUid__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11663 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__m_hashTable_set :: ( BtHashMap_btHashPtr_btPointerUid_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashPtr_btPointerUid__m_hashTable_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_btPointerUid__m_hashTable_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11667 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__m_hashTable_get :: ( BtHashMap_btHashPtr_btPointerUid_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashPtr_btPointerUid__m_hashTable_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_btPointerUid__m_hashTable_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11671 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__m_keyArray_set :: ( BtHashMap_btHashPtr_btPointerUid_Class bc , BtAlignedObjectArray_btHashPtr_Class a ) => bc -> a -> IO ()
btHashMap_btHashPtr_btPointerUid__m_keyArray_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_btPointerUid__m_keyArray_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11675 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__m_keyArray_get :: ( BtHashMap_btHashPtr_btPointerUid_Class bc ) => bc -> IO (BtAlignedObjectArray_btHashPtr_)
btHashMap_btHashPtr_btPointerUid__m_keyArray_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_btPointerUid__m_keyArray_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btHashPtr_ res >>= \res' ->
  return (res')
{-# LINE 11679 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__m_next_set :: ( BtHashMap_btHashPtr_btPointerUid_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashPtr_btPointerUid__m_next_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_btPointerUid__m_next_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11683 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__m_next_get :: ( BtHashMap_btHashPtr_btPointerUid_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashPtr_btPointerUid__m_next_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_btPointerUid__m_next_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11687 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__m_valueArray_set :: ( BtHashMap_btHashPtr_btPointerUid_Class bc , BtAlignedObjectArray_btPointerUid_Class a ) => bc -> a -> IO ()
btHashMap_btHashPtr_btPointerUid__m_valueArray_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_btPointerUid__m_valueArray_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11691 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_btPointerUid__m_valueArray_get :: ( BtHashMap_btHashPtr_btPointerUid_Class bc ) => bc -> IO (BtAlignedObjectArray_btPointerUid_)
btHashMap_btHashPtr_btPointerUid__m_valueArray_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_btPointerUid__m_valueArray_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btPointerUid_ res >>= \res' ->
  return (res')
{-# LINE 11695 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btHashMap<btHashPtr, char const*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#221>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_charconst_ptr_ :: IO (BtHashMap_btHashPtr_charconst_ptr_)
btHashMap_btHashPtr_charconst_ptr_ =
  btHashMap_btHashPtr_charconst_ptr_'_ >>= \res ->
  mkBtHashMap_btHashPtr_charconst_ptr_ res >>= \res' ->
  return (res')
{-# LINE 11700 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btHashMap_btHashPtr_charconst_ptr__free :: ( BtHashMap_btHashPtr_charconst_ptr_Class bc ) => bc -> IO ()
btHashMap_btHashPtr_charconst_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_charconst_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 11701 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#423>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_charconst_ptr__findIndex :: ( BtHashMap_btHashPtr_charconst_ptr_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO (Int)
btHashMap_btHashPtr_charconst_ptr__findIndex a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_charconst_ptr__findIndex'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11707 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#440>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_charconst_ptr__clear :: ( BtHashMap_btHashPtr_charconst_ptr_Class bc ) => bc -> IO ()
btHashMap_btHashPtr_charconst_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_charconst_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 11712 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_charconst_ptr__growTables :: ( BtHashMap_btHashPtr_charconst_ptr_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO ()
btHashMap_btHashPtr_charconst_ptr__growTables a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_charconst_ptr__growTables'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11718 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#379>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_charconst_ptr__size :: ( BtHashMap_btHashPtr_charconst_ptr_Class bc ) => bc -> IO (Int)
btHashMap_btHashPtr_charconst_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_charconst_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11723 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_charconst_ptr__m_hashTable_set :: ( BtHashMap_btHashPtr_charconst_ptr_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashPtr_charconst_ptr__m_hashTable_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_charconst_ptr__m_hashTable_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11727 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_charconst_ptr__m_hashTable_get :: ( BtHashMap_btHashPtr_charconst_ptr_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashPtr_charconst_ptr__m_hashTable_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_charconst_ptr__m_hashTable_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11731 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_charconst_ptr__m_keyArray_set :: ( BtHashMap_btHashPtr_charconst_ptr_Class bc , BtAlignedObjectArray_btHashPtr_Class a ) => bc -> a -> IO ()
btHashMap_btHashPtr_charconst_ptr__m_keyArray_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_charconst_ptr__m_keyArray_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11735 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_charconst_ptr__m_keyArray_get :: ( BtHashMap_btHashPtr_charconst_ptr_Class bc ) => bc -> IO (BtAlignedObjectArray_btHashPtr_)
btHashMap_btHashPtr_charconst_ptr__m_keyArray_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_charconst_ptr__m_keyArray_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btHashPtr_ res >>= \res' ->
  return (res')
{-# LINE 11739 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_charconst_ptr__m_next_set :: ( BtHashMap_btHashPtr_charconst_ptr_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashPtr_charconst_ptr__m_next_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_charconst_ptr__m_next_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11743 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_charconst_ptr__m_next_get :: ( BtHashMap_btHashPtr_charconst_ptr_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashPtr_charconst_ptr__m_next_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_charconst_ptr__m_next_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11747 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_charconst_ptr__m_valueArray_set :: ( BtHashMap_btHashPtr_charconst_ptr_Class bc , BtAlignedObjectArray_charconst_ptr_Class a ) => bc -> a -> IO ()
btHashMap_btHashPtr_charconst_ptr__m_valueArray_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_charconst_ptr__m_valueArray_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11751 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_charconst_ptr__m_valueArray_get :: ( BtHashMap_btHashPtr_charconst_ptr_Class bc ) => bc -> IO (BtAlignedObjectArray_charconst_ptr_)
btHashMap_btHashPtr_charconst_ptr__m_valueArray_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_charconst_ptr__m_valueArray_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_charconst_ptr_ res >>= \res' ->
  return (res')
{-# LINE 11755 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btHashMap<btHashPtr, void*>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#221>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_void_ptr_ :: IO (BtHashMap_btHashPtr_void_ptr_)
btHashMap_btHashPtr_void_ptr_ =
  btHashMap_btHashPtr_void_ptr_'_ >>= \res ->
  mkBtHashMap_btHashPtr_void_ptr_ res >>= \res' ->
  return (res')
{-# LINE 11760 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btHashMap_btHashPtr_void_ptr__free :: ( BtHashMap_btHashPtr_void_ptr_Class bc ) => bc -> IO ()
btHashMap_btHashPtr_void_ptr__free a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_void_ptr__free'_ a1' >>= \res ->
  return ()
{-# LINE 11761 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#423>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_void_ptr__findIndex :: ( BtHashMap_btHashPtr_void_ptr_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO (Int)
btHashMap_btHashPtr_void_ptr__findIndex a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_void_ptr__findIndex'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11767 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#440>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_void_ptr__clear :: ( BtHashMap_btHashPtr_void_ptr_Class bc ) => bc -> IO ()
btHashMap_btHashPtr_void_ptr__clear a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_void_ptr__clear'_ a1' >>= \res ->
  return ()
{-# LINE 11772 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_void_ptr__growTables :: ( BtHashMap_btHashPtr_void_ptr_Class bc , BtHashPtrClass p0 ) => bc -> p0 -> IO ()
btHashMap_btHashPtr_void_ptr__growTables a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_void_ptr__growTables'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11778 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#379>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_void_ptr__size :: ( BtHashMap_btHashPtr_void_ptr_Class bc ) => bc -> IO (Int)
btHashMap_btHashPtr_void_ptr__size a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_void_ptr__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11783 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_void_ptr__m_hashTable_set :: ( BtHashMap_btHashPtr_void_ptr_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashPtr_void_ptr__m_hashTable_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_void_ptr__m_hashTable_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11787 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_void_ptr__m_hashTable_get :: ( BtHashMap_btHashPtr_void_ptr_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashPtr_void_ptr__m_hashTable_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_void_ptr__m_hashTable_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11791 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_void_ptr__m_keyArray_set :: ( BtHashMap_btHashPtr_void_ptr_Class bc , BtAlignedObjectArray_btHashPtr_Class a ) => bc -> a -> IO ()
btHashMap_btHashPtr_void_ptr__m_keyArray_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_void_ptr__m_keyArray_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11795 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_void_ptr__m_keyArray_get :: ( BtHashMap_btHashPtr_void_ptr_Class bc ) => bc -> IO (BtAlignedObjectArray_btHashPtr_)
btHashMap_btHashPtr_void_ptr__m_keyArray_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_void_ptr__m_keyArray_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btHashPtr_ res >>= \res' ->
  return (res')
{-# LINE 11799 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_void_ptr__m_next_set :: ( BtHashMap_btHashPtr_void_ptr_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashPtr_void_ptr__m_next_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_void_ptr__m_next_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11803 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_void_ptr__m_next_get :: ( BtHashMap_btHashPtr_void_ptr_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashPtr_void_ptr__m_next_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_void_ptr__m_next_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11807 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_void_ptr__m_valueArray_set :: ( BtHashMap_btHashPtr_void_ptr_Class bc , BtAlignedObjectArray_void_ptr_Class a ) => bc -> a -> IO ()
btHashMap_btHashPtr_void_ptr__m_valueArray_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashPtr_void_ptr__m_valueArray_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11811 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashPtr_void_ptr__m_valueArray_get :: ( BtHashMap_btHashPtr_void_ptr_Class bc ) => bc -> IO (BtAlignedObjectArray_void_ptr_)
btHashMap_btHashPtr_void_ptr__m_valueArray_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashPtr_void_ptr__m_valueArray_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_void_ptr_ res >>= \res' ->
  return (res')
{-# LINE 11815 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btHashMap<btHashString, int>
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#221>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashString_int_ :: IO (BtHashMap_btHashString_int_)
btHashMap_btHashString_int_ =
  btHashMap_btHashString_int_'_ >>= \res ->
  mkBtHashMap_btHashString_int_ res >>= \res' ->
  return (res')
{-# LINE 11820 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btHashMap_btHashString_int__free :: ( BtHashMap_btHashString_int_Class bc ) => bc -> IO ()
btHashMap_btHashString_int__free a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashString_int__free'_ a1' >>= \res ->
  return ()
{-# LINE 11821 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#423>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashString_int__findIndex :: ( BtHashMap_btHashString_int_Class bc , BtHashStringClass p0 ) => bc -> p0 -> IO (Int)
btHashMap_btHashString_int__findIndex a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashString_int__findIndex'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11827 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#440>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashString_int__clear :: ( BtHashMap_btHashString_int_Class bc ) => bc -> IO ()
btHashMap_btHashString_int__clear a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashString_int__clear'_ a1' >>= \res ->
  return ()
{-# LINE 11832 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#230>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashString_int__growTables :: ( BtHashMap_btHashString_int_Class bc , BtHashStringClass p0 ) => bc -> p0 -> IO ()
btHashMap_btHashString_int__growTables a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashString_int__growTables'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11838 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#379>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashString_int__size :: ( BtHashMap_btHashString_int_Class bc ) => bc -> IO (Int)
btHashMap_btHashString_int__size a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashString_int__size'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11843 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashString_int__m_hashTable_set :: ( BtHashMap_btHashString_int_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashString_int__m_hashTable_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashString_int__m_hashTable_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11847 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#224>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashString_int__m_hashTable_get :: ( BtHashMap_btHashString_int_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashString_int__m_hashTable_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashString_int__m_hashTable_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11851 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashString_int__m_keyArray_set :: ( BtHashMap_btHashString_int_Class bc , BtAlignedObjectArray_btHashString_Class a ) => bc -> a -> IO ()
btHashMap_btHashString_int__m_keyArray_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashString_int__m_keyArray_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11855 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#228>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashString_int__m_keyArray_get :: ( BtHashMap_btHashString_int_Class bc ) => bc -> IO (BtAlignedObjectArray_btHashString_)
btHashMap_btHashString_int__m_keyArray_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashString_int__m_keyArray_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_btHashString_ res >>= \res' ->
  return (res')
{-# LINE 11859 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashString_int__m_next_set :: ( BtHashMap_btHashString_int_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashString_int__m_next_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashString_int__m_next_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11863 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#225>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashString_int__m_next_get :: ( BtHashMap_btHashString_int_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashString_int__m_next_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashString_int__m_next_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11867 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashString_int__m_valueArray_set :: ( BtHashMap_btHashString_int_Class bc , BtAlignedObjectArray_int_Class a ) => bc -> a -> IO ()
btHashMap_btHashString_int__m_valueArray_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashMap_btHashString_int__m_valueArray_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11871 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#227>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashMap_btHashString_int__m_valueArray_get :: ( BtHashMap_btHashString_int_Class bc ) => bc -> IO (BtAlignedObjectArray_int_)
btHashMap_btHashString_int__m_valueArray_get a1 =
  withBt a1 $ \a1' -> 
  btHashMap_btHashString_int__m_valueArray_get'_ a1' >>= \res ->
  mkBtAlignedObjectArray_int_ res >>= \res' ->
  return (res')
{-# LINE 11875 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btHashPtr
btHashPtr_free :: ( BtHashPtrClass bc ) => bc -> IO ()
btHashPtr_free a1 =
  withBt a1 $ \a1' -> 
  btHashPtr_free'_ a1' >>= \res ->
  return ()
{-# LINE 11877 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#139>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashPtr_getHash :: ( BtHashPtrClass bc ) => bc -> IO (Word32)
btHashPtr_getHash a1 =
  withBt a1 $ \a1' -> 
  btHashPtr_getHash'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11882 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#133>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashPtr_equals :: ( BtHashPtrClass bc , BtHashPtrClass p0 ) => bc -> p0 -> IO (Bool)
btHashPtr_equals a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashPtr_equals'_ a1' a2' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 11888 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btHashString
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#33>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashString :: String -> IO (BtHashString)
btHashString a1 =
  withCString a1 $ \a1' -> 
  btHashString'_ a1' >>= \res ->
  mkBtHashString res >>= \res' ->
  return (res')
{-# LINE 11893 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btHashString_free :: ( BtHashStringClass bc ) => bc -> IO ()
btHashString_free a1 =
  withBt a1 $ \a1' -> 
  btHashString_free'_ a1' >>= \res ->
  return ()
{-# LINE 11894 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#28>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashString_getHash :: ( BtHashStringClass bc ) => bc -> IO (Word32)
btHashString_getHash a1 =
  withBt a1 $ \a1' -> 
  btHashString_getHash'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11899 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#66>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashString_equals :: ( BtHashStringClass bc , BtHashStringClass p0 ) => bc -> p0 -> IO (Bool)
btHashString_equals a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btHashString_equals'_ a1' a2' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 11905 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#51>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashString_portableStringCompare :: ( BtHashStringClass bc ) => bc -> String -> String -> IO (Int)
btHashString_portableStringCompare a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  btHashString_portableStringCompare'_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11912 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#26>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashString_m_hash_set :: ( BtHashStringClass bc ) => bc -> Word32 -> IO ()
btHashString_m_hash_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btHashString_m_hash_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11916 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#26>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashString_m_hash_get :: ( BtHashStringClass bc ) => bc -> IO (Word32)
btHashString_m_hash_get a1 =
  withBt a1 $ \a1' -> 
  btHashString_m_hash_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 11920 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#25>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashString_m_string_set :: ( BtHashStringClass bc ) => bc -> String -> IO ()
btHashString_m_string_set a1 a2 =
  withBt a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  btHashString_m_string_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 11924 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.h?r=2223#25>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btHashMap.cpp?r=2223>
-}
btHashString_m_string_get :: ( BtHashStringClass bc ) => bc -> IO (String)
btHashString_m_string_get a1 =
  withBt a1 $ \a1' -> 
  btHashString_m_string_get'_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')
{-# LINE 11928 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btIDebugDraw
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#112>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_draw3dText :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> String -> IO (Vec3)
btIDebugDraw_draw3dText a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  btIDebugDraw_draw3dText'_ a1' a2' a3' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11936 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#112>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_draw3dText' :: ( BtIDebugDrawClass bc ) => bc -> String -> IO (Vec3)
btIDebugDraw_draw3dText' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  withCString a3 $ \a3' -> 
  btIDebugDraw_draw3dText''_ a1' a2' a3' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 11943 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#282>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawBox :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> IO (Vec3, Vec3, Vec3)
btIDebugDraw_drawBox a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btIDebugDraw_drawBox'_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 11951 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#282>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawBox' :: ( BtIDebugDrawClass bc ) => bc -> IO (Vec3, Vec3, Vec3)
btIDebugDraw_drawBox' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  btIDebugDraw_drawBox''_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 11959 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#282>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawBox0 :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> IO (Vec3, Vec3, Vec3)
btIDebugDraw_drawBox0 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btIDebugDraw_drawBox0'_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 11967 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#282>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawBox0' :: ( BtIDebugDrawClass bc ) => bc -> IO (Vec3, Vec3, Vec3)
btIDebugDraw_drawBox0' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  btIDebugDraw_drawBox0''_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 11975 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#297>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawBox1 :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Vec3 -> Transform -> Vec3 -> IO (Vec3, Vec3, Transform, Vec3)
btIDebugDraw_drawBox1 a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withTransform a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btIDebugDraw_drawBox1'_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')
{-# LINE 11984 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#297>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawBox1' :: ( BtIDebugDrawClass bc ) => bc -> IO (Vec3, Vec3, Transform, Vec3)
btIDebugDraw_drawBox1' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaTransform $ \a4' -> 
  allocaVec3 $ \a5' -> 
  btIDebugDraw_drawBox1''_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')
{-# LINE 11993 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#375>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawCone :: ( BtIDebugDrawClass bc ) => bc -> Float -> Float -> Int -> Transform -> Vec3 -> IO (Transform, Vec3)
btIDebugDraw_drawCone a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = fromIntegral a4} in 
  withTransform a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  btIDebugDraw_drawCone'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekTransform  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a5'', a6'')
{-# LINE 12003 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#375>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawCone' :: ( BtIDebugDrawClass bc ) => bc -> Float -> Float -> Int -> IO (Transform, Vec3)
btIDebugDraw_drawCone' a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = fromIntegral a4} in 
  allocaTransform $ \a5' -> 
  allocaVec3 $ \a6' -> 
  btIDebugDraw_drawCone''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekTransform  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a5'', a6'')
{-# LINE 12013 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#313>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawCapsule :: ( BtIDebugDrawClass bc ) => bc -> Float -> Float -> Int -> Transform -> Vec3 -> IO (Transform, Vec3)
btIDebugDraw_drawCapsule a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = fromIntegral a4} in 
  withTransform a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  btIDebugDraw_drawCapsule'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekTransform  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a5'', a6'')
{-# LINE 12023 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#313>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawCapsule' :: ( BtIDebugDrawClass bc ) => bc -> Float -> Float -> Int -> IO (Transform, Vec3)
btIDebugDraw_drawCapsule' a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = fromIntegral a4} in 
  allocaTransform $ \a5' -> 
  allocaVec3 $ \a6' -> 
  btIDebugDraw_drawCapsule''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekTransform  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a5'', a6'')
{-# LINE 12033 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#156>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawArc :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> Float -> Float -> Float -> Float -> Vec3 -> Bool -> Float -> IO (Vec3, Vec3, Vec3, Vec3)
btIDebugDraw_drawArc a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  let {a7' = realToFrac a7} in 
  let {a8' = realToFrac a8} in 
  withVec3 a9 $ \a9' -> 
  let {a10' = fromBool a10} in 
  let {a11' = realToFrac a11} in 
  btIDebugDraw_drawArc'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a9'>>= \a9'' -> 
  return (a2'', a3'', a4'', a9'')
{-# LINE 12048 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#156>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawArc' :: ( BtIDebugDrawClass bc ) => bc -> Float -> Float -> Float -> Float -> Bool -> Float -> IO (Vec3, Vec3, Vec3, Vec3)
btIDebugDraw_drawArc' a1 a5 a6 a7 a8 a10 a11 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  let {a7' = realToFrac a7} in 
  let {a8' = realToFrac a8} in 
  allocaVec3 $ \a9' -> 
  let {a10' = fromBool a10} in 
  let {a11' = realToFrac a11} in 
  btIDebugDraw_drawArc''_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a9'>>= \a9'' -> 
  return (a2'', a3'', a4'', a9'')
{-# LINE 12063 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#356>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawCylinder :: ( BtIDebugDrawClass bc ) => bc -> Float -> Float -> Int -> Transform -> Vec3 -> IO (Transform, Vec3)
btIDebugDraw_drawCylinder a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = fromIntegral a4} in 
  withTransform a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  btIDebugDraw_drawCylinder'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekTransform  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a5'', a6'')
{-# LINE 12073 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#356>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawCylinder' :: ( BtIDebugDrawClass bc ) => bc -> Float -> Float -> Int -> IO (Transform, Vec3)
btIDebugDraw_drawCylinder' a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = fromIntegral a4} in 
  allocaTransform $ \a5' -> 
  allocaVec3 $ \a6' -> 
  btIDebugDraw_drawCylinder''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekTransform  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a5'', a6'')
{-# LINE 12083 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#110>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_reportErrorWarning :: ( BtIDebugDrawClass bc ) => bc -> String -> IO ()
btIDebugDraw_reportErrorWarning a1 a2 =
  withBt a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  btIDebugDraw_reportErrorWarning'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12089 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawTriangle :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> Vec3 -> Vec3 -> Vec3 -> Vec3 -> Float -> IO (Vec3, Vec3, Vec3, Vec3, Vec3, Vec3, Vec3)
btIDebugDraw_drawTriangle a1 a2 a3 a4 a5 a6 a7 a8 a9 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  withVec3 a7 $ \a7' -> 
  withVec3 a8 $ \a8' -> 
  let {a9' = realToFrac a9} in 
  btIDebugDraw_drawTriangle'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  return (a2'', a3'', a4'', a5'', a6'', a7'', a8'')
{-# LINE 12102 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawTriangle' :: ( BtIDebugDrawClass bc ) => bc -> Float -> IO (Vec3, Vec3, Vec3, Vec3, Vec3, Vec3, Vec3)
btIDebugDraw_drawTriangle' a1 a9 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  allocaVec3 $ \a6' -> 
  allocaVec3 $ \a7' -> 
  allocaVec3 $ \a8' -> 
  let {a9' = realToFrac a9} in 
  btIDebugDraw_drawTriangle''_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  return (a2'', a3'', a4'', a5'', a6'', a7'', a8'')
{-# LINE 12115 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawTriangle0 :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> Vec3 -> Vec3 -> Vec3 -> Vec3 -> Float -> IO (Vec3, Vec3, Vec3, Vec3, Vec3, Vec3, Vec3)
btIDebugDraw_drawTriangle0 a1 a2 a3 a4 a5 a6 a7 a8 a9 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  withVec3 a6 $ \a6' -> 
  withVec3 a7 $ \a7' -> 
  withVec3 a8 $ \a8' -> 
  let {a9' = realToFrac a9} in 
  btIDebugDraw_drawTriangle0'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  return (a2'', a3'', a4'', a5'', a6'', a7'', a8'')
{-# LINE 12128 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#97>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawTriangle0' :: ( BtIDebugDrawClass bc ) => bc -> Float -> IO (Vec3, Vec3, Vec3, Vec3, Vec3, Vec3, Vec3)
btIDebugDraw_drawTriangle0' a1 a9 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  allocaVec3 $ \a6' -> 
  allocaVec3 $ \a7' -> 
  allocaVec3 $ \a8' -> 
  let {a9' = realToFrac a9} in 
  btIDebugDraw_drawTriangle0''_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  peekVec3  a8'>>= \a8'' -> 
  return (a2'', a3'', a4'', a5'', a6'', a7'', a8'')
{-# LINE 12141 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#101>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawTriangle1 :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> Vec3 -> Float -> IO (Vec3, Vec3, Vec3, Vec3)
btIDebugDraw_drawTriangle1 a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  let {a6' = realToFrac a6} in 
  btIDebugDraw_drawTriangle1'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')
{-# LINE 12151 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#101>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawTriangle1' :: ( BtIDebugDrawClass bc ) => bc -> Float -> IO (Vec3, Vec3, Vec3, Vec3)
btIDebugDraw_drawTriangle1' a1 a6 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  let {a6' = realToFrac a6} in 
  btIDebugDraw_drawTriangle1''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')
{-# LINE 12161 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#116>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_getDebugMode :: ( BtIDebugDrawClass bc ) => bc -> IO (Int)
btIDebugDraw_getDebugMode a1 =
  withBt a1 $ \a1' -> 
  btIDebugDraw_getDebugMode'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 12166 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawLine :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> IO (Vec3, Vec3, Vec3)
btIDebugDraw_drawLine a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btIDebugDraw_drawLine'_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 12174 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawLine' :: ( BtIDebugDrawClass bc ) => bc -> IO (Vec3, Vec3, Vec3)
btIDebugDraw_drawLine' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  btIDebugDraw_drawLine''_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 12182 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawLine0 :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> IO (Vec3, Vec3, Vec3)
btIDebugDraw_drawLine0 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btIDebugDraw_drawLine0'_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 12190 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#54>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawLine0' :: ( BtIDebugDrawClass bc ) => bc -> IO (Vec3, Vec3, Vec3)
btIDebugDraw_drawLine0' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  btIDebugDraw_drawLine0''_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 12198 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#56>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawLine1 :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> Vec3 -> IO (Vec3, Vec3, Vec3, Vec3)
btIDebugDraw_drawLine1 a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btIDebugDraw_drawLine1'_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')
{-# LINE 12207 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#56>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawLine1' :: ( BtIDebugDrawClass bc ) => bc -> IO (Vec3, Vec3, Vec3, Vec3)
btIDebugDraw_drawLine1' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  btIDebugDraw_drawLine1''_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')
{-# LINE 12216 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawTransform :: ( BtIDebugDrawClass bc ) => bc -> Transform -> Float -> IO (Transform)
btIDebugDraw_drawTransform a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btIDebugDraw_drawTransform'_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 12223 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#147>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawTransform' :: ( BtIDebugDrawClass bc ) => bc -> Float -> IO (Transform)
btIDebugDraw_drawTransform' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  let {a3' = realToFrac a3} in 
  btIDebugDraw_drawTransform''_ a1' a2' a3' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 12230 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#118>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawAabb :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> IO (Vec3, Vec3, Vec3)
btIDebugDraw_drawAabb a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btIDebugDraw_drawAabb'_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 12238 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#118>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawAabb' :: ( BtIDebugDrawClass bc ) => bc -> IO (Vec3, Vec3, Vec3)
btIDebugDraw_drawAabb' a1 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  btIDebugDraw_drawAabb''_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 12246 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#400>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawPlane :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Float -> Transform -> Vec3 -> IO (Vec3, Transform, Vec3)
btIDebugDraw_drawPlane a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  withTransform a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btIDebugDraw_drawPlane'_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a4'', a5'')
{-# LINE 12255 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#400>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawPlane' :: ( BtIDebugDrawClass bc ) => bc -> Float -> IO (Vec3, Transform, Vec3)
btIDebugDraw_drawPlane' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  allocaTransform $ \a4' -> 
  allocaVec3 $ \a5' -> 
  btIDebugDraw_drawPlane''_ a1' a2' a3' a4' a5' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekTransform  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a4'', a5'')
{-# LINE 12264 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#108>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawContactPoint :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Vec3 -> Float -> Int -> Vec3 -> IO (Vec3, Vec3, Vec3)
btIDebugDraw_drawContactPoint a1 a2 a3 a4 a5 a6 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  let {a5' = fromIntegral a5} in 
  withVec3 a6 $ \a6' -> 
  btIDebugDraw_drawContactPoint'_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a2'', a3'', a6'')
{-# LINE 12274 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#108>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawContactPoint' :: ( BtIDebugDrawClass bc ) => bc -> Float -> Int -> IO (Vec3, Vec3, Vec3)
btIDebugDraw_drawContactPoint' a1 a4 a5 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  let {a5' = fromIntegral a5} in 
  allocaVec3 $ \a6' -> 
  btIDebugDraw_drawContactPoint''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a2'', a3'', a6'')
{-# LINE 12284 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#114>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_setDebugMode :: ( BtIDebugDrawClass bc ) => bc -> Int -> IO ()
btIDebugDraw_setDebugMode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btIDebugDraw_setDebugMode'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12290 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#181>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawSpherePatch :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Vec3 -> Vec3 -> Float -> Float -> Float -> Float -> Float -> Vec3 -> Float -> IO (Vec3, Vec3, Vec3, Vec3)
btIDebugDraw_drawSpherePatch a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  let {a7' = realToFrac a7} in 
  let {a8' = realToFrac a8} in 
  let {a9' = realToFrac a9} in 
  withVec3 a10 $ \a10' -> 
  let {a11' = realToFrac a11} in 
  btIDebugDraw_drawSpherePatch'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a10'>>= \a10'' -> 
  return (a2'', a3'', a4'', a10'')
{-# LINE 12305 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#181>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawSpherePatch' :: ( BtIDebugDrawClass bc ) => bc -> Float -> Float -> Float -> Float -> Float -> Float -> IO (Vec3, Vec3, Vec3, Vec3)
btIDebugDraw_drawSpherePatch' a1 a5 a6 a7 a8 a9 a11 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  let {a7' = realToFrac a7} in 
  let {a8' = realToFrac a8} in 
  let {a9' = realToFrac a9} in 
  allocaVec3 $ \a10' -> 
  let {a11' = realToFrac a11} in 
  btIDebugDraw_drawSpherePatch''_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' a11' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a10'>>= \a10'' -> 
  return (a2'', a3'', a4'', a10'')
{-# LINE 12320 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawSphere :: ( BtIDebugDrawClass bc ) => bc -> Float -> Transform -> Vec3 -> IO (Transform, Vec3)
btIDebugDraw_drawSphere a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  withTransform a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btIDebugDraw_drawSphere'_ a1' a2' a3' a4' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a3'', a4'')
{-# LINE 12328 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawSphere' :: ( BtIDebugDrawClass bc ) => bc -> Float -> IO (Transform, Vec3)
btIDebugDraw_drawSphere' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  allocaTransform $ \a3' -> 
  allocaVec3 $ \a4' -> 
  btIDebugDraw_drawSphere''_ a1' a2' a3' a4' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a3'', a4'')
{-# LINE 12336 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawSphere0 :: ( BtIDebugDrawClass bc ) => bc -> Float -> Transform -> Vec3 -> IO (Transform, Vec3)
btIDebugDraw_drawSphere0 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  withTransform a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btIDebugDraw_drawSphere0'_ a1' a2' a3' a4' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a3'', a4'')
{-# LINE 12344 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#62>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawSphere0' :: ( BtIDebugDrawClass bc ) => bc -> Float -> IO (Transform, Vec3)
btIDebugDraw_drawSphere0' a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  allocaTransform $ \a3' -> 
  allocaVec3 $ \a4' -> 
  btIDebugDraw_drawSphere0''_ a1' a2' a3' a4' >>= \res ->
  peekTransform  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a3'', a4'')
{-# LINE 12352 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawSphere1 :: ( BtIDebugDrawClass bc ) => bc -> Vec3 -> Float -> Vec3 -> IO (Vec3, Vec3)
btIDebugDraw_drawSphere1 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  withVec3 a4 $ \a4' -> 
  btIDebugDraw_drawSphere1'_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a4'')
{-# LINE 12360 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btIDebugDraw.cpp?r=2223>
-}
btIDebugDraw_drawSphere1' :: ( BtIDebugDrawClass bc ) => bc -> Float -> IO (Vec3, Vec3)
btIDebugDraw_drawSphere1' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  allocaVec3 $ \a4' -> 
  btIDebugDraw_drawSphere1''_ a1' a2' a3' a4' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a4'')
{-# LINE 12368 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btMatrix3x3DoubleData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btMatrix3x3.h?r=2223#732>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btMatrix3x3.cpp?r=2223>
-}
btMatrix3x3DoubleData :: IO (BtMatrix3x3DoubleData)
btMatrix3x3DoubleData =
  btMatrix3x3DoubleData'_ >>= \res ->
  mkBtMatrix3x3DoubleData res >>= \res' ->
  return (res')
{-# LINE 12373 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btMatrix3x3DoubleData_free :: ( BtMatrix3x3DoubleDataClass bc ) => bc -> IO ()
btMatrix3x3DoubleData_free a1 =
  withBt a1 $ \a1' -> 
  btMatrix3x3DoubleData_free'_ a1' >>= \res ->
  return ()
{-# LINE 12374 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btMatrix3x3FloatData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btMatrix3x3.h?r=2223#726>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btMatrix3x3.cpp?r=2223>
-}
btMatrix3x3FloatData :: IO (BtMatrix3x3FloatData)
btMatrix3x3FloatData =
  btMatrix3x3FloatData'_ >>= \res ->
  mkBtMatrix3x3FloatData res >>= \res' ->
  return (res')
{-# LINE 12379 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btMatrix3x3FloatData_free :: ( BtMatrix3x3FloatDataClass bc ) => bc -> IO ()
btMatrix3x3FloatData_free a1 =
  withBt a1 $ \a1' -> 
  btMatrix3x3FloatData_free'_ a1' >>= \res ->
  return ()
{-# LINE 12380 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btMotionState
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btMotionState.h?r=2223#35>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btMotionState.cpp?r=2223>
-}
btMotionState_setWorldTransform :: ( BtMotionStateClass bc ) => bc -> Transform -> IO (Transform)
btMotionState_setWorldTransform a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btMotionState_setWorldTransform'_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 12387 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btMotionState.h?r=2223#35>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btMotionState.cpp?r=2223>
-}
btMotionState_setWorldTransform' :: ( BtMotionStateClass bc ) => bc -> IO (Transform)
btMotionState_setWorldTransform' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btMotionState_setWorldTransform''_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 12393 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btMotionState.h?r=2223#32>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btMotionState.cpp?r=2223>
-}
btMotionState_getWorldTransform :: ( BtMotionStateClass bc ) => bc -> Transform -> IO (Transform)
btMotionState_getWorldTransform a1 a2 =
  withBt a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  btMotionState_getWorldTransform'_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 12399 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btMotionState.h?r=2223#32>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btMotionState.cpp?r=2223>
-}
btMotionState_getWorldTransform' :: ( BtMotionStateClass bc ) => bc -> IO (Transform)
btMotionState_getWorldTransform' a1 =
  withBt a1 $ \a1' -> 
  allocaTransform $ \a2' -> 
  btMotionState_getWorldTransform''_ a1' a2' >>= \res ->
  peekTransform  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 12405 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btPointerUid
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#129>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btPointerUid :: IO (BtPointerUid)
btPointerUid =
  btPointerUid'_ >>= \res ->
  mkBtPointerUid res >>= \res' ->
  return (res')
{-# LINE 12410 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btPointerUid_free :: ( BtPointerUidClass bc ) => bc -> IO ()
btPointerUid_free a1 =
  withBt a1 $ \a1' -> 
  btPointerUid_free'_ a1' >>= \res ->
  return ()
{-# LINE 12411 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btQuadWord
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#129>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord0 :: IO (BtQuadWord)
btQuadWord0 =
  btQuadWord0'_ >>= \res ->
  mkBtQuadWord res >>= \res' ->
  return (res')
{-# LINE 12416 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#139>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord1 :: Float -> Float -> Float -> IO (BtQuadWord)
btQuadWord1 a1 a2 a3 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  btQuadWord1'_ a1' a2' a3' >>= \res ->
  mkBtQuadWord res >>= \res' ->
  return (res')
{-# LINE 12420 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#150>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord2 :: Float -> Float -> Float -> Float -> IO (BtQuadWord)
btQuadWord2 a1 a2 a3 a4 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  btQuadWord2'_ a1' a2' a3' a4' >>= \res ->
  mkBtQuadWord res >>= \res' ->
  return (res')
{-# LINE 12424 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btQuadWord_free :: ( BtQuadWordClass bc ) => bc -> IO ()
btQuadWord_free a1 =
  withBt a1 $ \a1' -> 
  btQuadWord_free'_ a1' >>= \res ->
  return ()
{-# LINE 12425 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#168>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_setMin :: ( BtQuadWordClass bc , BtQuadWordClass p0 ) => bc -> p0 -> IO ()
btQuadWord_setMin a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btQuadWord_setMin'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12431 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#100>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_setValue :: ( BtQuadWordClass bc ) => bc -> Float -> Float -> Float -> IO ()
btQuadWord_setValue a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  btQuadWord_setValue'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 12439 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#100>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_setValue0 :: ( BtQuadWordClass bc ) => bc -> Float -> Float -> Float -> IO ()
btQuadWord_setValue0 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  btQuadWord_setValue0'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 12447 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#121>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_setValue1 :: ( BtQuadWordClass bc ) => bc -> Float -> Float -> Float -> Float -> IO ()
btQuadWord_setValue1 a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  btQuadWord_setValue1'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 12456 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#158>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_setMax :: ( BtQuadWordClass bc , BtQuadWordClass p0 ) => bc -> p0 -> IO ()
btQuadWord_setMax a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btQuadWord_setMax'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12462 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#57>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_getX :: ( BtQuadWordClass bc ) => bc -> IO (Float)
btQuadWord_getX a1 =
  withBt a1 $ \a1' -> 
  btQuadWord_getX'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 12467 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#59>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_getY :: ( BtQuadWordClass bc ) => bc -> IO (Float)
btQuadWord_getY a1 =
  withBt a1 $ \a1' -> 
  btQuadWord_getY'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 12472 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#61>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_getZ :: ( BtQuadWordClass bc ) => bc -> IO (Float)
btQuadWord_getZ a1 =
  withBt a1 $ \a1' -> 
  btQuadWord_getZ'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 12477 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#69>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_setW :: ( BtQuadWordClass bc ) => bc -> Float -> IO ()
btQuadWord_setW a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btQuadWord_setW'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12483 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#77>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_w :: ( BtQuadWordClass bc ) => bc -> IO (Float)
btQuadWord_w a1 =
  withBt a1 $ \a1' -> 
  btQuadWord_w'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 12488 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#73>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_y :: ( BtQuadWordClass bc ) => bc -> IO (Float)
btQuadWord_y a1 =
  withBt a1 $ \a1' -> 
  btQuadWord_y'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 12493 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#71>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_x :: ( BtQuadWordClass bc ) => bc -> IO (Float)
btQuadWord_x a1 =
  withBt a1 $ \a1' -> 
  btQuadWord_x'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 12498 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#75>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_z :: ( BtQuadWordClass bc ) => bc -> IO (Float)
btQuadWord_z a1 =
  withBt a1 $ \a1' -> 
  btQuadWord_z'_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 12503 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#63>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_setX :: ( BtQuadWordClass bc ) => bc -> Float -> IO ()
btQuadWord_setX a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btQuadWord_setX'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12509 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#65>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_setY :: ( BtQuadWordClass bc ) => bc -> Float -> IO ()
btQuadWord_setY a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btQuadWord_setY'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12515 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.h?r=2223#67>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btQuadWord.cpp?r=2223>
-}
btQuadWord_setZ :: ( BtQuadWordClass bc ) => bc -> Float -> IO ()
btQuadWord_setZ a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  btQuadWord_setZ'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12521 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btSerializer
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#100>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btSerializer_setSerializationFlags :: ( BtSerializerClass bc ) => bc -> Int -> IO ()
btSerializer_setSerializationFlags a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btSerializer_setSerializationFlags'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12528 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#78>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btSerializer_getCurrentBufferSize :: ( BtSerializerClass bc ) => bc -> IO (Int)
btSerializer_getCurrentBufferSize a1 =
  withBt a1 $ \a1' -> 
  btSerializer_getCurrentBufferSize'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 12533 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#88>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btSerializer_startSerialization :: ( BtSerializerClass bc ) => bc -> IO ()
btSerializer_startSerialization a1 =
  withBt a1 $ \a1' -> 
  btSerializer_startSerialization'_ a1' >>= \res ->
  return ()
{-# LINE 12538 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#98>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btSerializer_getSerializationFlags :: ( BtSerializerClass bc ) => bc -> IO (Int)
btSerializer_getSerializationFlags a1 =
  withBt a1 $ \a1' -> 
  btSerializer_getSerializationFlags'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 12543 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#90>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btSerializer_finishSerialization :: ( BtSerializerClass bc ) => bc -> IO ()
btSerializer_finishSerialization a1 =
  withBt a1 $ \a1' -> 
  btSerializer_finishSerialization'_ a1' >>= \res ->
  return ()
{-# LINE 12548 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#86>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btSerializer_getUniquePointer :: ( BtSerializerClass bc ) => bc -> VoidPtr -> IO (VoidPtr)
btSerializer_getUniquePointer a1 a2 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  btSerializer_getUniquePointer'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 12554 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btSerializer_finalizeChunk :: ( BtSerializerClass bc , BtChunkClass p0 ) => bc -> p0 -> String -> Int -> VoidPtr -> IO ()
btSerializer_finalizeChunk a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  let {a4' = fromIntegral a4} in 
  withVoidPtr a5 $ \a5' -> 
  btSerializer_finalizeChunk'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 12563 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#96>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btSerializer_serializeName :: ( BtSerializerClass bc ) => bc -> String -> IO ()
btSerializer_serializeName a1 a2 =
  withBt a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  btSerializer_serializeName'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12569 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.h?r=2223#84>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btSerializer.cpp?r=2223>
-}
btSerializer_findPointer :: ( BtSerializerClass bc ) => bc -> VoidPtr -> IO (VoidPtr)
btSerializer_findPointer a1 a2 =
  withBt a1 $ \a1' -> 
  withVoidPtr a2 $ \a2' -> 
  btSerializer_findPointer'_ a1' a2' >>= \res ->
  mkVoidPtr res >>= \res' ->
  return (res')
{-# LINE 12575 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btStackAlloc
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#38>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc :: Word32 -> IO (BtStackAlloc)
btStackAlloc a1 =
  let {a1' = fromIntegral a1} in 
  btStackAlloc'_ a1' >>= \res ->
  mkBtStackAlloc res >>= \res' ->
  return (res')
{-# LINE 12580 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btStackAlloc_free :: ( BtStackAllocClass bc ) => bc -> IO ()
btStackAlloc_free a1 =
  withBt a1 $ \a1' -> 
  btStackAlloc_free'_ a1' >>= \res ->
  return ()
{-# LINE 12581 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#41>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_create :: ( BtStackAllocClass bc ) => bc -> Word32 -> IO ()
btStackAlloc_create a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btStackAlloc_create'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12587 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#101>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_ctor :: ( BtStackAllocClass bc ) => bc -> IO ()
btStackAlloc_ctor a1 =
  withBt a1 $ \a1' -> 
  btStackAlloc_ctor'_ a1' >>= \res ->
  return ()
{-# LINE 12592 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#47>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_destroy :: ( BtStackAllocClass bc ) => bc -> IO ()
btStackAlloc_destroy a1 =
  withBt a1 $ \a1' -> 
  btStackAlloc_destroy'_ a1' >>= \res ->
  return ()
{-# LINE 12597 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#81>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_beginBlock :: ( BtStackAllocClass bc ) => bc -> IO (BtBlock)
btStackAlloc_beginBlock a1 =
  withBt a1 $ \a1' -> 
  btStackAlloc_beginBlock'_ a1' >>= \res ->
  mkBtBlock res >>= \res' ->
  return (res')
{-# LINE 12602 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#63>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_getAvailableMemory :: ( BtStackAllocClass bc ) => bc -> IO (Int)
btStackAlloc_getAvailableMemory a1 =
  withBt a1 $ \a1' -> 
  btStackAlloc_getAvailableMemory'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 12607 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#89>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_endBlock :: ( BtStackAllocClass bc , BtBlockClass p0 ) => bc -> p0 -> IO ()
btStackAlloc_endBlock a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btStackAlloc_endBlock'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12613 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#110>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_totalsize_set :: ( BtStackAllocClass bc ) => bc -> Word32 -> IO ()
btStackAlloc_totalsize_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btStackAlloc_totalsize_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12617 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#110>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_totalsize_get :: ( BtStackAllocClass bc ) => bc -> IO (Word32)
btStackAlloc_totalsize_get a1 =
  withBt a1 $ \a1' -> 
  btStackAlloc_totalsize_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 12621 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_usedsize_set :: ( BtStackAllocClass bc ) => bc -> Word32 -> IO ()
btStackAlloc_usedsize_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btStackAlloc_usedsize_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12625 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#111>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_usedsize_get :: ( BtStackAllocClass bc ) => bc -> IO (Word32)
btStackAlloc_usedsize_get a1 =
  withBt a1 $ \a1' -> 
  btStackAlloc_usedsize_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 12629 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#112>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_current_set :: ( BtStackAllocClass bc , BtBlockClass a ) => bc -> a -> IO ()
btStackAlloc_current_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btStackAlloc_current_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12633 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#112>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_current_get :: ( BtStackAllocClass bc ) => bc -> IO (BtBlock)
btStackAlloc_current_get a1 =
  withBt a1 $ \a1' -> 
  btStackAlloc_current_get'_ a1' >>= \res ->
  mkBtBlock res >>= \res' ->
  return (res')
{-# LINE 12637 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_ischild_set :: ( BtStackAllocClass bc ) => bc -> Bool -> IO ()
btStackAlloc_ischild_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  btStackAlloc_ischild_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12641 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.h?r=2223#113>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btStackAlloc.cpp?r=2223>
-}
btStackAlloc_ischild_get :: ( BtStackAllocClass bc ) => bc -> IO (Bool)
btStackAlloc_ischild_get a1 =
  withBt a1 $ \a1' -> 
  btStackAlloc_ischild_get'_ a1' >>= \res ->
  let {res' = toBool res} in
  return (res')
{-# LINE 12645 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btTransformDoubleData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.h?r=2223#262>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.cpp?r=2223>
-}
btTransformDoubleData :: IO (BtTransformDoubleData)
btTransformDoubleData =
  btTransformDoubleData'_ >>= \res ->
  mkBtTransformDoubleData res >>= \res' ->
  return (res')
{-# LINE 12650 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btTransformDoubleData_free :: ( BtTransformDoubleDataClass bc ) => bc -> IO ()
btTransformDoubleData_free a1 =
  withBt a1 $ \a1' -> 
  btTransformDoubleData_free'_ a1' >>= \res ->
  return ()
{-# LINE 12651 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.h?r=2223#263>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.cpp?r=2223>
-}
btTransformDoubleData_m_basis_set :: ( BtTransformDoubleDataClass bc , BtMatrix3x3DoubleDataClass a ) => bc -> a -> IO ()
btTransformDoubleData_m_basis_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btTransformDoubleData_m_basis_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12655 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.h?r=2223#263>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.cpp?r=2223>
-}
btTransformDoubleData_m_basis_get :: ( BtTransformDoubleDataClass bc ) => bc -> IO (BtMatrix3x3DoubleData)
btTransformDoubleData_m_basis_get a1 =
  withBt a1 $ \a1' -> 
  btTransformDoubleData_m_basis_get'_ a1' >>= \res ->
  mkBtMatrix3x3DoubleData res >>= \res' ->
  return (res')
{-# LINE 12659 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.h?r=2223#264>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.cpp?r=2223>
-}
btTransformDoubleData_m_origin_set :: ( BtTransformDoubleDataClass bc , BtVector3DoubleDataClass a ) => bc -> a -> IO ()
btTransformDoubleData_m_origin_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btTransformDoubleData_m_origin_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12663 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.h?r=2223#264>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.cpp?r=2223>
-}
btTransformDoubleData_m_origin_get :: ( BtTransformDoubleDataClass bc ) => bc -> IO (BtVector3DoubleData)
btTransformDoubleData_m_origin_get a1 =
  withBt a1 $ \a1' -> 
  btTransformDoubleData_m_origin_get'_ a1' >>= \res ->
  mkBtVector3DoubleData res >>= \res' ->
  return (res')
{-# LINE 12667 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btTransformFloatData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.h?r=2223#256>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.cpp?r=2223>
-}
btTransformFloatData :: IO (BtTransformFloatData)
btTransformFloatData =
  btTransformFloatData'_ >>= \res ->
  mkBtTransformFloatData res >>= \res' ->
  return (res')
{-# LINE 12672 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btTransformFloatData_free :: ( BtTransformFloatDataClass bc ) => bc -> IO ()
btTransformFloatData_free a1 =
  withBt a1 $ \a1' -> 
  btTransformFloatData_free'_ a1' >>= \res ->
  return ()
{-# LINE 12673 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.h?r=2223#257>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.cpp?r=2223>
-}
btTransformFloatData_m_basis_set :: ( BtTransformFloatDataClass bc , BtMatrix3x3FloatDataClass a ) => bc -> a -> IO ()
btTransformFloatData_m_basis_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btTransformFloatData_m_basis_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12677 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.h?r=2223#257>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.cpp?r=2223>
-}
btTransformFloatData_m_basis_get :: ( BtTransformFloatDataClass bc ) => bc -> IO (BtMatrix3x3FloatData)
btTransformFloatData_m_basis_get a1 =
  withBt a1 $ \a1' -> 
  btTransformFloatData_m_basis_get'_ a1' >>= \res ->
  mkBtMatrix3x3FloatData res >>= \res' ->
  return (res')
{-# LINE 12681 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.h?r=2223#258>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.cpp?r=2223>
-}
btTransformFloatData_m_origin_set :: ( BtTransformFloatDataClass bc , BtVector3FloatDataClass a ) => bc -> a -> IO ()
btTransformFloatData_m_origin_set a1 a2 =
  withBt a1 $ \a1' -> 
  withBt a2 $ \a2' -> 
  btTransformFloatData_m_origin_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12685 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.h?r=2223#258>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransform.cpp?r=2223>
-}
btTransformFloatData_m_origin_get :: ( BtTransformFloatDataClass bc ) => bc -> IO (BtVector3FloatData)
btTransformFloatData_m_origin_get a1 =
  withBt a1 $ \a1' -> 
  btTransformFloatData_m_origin_get'_ a1' >>= \res ->
  mkBtVector3FloatData res >>= \res' ->
  return (res')
{-# LINE 12689 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btTransformUtil
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#39>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btTransformUtil :: IO (BtTransformUtil)
btTransformUtil =
  btTransformUtil'_ >>= \res ->
  mkBtTransformUtil res >>= \res' ->
  return (res')
{-# LINE 12694 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btTransformUtil_free :: ( BtTransformUtilClass bc ) => bc -> IO ()
btTransformUtil_free a1 =
  withBt a1 $ \a1' -> 
  btTransformUtil_free'_ a1' >>= \res ->
  return ()
{-# LINE 12695 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#112>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btTransformUtil_calculateVelocity :: ( ) => Transform -> Transform -> Float -> Vec3 -> Vec3 -> IO (Transform, Transform, Vec3, Vec3)
btTransformUtil_calculateVelocity a1 a2 a3 a4 a5 =
  withTransform a1 $ \a1' -> 
  withTransform a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btTransformUtil_calculateVelocity'_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a1'>>= \a1'' -> 
  peekTransform  a2'>>= \a2'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a1'', a2'', a4'', a5'')
{-# LINE 12704 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#112>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btTransformUtil_calculateVelocity' :: ( ) => Float -> IO (Transform, Transform, Vec3, Vec3)
btTransformUtil_calculateVelocity' a3 =
  allocaTransform $ \a1' -> 
  allocaTransform $ \a2' -> 
  let {a3' = realToFrac a3} in 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  btTransformUtil_calculateVelocity''_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a1'>>= \a1'' -> 
  peekTransform  a2'>>= \a2'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a1'', a2'', a4'', a5'')
{-# LINE 12713 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#43>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btTransformUtil_integrateTransform :: ( ) => Transform -> Vec3 -> Vec3 -> Float -> Transform -> IO (Transform, Vec3, Vec3, Transform)
btTransformUtil_integrateTransform a1 a2 a3 a4 a5 =
  withTransform a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  withTransform a5 $ \a5' -> 
  btTransformUtil_integrateTransform'_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a1'>>= \a1'' -> 
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekTransform  a5'>>= \a5'' -> 
  return (a1'', a2'', a3'', a5'')
{-# LINE 12722 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#43>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btTransformUtil_integrateTransform' :: ( ) => Float -> IO (Transform, Vec3, Vec3, Transform)
btTransformUtil_integrateTransform' a4 =
  allocaTransform $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  allocaTransform $ \a5' -> 
  btTransformUtil_integrateTransform''_ a1' a2' a3' a4' a5' >>= \res ->
  peekTransform  a1'>>= \a1'' -> 
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekTransform  a5'>>= \a5'' -> 
  return (a1'', a2'', a3'', a5'')
{-# LINE 12731 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btTransformUtil_calculateVelocityQuaternion :: ( ) => Vec3 -> Vec3 -> UnitQuaternion -> UnitQuaternion -> Float -> Vec3 -> Vec3 -> IO (Vec3, Vec3, UnitQuaternion, UnitQuaternion, Vec3, Vec3)
btTransformUtil_calculateVelocityQuaternion a1 a2 a3 a4 a5 a6 a7 =
  withVec3 a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withUnitQuaternion a3 $ \a3' -> 
  withUnitQuaternion a4 $ \a4' -> 
  let {a5' = realToFrac a5} in 
  withVec3 a6 $ \a6' -> 
  withVec3 a7 $ \a7' -> 
  btTransformUtil_calculateVelocityQuaternion'_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
  peekVec3  a1'>>= \a1'' -> 
  peekVec3  a2'>>= \a2'' -> 
  peekUnitQuaternion  a3'>>= \a3'' -> 
  peekUnitQuaternion  a4'>>= \a4'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  return (a1'', a2'', a3'', a4'', a6'', a7'')
{-# LINE 12742 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.h?r=2223#82>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btTransformUtil.cpp?r=2223>
-}
btTransformUtil_calculateVelocityQuaternion' :: ( ) => Float -> IO (Vec3, Vec3, UnitQuaternion, UnitQuaternion, Vec3, Vec3)
btTransformUtil_calculateVelocityQuaternion' a5 =
  allocaVec3 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaUnitQuaternion $ \a3' -> 
  allocaUnitQuaternion $ \a4' -> 
  let {a5' = realToFrac a5} in 
  allocaVec3 $ \a6' -> 
  allocaVec3 $ \a7' -> 
  btTransformUtil_calculateVelocityQuaternion''_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
  peekVec3  a1'>>= \a1'' -> 
  peekVec3  a2'>>= \a2'' -> 
  peekUnitQuaternion  a3'>>= \a3'' -> 
  peekUnitQuaternion  a4'>>= \a4'' -> 
  peekVec3  a6'>>= \a6'' -> 
  peekVec3  a7'>>= \a7'' -> 
  return (a1'', a2'', a3'', a4'', a6'', a7'')
{-# LINE 12753 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btTypedObject
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btScalar.h?r=2223#512>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btScalar.cpp?r=2223>
-}
btTypedObject :: Int -> IO (BtTypedObject)
btTypedObject a1 =
  let {a1' = fromIntegral a1} in 
  btTypedObject'_ a1' >>= \res ->
  mkBtTypedObject res >>= \res' ->
  return (res')
{-# LINE 12758 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btTypedObject_free :: ( BtTypedObjectClass bc ) => bc -> IO ()
btTypedObject_free a1 =
  withBt a1 $ \a1' -> 
  btTypedObject_free'_ a1' >>= \res ->
  return ()
{-# LINE 12759 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btScalar.h?r=2223#517>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btScalar.cpp?r=2223>
-}
btTypedObject_getObjectType :: ( BtTypedObjectClass bc ) => bc -> IO (Int)
btTypedObject_getObjectType a1 =
  withBt a1 $ \a1' -> 
  btTypedObject_getObjectType'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 12764 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btScalar.h?r=2223#516>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btScalar.cpp?r=2223>
-}
btTypedObject_m_objectType_set :: ( BtTypedObjectClass bc ) => bc -> Int -> IO ()
btTypedObject_m_objectType_set a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btTypedObject_m_objectType_set'_ a1' a2' >>= \res ->
  return ()
{-# LINE 12768 "./Physics/Bullet/Raw/LinearMath.chs" #-}
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btScalar.h?r=2223#516>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btScalar.cpp?r=2223>
-}
btTypedObject_m_objectType_get :: ( BtTypedObjectClass bc ) => bc -> IO (Int)
btTypedObject_m_objectType_get a1 =
  withBt a1 $ \a1' -> 
  btTypedObject_m_objectType_get'_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')
{-# LINE 12772 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btVector3DoubleData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btVector3.h?r=2223#719>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btVector3.cpp?r=2223>
-}
btVector3DoubleData :: IO (BtVector3DoubleData)
btVector3DoubleData =
  btVector3DoubleData'_ >>= \res ->
  mkBtVector3DoubleData res >>= \res' ->
  return (res')
{-# LINE 12777 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btVector3DoubleData_free :: ( BtVector3DoubleDataClass bc ) => bc -> IO ()
btVector3DoubleData_free a1 =
  withBt a1 $ \a1' -> 
  btVector3DoubleData_free'_ a1' >>= \res ->
  return ()
{-# LINE 12778 "./Physics/Bullet/Raw/LinearMath.chs" #-}
-- * btVector3FloatData
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btVector3.h?r=2223#714>
     <http://code.google.com/p/bullet/source/browse/trunk/src/LinearMath/btVector3.cpp?r=2223>
-}
btVector3FloatData :: IO (BtVector3FloatData)
btVector3FloatData =
  btVector3FloatData'_ >>= \res ->
  mkBtVector3FloatData res >>= \res' ->
  return (res')
{-# LINE 12783 "./Physics/Bullet/Raw/LinearMath.chs" #-}
btVector3FloatData_free :: ( BtVector3FloatDataClass bc ) => bc -> IO ()
btVector3FloatData_free a1 =
  withBt a1 $ \a1' -> 
  btVector3FloatData_free'_ a1' >>= \res ->
  return ()
{-# LINE 12784 "./Physics/Bullet/Raw/LinearMath.chs" #-}

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileIterator_new"
  cProfileIterator'_ :: ((Ptr ()) -> (IO (Ptr ())))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileManager_new"
  cProfileManager'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileManager_Reset"
  cProfileManager_Reset'_ :: (IO ())

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileManager_dumpAll"
  cProfileManager_dumpAll'_ :: (IO ())

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileManager_Get_Frame_Count_Since_Reset"
  cProfileManager_Get_Frame_Count_Since_Reset'_ :: (IO CInt)

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileManager_Stop_Profile"
  cProfileManager_Stop_Profile'_ :: (IO ())

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileManager_CleanupMemory"
  cProfileManager_CleanupMemory'_ :: (IO ())

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileManager_Get_Time_Since_Reset"
  cProfileManager_Get_Time_Since_Reset'_ :: (IO CFloat)

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileManager_Increment_Frame_Counter"
  cProfileManager_Increment_Frame_Counter'_ :: (IO ())

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileManager_Get_Iterator"
  cProfileManager_Get_Iterator'_ :: (IO (Ptr ()))

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileManager_ResetTime_set"
  cProfileManager_ResetTime_set'_ :: ((Ptr ()) -> (CULong -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileManager_ResetTime_get"
  cProfileManager_ResetTime_get'_ :: ((Ptr ()) -> (IO CULong))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileNode_new"
  cProfileNode'_ :: ((Ptr CChar) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileNode_StartTime_set"
  cProfileNode_StartTime_set'_ :: ((Ptr ()) -> (CULong -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileNode_StartTime_get"
  cProfileNode_StartTime_get'_ :: ((Ptr ()) -> (IO CULong))

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h cProfileSample_new"
  cProfileSample'_ :: ((Ptr CChar) -> (IO (Ptr ())))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__new"
  btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__address0"
  btAlignedAllocator_BT_QUANTIZED_BVH_NODE_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_GIM_BVH_DATA_16u__new"
  btAlignedAllocator_GIM_BVH_DATA_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_GIM_BVH_DATA_16u__address0"
  btAlignedAllocator_GIM_BVH_DATA_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_GIM_BVH_TREE_NODE_16u__new"
  btAlignedAllocator_GIM_BVH_TREE_NODE_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_GIM_BVH_TREE_NODE_16u__address0"
  btAlignedAllocator_GIM_BVH_TREE_NODE_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_GIM_PAIR_16u__new"
  btAlignedAllocator_GIM_PAIR_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_GIM_PAIR_16u__address0"
  btAlignedAllocator_GIM_PAIR_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_bool_16u__new"
  btAlignedAllocator_bool_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btActionInterface_ptr_16u__new"
  btAlignedAllocator_btActionInterface_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btBroadphaseInterface_ptr_16u__new"
  btAlignedAllocator_btBroadphaseInterface_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btBroadphasePair_16u__new"
  btAlignedAllocator_btBroadphasePair_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btBroadphasePair_16u__address0"
  btAlignedAllocator_btBroadphasePair_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btBvhSubtreeInfo_16u__new"
  btAlignedAllocator_btBvhSubtreeInfo_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btBvhSubtreeInfo_16u__address0"
  btAlignedAllocator_btBvhSubtreeInfo_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btChunk_ptr_16u__new"
  btAlignedAllocator_btChunk_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btCollisionObject_ptr_16u__new"
  btAlignedAllocator_btCollisionObject_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btCollisionShape_ptr_16u__new"
  btAlignedAllocator_btCollisionShape_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btCompoundShapeChild_16u__new"
  btAlignedAllocator_btCompoundShapeChild_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btCompoundShapeChild_16u__address0"
  btAlignedAllocator_btCompoundShapeChild_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btDbvt_sStkNN_16u__new"
  btAlignedAllocator_btDbvt_sStkNN_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btDbvt_sStkNN_16u__address0"
  btAlignedAllocator_btDbvt_sStkNN_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btDbvt_sStkNP_16u__new"
  btAlignedAllocator_btDbvt_sStkNP_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btDbvt_sStkNP_16u__address0"
  btAlignedAllocator_btDbvt_sStkNP_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btDbvt_sStkNPS_16u__new"
  btAlignedAllocator_btDbvt_sStkNPS_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btDbvt_sStkNPS_16u__address0"
  btAlignedAllocator_btDbvt_sStkNPS_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btDbvtNodeconst_ptr_16u__new"
  btAlignedAllocator_btDbvtNodeconst_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btGImpactMeshShapePart_ptr_16u__new"
  btAlignedAllocator_btGImpactMeshShapePart_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btHashInt_16u__new"
  btAlignedAllocator_btHashInt_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btHashInt_16u__address0"
  btAlignedAllocator_btHashInt_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btHashPtr_16u__new"
  btAlignedAllocator_btHashPtr_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btHashPtr_16u__address0"
  btAlignedAllocator_btHashPtr_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btHashString_16u__new"
  btAlignedAllocator_btHashString_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btHashString_16u__address0"
  btAlignedAllocator_btHashString_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btIndexedMesh_16u__new"
  btAlignedAllocator_btIndexedMesh_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btIndexedMesh_16u__address0"
  btAlignedAllocator_btIndexedMesh_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u__new"
  btAlignedAllocator_btMultiSapBroadphase_btBridgeProxy_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u__new"
  btAlignedAllocator_btMultiSapBroadphase_btMultiSapProxy_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btOptimizedBvhNode_16u__new"
  btAlignedAllocator_btOptimizedBvhNode_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btOptimizedBvhNode_16u__address0"
  btAlignedAllocator_btOptimizedBvhNode_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btPersistentManifold_ptr_16u__new"
  btAlignedAllocator_btPersistentManifold_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btPointerUid_16u__new"
  btAlignedAllocator_btPointerUid_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btPointerUid_16u__address0"
  btAlignedAllocator_btPointerUid_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btQuantizedBvhNode_16u__new"
  btAlignedAllocator_btQuantizedBvhNode_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btQuantizedBvhNode_16u__address0"
  btAlignedAllocator_btQuantizedBvhNode_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btRigidBody_ptr_16u__new"
  btAlignedAllocator_btRigidBody_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_ptr_16u__new"
  btAlignedAllocator_btSoftBody_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Anchor_16u__new"
  btAlignedAllocator_btSoftBody_Anchor_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Anchor_16u__address0"
  btAlignedAllocator_btSoftBody_Anchor_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Cluster_ptr_16u__new"
  btAlignedAllocator_btSoftBody_Cluster_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Face_16u__new"
  btAlignedAllocator_btSoftBody_Face_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Face_16u__address0"
  btAlignedAllocator_btSoftBody_Face_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Joint_ptr_16u__new"
  btAlignedAllocator_btSoftBody_Joint_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Link_16u__new"
  btAlignedAllocator_btSoftBody_Link_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Link_16u__address0"
  btAlignedAllocator_btSoftBody_Link_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Material_ptr_16u__new"
  btAlignedAllocator_btSoftBody_Material_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Node_ptr_16u__new"
  btAlignedAllocator_btSoftBody_Node_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Node_16u__new"
  btAlignedAllocator_btSoftBody_Node_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Node_16u__address0"
  btAlignedAllocator_btSoftBody_Node_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Note_16u__new"
  btAlignedAllocator_btSoftBody_Note_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Note_16u__address0"
  btAlignedAllocator_btSoftBody_Note_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_RContact_16u__new"
  btAlignedAllocator_btSoftBody_RContact_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_RContact_16u__address0"
  btAlignedAllocator_btSoftBody_RContact_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_SContact_16u__new"
  btAlignedAllocator_btSoftBody_SContact_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_SContact_16u__address0"
  btAlignedAllocator_btSoftBody_SContact_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Tetra_16u__new"
  btAlignedAllocator_btSoftBody_Tetra_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_Tetra_16u__address0"
  btAlignedAllocator_btSoftBody_Tetra_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_ePSolver___16u__new"
  btAlignedAllocator_btSoftBody_ePSolver___16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSoftBody_eVSolver___16u__new"
  btAlignedAllocator_btSoftBody_eVSolver___16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSolverConstraint_16u__new"
  btAlignedAllocator_btSolverConstraint_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSolverConstraint_16u__address0"
  btAlignedAllocator_btSolverConstraint_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btSparseSdf_3__Cell_ptr_16u__new"
  btAlignedAllocator_btSparseSdf_3__Cell_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btTransform_16u__new"
  btAlignedAllocator_btTransform_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btTriangleInfo_16u__new"
  btAlignedAllocator_btTriangleInfo_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btTriangleInfo_16u__address0"
  btAlignedAllocator_btTriangleInfo_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btTypedConstraint_ptr_16u__new"
  btAlignedAllocator_btTypedConstraint_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__new"
  btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__address0"
  btAlignedAllocator_btTypedConstraint_btConstraintInfo1_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btVector3_16u__new"
  btAlignedAllocator_btVector3_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btWheelInfo_16u__new"
  btAlignedAllocator_btWheelInfo_16u_'_ :: (IO (Ptr ()))

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_btWheelInfo_16u__address0"
  btAlignedAllocator_btWheelInfo_16u__address'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_charconst_ptr_16u__new"
  btAlignedAllocator_charconst_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_char_ptr_16u__new"
  btAlignedAllocator_char_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_float_16u__new"
  btAlignedAllocator_float_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_int_16u__new"
  btAlignedAllocator_int_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_short_ptr_16u__new"
  btAlignedAllocator_short_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_short_16u__new"
  btAlignedAllocator_short_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_unsignedint_16u__new"
  btAlignedAllocator_unsignedint_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_unsignedshort_16u__new"
  btAlignedAllocator_unsignedshort_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedAllocator_void_ptr_16u__new"
  btAlignedAllocator_void_ptr_16u_'_ :: (IO (Ptr ()))

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__new"
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__at0"
  btAlignedObjectArray_BT_QUANTIZED_BVH_NODE__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_GIM_BVH_DATA__new"
  btAlignedObjectArray_GIM_BVH_DATA_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_GIM_BVH_DATA__at0"
  btAlignedObjectArray_GIM_BVH_DATA__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_GIM_BVH_TREE_NODE__new"
  btAlignedObjectArray_GIM_BVH_TREE_NODE_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_GIM_BVH_TREE_NODE__at0"
  btAlignedObjectArray_GIM_BVH_TREE_NODE__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_GIM_PAIR__new"
  btAlignedObjectArray_GIM_PAIR_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_GIM_PAIR__at0"
  btAlignedObjectArray_GIM_PAIR__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_bool__new"
  btAlignedObjectArray_bool_'_ :: (IO (Ptr ()))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btActionInterface_ptr__new"
  btAlignedObjectArray_btActionInterface_ptr_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btActionInterface_ptr__at0"
  btAlignedObjectArray_btActionInterface_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btBroadphaseInterface_ptr__new"
  btAlignedObjectArray_btBroadphaseInterface_ptr_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btBroadphaseInterface_ptr__at0"
  btAlignedObjectArray_btBroadphaseInterface_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btBroadphasePair__new"
  btAlignedObjectArray_btBroadphasePair_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btBroadphasePair__at0"
  btAlignedObjectArray_btBroadphasePair__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btBvhSubtreeInfo__new"
  btAlignedObjectArray_btBvhSubtreeInfo_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btBvhSubtreeInfo__at0"
  btAlignedObjectArray_btBvhSubtreeInfo__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btChunk_ptr__new"
  btAlignedObjectArray_btChunk_ptr_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btChunk_ptr__at0"
  btAlignedObjectArray_btChunk_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btCollisionObject_ptr__new"
  btAlignedObjectArray_btCollisionObject_ptr_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btCollisionObject_ptr__at0"
  btAlignedObjectArray_btCollisionObject_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btCollisionShape_ptr__new"
  btAlignedObjectArray_btCollisionShape_ptr_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btCollisionShape_ptr__at0"
  btAlignedObjectArray_btCollisionShape_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btCompoundShapeChild__new"
  btAlignedObjectArray_btCompoundShapeChild_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btCompoundShapeChild__at0"
  btAlignedObjectArray_btCompoundShapeChild__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btDbvt_sStkNN__new"
  btAlignedObjectArray_btDbvt_sStkNN_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btDbvt_sStkNN__at0"
  btAlignedObjectArray_btDbvt_sStkNN__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btDbvt_sStkNP__new"
  btAlignedObjectArray_btDbvt_sStkNP_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btDbvt_sStkNP__at0"
  btAlignedObjectArray_btDbvt_sStkNP__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btDbvt_sStkNPS__new"
  btAlignedObjectArray_btDbvt_sStkNPS_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btDbvt_sStkNPS__at0"
  btAlignedObjectArray_btDbvt_sStkNPS__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btDbvtNodeconst_ptr__new"
  btAlignedObjectArray_btDbvtNodeconst_ptr_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btDbvtNodeconst_ptr__at0"
  btAlignedObjectArray_btDbvtNodeconst_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btGImpactMeshShapePart_ptr__new"
  btAlignedObjectArray_btGImpactMeshShapePart_ptr_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btGImpactMeshShapePart_ptr__at0"
  btAlignedObjectArray_btGImpactMeshShapePart_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashInt__new"
  btAlignedObjectArray_btHashInt_'_ :: (IO (Ptr ()))

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashInt__at0"
  btAlignedObjectArray_btHashInt__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashInt__m_capacity_set"
  btAlignedObjectArray_btHashInt__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashInt__m_capacity_get"
  btAlignedObjectArray_btHashInt__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashInt__m_data_set"
  btAlignedObjectArray_btHashInt__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashInt__m_data_get"
  btAlignedObjectArray_btHashInt__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashInt__m_ownsMemory_set"
  btAlignedObjectArray_btHashInt__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashInt__m_ownsMemory_get"
  btAlignedObjectArray_btHashInt__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__new"
  btAlignedObjectArray_btHashPtr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__free"
  btAlignedObjectArray_btHashPtr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__push_back"
  btAlignedObjectArray_btHashPtr__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__at0"
  btAlignedObjectArray_btHashPtr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__at0"
  btAlignedObjectArray_btHashPtr__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__at1"
  btAlignedObjectArray_btHashPtr__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__size"
  btAlignedObjectArray_btHashPtr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__capacity"
  btAlignedObjectArray_btHashPtr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__init"
  btAlignedObjectArray_btHashPtr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__allocate"
  btAlignedObjectArray_btHashPtr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__pop_back"
  btAlignedObjectArray_btHashPtr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__deallocate"
  btAlignedObjectArray_btHashPtr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__swap"
  btAlignedObjectArray_btHashPtr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__initializeFromBuffer"
  btAlignedObjectArray_btHashPtr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__expandNonInitializing"
  btAlignedObjectArray_btHashPtr__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__resize"
  btAlignedObjectArray_btHashPtr__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__destroy"
  btAlignedObjectArray_btHashPtr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__copy"
  btAlignedObjectArray_btHashPtr__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__expand"
  btAlignedObjectArray_btHashPtr__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__clear"
  btAlignedObjectArray_btHashPtr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__allocSize"
  btAlignedObjectArray_btHashPtr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__reserve"
  btAlignedObjectArray_btHashPtr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__m_allocator_set"
  btAlignedObjectArray_btHashPtr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__m_allocator_get"
  btAlignedObjectArray_btHashPtr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__m_size_set"
  btAlignedObjectArray_btHashPtr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__m_size_get"
  btAlignedObjectArray_btHashPtr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__m_capacity_set"
  btAlignedObjectArray_btHashPtr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__m_capacity_get"
  btAlignedObjectArray_btHashPtr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__m_data_set"
  btAlignedObjectArray_btHashPtr__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__m_data_get"
  btAlignedObjectArray_btHashPtr__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__m_ownsMemory_set"
  btAlignedObjectArray_btHashPtr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashPtr__m_ownsMemory_get"
  btAlignedObjectArray_btHashPtr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__new"
  btAlignedObjectArray_btHashString_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__free"
  btAlignedObjectArray_btHashString__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__push_back"
  btAlignedObjectArray_btHashString__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__at0"
  btAlignedObjectArray_btHashString__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__at0"
  btAlignedObjectArray_btHashString__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__at1"
  btAlignedObjectArray_btHashString__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__size"
  btAlignedObjectArray_btHashString__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__capacity"
  btAlignedObjectArray_btHashString__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__init"
  btAlignedObjectArray_btHashString__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__allocate"
  btAlignedObjectArray_btHashString__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__pop_back"
  btAlignedObjectArray_btHashString__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__deallocate"
  btAlignedObjectArray_btHashString__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__swap"
  btAlignedObjectArray_btHashString__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__initializeFromBuffer"
  btAlignedObjectArray_btHashString__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__expandNonInitializing"
  btAlignedObjectArray_btHashString__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__resize"
  btAlignedObjectArray_btHashString__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__destroy"
  btAlignedObjectArray_btHashString__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__copy"
  btAlignedObjectArray_btHashString__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__expand"
  btAlignedObjectArray_btHashString__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__clear"
  btAlignedObjectArray_btHashString__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__allocSize"
  btAlignedObjectArray_btHashString__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__reserve"
  btAlignedObjectArray_btHashString__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__m_allocator_set"
  btAlignedObjectArray_btHashString__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__m_allocator_get"
  btAlignedObjectArray_btHashString__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__m_size_set"
  btAlignedObjectArray_btHashString__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__m_size_get"
  btAlignedObjectArray_btHashString__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__m_capacity_set"
  btAlignedObjectArray_btHashString__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__m_capacity_get"
  btAlignedObjectArray_btHashString__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__m_data_set"
  btAlignedObjectArray_btHashString__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__m_data_get"
  btAlignedObjectArray_btHashString__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__m_ownsMemory_set"
  btAlignedObjectArray_btHashString__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btHashString__m_ownsMemory_get"
  btAlignedObjectArray_btHashString__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__new"
  btAlignedObjectArray_btIndexedMesh_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__free"
  btAlignedObjectArray_btIndexedMesh__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__push_back"
  btAlignedObjectArray_btIndexedMesh__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__at0"
  btAlignedObjectArray_btIndexedMesh__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__at0"
  btAlignedObjectArray_btIndexedMesh__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__at1"
  btAlignedObjectArray_btIndexedMesh__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__size"
  btAlignedObjectArray_btIndexedMesh__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__capacity"
  btAlignedObjectArray_btIndexedMesh__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__init"
  btAlignedObjectArray_btIndexedMesh__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__allocate"
  btAlignedObjectArray_btIndexedMesh__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__pop_back"
  btAlignedObjectArray_btIndexedMesh__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__deallocate"
  btAlignedObjectArray_btIndexedMesh__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__swap"
  btAlignedObjectArray_btIndexedMesh__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__initializeFromBuffer"
  btAlignedObjectArray_btIndexedMesh__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__expandNonInitializing"
  btAlignedObjectArray_btIndexedMesh__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__resize"
  btAlignedObjectArray_btIndexedMesh__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__destroy"
  btAlignedObjectArray_btIndexedMesh__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__copy"
  btAlignedObjectArray_btIndexedMesh__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__expand"
  btAlignedObjectArray_btIndexedMesh__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__clear"
  btAlignedObjectArray_btIndexedMesh__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__allocSize"
  btAlignedObjectArray_btIndexedMesh__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__reserve"
  btAlignedObjectArray_btIndexedMesh__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__m_allocator_set"
  btAlignedObjectArray_btIndexedMesh__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__m_allocator_get"
  btAlignedObjectArray_btIndexedMesh__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__m_size_set"
  btAlignedObjectArray_btIndexedMesh__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__m_size_get"
  btAlignedObjectArray_btIndexedMesh__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__m_capacity_set"
  btAlignedObjectArray_btIndexedMesh__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__m_capacity_get"
  btAlignedObjectArray_btIndexedMesh__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__m_data_set"
  btAlignedObjectArray_btIndexedMesh__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__m_data_get"
  btAlignedObjectArray_btIndexedMesh__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__m_ownsMemory_set"
  btAlignedObjectArray_btIndexedMesh__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btIndexedMesh__m_ownsMemory_get"
  btAlignedObjectArray_btIndexedMesh__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__new"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__free"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__push_back"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at0"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at0"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at1"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__size"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__capacity"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__init"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__allocate"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__pop_back"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__deallocate"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__swap"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__initializeFromBuffer"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__expandNonInitializing"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__resize"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__destroy"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__expand"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__clear"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__allocSize"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__reserve"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_allocator_set"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_allocator_get"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_size_set"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_size_get"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_capacity_set"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_capacity_get"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_ownsMemory_set"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_ownsMemory_get"
  btAlignedObjectArray_btMultiSapBroadphase_btBridgeProxy_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__new"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__free"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__push_back"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at0"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at0"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at1"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__size"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__capacity"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__init"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__allocate"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__pop_back"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__deallocate"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__swap"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__initializeFromBuffer"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__expandNonInitializing"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__resize"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__destroy"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__expand"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__clear"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__allocSize"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__reserve"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_allocator_set"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_allocator_get"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_size_set"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_size_get"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_capacity_set"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_capacity_get"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_ownsMemory_set"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_ownsMemory_get"
  btAlignedObjectArray_btMultiSapBroadphase_btMultiSapProxy_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__new"
  btAlignedObjectArray_btOptimizedBvhNode_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__free"
  btAlignedObjectArray_btOptimizedBvhNode__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__push_back"
  btAlignedObjectArray_btOptimizedBvhNode__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__at0"
  btAlignedObjectArray_btOptimizedBvhNode__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__at0"
  btAlignedObjectArray_btOptimizedBvhNode__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__at1"
  btAlignedObjectArray_btOptimizedBvhNode__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__size"
  btAlignedObjectArray_btOptimizedBvhNode__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__capacity"
  btAlignedObjectArray_btOptimizedBvhNode__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__init"
  btAlignedObjectArray_btOptimizedBvhNode__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__allocate"
  btAlignedObjectArray_btOptimizedBvhNode__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__pop_back"
  btAlignedObjectArray_btOptimizedBvhNode__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__deallocate"
  btAlignedObjectArray_btOptimizedBvhNode__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__swap"
  btAlignedObjectArray_btOptimizedBvhNode__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__initializeFromBuffer"
  btAlignedObjectArray_btOptimizedBvhNode__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__expandNonInitializing"
  btAlignedObjectArray_btOptimizedBvhNode__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__resize"
  btAlignedObjectArray_btOptimizedBvhNode__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__destroy"
  btAlignedObjectArray_btOptimizedBvhNode__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__copy"
  btAlignedObjectArray_btOptimizedBvhNode__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__expand"
  btAlignedObjectArray_btOptimizedBvhNode__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__clear"
  btAlignedObjectArray_btOptimizedBvhNode__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__allocSize"
  btAlignedObjectArray_btOptimizedBvhNode__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__reserve"
  btAlignedObjectArray_btOptimizedBvhNode__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__m_allocator_set"
  btAlignedObjectArray_btOptimizedBvhNode__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__m_allocator_get"
  btAlignedObjectArray_btOptimizedBvhNode__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__m_size_set"
  btAlignedObjectArray_btOptimizedBvhNode__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__m_size_get"
  btAlignedObjectArray_btOptimizedBvhNode__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__m_capacity_set"
  btAlignedObjectArray_btOptimizedBvhNode__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__m_capacity_get"
  btAlignedObjectArray_btOptimizedBvhNode__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__m_data_set"
  btAlignedObjectArray_btOptimizedBvhNode__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__m_data_get"
  btAlignedObjectArray_btOptimizedBvhNode__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__m_ownsMemory_set"
  btAlignedObjectArray_btOptimizedBvhNode__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btOptimizedBvhNode__m_ownsMemory_get"
  btAlignedObjectArray_btOptimizedBvhNode__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__new"
  btAlignedObjectArray_btPersistentManifold_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__free"
  btAlignedObjectArray_btPersistentManifold_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__push_back"
  btAlignedObjectArray_btPersistentManifold_ptr__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__at0"
  btAlignedObjectArray_btPersistentManifold_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__at0"
  btAlignedObjectArray_btPersistentManifold_ptr__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__at1"
  btAlignedObjectArray_btPersistentManifold_ptr__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__size"
  btAlignedObjectArray_btPersistentManifold_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__capacity"
  btAlignedObjectArray_btPersistentManifold_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__init"
  btAlignedObjectArray_btPersistentManifold_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__allocate"
  btAlignedObjectArray_btPersistentManifold_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__pop_back"
  btAlignedObjectArray_btPersistentManifold_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__deallocate"
  btAlignedObjectArray_btPersistentManifold_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__swap"
  btAlignedObjectArray_btPersistentManifold_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__initializeFromBuffer"
  btAlignedObjectArray_btPersistentManifold_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__expandNonInitializing"
  btAlignedObjectArray_btPersistentManifold_ptr__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__resize"
  btAlignedObjectArray_btPersistentManifold_ptr__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__destroy"
  btAlignedObjectArray_btPersistentManifold_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__expand"
  btAlignedObjectArray_btPersistentManifold_ptr__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__clear"
  btAlignedObjectArray_btPersistentManifold_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__allocSize"
  btAlignedObjectArray_btPersistentManifold_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__reserve"
  btAlignedObjectArray_btPersistentManifold_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__m_allocator_set"
  btAlignedObjectArray_btPersistentManifold_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__m_allocator_get"
  btAlignedObjectArray_btPersistentManifold_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__m_size_set"
  btAlignedObjectArray_btPersistentManifold_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__m_size_get"
  btAlignedObjectArray_btPersistentManifold_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__m_capacity_set"
  btAlignedObjectArray_btPersistentManifold_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__m_capacity_get"
  btAlignedObjectArray_btPersistentManifold_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__m_ownsMemory_set"
  btAlignedObjectArray_btPersistentManifold_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPersistentManifold_ptr__m_ownsMemory_get"
  btAlignedObjectArray_btPersistentManifold_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__new"
  btAlignedObjectArray_btPointerUid_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__free"
  btAlignedObjectArray_btPointerUid__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__push_back"
  btAlignedObjectArray_btPointerUid__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__at0"
  btAlignedObjectArray_btPointerUid__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__at0"
  btAlignedObjectArray_btPointerUid__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__at1"
  btAlignedObjectArray_btPointerUid__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__size"
  btAlignedObjectArray_btPointerUid__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__capacity"
  btAlignedObjectArray_btPointerUid__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__init"
  btAlignedObjectArray_btPointerUid__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__allocate"
  btAlignedObjectArray_btPointerUid__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__pop_back"
  btAlignedObjectArray_btPointerUid__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__deallocate"
  btAlignedObjectArray_btPointerUid__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__swap"
  btAlignedObjectArray_btPointerUid__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__initializeFromBuffer"
  btAlignedObjectArray_btPointerUid__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__expandNonInitializing"
  btAlignedObjectArray_btPointerUid__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__resize"
  btAlignedObjectArray_btPointerUid__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__destroy"
  btAlignedObjectArray_btPointerUid__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__copy"
  btAlignedObjectArray_btPointerUid__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__expand"
  btAlignedObjectArray_btPointerUid__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__clear"
  btAlignedObjectArray_btPointerUid__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__allocSize"
  btAlignedObjectArray_btPointerUid__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__reserve"
  btAlignedObjectArray_btPointerUid__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__m_allocator_set"
  btAlignedObjectArray_btPointerUid__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__m_allocator_get"
  btAlignedObjectArray_btPointerUid__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__m_size_set"
  btAlignedObjectArray_btPointerUid__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__m_size_get"
  btAlignedObjectArray_btPointerUid__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__m_capacity_set"
  btAlignedObjectArray_btPointerUid__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__m_capacity_get"
  btAlignedObjectArray_btPointerUid__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__m_data_set"
  btAlignedObjectArray_btPointerUid__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__m_data_get"
  btAlignedObjectArray_btPointerUid__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__m_ownsMemory_set"
  btAlignedObjectArray_btPointerUid__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btPointerUid__m_ownsMemory_get"
  btAlignedObjectArray_btPointerUid__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__new"
  btAlignedObjectArray_btQuantizedBvhNode_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__free"
  btAlignedObjectArray_btQuantizedBvhNode__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__push_back"
  btAlignedObjectArray_btQuantizedBvhNode__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__at0"
  btAlignedObjectArray_btQuantizedBvhNode__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__at0"
  btAlignedObjectArray_btQuantizedBvhNode__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__at1"
  btAlignedObjectArray_btQuantizedBvhNode__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__size"
  btAlignedObjectArray_btQuantizedBvhNode__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__capacity"
  btAlignedObjectArray_btQuantizedBvhNode__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__init"
  btAlignedObjectArray_btQuantizedBvhNode__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__allocate"
  btAlignedObjectArray_btQuantizedBvhNode__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__pop_back"
  btAlignedObjectArray_btQuantizedBvhNode__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__deallocate"
  btAlignedObjectArray_btQuantizedBvhNode__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__swap"
  btAlignedObjectArray_btQuantizedBvhNode__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__initializeFromBuffer"
  btAlignedObjectArray_btQuantizedBvhNode__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__expandNonInitializing"
  btAlignedObjectArray_btQuantizedBvhNode__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__resize"
  btAlignedObjectArray_btQuantizedBvhNode__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__destroy"
  btAlignedObjectArray_btQuantizedBvhNode__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__copy"
  btAlignedObjectArray_btQuantizedBvhNode__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__expand"
  btAlignedObjectArray_btQuantizedBvhNode__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__clear"
  btAlignedObjectArray_btQuantizedBvhNode__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__allocSize"
  btAlignedObjectArray_btQuantizedBvhNode__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__reserve"
  btAlignedObjectArray_btQuantizedBvhNode__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__m_allocator_set"
  btAlignedObjectArray_btQuantizedBvhNode__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__m_allocator_get"
  btAlignedObjectArray_btQuantizedBvhNode__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__m_size_set"
  btAlignedObjectArray_btQuantizedBvhNode__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__m_size_get"
  btAlignedObjectArray_btQuantizedBvhNode__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__m_capacity_set"
  btAlignedObjectArray_btQuantizedBvhNode__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__m_capacity_get"
  btAlignedObjectArray_btQuantizedBvhNode__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__m_data_set"
  btAlignedObjectArray_btQuantizedBvhNode__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__m_data_get"
  btAlignedObjectArray_btQuantizedBvhNode__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__m_ownsMemory_set"
  btAlignedObjectArray_btQuantizedBvhNode__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btQuantizedBvhNode__m_ownsMemory_get"
  btAlignedObjectArray_btQuantizedBvhNode__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__new"
  btAlignedObjectArray_btRigidBody_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__free"
  btAlignedObjectArray_btRigidBody_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__push_back"
  btAlignedObjectArray_btRigidBody_ptr__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__at0"
  btAlignedObjectArray_btRigidBody_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__at0"
  btAlignedObjectArray_btRigidBody_ptr__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__at1"
  btAlignedObjectArray_btRigidBody_ptr__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__size"
  btAlignedObjectArray_btRigidBody_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__capacity"
  btAlignedObjectArray_btRigidBody_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__init"
  btAlignedObjectArray_btRigidBody_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__allocate"
  btAlignedObjectArray_btRigidBody_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__pop_back"
  btAlignedObjectArray_btRigidBody_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__deallocate"
  btAlignedObjectArray_btRigidBody_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__swap"
  btAlignedObjectArray_btRigidBody_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__initializeFromBuffer"
  btAlignedObjectArray_btRigidBody_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__expandNonInitializing"
  btAlignedObjectArray_btRigidBody_ptr__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__resize"
  btAlignedObjectArray_btRigidBody_ptr__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__destroy"
  btAlignedObjectArray_btRigidBody_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__expand"
  btAlignedObjectArray_btRigidBody_ptr__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__clear"
  btAlignedObjectArray_btRigidBody_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__allocSize"
  btAlignedObjectArray_btRigidBody_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__reserve"
  btAlignedObjectArray_btRigidBody_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__m_allocator_set"
  btAlignedObjectArray_btRigidBody_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__m_allocator_get"
  btAlignedObjectArray_btRigidBody_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__m_size_set"
  btAlignedObjectArray_btRigidBody_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__m_size_get"
  btAlignedObjectArray_btRigidBody_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__m_capacity_set"
  btAlignedObjectArray_btRigidBody_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__m_capacity_get"
  btAlignedObjectArray_btRigidBody_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__m_ownsMemory_set"
  btAlignedObjectArray_btRigidBody_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btRigidBody_ptr__m_ownsMemory_get"
  btAlignedObjectArray_btRigidBody_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__new"
  btAlignedObjectArray_btSoftBody_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__free"
  btAlignedObjectArray_btSoftBody_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__push_back"
  btAlignedObjectArray_btSoftBody_ptr__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__at0"
  btAlignedObjectArray_btSoftBody_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__at0"
  btAlignedObjectArray_btSoftBody_ptr__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__at1"
  btAlignedObjectArray_btSoftBody_ptr__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__size"
  btAlignedObjectArray_btSoftBody_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__capacity"
  btAlignedObjectArray_btSoftBody_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__init"
  btAlignedObjectArray_btSoftBody_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__swap"
  btAlignedObjectArray_btSoftBody_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__pop_back"
  btAlignedObjectArray_btSoftBody_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__deallocate"
  btAlignedObjectArray_btSoftBody_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__allocate"
  btAlignedObjectArray_btSoftBody_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__expandNonInitializing"
  btAlignedObjectArray_btSoftBody_ptr__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__destroy"
  btAlignedObjectArray_btSoftBody_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__resize"
  btAlignedObjectArray_btSoftBody_ptr__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__clear"
  btAlignedObjectArray_btSoftBody_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__allocSize"
  btAlignedObjectArray_btSoftBody_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__expand"
  btAlignedObjectArray_btSoftBody_ptr__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__reserve"
  btAlignedObjectArray_btSoftBody_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__m_allocator_set"
  btAlignedObjectArray_btSoftBody_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__m_allocator_get"
  btAlignedObjectArray_btSoftBody_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__m_capacity_set"
  btAlignedObjectArray_btSoftBody_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__m_capacity_get"
  btAlignedObjectArray_btSoftBody_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__m_size_set"
  btAlignedObjectArray_btSoftBody_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ptr__m_size_get"
  btAlignedObjectArray_btSoftBody_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__new"
  btAlignedObjectArray_btSoftBody_Anchor_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__free"
  btAlignedObjectArray_btSoftBody_Anchor__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__push_back"
  btAlignedObjectArray_btSoftBody_Anchor__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__at0"
  btAlignedObjectArray_btSoftBody_Anchor__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__at0"
  btAlignedObjectArray_btSoftBody_Anchor__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__at1"
  btAlignedObjectArray_btSoftBody_Anchor__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__size"
  btAlignedObjectArray_btSoftBody_Anchor__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__capacity"
  btAlignedObjectArray_btSoftBody_Anchor__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__init"
  btAlignedObjectArray_btSoftBody_Anchor__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__swap"
  btAlignedObjectArray_btSoftBody_Anchor__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__pop_back"
  btAlignedObjectArray_btSoftBody_Anchor__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__deallocate"
  btAlignedObjectArray_btSoftBody_Anchor__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__allocate"
  btAlignedObjectArray_btSoftBody_Anchor__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_Anchor__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__expandNonInitializing"
  btAlignedObjectArray_btSoftBody_Anchor__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__destroy"
  btAlignedObjectArray_btSoftBody_Anchor__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__copy"
  btAlignedObjectArray_btSoftBody_Anchor__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__resize"
  btAlignedObjectArray_btSoftBody_Anchor__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__clear"
  btAlignedObjectArray_btSoftBody_Anchor__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__allocSize"
  btAlignedObjectArray_btSoftBody_Anchor__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__expand"
  btAlignedObjectArray_btSoftBody_Anchor__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__reserve"
  btAlignedObjectArray_btSoftBody_Anchor__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__m_allocator_set"
  btAlignedObjectArray_btSoftBody_Anchor__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__m_allocator_get"
  btAlignedObjectArray_btSoftBody_Anchor__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__m_capacity_set"
  btAlignedObjectArray_btSoftBody_Anchor__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__m_capacity_get"
  btAlignedObjectArray_btSoftBody_Anchor__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__m_data_set"
  btAlignedObjectArray_btSoftBody_Anchor__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__m_data_get"
  btAlignedObjectArray_btSoftBody_Anchor__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_Anchor__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_Anchor__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__m_size_set"
  btAlignedObjectArray_btSoftBody_Anchor__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Anchor__m_size_get"
  btAlignedObjectArray_btSoftBody_Anchor__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__new"
  btAlignedObjectArray_btSoftBody_Cluster_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__free"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__push_back"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__at0"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__at0"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__at1"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__size"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__capacity"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__init"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__swap"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__pop_back"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__deallocate"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__allocate"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__expandNonInitializing"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__destroy"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__resize"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__clear"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__allocSize"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__expand"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__reserve"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__m_allocator_set"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__m_allocator_get"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__m_capacity_set"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__m_capacity_get"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__m_size_set"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Cluster_ptr__m_size_get"
  btAlignedObjectArray_btSoftBody_Cluster_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__new"
  btAlignedObjectArray_btSoftBody_Face_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__free"
  btAlignedObjectArray_btSoftBody_Face__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__push_back"
  btAlignedObjectArray_btSoftBody_Face__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__at0"
  btAlignedObjectArray_btSoftBody_Face__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__at0"
  btAlignedObjectArray_btSoftBody_Face__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__at1"
  btAlignedObjectArray_btSoftBody_Face__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__size"
  btAlignedObjectArray_btSoftBody_Face__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__capacity"
  btAlignedObjectArray_btSoftBody_Face__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__init"
  btAlignedObjectArray_btSoftBody_Face__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__swap"
  btAlignedObjectArray_btSoftBody_Face__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__pop_back"
  btAlignedObjectArray_btSoftBody_Face__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__deallocate"
  btAlignedObjectArray_btSoftBody_Face__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__allocate"
  btAlignedObjectArray_btSoftBody_Face__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_Face__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__expandNonInitializing"
  btAlignedObjectArray_btSoftBody_Face__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__destroy"
  btAlignedObjectArray_btSoftBody_Face__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__copy"
  btAlignedObjectArray_btSoftBody_Face__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__resize"
  btAlignedObjectArray_btSoftBody_Face__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__clear"
  btAlignedObjectArray_btSoftBody_Face__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__allocSize"
  btAlignedObjectArray_btSoftBody_Face__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__expand"
  btAlignedObjectArray_btSoftBody_Face__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__reserve"
  btAlignedObjectArray_btSoftBody_Face__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__m_allocator_set"
  btAlignedObjectArray_btSoftBody_Face__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__m_allocator_get"
  btAlignedObjectArray_btSoftBody_Face__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__m_capacity_set"
  btAlignedObjectArray_btSoftBody_Face__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__m_capacity_get"
  btAlignedObjectArray_btSoftBody_Face__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__m_data_set"
  btAlignedObjectArray_btSoftBody_Face__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__m_data_get"
  btAlignedObjectArray_btSoftBody_Face__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_Face__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_Face__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__m_size_set"
  btAlignedObjectArray_btSoftBody_Face__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Face__m_size_get"
  btAlignedObjectArray_btSoftBody_Face__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__new"
  btAlignedObjectArray_btSoftBody_Joint_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__free"
  btAlignedObjectArray_btSoftBody_Joint_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__push_back"
  btAlignedObjectArray_btSoftBody_Joint_ptr__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__at0"
  btAlignedObjectArray_btSoftBody_Joint_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__at0"
  btAlignedObjectArray_btSoftBody_Joint_ptr__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__at1"
  btAlignedObjectArray_btSoftBody_Joint_ptr__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__size"
  btAlignedObjectArray_btSoftBody_Joint_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__capacity"
  btAlignedObjectArray_btSoftBody_Joint_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__init"
  btAlignedObjectArray_btSoftBody_Joint_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__swap"
  btAlignedObjectArray_btSoftBody_Joint_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__pop_back"
  btAlignedObjectArray_btSoftBody_Joint_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__deallocate"
  btAlignedObjectArray_btSoftBody_Joint_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__allocate"
  btAlignedObjectArray_btSoftBody_Joint_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_Joint_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__expandNonInitializing"
  btAlignedObjectArray_btSoftBody_Joint_ptr__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__destroy"
  btAlignedObjectArray_btSoftBody_Joint_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__resize"
  btAlignedObjectArray_btSoftBody_Joint_ptr__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__clear"
  btAlignedObjectArray_btSoftBody_Joint_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__allocSize"
  btAlignedObjectArray_btSoftBody_Joint_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__expand"
  btAlignedObjectArray_btSoftBody_Joint_ptr__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__reserve"
  btAlignedObjectArray_btSoftBody_Joint_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__m_allocator_set"
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__m_allocator_get"
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__m_capacity_set"
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__m_capacity_get"
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__m_size_set"
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Joint_ptr__m_size_get"
  btAlignedObjectArray_btSoftBody_Joint_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__new"
  btAlignedObjectArray_btSoftBody_Link_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__free"
  btAlignedObjectArray_btSoftBody_Link__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__push_back"
  btAlignedObjectArray_btSoftBody_Link__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__at0"
  btAlignedObjectArray_btSoftBody_Link__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__at0"
  btAlignedObjectArray_btSoftBody_Link__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__at1"
  btAlignedObjectArray_btSoftBody_Link__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__size"
  btAlignedObjectArray_btSoftBody_Link__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__capacity"
  btAlignedObjectArray_btSoftBody_Link__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__init"
  btAlignedObjectArray_btSoftBody_Link__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__swap"
  btAlignedObjectArray_btSoftBody_Link__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__pop_back"
  btAlignedObjectArray_btSoftBody_Link__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__deallocate"
  btAlignedObjectArray_btSoftBody_Link__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__allocate"
  btAlignedObjectArray_btSoftBody_Link__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_Link__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__expandNonInitializing"
  btAlignedObjectArray_btSoftBody_Link__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__destroy"
  btAlignedObjectArray_btSoftBody_Link__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__copy"
  btAlignedObjectArray_btSoftBody_Link__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__resize"
  btAlignedObjectArray_btSoftBody_Link__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__clear"
  btAlignedObjectArray_btSoftBody_Link__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__allocSize"
  btAlignedObjectArray_btSoftBody_Link__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__expand"
  btAlignedObjectArray_btSoftBody_Link__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__reserve"
  btAlignedObjectArray_btSoftBody_Link__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__m_allocator_set"
  btAlignedObjectArray_btSoftBody_Link__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__m_allocator_get"
  btAlignedObjectArray_btSoftBody_Link__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__m_capacity_set"
  btAlignedObjectArray_btSoftBody_Link__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__m_capacity_get"
  btAlignedObjectArray_btSoftBody_Link__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__m_data_set"
  btAlignedObjectArray_btSoftBody_Link__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__m_data_get"
  btAlignedObjectArray_btSoftBody_Link__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_Link__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_Link__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__m_size_set"
  btAlignedObjectArray_btSoftBody_Link__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Link__m_size_get"
  btAlignedObjectArray_btSoftBody_Link__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__new"
  btAlignedObjectArray_btSoftBody_Material_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__free"
  btAlignedObjectArray_btSoftBody_Material_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__push_back"
  btAlignedObjectArray_btSoftBody_Material_ptr__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__at0"
  btAlignedObjectArray_btSoftBody_Material_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__at0"
  btAlignedObjectArray_btSoftBody_Material_ptr__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__at1"
  btAlignedObjectArray_btSoftBody_Material_ptr__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__size"
  btAlignedObjectArray_btSoftBody_Material_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__capacity"
  btAlignedObjectArray_btSoftBody_Material_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__init"
  btAlignedObjectArray_btSoftBody_Material_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__swap"
  btAlignedObjectArray_btSoftBody_Material_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__pop_back"
  btAlignedObjectArray_btSoftBody_Material_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__deallocate"
  btAlignedObjectArray_btSoftBody_Material_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__allocate"
  btAlignedObjectArray_btSoftBody_Material_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_Material_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__expandNonInitializing"
  btAlignedObjectArray_btSoftBody_Material_ptr__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__destroy"
  btAlignedObjectArray_btSoftBody_Material_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__resize"
  btAlignedObjectArray_btSoftBody_Material_ptr__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__clear"
  btAlignedObjectArray_btSoftBody_Material_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__allocSize"
  btAlignedObjectArray_btSoftBody_Material_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__expand"
  btAlignedObjectArray_btSoftBody_Material_ptr__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__reserve"
  btAlignedObjectArray_btSoftBody_Material_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__m_allocator_set"
  btAlignedObjectArray_btSoftBody_Material_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__m_allocator_get"
  btAlignedObjectArray_btSoftBody_Material_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__m_capacity_set"
  btAlignedObjectArray_btSoftBody_Material_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__m_capacity_get"
  btAlignedObjectArray_btSoftBody_Material_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_Material_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_Material_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__m_size_set"
  btAlignedObjectArray_btSoftBody_Material_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Material_ptr__m_size_get"
  btAlignedObjectArray_btSoftBody_Material_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__new"
  btAlignedObjectArray_btSoftBody_Node_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__free"
  btAlignedObjectArray_btSoftBody_Node_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__push_back"
  btAlignedObjectArray_btSoftBody_Node_ptr__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__at0"
  btAlignedObjectArray_btSoftBody_Node_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__at0"
  btAlignedObjectArray_btSoftBody_Node_ptr__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__at1"
  btAlignedObjectArray_btSoftBody_Node_ptr__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__size"
  btAlignedObjectArray_btSoftBody_Node_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__capacity"
  btAlignedObjectArray_btSoftBody_Node_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__init"
  btAlignedObjectArray_btSoftBody_Node_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__swap"
  btAlignedObjectArray_btSoftBody_Node_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__pop_back"
  btAlignedObjectArray_btSoftBody_Node_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__deallocate"
  btAlignedObjectArray_btSoftBody_Node_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__allocate"
  btAlignedObjectArray_btSoftBody_Node_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_Node_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__expandNonInitializing"
  btAlignedObjectArray_btSoftBody_Node_ptr__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__destroy"
  btAlignedObjectArray_btSoftBody_Node_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__resize"
  btAlignedObjectArray_btSoftBody_Node_ptr__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__clear"
  btAlignedObjectArray_btSoftBody_Node_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__allocSize"
  btAlignedObjectArray_btSoftBody_Node_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__expand"
  btAlignedObjectArray_btSoftBody_Node_ptr__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__reserve"
  btAlignedObjectArray_btSoftBody_Node_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__m_allocator_set"
  btAlignedObjectArray_btSoftBody_Node_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__m_allocator_get"
  btAlignedObjectArray_btSoftBody_Node_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__m_capacity_set"
  btAlignedObjectArray_btSoftBody_Node_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__m_capacity_get"
  btAlignedObjectArray_btSoftBody_Node_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_Node_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_Node_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__m_size_set"
  btAlignedObjectArray_btSoftBody_Node_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node_ptr__m_size_get"
  btAlignedObjectArray_btSoftBody_Node_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__new"
  btAlignedObjectArray_btSoftBody_Node_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__free"
  btAlignedObjectArray_btSoftBody_Node__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__push_back"
  btAlignedObjectArray_btSoftBody_Node__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__at0"
  btAlignedObjectArray_btSoftBody_Node__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__at0"
  btAlignedObjectArray_btSoftBody_Node__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__at1"
  btAlignedObjectArray_btSoftBody_Node__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__size"
  btAlignedObjectArray_btSoftBody_Node__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__capacity"
  btAlignedObjectArray_btSoftBody_Node__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__init"
  btAlignedObjectArray_btSoftBody_Node__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__swap"
  btAlignedObjectArray_btSoftBody_Node__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__pop_back"
  btAlignedObjectArray_btSoftBody_Node__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__deallocate"
  btAlignedObjectArray_btSoftBody_Node__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__allocate"
  btAlignedObjectArray_btSoftBody_Node__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_Node__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__expandNonInitializing"
  btAlignedObjectArray_btSoftBody_Node__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__destroy"
  btAlignedObjectArray_btSoftBody_Node__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__copy"
  btAlignedObjectArray_btSoftBody_Node__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__resize"
  btAlignedObjectArray_btSoftBody_Node__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__clear"
  btAlignedObjectArray_btSoftBody_Node__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__allocSize"
  btAlignedObjectArray_btSoftBody_Node__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__expand"
  btAlignedObjectArray_btSoftBody_Node__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__reserve"
  btAlignedObjectArray_btSoftBody_Node__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__m_allocator_set"
  btAlignedObjectArray_btSoftBody_Node__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__m_allocator_get"
  btAlignedObjectArray_btSoftBody_Node__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__m_capacity_set"
  btAlignedObjectArray_btSoftBody_Node__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__m_capacity_get"
  btAlignedObjectArray_btSoftBody_Node__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__m_data_set"
  btAlignedObjectArray_btSoftBody_Node__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__m_data_get"
  btAlignedObjectArray_btSoftBody_Node__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_Node__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_Node__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__m_size_set"
  btAlignedObjectArray_btSoftBody_Node__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Node__m_size_get"
  btAlignedObjectArray_btSoftBody_Node__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__new"
  btAlignedObjectArray_btSoftBody_Note_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__free"
  btAlignedObjectArray_btSoftBody_Note__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__push_back"
  btAlignedObjectArray_btSoftBody_Note__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__at0"
  btAlignedObjectArray_btSoftBody_Note__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__at0"
  btAlignedObjectArray_btSoftBody_Note__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__at1"
  btAlignedObjectArray_btSoftBody_Note__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__size"
  btAlignedObjectArray_btSoftBody_Note__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__capacity"
  btAlignedObjectArray_btSoftBody_Note__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__init"
  btAlignedObjectArray_btSoftBody_Note__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__swap"
  btAlignedObjectArray_btSoftBody_Note__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__pop_back"
  btAlignedObjectArray_btSoftBody_Note__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__deallocate"
  btAlignedObjectArray_btSoftBody_Note__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__allocate"
  btAlignedObjectArray_btSoftBody_Note__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_Note__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__expandNonInitializing"
  btAlignedObjectArray_btSoftBody_Note__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__destroy"
  btAlignedObjectArray_btSoftBody_Note__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__copy"
  btAlignedObjectArray_btSoftBody_Note__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__resize"
  btAlignedObjectArray_btSoftBody_Note__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__clear"
  btAlignedObjectArray_btSoftBody_Note__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__allocSize"
  btAlignedObjectArray_btSoftBody_Note__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__expand"
  btAlignedObjectArray_btSoftBody_Note__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__reserve"
  btAlignedObjectArray_btSoftBody_Note__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__m_allocator_set"
  btAlignedObjectArray_btSoftBody_Note__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__m_allocator_get"
  btAlignedObjectArray_btSoftBody_Note__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__m_capacity_set"
  btAlignedObjectArray_btSoftBody_Note__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__m_capacity_get"
  btAlignedObjectArray_btSoftBody_Note__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__m_data_set"
  btAlignedObjectArray_btSoftBody_Note__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__m_data_get"
  btAlignedObjectArray_btSoftBody_Note__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_Note__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_Note__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__m_size_set"
  btAlignedObjectArray_btSoftBody_Note__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Note__m_size_get"
  btAlignedObjectArray_btSoftBody_Note__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__new"
  btAlignedObjectArray_btSoftBody_RContact_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__free"
  btAlignedObjectArray_btSoftBody_RContact__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__push_back"
  btAlignedObjectArray_btSoftBody_RContact__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__at0"
  btAlignedObjectArray_btSoftBody_RContact__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__at0"
  btAlignedObjectArray_btSoftBody_RContact__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__at1"
  btAlignedObjectArray_btSoftBody_RContact__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__size"
  btAlignedObjectArray_btSoftBody_RContact__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__capacity"
  btAlignedObjectArray_btSoftBody_RContact__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__init"
  btAlignedObjectArray_btSoftBody_RContact__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__swap"
  btAlignedObjectArray_btSoftBody_RContact__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__pop_back"
  btAlignedObjectArray_btSoftBody_RContact__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__deallocate"
  btAlignedObjectArray_btSoftBody_RContact__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__allocate"
  btAlignedObjectArray_btSoftBody_RContact__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_RContact__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__expandNonInitializing"
  btAlignedObjectArray_btSoftBody_RContact__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__destroy"
  btAlignedObjectArray_btSoftBody_RContact__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__copy"
  btAlignedObjectArray_btSoftBody_RContact__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__resize"
  btAlignedObjectArray_btSoftBody_RContact__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__clear"
  btAlignedObjectArray_btSoftBody_RContact__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__allocSize"
  btAlignedObjectArray_btSoftBody_RContact__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__expand"
  btAlignedObjectArray_btSoftBody_RContact__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__reserve"
  btAlignedObjectArray_btSoftBody_RContact__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__m_allocator_set"
  btAlignedObjectArray_btSoftBody_RContact__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__m_allocator_get"
  btAlignedObjectArray_btSoftBody_RContact__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__m_capacity_set"
  btAlignedObjectArray_btSoftBody_RContact__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__m_capacity_get"
  btAlignedObjectArray_btSoftBody_RContact__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__m_data_set"
  btAlignedObjectArray_btSoftBody_RContact__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__m_data_get"
  btAlignedObjectArray_btSoftBody_RContact__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_RContact__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_RContact__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__m_size_set"
  btAlignedObjectArray_btSoftBody_RContact__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_RContact__m_size_get"
  btAlignedObjectArray_btSoftBody_RContact__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__new"
  btAlignedObjectArray_btSoftBody_SContact_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__free"
  btAlignedObjectArray_btSoftBody_SContact__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__push_back"
  btAlignedObjectArray_btSoftBody_SContact__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__at0"
  btAlignedObjectArray_btSoftBody_SContact__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__at0"
  btAlignedObjectArray_btSoftBody_SContact__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__at1"
  btAlignedObjectArray_btSoftBody_SContact__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__size"
  btAlignedObjectArray_btSoftBody_SContact__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__capacity"
  btAlignedObjectArray_btSoftBody_SContact__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__init"
  btAlignedObjectArray_btSoftBody_SContact__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__swap"
  btAlignedObjectArray_btSoftBody_SContact__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__pop_back"
  btAlignedObjectArray_btSoftBody_SContact__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__deallocate"
  btAlignedObjectArray_btSoftBody_SContact__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__allocate"
  btAlignedObjectArray_btSoftBody_SContact__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_SContact__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__expandNonInitializing"
  btAlignedObjectArray_btSoftBody_SContact__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__destroy"
  btAlignedObjectArray_btSoftBody_SContact__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__copy"
  btAlignedObjectArray_btSoftBody_SContact__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__resize"
  btAlignedObjectArray_btSoftBody_SContact__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__clear"
  btAlignedObjectArray_btSoftBody_SContact__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__allocSize"
  btAlignedObjectArray_btSoftBody_SContact__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__expand"
  btAlignedObjectArray_btSoftBody_SContact__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__reserve"
  btAlignedObjectArray_btSoftBody_SContact__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__m_allocator_set"
  btAlignedObjectArray_btSoftBody_SContact__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__m_allocator_get"
  btAlignedObjectArray_btSoftBody_SContact__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__m_capacity_set"
  btAlignedObjectArray_btSoftBody_SContact__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__m_capacity_get"
  btAlignedObjectArray_btSoftBody_SContact__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__m_data_set"
  btAlignedObjectArray_btSoftBody_SContact__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__m_data_get"
  btAlignedObjectArray_btSoftBody_SContact__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_SContact__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_SContact__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__m_size_set"
  btAlignedObjectArray_btSoftBody_SContact__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_SContact__m_size_get"
  btAlignedObjectArray_btSoftBody_SContact__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__new"
  btAlignedObjectArray_btSoftBody_Tetra_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__free"
  btAlignedObjectArray_btSoftBody_Tetra__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__push_back"
  btAlignedObjectArray_btSoftBody_Tetra__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__at0"
  btAlignedObjectArray_btSoftBody_Tetra__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__at0"
  btAlignedObjectArray_btSoftBody_Tetra__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__at1"
  btAlignedObjectArray_btSoftBody_Tetra__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__size"
  btAlignedObjectArray_btSoftBody_Tetra__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__capacity"
  btAlignedObjectArray_btSoftBody_Tetra__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__init"
  btAlignedObjectArray_btSoftBody_Tetra__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__swap"
  btAlignedObjectArray_btSoftBody_Tetra__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__pop_back"
  btAlignedObjectArray_btSoftBody_Tetra__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__deallocate"
  btAlignedObjectArray_btSoftBody_Tetra__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__allocate"
  btAlignedObjectArray_btSoftBody_Tetra__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_Tetra__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__expandNonInitializing"
  btAlignedObjectArray_btSoftBody_Tetra__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__destroy"
  btAlignedObjectArray_btSoftBody_Tetra__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__copy"
  btAlignedObjectArray_btSoftBody_Tetra__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__resize"
  btAlignedObjectArray_btSoftBody_Tetra__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__clear"
  btAlignedObjectArray_btSoftBody_Tetra__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__allocSize"
  btAlignedObjectArray_btSoftBody_Tetra__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__expand"
  btAlignedObjectArray_btSoftBody_Tetra__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__reserve"
  btAlignedObjectArray_btSoftBody_Tetra__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__m_allocator_set"
  btAlignedObjectArray_btSoftBody_Tetra__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__m_allocator_get"
  btAlignedObjectArray_btSoftBody_Tetra__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__m_capacity_set"
  btAlignedObjectArray_btSoftBody_Tetra__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__m_capacity_get"
  btAlignedObjectArray_btSoftBody_Tetra__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__m_data_set"
  btAlignedObjectArray_btSoftBody_Tetra__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__m_data_get"
  btAlignedObjectArray_btSoftBody_Tetra__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_Tetra__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_Tetra__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__m_size_set"
  btAlignedObjectArray_btSoftBody_Tetra__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_Tetra__m_size_get"
  btAlignedObjectArray_btSoftBody_Tetra__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____new"
  btAlignedObjectArray_btSoftBody_ePSolver___'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____free"
  btAlignedObjectArray_btSoftBody_ePSolver____free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____size"
  btAlignedObjectArray_btSoftBody_ePSolver____size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____capacity"
  btAlignedObjectArray_btSoftBody_ePSolver____capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____init"
  btAlignedObjectArray_btSoftBody_ePSolver____init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____swap"
  btAlignedObjectArray_btSoftBody_ePSolver____swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____pop_back"
  btAlignedObjectArray_btSoftBody_ePSolver____pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____deallocate"
  btAlignedObjectArray_btSoftBody_ePSolver____deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____allocate"
  btAlignedObjectArray_btSoftBody_ePSolver____allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_ePSolver____initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____destroy"
  btAlignedObjectArray_btSoftBody_ePSolver____destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____clear"
  btAlignedObjectArray_btSoftBody_ePSolver____clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____allocSize"
  btAlignedObjectArray_btSoftBody_ePSolver____allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____reserve"
  btAlignedObjectArray_btSoftBody_ePSolver____reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____m_allocator_set"
  btAlignedObjectArray_btSoftBody_ePSolver____m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____m_allocator_get"
  btAlignedObjectArray_btSoftBody_ePSolver____m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____m_capacity_set"
  btAlignedObjectArray_btSoftBody_ePSolver____m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____m_capacity_get"
  btAlignedObjectArray_btSoftBody_ePSolver____m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_ePSolver____m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_ePSolver____m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____m_size_set"
  btAlignedObjectArray_btSoftBody_ePSolver____m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_ePSolver____m_size_get"
  btAlignedObjectArray_btSoftBody_ePSolver____m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____new"
  btAlignedObjectArray_btSoftBody_eVSolver___'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____free"
  btAlignedObjectArray_btSoftBody_eVSolver____free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____size"
  btAlignedObjectArray_btSoftBody_eVSolver____size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____capacity"
  btAlignedObjectArray_btSoftBody_eVSolver____capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____init"
  btAlignedObjectArray_btSoftBody_eVSolver____init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____swap"
  btAlignedObjectArray_btSoftBody_eVSolver____swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____pop_back"
  btAlignedObjectArray_btSoftBody_eVSolver____pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____deallocate"
  btAlignedObjectArray_btSoftBody_eVSolver____deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____allocate"
  btAlignedObjectArray_btSoftBody_eVSolver____allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____initializeFromBuffer"
  btAlignedObjectArray_btSoftBody_eVSolver____initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____destroy"
  btAlignedObjectArray_btSoftBody_eVSolver____destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____clear"
  btAlignedObjectArray_btSoftBody_eVSolver____clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____allocSize"
  btAlignedObjectArray_btSoftBody_eVSolver____allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____reserve"
  btAlignedObjectArray_btSoftBody_eVSolver____reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____m_allocator_set"
  btAlignedObjectArray_btSoftBody_eVSolver____m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____m_allocator_get"
  btAlignedObjectArray_btSoftBody_eVSolver____m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____m_capacity_set"
  btAlignedObjectArray_btSoftBody_eVSolver____m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____m_capacity_get"
  btAlignedObjectArray_btSoftBody_eVSolver____m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____m_ownsMemory_set"
  btAlignedObjectArray_btSoftBody_eVSolver____m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____m_ownsMemory_get"
  btAlignedObjectArray_btSoftBody_eVSolver____m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____m_size_set"
  btAlignedObjectArray_btSoftBody_eVSolver____m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSoftBody_eVSolver____m_size_get"
  btAlignedObjectArray_btSoftBody_eVSolver____m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__new"
  btAlignedObjectArray_btSolverConstraint_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__free"
  btAlignedObjectArray_btSolverConstraint__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__push_back"
  btAlignedObjectArray_btSolverConstraint__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__at0"
  btAlignedObjectArray_btSolverConstraint__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__at0"
  btAlignedObjectArray_btSolverConstraint__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__at1"
  btAlignedObjectArray_btSolverConstraint__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__size"
  btAlignedObjectArray_btSolverConstraint__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__capacity"
  btAlignedObjectArray_btSolverConstraint__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__init"
  btAlignedObjectArray_btSolverConstraint__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__allocate"
  btAlignedObjectArray_btSolverConstraint__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__pop_back"
  btAlignedObjectArray_btSolverConstraint__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__deallocate"
  btAlignedObjectArray_btSolverConstraint__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__swap"
  btAlignedObjectArray_btSolverConstraint__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__initializeFromBuffer"
  btAlignedObjectArray_btSolverConstraint__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__expandNonInitializing"
  btAlignedObjectArray_btSolverConstraint__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__resize"
  btAlignedObjectArray_btSolverConstraint__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__destroy"
  btAlignedObjectArray_btSolverConstraint__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__copy"
  btAlignedObjectArray_btSolverConstraint__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__expand"
  btAlignedObjectArray_btSolverConstraint__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__clear"
  btAlignedObjectArray_btSolverConstraint__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__allocSize"
  btAlignedObjectArray_btSolverConstraint__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__reserve"
  btAlignedObjectArray_btSolverConstraint__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__m_allocator_set"
  btAlignedObjectArray_btSolverConstraint__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__m_allocator_get"
  btAlignedObjectArray_btSolverConstraint__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__m_size_set"
  btAlignedObjectArray_btSolverConstraint__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__m_size_get"
  btAlignedObjectArray_btSolverConstraint__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__m_capacity_set"
  btAlignedObjectArray_btSolverConstraint__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__m_capacity_get"
  btAlignedObjectArray_btSolverConstraint__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__m_data_set"
  btAlignedObjectArray_btSolverConstraint__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__m_data_get"
  btAlignedObjectArray_btSolverConstraint__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__m_ownsMemory_set"
  btAlignedObjectArray_btSolverConstraint__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSolverConstraint__m_ownsMemory_get"
  btAlignedObjectArray_btSolverConstraint__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__new"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__free"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__size"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__capacity"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__init"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__swap"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__pop_back"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__deallocate"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__allocate"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__initializeFromBuffer"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__destroy"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__clear"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__allocSize"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__reserve"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_allocator_set"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_allocator_get"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_capacity_set"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_capacity_get"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_ownsMemory_set"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_ownsMemory_get"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_size_set"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_size_get"
  btAlignedObjectArray_btSparseSdf_3__Cell_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__new"
  btAlignedObjectArray_btTransform_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__free"
  btAlignedObjectArray_btTransform__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__push_back"
  btAlignedObjectArray_btTransform__push_back'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__push_back"
  btAlignedObjectArray_btTransform__push_back''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__at0"
  btAlignedObjectArray_btTransform__at'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__at0"
  btAlignedObjectArray_btTransform__at0'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__at1"
  btAlignedObjectArray_btTransform__at1'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__size"
  btAlignedObjectArray_btTransform__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__capacity"
  btAlignedObjectArray_btTransform__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__init"
  btAlignedObjectArray_btTransform__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__allocate"
  btAlignedObjectArray_btTransform__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__pop_back"
  btAlignedObjectArray_btTransform__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__deallocate"
  btAlignedObjectArray_btTransform__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__swap"
  btAlignedObjectArray_btTransform__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__initializeFromBuffer"
  btAlignedObjectArray_btTransform__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__expandNonInitializing"
  btAlignedObjectArray_btTransform__expandNonInitializing'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__resize"
  btAlignedObjectArray_btTransform__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__resize"
  btAlignedObjectArray_btTransform__resize''_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__destroy"
  btAlignedObjectArray_btTransform__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__expand"
  btAlignedObjectArray_btTransform__expand'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__expand"
  btAlignedObjectArray_btTransform__expand''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__clear"
  btAlignedObjectArray_btTransform__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__allocSize"
  btAlignedObjectArray_btTransform__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__reserve"
  btAlignedObjectArray_btTransform__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__m_allocator_set"
  btAlignedObjectArray_btTransform__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__m_allocator_get"
  btAlignedObjectArray_btTransform__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__m_size_set"
  btAlignedObjectArray_btTransform__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__m_size_get"
  btAlignedObjectArray_btTransform__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__m_capacity_set"
  btAlignedObjectArray_btTransform__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__m_capacity_get"
  btAlignedObjectArray_btTransform__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__m_ownsMemory_set"
  btAlignedObjectArray_btTransform__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTransform__m_ownsMemory_get"
  btAlignedObjectArray_btTransform__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__new"
  btAlignedObjectArray_btTriangleInfo_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__free"
  btAlignedObjectArray_btTriangleInfo__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__push_back"
  btAlignedObjectArray_btTriangleInfo__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__at0"
  btAlignedObjectArray_btTriangleInfo__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__at0"
  btAlignedObjectArray_btTriangleInfo__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__at1"
  btAlignedObjectArray_btTriangleInfo__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__size"
  btAlignedObjectArray_btTriangleInfo__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__capacity"
  btAlignedObjectArray_btTriangleInfo__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__init"
  btAlignedObjectArray_btTriangleInfo__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__allocate"
  btAlignedObjectArray_btTriangleInfo__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__pop_back"
  btAlignedObjectArray_btTriangleInfo__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__deallocate"
  btAlignedObjectArray_btTriangleInfo__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__swap"
  btAlignedObjectArray_btTriangleInfo__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__initializeFromBuffer"
  btAlignedObjectArray_btTriangleInfo__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__expandNonInitializing"
  btAlignedObjectArray_btTriangleInfo__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__resize"
  btAlignedObjectArray_btTriangleInfo__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__destroy"
  btAlignedObjectArray_btTriangleInfo__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__copy"
  btAlignedObjectArray_btTriangleInfo__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__expand"
  btAlignedObjectArray_btTriangleInfo__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__clear"
  btAlignedObjectArray_btTriangleInfo__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__allocSize"
  btAlignedObjectArray_btTriangleInfo__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__reserve"
  btAlignedObjectArray_btTriangleInfo__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__m_allocator_set"
  btAlignedObjectArray_btTriangleInfo__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__m_allocator_get"
  btAlignedObjectArray_btTriangleInfo__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__m_size_set"
  btAlignedObjectArray_btTriangleInfo__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__m_size_get"
  btAlignedObjectArray_btTriangleInfo__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__m_capacity_set"
  btAlignedObjectArray_btTriangleInfo__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__m_capacity_get"
  btAlignedObjectArray_btTriangleInfo__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__m_data_set"
  btAlignedObjectArray_btTriangleInfo__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__m_data_get"
  btAlignedObjectArray_btTriangleInfo__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__m_ownsMemory_set"
  btAlignedObjectArray_btTriangleInfo__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTriangleInfo__m_ownsMemory_get"
  btAlignedObjectArray_btTriangleInfo__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__new"
  btAlignedObjectArray_btTypedConstraint_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__free"
  btAlignedObjectArray_btTypedConstraint_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__push_back"
  btAlignedObjectArray_btTypedConstraint_ptr__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__at0"
  btAlignedObjectArray_btTypedConstraint_ptr__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__at0"
  btAlignedObjectArray_btTypedConstraint_ptr__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__at1"
  btAlignedObjectArray_btTypedConstraint_ptr__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__size"
  btAlignedObjectArray_btTypedConstraint_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__capacity"
  btAlignedObjectArray_btTypedConstraint_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__init"
  btAlignedObjectArray_btTypedConstraint_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__allocate"
  btAlignedObjectArray_btTypedConstraint_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__pop_back"
  btAlignedObjectArray_btTypedConstraint_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__deallocate"
  btAlignedObjectArray_btTypedConstraint_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__swap"
  btAlignedObjectArray_btTypedConstraint_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__initializeFromBuffer"
  btAlignedObjectArray_btTypedConstraint_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__expandNonInitializing"
  btAlignedObjectArray_btTypedConstraint_ptr__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__resize"
  btAlignedObjectArray_btTypedConstraint_ptr__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__destroy"
  btAlignedObjectArray_btTypedConstraint_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__expand"
  btAlignedObjectArray_btTypedConstraint_ptr__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__clear"
  btAlignedObjectArray_btTypedConstraint_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__allocSize"
  btAlignedObjectArray_btTypedConstraint_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__reserve"
  btAlignedObjectArray_btTypedConstraint_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__m_allocator_set"
  btAlignedObjectArray_btTypedConstraint_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__m_allocator_get"
  btAlignedObjectArray_btTypedConstraint_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__m_size_set"
  btAlignedObjectArray_btTypedConstraint_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__m_size_get"
  btAlignedObjectArray_btTypedConstraint_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__m_capacity_set"
  btAlignedObjectArray_btTypedConstraint_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__m_capacity_get"
  btAlignedObjectArray_btTypedConstraint_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__m_ownsMemory_set"
  btAlignedObjectArray_btTypedConstraint_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_ptr__m_ownsMemory_get"
  btAlignedObjectArray_btTypedConstraint_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__new"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__free"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__push_back"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at0"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at0"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at1"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__size"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__capacity"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__init"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__allocate"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__pop_back"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__deallocate"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__swap"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__initializeFromBuffer"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__expandNonInitializing"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__resize"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__destroy"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__copy"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__expand"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__clear"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__allocSize"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__reserve"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_allocator_set"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_allocator_get"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_size_set"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_size_get"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_capacity_set"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_capacity_get"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_data_set"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_data_get"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_ownsMemory_set"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_ownsMemory_get"
  btAlignedObjectArray_btTypedConstraint_btConstraintInfo1__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__new"
  btAlignedObjectArray_btVector3_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__free"
  btAlignedObjectArray_btVector3__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__push_back"
  btAlignedObjectArray_btVector3__push_back'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__push_back"
  btAlignedObjectArray_btVector3__push_back''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__at0"
  btAlignedObjectArray_btVector3__at'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__at0"
  btAlignedObjectArray_btVector3__at0'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__at1"
  btAlignedObjectArray_btVector3__at1'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__size"
  btAlignedObjectArray_btVector3__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__capacity"
  btAlignedObjectArray_btVector3__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__init"
  btAlignedObjectArray_btVector3__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__swap"
  btAlignedObjectArray_btVector3__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__pop_back"
  btAlignedObjectArray_btVector3__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__deallocate"
  btAlignedObjectArray_btVector3__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__allocate"
  btAlignedObjectArray_btVector3__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__initializeFromBuffer"
  btAlignedObjectArray_btVector3__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__expandNonInitializing"
  btAlignedObjectArray_btVector3__expandNonInitializing'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__destroy"
  btAlignedObjectArray_btVector3__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__resize"
  btAlignedObjectArray_btVector3__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__resize"
  btAlignedObjectArray_btVector3__resize''_ :: ((Ptr ()) -> (CInt -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__clear"
  btAlignedObjectArray_btVector3__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__allocSize"
  btAlignedObjectArray_btVector3__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__expand"
  btAlignedObjectArray_btVector3__expand'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__expand"
  btAlignedObjectArray_btVector3__expand''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__reserve"
  btAlignedObjectArray_btVector3__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__m_allocator_set"
  btAlignedObjectArray_btVector3__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__m_allocator_get"
  btAlignedObjectArray_btVector3__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__m_capacity_set"
  btAlignedObjectArray_btVector3__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__m_capacity_get"
  btAlignedObjectArray_btVector3__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__m_ownsMemory_set"
  btAlignedObjectArray_btVector3__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__m_ownsMemory_get"
  btAlignedObjectArray_btVector3__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__m_size_set"
  btAlignedObjectArray_btVector3__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btVector3__m_size_get"
  btAlignedObjectArray_btVector3__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__new"
  btAlignedObjectArray_btWheelInfo_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__free"
  btAlignedObjectArray_btWheelInfo__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__push_back"
  btAlignedObjectArray_btWheelInfo__push_back'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__at0"
  btAlignedObjectArray_btWheelInfo__at'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__at0"
  btAlignedObjectArray_btWheelInfo__at0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__at1"
  btAlignedObjectArray_btWheelInfo__at1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__size"
  btAlignedObjectArray_btWheelInfo__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__capacity"
  btAlignedObjectArray_btWheelInfo__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__init"
  btAlignedObjectArray_btWheelInfo__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__allocate"
  btAlignedObjectArray_btWheelInfo__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__pop_back"
  btAlignedObjectArray_btWheelInfo__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__deallocate"
  btAlignedObjectArray_btWheelInfo__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__swap"
  btAlignedObjectArray_btWheelInfo__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__initializeFromBuffer"
  btAlignedObjectArray_btWheelInfo__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__expandNonInitializing"
  btAlignedObjectArray_btWheelInfo__expandNonInitializing'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__resize"
  btAlignedObjectArray_btWheelInfo__resize'_ :: ((Ptr ()) -> (CInt -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__destroy"
  btAlignedObjectArray_btWheelInfo__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__copy"
  btAlignedObjectArray_btWheelInfo__copy'_ :: ((Ptr ()) -> (CInt -> (CInt -> ((Ptr ()) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__expand"
  btAlignedObjectArray_btWheelInfo__expand'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__clear"
  btAlignedObjectArray_btWheelInfo__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__allocSize"
  btAlignedObjectArray_btWheelInfo__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__reserve"
  btAlignedObjectArray_btWheelInfo__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__m_allocator_set"
  btAlignedObjectArray_btWheelInfo__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__m_allocator_get"
  btAlignedObjectArray_btWheelInfo__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__m_size_set"
  btAlignedObjectArray_btWheelInfo__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__m_size_get"
  btAlignedObjectArray_btWheelInfo__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__m_capacity_set"
  btAlignedObjectArray_btWheelInfo__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__m_capacity_get"
  btAlignedObjectArray_btWheelInfo__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__m_data_set"
  btAlignedObjectArray_btWheelInfo__m_data_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__m_data_get"
  btAlignedObjectArray_btWheelInfo__m_data_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__m_ownsMemory_set"
  btAlignedObjectArray_btWheelInfo__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_btWheelInfo__m_ownsMemory_get"
  btAlignedObjectArray_btWheelInfo__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__new"
  btAlignedObjectArray_charconst_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__free"
  btAlignedObjectArray_charconst_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__size"
  btAlignedObjectArray_charconst_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__capacity"
  btAlignedObjectArray_charconst_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__init"
  btAlignedObjectArray_charconst_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__allocate"
  btAlignedObjectArray_charconst_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__pop_back"
  btAlignedObjectArray_charconst_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__deallocate"
  btAlignedObjectArray_charconst_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__swap"
  btAlignedObjectArray_charconst_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__initializeFromBuffer"
  btAlignedObjectArray_charconst_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__destroy"
  btAlignedObjectArray_charconst_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__clear"
  btAlignedObjectArray_charconst_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__allocSize"
  btAlignedObjectArray_charconst_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__reserve"
  btAlignedObjectArray_charconst_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__m_allocator_set"
  btAlignedObjectArray_charconst_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__m_allocator_get"
  btAlignedObjectArray_charconst_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__m_size_set"
  btAlignedObjectArray_charconst_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__m_size_get"
  btAlignedObjectArray_charconst_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__m_capacity_set"
  btAlignedObjectArray_charconst_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__m_capacity_get"
  btAlignedObjectArray_charconst_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__m_ownsMemory_set"
  btAlignedObjectArray_charconst_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_charconst_ptr__m_ownsMemory_get"
  btAlignedObjectArray_charconst_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__new"
  btAlignedObjectArray_char_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__free"
  btAlignedObjectArray_char_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__size"
  btAlignedObjectArray_char_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__capacity"
  btAlignedObjectArray_char_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__init"
  btAlignedObjectArray_char_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__allocate"
  btAlignedObjectArray_char_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__pop_back"
  btAlignedObjectArray_char_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__deallocate"
  btAlignedObjectArray_char_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__swap"
  btAlignedObjectArray_char_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__initializeFromBuffer"
  btAlignedObjectArray_char_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__destroy"
  btAlignedObjectArray_char_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__clear"
  btAlignedObjectArray_char_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__allocSize"
  btAlignedObjectArray_char_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__reserve"
  btAlignedObjectArray_char_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__m_allocator_set"
  btAlignedObjectArray_char_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__m_allocator_get"
  btAlignedObjectArray_char_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__m_size_set"
  btAlignedObjectArray_char_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__m_size_get"
  btAlignedObjectArray_char_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__m_capacity_set"
  btAlignedObjectArray_char_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__m_capacity_get"
  btAlignedObjectArray_char_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__m_ownsMemory_set"
  btAlignedObjectArray_char_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_char_ptr__m_ownsMemory_get"
  btAlignedObjectArray_char_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__new"
  btAlignedObjectArray_float_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__free"
  btAlignedObjectArray_float__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__size"
  btAlignedObjectArray_float__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__capacity"
  btAlignedObjectArray_float__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__init"
  btAlignedObjectArray_float__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__swap"
  btAlignedObjectArray_float__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__pop_back"
  btAlignedObjectArray_float__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__deallocate"
  btAlignedObjectArray_float__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__allocate"
  btAlignedObjectArray_float__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__initializeFromBuffer"
  btAlignedObjectArray_float__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__destroy"
  btAlignedObjectArray_float__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__clear"
  btAlignedObjectArray_float__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__allocSize"
  btAlignedObjectArray_float__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__reserve"
  btAlignedObjectArray_float__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__m_allocator_set"
  btAlignedObjectArray_float__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__m_allocator_get"
  btAlignedObjectArray_float__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__m_capacity_set"
  btAlignedObjectArray_float__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__m_capacity_get"
  btAlignedObjectArray_float__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__m_ownsMemory_set"
  btAlignedObjectArray_float__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__m_ownsMemory_get"
  btAlignedObjectArray_float__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__m_size_set"
  btAlignedObjectArray_float__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_float__m_size_get"
  btAlignedObjectArray_float__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__new"
  btAlignedObjectArray_int_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__free"
  btAlignedObjectArray_int__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__size"
  btAlignedObjectArray_int__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__capacity"
  btAlignedObjectArray_int__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__init"
  btAlignedObjectArray_int__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__swap"
  btAlignedObjectArray_int__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__pop_back"
  btAlignedObjectArray_int__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__deallocate"
  btAlignedObjectArray_int__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__allocate"
  btAlignedObjectArray_int__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__initializeFromBuffer"
  btAlignedObjectArray_int__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__destroy"
  btAlignedObjectArray_int__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__clear"
  btAlignedObjectArray_int__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__allocSize"
  btAlignedObjectArray_int__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__reserve"
  btAlignedObjectArray_int__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__m_allocator_set"
  btAlignedObjectArray_int__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__m_allocator_get"
  btAlignedObjectArray_int__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__m_capacity_set"
  btAlignedObjectArray_int__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__m_capacity_get"
  btAlignedObjectArray_int__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__m_ownsMemory_set"
  btAlignedObjectArray_int__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__m_ownsMemory_get"
  btAlignedObjectArray_int__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__m_size_set"
  btAlignedObjectArray_int__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_int__m_size_get"
  btAlignedObjectArray_int__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__new"
  btAlignedObjectArray_short_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__free"
  btAlignedObjectArray_short_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__size"
  btAlignedObjectArray_short_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__capacity"
  btAlignedObjectArray_short_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__init"
  btAlignedObjectArray_short_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__allocate"
  btAlignedObjectArray_short_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__pop_back"
  btAlignedObjectArray_short_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__deallocate"
  btAlignedObjectArray_short_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__swap"
  btAlignedObjectArray_short_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__initializeFromBuffer"
  btAlignedObjectArray_short_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__destroy"
  btAlignedObjectArray_short_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__clear"
  btAlignedObjectArray_short_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__allocSize"
  btAlignedObjectArray_short_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__reserve"
  btAlignedObjectArray_short_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__m_allocator_set"
  btAlignedObjectArray_short_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__m_allocator_get"
  btAlignedObjectArray_short_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__m_size_set"
  btAlignedObjectArray_short_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__m_size_get"
  btAlignedObjectArray_short_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__m_capacity_set"
  btAlignedObjectArray_short_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__m_capacity_get"
  btAlignedObjectArray_short_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__m_ownsMemory_set"
  btAlignedObjectArray_short_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short_ptr__m_ownsMemory_get"
  btAlignedObjectArray_short_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__new"
  btAlignedObjectArray_short_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__free"
  btAlignedObjectArray_short__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__size"
  btAlignedObjectArray_short__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__capacity"
  btAlignedObjectArray_short__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__init"
  btAlignedObjectArray_short__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__allocate"
  btAlignedObjectArray_short__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__pop_back"
  btAlignedObjectArray_short__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__deallocate"
  btAlignedObjectArray_short__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__swap"
  btAlignedObjectArray_short__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__initializeFromBuffer"
  btAlignedObjectArray_short__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__destroy"
  btAlignedObjectArray_short__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__clear"
  btAlignedObjectArray_short__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__allocSize"
  btAlignedObjectArray_short__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__reserve"
  btAlignedObjectArray_short__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__m_allocator_set"
  btAlignedObjectArray_short__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__m_allocator_get"
  btAlignedObjectArray_short__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__m_size_set"
  btAlignedObjectArray_short__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__m_size_get"
  btAlignedObjectArray_short__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__m_capacity_set"
  btAlignedObjectArray_short__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__m_capacity_get"
  btAlignedObjectArray_short__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__m_ownsMemory_set"
  btAlignedObjectArray_short__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_short__m_ownsMemory_get"
  btAlignedObjectArray_short__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__new"
  btAlignedObjectArray_unsignedint_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__free"
  btAlignedObjectArray_unsignedint__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__size"
  btAlignedObjectArray_unsignedint__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__capacity"
  btAlignedObjectArray_unsignedint__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__init"
  btAlignedObjectArray_unsignedint__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__allocate"
  btAlignedObjectArray_unsignedint__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__pop_back"
  btAlignedObjectArray_unsignedint__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__deallocate"
  btAlignedObjectArray_unsignedint__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__swap"
  btAlignedObjectArray_unsignedint__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__initializeFromBuffer"
  btAlignedObjectArray_unsignedint__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__destroy"
  btAlignedObjectArray_unsignedint__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__clear"
  btAlignedObjectArray_unsignedint__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__allocSize"
  btAlignedObjectArray_unsignedint__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__reserve"
  btAlignedObjectArray_unsignedint__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__m_allocator_set"
  btAlignedObjectArray_unsignedint__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__m_allocator_get"
  btAlignedObjectArray_unsignedint__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__m_size_set"
  btAlignedObjectArray_unsignedint__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__m_size_get"
  btAlignedObjectArray_unsignedint__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__m_capacity_set"
  btAlignedObjectArray_unsignedint__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__m_capacity_get"
  btAlignedObjectArray_unsignedint__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__m_ownsMemory_set"
  btAlignedObjectArray_unsignedint__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedint__m_ownsMemory_get"
  btAlignedObjectArray_unsignedint__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__new"
  btAlignedObjectArray_unsignedshort_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__free"
  btAlignedObjectArray_unsignedshort__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__size"
  btAlignedObjectArray_unsignedshort__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__capacity"
  btAlignedObjectArray_unsignedshort__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__init"
  btAlignedObjectArray_unsignedshort__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__allocate"
  btAlignedObjectArray_unsignedshort__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__pop_back"
  btAlignedObjectArray_unsignedshort__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__deallocate"
  btAlignedObjectArray_unsignedshort__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__swap"
  btAlignedObjectArray_unsignedshort__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__initializeFromBuffer"
  btAlignedObjectArray_unsignedshort__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__destroy"
  btAlignedObjectArray_unsignedshort__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__clear"
  btAlignedObjectArray_unsignedshort__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__allocSize"
  btAlignedObjectArray_unsignedshort__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__reserve"
  btAlignedObjectArray_unsignedshort__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__m_allocator_set"
  btAlignedObjectArray_unsignedshort__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__m_allocator_get"
  btAlignedObjectArray_unsignedshort__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__m_size_set"
  btAlignedObjectArray_unsignedshort__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__m_size_get"
  btAlignedObjectArray_unsignedshort__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__m_capacity_set"
  btAlignedObjectArray_unsignedshort__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__m_capacity_get"
  btAlignedObjectArray_unsignedshort__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__m_ownsMemory_set"
  btAlignedObjectArray_unsignedshort__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_unsignedshort__m_ownsMemory_get"
  btAlignedObjectArray_unsignedshort__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__new"
  btAlignedObjectArray_void_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__free"
  btAlignedObjectArray_void_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__size"
  btAlignedObjectArray_void_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__capacity"
  btAlignedObjectArray_void_ptr__capacity'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__init"
  btAlignedObjectArray_void_ptr__init'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__allocate"
  btAlignedObjectArray_void_ptr__allocate'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__pop_back"
  btAlignedObjectArray_void_ptr__pop_back'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__deallocate"
  btAlignedObjectArray_void_ptr__deallocate'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__swap"
  btAlignedObjectArray_void_ptr__swap'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__initializeFromBuffer"
  btAlignedObjectArray_void_ptr__initializeFromBuffer'_ :: ((Ptr ()) -> ((Ptr ()) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__destroy"
  btAlignedObjectArray_void_ptr__destroy'_ :: ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__clear"
  btAlignedObjectArray_void_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__allocSize"
  btAlignedObjectArray_void_ptr__allocSize'_ :: ((Ptr ()) -> (CInt -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__reserve"
  btAlignedObjectArray_void_ptr__reserve'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__m_allocator_set"
  btAlignedObjectArray_void_ptr__m_allocator_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__m_allocator_get"
  btAlignedObjectArray_void_ptr__m_allocator_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__m_size_set"
  btAlignedObjectArray_void_ptr__m_size_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__m_size_get"
  btAlignedObjectArray_void_ptr__m_size_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__m_capacity_set"
  btAlignedObjectArray_void_ptr__m_capacity_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__m_capacity_get"
  btAlignedObjectArray_void_ptr__m_capacity_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__m_ownsMemory_set"
  btAlignedObjectArray_void_ptr__m_ownsMemory_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btAlignedObjectArray_void_ptr__m_ownsMemory_get"
  btAlignedObjectArray_void_ptr__m_ownsMemory_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btBlock_new"
  btBlock'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btBlock_free"
  btBlock_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btBlock_previous_set"
  btBlock_previous_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btBlock_previous_get"
  btBlock_previous_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btChunk_new"
  btChunk'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btChunk_free"
  btChunk_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btChunk_m_chunkCode_set"
  btChunk_m_chunkCode_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btChunk_m_chunkCode_get"
  btChunk_m_chunkCode_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btChunk_m_dna_nr_set"
  btChunk_m_dna_nr_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btChunk_m_dna_nr_get"
  btChunk_m_dna_nr_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btChunk_m_length_set"
  btChunk_m_length_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btChunk_m_length_get"
  btChunk_m_length_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btChunk_m_number_set"
  btChunk_m_number_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btChunk_m_number_get"
  btChunk_m_number_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btChunk_m_oldPtr_set"
  btChunk_m_oldPtr_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btChunk_m_oldPtr_get"
  btChunk_m_oldPtr_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btClock_new"
  btClock'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btClock_free"
  btClock_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btClock_reset"
  btClock_reset'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btClock_getTimeMilliseconds"
  btClock_getTimeMilliseconds'_ :: ((Ptr ()) -> (IO CULong))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btClock_getTimeMicroseconds"
  btClock_getTimeMicroseconds'_ :: ((Ptr ()) -> (IO CULong))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_new"
  btConvexSeparatingDistanceUtil'_ :: (CFloat -> (CFloat -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_free"
  btConvexSeparatingDistanceUtil_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_updateSeparatingDistance"
  btConvexSeparatingDistanceUtil_updateSeparatingDistance'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_updateSeparatingDistance"
  btConvexSeparatingDistanceUtil_updateSeparatingDistance''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_getConservativeSeparatingDistance"
  btConvexSeparatingDistanceUtil_getConservativeSeparatingDistance'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_initSeparatingDistance"
  btConvexSeparatingDistanceUtil_initSeparatingDistance'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (CFloat -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_initSeparatingDistance"
  btConvexSeparatingDistanceUtil_initSeparatingDistance''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (CFloat -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_ornA_set"
  btConvexSeparatingDistanceUtil_m_ornA_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_ornA_get"
  btConvexSeparatingDistanceUtil_m_ornA_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_ornB_set"
  btConvexSeparatingDistanceUtil_m_ornB_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_ornB_get"
  btConvexSeparatingDistanceUtil_m_ornB_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_posA_set"
  btConvexSeparatingDistanceUtil_m_posA_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_posA_get"
  btConvexSeparatingDistanceUtil_m_posA_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_posB_set"
  btConvexSeparatingDistanceUtil_m_posB_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_posB_get"
  btConvexSeparatingDistanceUtil_m_posB_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_separatingNormal_set"
  btConvexSeparatingDistanceUtil_m_separatingNormal_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_separatingNormal_get"
  btConvexSeparatingDistanceUtil_m_separatingNormal_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_boundingRadiusA_set"
  btConvexSeparatingDistanceUtil_m_boundingRadiusA_set'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_boundingRadiusA_get"
  btConvexSeparatingDistanceUtil_m_boundingRadiusA_get'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_boundingRadiusB_set"
  btConvexSeparatingDistanceUtil_m_boundingRadiusB_set'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_boundingRadiusB_get"
  btConvexSeparatingDistanceUtil_m_boundingRadiusB_get'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_separatingDistance_set"
  btConvexSeparatingDistanceUtil_m_separatingDistance_set'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btConvexSeparatingDistanceUtil_m_separatingDistance_get"
  btConvexSeparatingDistanceUtil_m_separatingDistance_get'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_new"
  btDefaultMotionState'_ :: ((Ptr CFloat) -> ((Ptr CFloat) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_free"
  btDefaultMotionState_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_setWorldTransform"
  btDefaultMotionState_setWorldTransform'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_setWorldTransform"
  btDefaultMotionState_setWorldTransform''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_getWorldTransform"
  btDefaultMotionState_getWorldTransform'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_getWorldTransform"
  btDefaultMotionState_getWorldTransform''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_m_graphicsWorldTrans_set"
  btDefaultMotionState_m_graphicsWorldTrans_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_m_graphicsWorldTrans_get"
  btDefaultMotionState_m_graphicsWorldTrans_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_m_centerOfMassOffset_set"
  btDefaultMotionState_m_centerOfMassOffset_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_m_centerOfMassOffset_get"
  btDefaultMotionState_m_centerOfMassOffset_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_m_startWorldTrans_set"
  btDefaultMotionState_m_startWorldTrans_set'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_m_startWorldTrans_get"
  btDefaultMotionState_m_startWorldTrans_get'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_m_userPointer_set"
  btDefaultMotionState_m_userPointer_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultMotionState_m_userPointer_get"
  btDefaultMotionState_m_userPointer_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_new"
  btDefaultSerializer'_ :: (CInt -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_free"
  btDefaultSerializer_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_finishSerialization"
  btDefaultSerializer_finishSerialization'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_startSerialization"
  btDefaultSerializer_startSerialization'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_getSerializationFlags"
  btDefaultSerializer_getSerializationFlags'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_setSerializationFlags"
  btDefaultSerializer_setSerializationFlags'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_getReverseType"
  btDefaultSerializer_getReverseType'_ :: ((Ptr ()) -> ((Ptr CChar) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_finalizeChunk"
  btDefaultSerializer_finalizeChunk'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CChar) -> (CInt -> ((Ptr ()) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_initDNA"
  btDefaultSerializer_initDNA'_ :: ((Ptr ()) -> ((Ptr CChar) -> (CInt -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_writeDNA"
  btDefaultSerializer_writeDNA'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_getCurrentBufferSize"
  btDefaultSerializer_getCurrentBufferSize'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_getUniquePointer"
  btDefaultSerializer_getUniquePointer'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_serializeName"
  btDefaultSerializer_serializeName'_ :: ((Ptr ()) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_findPointer"
  btDefaultSerializer_findPointer'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_mTypes_set"
  btDefaultSerializer_mTypes_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_mTypes_get"
  btDefaultSerializer_mTypes_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_mStructs_set"
  btDefaultSerializer_mStructs_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_mStructs_get"
  btDefaultSerializer_mStructs_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_mTlens_set"
  btDefaultSerializer_mTlens_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_mTlens_get"
  btDefaultSerializer_mTlens_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_mStructReverse_set"
  btDefaultSerializer_mStructReverse_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_mStructReverse_get"
  btDefaultSerializer_mStructReverse_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_mTypeLookup_set"
  btDefaultSerializer_mTypeLookup_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_mTypeLookup_get"
  btDefaultSerializer_mTypeLookup_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_chunkP_set"
  btDefaultSerializer_m_chunkP_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_chunkP_get"
  btDefaultSerializer_m_chunkP_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_nameMap_set"
  btDefaultSerializer_m_nameMap_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_nameMap_get"
  btDefaultSerializer_m_nameMap_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_uniquePointers_set"
  btDefaultSerializer_m_uniquePointers_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_uniquePointers_get"
  btDefaultSerializer_m_uniquePointers_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_uniqueIdGenerator_set"
  btDefaultSerializer_m_uniqueIdGenerator_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_uniqueIdGenerator_get"
  btDefaultSerializer_m_uniqueIdGenerator_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_totalSize_set"
  btDefaultSerializer_m_totalSize_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_totalSize_get"
  btDefaultSerializer_m_totalSize_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_currentSize_set"
  btDefaultSerializer_m_currentSize_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_currentSize_get"
  btDefaultSerializer_m_currentSize_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_dna_set"
  btDefaultSerializer_m_dna_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_dna_get"
  btDefaultSerializer_m_dna_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_dnaLength_set"
  btDefaultSerializer_m_dnaLength_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_dnaLength_get"
  btDefaultSerializer_m_dnaLength_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_serializationFlags_set"
  btDefaultSerializer_m_serializationFlags_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_serializationFlags_get"
  btDefaultSerializer_m_serializationFlags_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_chunkPtrs_set"
  btDefaultSerializer_m_chunkPtrs_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btDefaultSerializer_m_chunkPtrs_get"
  btDefaultSerializer_m_chunkPtrs_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btGeometryUtil_new"
  btGeometryUtil'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btGeometryUtil_free"
  btGeometryUtil_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btGeometryUtil_isPointInsidePlanes"
  btGeometryUtil_isPointInsidePlanes'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (CFloat -> (IO CInt))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btGeometryUtil_isPointInsidePlanes"
  btGeometryUtil_isPointInsidePlanes''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (CFloat -> (IO CInt))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btGeometryUtil_getVerticesFromPlaneEquations"
  btGeometryUtil_getVerticesFromPlaneEquations'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btGeometryUtil_areVerticesBehindPlane"
  btGeometryUtil_areVerticesBehindPlane'_ :: ((Ptr CFloat) -> ((Ptr ()) -> (CFloat -> (IO CInt))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btGeometryUtil_areVerticesBehindPlane"
  btGeometryUtil_areVerticesBehindPlane''_ :: ((Ptr CFloat) -> ((Ptr ()) -> (CFloat -> (IO CInt))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btGeometryUtil_getPlaneEquationsFromVertices"
  btGeometryUtil_getPlaneEquationsFromVertices'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashInt_new"
  btHashInt'_ :: (CInt -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashInt_free"
  btHashInt_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashInt_getUid1"
  btHashInt_getUid1'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashInt_getHash"
  btHashInt_getHash'_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashInt_setUid1"
  btHashInt_setUid1'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashInt_equals"
  btHashInt_equals'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashInt_m_uid_set"
  btHashInt_m_uid_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashInt_m_uid_get"
  btHashInt_m_uid_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__new"
  btHashMap_btHashInt_btTriangleInfo_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__free"
  btHashMap_btHashInt_btTriangleInfo__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__insert"
  btHashMap_btHashInt_btTriangleInfo__insert'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__findIndex"
  btHashMap_btHashInt_btTriangleInfo__findIndex'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__clear"
  btHashMap_btHashInt_btTriangleInfo__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__getAtIndex0"
  btHashMap_btHashInt_btTriangleInfo__getAtIndex'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__getAtIndex0"
  btHashMap_btHashInt_btTriangleInfo__getAtIndex0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__getAtIndex1"
  btHashMap_btHashInt_btTriangleInfo__getAtIndex1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__growTables"
  btHashMap_btHashInt_btTriangleInfo__growTables'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__find0"
  btHashMap_btHashInt_btTriangleInfo__find'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__find0"
  btHashMap_btHashInt_btTriangleInfo__find0'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__find1"
  btHashMap_btHashInt_btTriangleInfo__find1'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__size"
  btHashMap_btHashInt_btTriangleInfo__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__m_hashTable_set"
  btHashMap_btHashInt_btTriangleInfo__m_hashTable_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__m_hashTable_get"
  btHashMap_btHashInt_btTriangleInfo__m_hashTable_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__m_next_set"
  btHashMap_btHashInt_btTriangleInfo__m_next_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__m_next_get"
  btHashMap_btHashInt_btTriangleInfo__m_next_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__m_valueArray_set"
  btHashMap_btHashInt_btTriangleInfo__m_valueArray_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__m_valueArray_get"
  btHashMap_btHashInt_btTriangleInfo__m_valueArray_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__m_keyArray_set"
  btHashMap_btHashInt_btTriangleInfo__m_keyArray_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_btTriangleInfo__m_keyArray_get"
  btHashMap_btHashInt_btTriangleInfo__m_keyArray_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__new"
  btHashMap_btHashInt_int_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__free"
  btHashMap_btHashInt_int__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__findIndex"
  btHashMap_btHashInt_int__findIndex'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__clear"
  btHashMap_btHashInt_int__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__growTables"
  btHashMap_btHashInt_int__growTables'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__size"
  btHashMap_btHashInt_int__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__m_hashTable_set"
  btHashMap_btHashInt_int__m_hashTable_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__m_hashTable_get"
  btHashMap_btHashInt_int__m_hashTable_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__m_keyArray_set"
  btHashMap_btHashInt_int__m_keyArray_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__m_keyArray_get"
  btHashMap_btHashInt_int__m_keyArray_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__m_next_set"
  btHashMap_btHashInt_int__m_next_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__m_next_get"
  btHashMap_btHashInt_int__m_next_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__m_valueArray_set"
  btHashMap_btHashInt_int__m_valueArray_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashInt_int__m_valueArray_get"
  btHashMap_btHashInt_int__m_valueArray_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__new"
  btHashMap_btHashPtr_btPointerUid_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__free"
  btHashMap_btHashPtr_btPointerUid__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__insert"
  btHashMap_btHashPtr_btPointerUid__insert'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr ()) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__findIndex"
  btHashMap_btHashPtr_btPointerUid__findIndex'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__clear"
  btHashMap_btHashPtr_btPointerUid__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__getAtIndex0"
  btHashMap_btHashPtr_btPointerUid__getAtIndex'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__getAtIndex0"
  btHashMap_btHashPtr_btPointerUid__getAtIndex0'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__getAtIndex1"
  btHashMap_btHashPtr_btPointerUid__getAtIndex1'_ :: ((Ptr ()) -> (CInt -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__growTables"
  btHashMap_btHashPtr_btPointerUid__growTables'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__find0"
  btHashMap_btHashPtr_btPointerUid__find'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__find0"
  btHashMap_btHashPtr_btPointerUid__find0'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__find1"
  btHashMap_btHashPtr_btPointerUid__find1'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__size"
  btHashMap_btHashPtr_btPointerUid__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__m_hashTable_set"
  btHashMap_btHashPtr_btPointerUid__m_hashTable_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__m_hashTable_get"
  btHashMap_btHashPtr_btPointerUid__m_hashTable_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__m_keyArray_set"
  btHashMap_btHashPtr_btPointerUid__m_keyArray_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__m_keyArray_get"
  btHashMap_btHashPtr_btPointerUid__m_keyArray_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__m_next_set"
  btHashMap_btHashPtr_btPointerUid__m_next_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__m_next_get"
  btHashMap_btHashPtr_btPointerUid__m_next_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__m_valueArray_set"
  btHashMap_btHashPtr_btPointerUid__m_valueArray_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_btPointerUid__m_valueArray_get"
  btHashMap_btHashPtr_btPointerUid__m_valueArray_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__new"
  btHashMap_btHashPtr_charconst_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__free"
  btHashMap_btHashPtr_charconst_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__findIndex"
  btHashMap_btHashPtr_charconst_ptr__findIndex'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__clear"
  btHashMap_btHashPtr_charconst_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__growTables"
  btHashMap_btHashPtr_charconst_ptr__growTables'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__size"
  btHashMap_btHashPtr_charconst_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__m_hashTable_set"
  btHashMap_btHashPtr_charconst_ptr__m_hashTable_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__m_hashTable_get"
  btHashMap_btHashPtr_charconst_ptr__m_hashTable_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__m_keyArray_set"
  btHashMap_btHashPtr_charconst_ptr__m_keyArray_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__m_keyArray_get"
  btHashMap_btHashPtr_charconst_ptr__m_keyArray_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__m_next_set"
  btHashMap_btHashPtr_charconst_ptr__m_next_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__m_next_get"
  btHashMap_btHashPtr_charconst_ptr__m_next_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__m_valueArray_set"
  btHashMap_btHashPtr_charconst_ptr__m_valueArray_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_charconst_ptr__m_valueArray_get"
  btHashMap_btHashPtr_charconst_ptr__m_valueArray_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__new"
  btHashMap_btHashPtr_void_ptr_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__free"
  btHashMap_btHashPtr_void_ptr__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__findIndex"
  btHashMap_btHashPtr_void_ptr__findIndex'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__clear"
  btHashMap_btHashPtr_void_ptr__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__growTables"
  btHashMap_btHashPtr_void_ptr__growTables'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__size"
  btHashMap_btHashPtr_void_ptr__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__m_hashTable_set"
  btHashMap_btHashPtr_void_ptr__m_hashTable_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__m_hashTable_get"
  btHashMap_btHashPtr_void_ptr__m_hashTable_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__m_keyArray_set"
  btHashMap_btHashPtr_void_ptr__m_keyArray_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__m_keyArray_get"
  btHashMap_btHashPtr_void_ptr__m_keyArray_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__m_next_set"
  btHashMap_btHashPtr_void_ptr__m_next_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__m_next_get"
  btHashMap_btHashPtr_void_ptr__m_next_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__m_valueArray_set"
  btHashMap_btHashPtr_void_ptr__m_valueArray_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashPtr_void_ptr__m_valueArray_get"
  btHashMap_btHashPtr_void_ptr__m_valueArray_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__new"
  btHashMap_btHashString_int_'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__free"
  btHashMap_btHashString_int__free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__findIndex"
  btHashMap_btHashString_int__findIndex'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__clear"
  btHashMap_btHashString_int__clear'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__growTables"
  btHashMap_btHashString_int__growTables'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__size"
  btHashMap_btHashString_int__size'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__m_hashTable_set"
  btHashMap_btHashString_int__m_hashTable_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__m_hashTable_get"
  btHashMap_btHashString_int__m_hashTable_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__m_keyArray_set"
  btHashMap_btHashString_int__m_keyArray_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__m_keyArray_get"
  btHashMap_btHashString_int__m_keyArray_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__m_next_set"
  btHashMap_btHashString_int__m_next_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__m_next_get"
  btHashMap_btHashString_int__m_next_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__m_valueArray_set"
  btHashMap_btHashString_int__m_valueArray_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashMap_btHashString_int__m_valueArray_get"
  btHashMap_btHashString_int__m_valueArray_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashPtr_free"
  btHashPtr_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashPtr_getHash"
  btHashPtr_getHash'_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashPtr_equals"
  btHashPtr_equals'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashString_new"
  btHashString'_ :: ((Ptr CChar) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashString_free"
  btHashString_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashString_getHash"
  btHashString_getHash'_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashString_equals"
  btHashString_equals'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO CInt)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashString_portableStringCompare"
  btHashString_portableStringCompare'_ :: ((Ptr ()) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO CInt))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashString_m_hash_set"
  btHashString_m_hash_set'_ :: ((Ptr ()) -> (CUInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashString_m_hash_get"
  btHashString_m_hash_get'_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashString_m_string_set"
  btHashString_m_string_set'_ :: ((Ptr ()) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btHashString_m_string_get"
  btHashString_m_string_get'_ :: ((Ptr ()) -> (IO (Ptr CChar)))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_draw3dText"
  btIDebugDraw_draw3dText'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CChar) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_draw3dText"
  btIDebugDraw_draw3dText''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CChar) -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawBox0"
  btIDebugDraw_drawBox'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawBox0"
  btIDebugDraw_drawBox''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawBox0"
  btIDebugDraw_drawBox0'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawBox0"
  btIDebugDraw_drawBox0''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawBox1"
  btIDebugDraw_drawBox1'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawBox1"
  btIDebugDraw_drawBox1''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawCone"
  btIDebugDraw_drawCone'_ :: ((Ptr ()) -> (CFloat -> (CFloat -> (CInt -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawCone"
  btIDebugDraw_drawCone''_ :: ((Ptr ()) -> (CFloat -> (CFloat -> (CInt -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawCapsule"
  btIDebugDraw_drawCapsule'_ :: ((Ptr ()) -> (CFloat -> (CFloat -> (CInt -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawCapsule"
  btIDebugDraw_drawCapsule''_ :: ((Ptr ()) -> (CFloat -> (CFloat -> (CInt -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawArc"
  btIDebugDraw_drawArc'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> ((Ptr CFloat) -> (CInt -> (CFloat -> (IO ()))))))))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawArc"
  btIDebugDraw_drawArc''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> ((Ptr CFloat) -> (CInt -> (CFloat -> (IO ()))))))))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawCylinder"
  btIDebugDraw_drawCylinder'_ :: ((Ptr ()) -> (CFloat -> (CFloat -> (CInt -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawCylinder"
  btIDebugDraw_drawCylinder''_ :: ((Ptr ()) -> (CFloat -> (CFloat -> (CInt -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_reportErrorWarning"
  btIDebugDraw_reportErrorWarning'_ :: ((Ptr ()) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawTriangle0"
  btIDebugDraw_drawTriangle'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (IO ()))))))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawTriangle0"
  btIDebugDraw_drawTriangle''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (IO ()))))))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawTriangle0"
  btIDebugDraw_drawTriangle0'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (IO ()))))))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawTriangle0"
  btIDebugDraw_drawTriangle0''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (IO ()))))))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawTriangle1"
  btIDebugDraw_drawTriangle1'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawTriangle1"
  btIDebugDraw_drawTriangle1''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_getDebugMode"
  btIDebugDraw_getDebugMode'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawLine0"
  btIDebugDraw_drawLine'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawLine0"
  btIDebugDraw_drawLine''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawLine0"
  btIDebugDraw_drawLine0'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawLine0"
  btIDebugDraw_drawLine0''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawLine1"
  btIDebugDraw_drawLine1'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawLine1"
  btIDebugDraw_drawLine1''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawTransform"
  btIDebugDraw_drawTransform'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawTransform"
  btIDebugDraw_drawTransform''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (CFloat -> (IO ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawAabb"
  btIDebugDraw_drawAabb'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawAabb"
  btIDebugDraw_drawAabb''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawPlane"
  btIDebugDraw_drawPlane'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (CFloat -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawPlane"
  btIDebugDraw_drawPlane''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (CFloat -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawContactPoint"
  btIDebugDraw_drawContactPoint'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (CInt -> ((Ptr CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawContactPoint"
  btIDebugDraw_drawContactPoint''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (CInt -> ((Ptr CFloat) -> (IO ())))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_setDebugMode"
  btIDebugDraw_setDebugMode'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawSpherePatch"
  btIDebugDraw_drawSpherePatch'_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> ((Ptr CFloat) -> (CFloat -> (IO ()))))))))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawSpherePatch"
  btIDebugDraw_drawSpherePatch''_ :: ((Ptr ()) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> ((Ptr CFloat) -> (CFloat -> (IO ()))))))))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawSphere0"
  btIDebugDraw_drawSphere'_ :: ((Ptr ()) -> (CFloat -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawSphere0"
  btIDebugDraw_drawSphere''_ :: ((Ptr ()) -> (CFloat -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawSphere0"
  btIDebugDraw_drawSphere0'_ :: ((Ptr ()) -> (CFloat -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawSphere0"
  btIDebugDraw_drawSphere0''_ :: ((Ptr ()) -> (CFloat -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawSphere1"
  btIDebugDraw_drawSphere1'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (CFloat -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btIDebugDraw_drawSphere1"
  btIDebugDraw_drawSphere1''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (CFloat -> ((Ptr CFloat) -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btMatrix3x3DoubleData_new"
  btMatrix3x3DoubleData'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btMatrix3x3DoubleData_free"
  btMatrix3x3DoubleData_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btMatrix3x3FloatData_new"
  btMatrix3x3FloatData'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btMatrix3x3FloatData_free"
  btMatrix3x3FloatData_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btMotionState_setWorldTransform"
  btMotionState_setWorldTransform'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btMotionState_setWorldTransform"
  btMotionState_setWorldTransform''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btMotionState_getWorldTransform"
  btMotionState_getWorldTransform'_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btMotionState_getWorldTransform"
  btMotionState_getWorldTransform''_ :: ((Ptr ()) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btPointerUid_new"
  btPointerUid'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btPointerUid_free"
  btPointerUid_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_new0"
  btQuadWord0'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_new1"
  btQuadWord1'_ :: (CFloat -> (CFloat -> (CFloat -> (IO (Ptr ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_new2"
  btQuadWord2'_ :: (CFloat -> (CFloat -> (CFloat -> (CFloat -> (IO (Ptr ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_free"
  btQuadWord_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_setMin"
  btQuadWord_setMin'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_setValue0"
  btQuadWord_setValue'_ :: ((Ptr ()) -> (CFloat -> (CFloat -> (CFloat -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_setValue0"
  btQuadWord_setValue0'_ :: ((Ptr ()) -> (CFloat -> (CFloat -> (CFloat -> (IO ())))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_setValue1"
  btQuadWord_setValue1'_ :: ((Ptr ()) -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_setMax"
  btQuadWord_setMax'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_getX"
  btQuadWord_getX'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_getY"
  btQuadWord_getY'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_getZ"
  btQuadWord_getZ'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_setW"
  btQuadWord_setW'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_w"
  btQuadWord_w'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_y"
  btQuadWord_y'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_x"
  btQuadWord_x'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_z"
  btQuadWord_z'_ :: ((Ptr ()) -> (IO CFloat))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_setX"
  btQuadWord_setX'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_setY"
  btQuadWord_setY'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btQuadWord_setZ"
  btQuadWord_setZ'_ :: ((Ptr ()) -> (CFloat -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btSerializer_setSerializationFlags"
  btSerializer_setSerializationFlags'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btSerializer_getCurrentBufferSize"
  btSerializer_getCurrentBufferSize'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btSerializer_startSerialization"
  btSerializer_startSerialization'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btSerializer_getSerializationFlags"
  btSerializer_getSerializationFlags'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btSerializer_finishSerialization"
  btSerializer_finishSerialization'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btSerializer_getUniquePointer"
  btSerializer_getUniquePointer'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btSerializer_finalizeChunk"
  btSerializer_finalizeChunk'_ :: ((Ptr ()) -> ((Ptr ()) -> ((Ptr CChar) -> (CInt -> ((Ptr ()) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btSerializer_serializeName"
  btSerializer_serializeName'_ :: ((Ptr ()) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btSerializer_findPointer"
  btSerializer_findPointer'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO (Ptr ()))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_new"
  btStackAlloc'_ :: (CUInt -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_free"
  btStackAlloc_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_create"
  btStackAlloc_create'_ :: ((Ptr ()) -> (CUInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_ctor"
  btStackAlloc_ctor'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_destroy"
  btStackAlloc_destroy'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_beginBlock"
  btStackAlloc_beginBlock'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_getAvailableMemory"
  btStackAlloc_getAvailableMemory'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_endBlock"
  btStackAlloc_endBlock'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_totalsize_set"
  btStackAlloc_totalsize_set'_ :: ((Ptr ()) -> (CUInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_totalsize_get"
  btStackAlloc_totalsize_get'_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_usedsize_set"
  btStackAlloc_usedsize_set'_ :: ((Ptr ()) -> (CUInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_usedsize_get"
  btStackAlloc_usedsize_get'_ :: ((Ptr ()) -> (IO CUInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_current_set"
  btStackAlloc_current_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_current_get"
  btStackAlloc_current_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_ischild_set"
  btStackAlloc_ischild_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btStackAlloc_ischild_get"
  btStackAlloc_ischild_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformDoubleData_new"
  btTransformDoubleData'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformDoubleData_free"
  btTransformDoubleData_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformDoubleData_m_basis_set"
  btTransformDoubleData_m_basis_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformDoubleData_m_basis_get"
  btTransformDoubleData_m_basis_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformDoubleData_m_origin_set"
  btTransformDoubleData_m_origin_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformDoubleData_m_origin_get"
  btTransformDoubleData_m_origin_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformFloatData_new"
  btTransformFloatData'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformFloatData_free"
  btTransformFloatData_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformFloatData_m_basis_set"
  btTransformFloatData_m_basis_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformFloatData_m_basis_get"
  btTransformFloatData_m_basis_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformFloatData_m_origin_set"
  btTransformFloatData_m_origin_set'_ :: ((Ptr ()) -> ((Ptr ()) -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformFloatData_m_origin_get"
  btTransformFloatData_m_origin_get'_ :: ((Ptr ()) -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformUtil_new"
  btTransformUtil'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformUtil_free"
  btTransformUtil_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformUtil_calculateVelocity"
  btTransformUtil_calculateVelocity'_ :: ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformUtil_calculateVelocity"
  btTransformUtil_calculateVelocity''_ :: ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformUtil_integrateTransform"
  btTransformUtil_integrateTransform'_ :: ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformUtil_integrateTransform"
  btTransformUtil_integrateTransform''_ :: ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformUtil_calculateVelocityQuaternion"
  btTransformUtil_calculateVelocityQuaternion'_ :: ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTransformUtil_calculateVelocityQuaternion"
  btTransformUtil_calculateVelocityQuaternion''_ :: ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (CFloat -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTypedObject_new"
  btTypedObject'_ :: (CInt -> (IO (Ptr ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTypedObject_free"
  btTypedObject_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTypedObject_getObjectType"
  btTypedObject_getObjectType'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTypedObject_m_objectType_set"
  btTypedObject_m_objectType_set'_ :: ((Ptr ()) -> (CInt -> (IO ())))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btTypedObject_m_objectType_get"
  btTypedObject_m_objectType_get'_ :: ((Ptr ()) -> (IO CInt))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btVector3DoubleData_new"
  btVector3DoubleData'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btVector3DoubleData_free"
  btVector3DoubleData_free'_ :: ((Ptr ()) -> (IO ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btVector3FloatData_new"
  btVector3FloatData'_ :: (IO (Ptr ()))

foreign import ccall safe "Physics/Bullet/Raw/LinearMath.chs.h btVector3FloatData_free"
  btVector3FloatData_free'_ :: ((Ptr ()) -> (IO ()))