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


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

module Physics.Bullet.Raw (
module Physics.Bullet.Raw.BulletSoftBody,
module Physics.Bullet.Raw.LinearMath,
module Physics.Bullet.Raw.BulletDynamics,
module Physics.Bullet.Raw.BulletCollision,
module Physics.Bullet.Raw
) where
import qualified Foreign.C.String as C2HSImp
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp


import Control.Monad
import Foreign.Marshal.Alloc
import Foreign.ForeignPtr.Unsafe
import Foreign.Ptr
import Physics.Bullet.Raw.C2HS
import Physics.Bullet.Raw.Types
import Physics.Bullet.Raw.Class
import Physics.Bullet.Raw.BulletSoftBody
import Physics.Bullet.Raw.LinearMath
import Physics.Bullet.Raw.BulletDynamics
import Physics.Bullet.Raw.BulletCollision
-- * btGLDebugDrawer
{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#14>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer :: IO ((BtGLDebugDrawer))
btGLDebugDrawer =
  btGLDebugDrawer'_ >>= \res ->
  mkBtGLDebugDrawer res >>= \res' ->
  return (res')

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

btGLDebugDrawer_free :: ( BtGLDebugDrawerClass bc ) => (bc) -> IO ()
btGLDebugDrawer_free a1 =
  withBt a1 $ \a1' -> 
  btGLDebugDrawer_free'_ a1' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#29>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_draw3dText :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ location
 -> (String) -- ^ textString
 -> IO ((Vec3))
btGLDebugDrawer_draw3dText a1 a2 a3 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  C2HSImp.withCString a3 $ \a3' -> 
  btGLDebugDrawer_draw3dText'_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#29>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_draw3dText' :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (String) -- ^ textString
 -> IO ((Vec3))
btGLDebugDrawer_draw3dText' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  C2HSImp.withCString a3 $ \a3' -> 
  btGLDebugDrawer_draw3dText''_ a1' a2' a3' >>
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#23>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_drawTriangle :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ a
 -> (Vec3) -- ^ b
 -> (Vec3) -- ^ c
 -> (Vec3) -- ^ color
 -> (Float) -- ^ alpha
 -> IO ((Vec3), (Vec3), (Vec3), (Vec3))
btGLDebugDrawer_drawTriangle 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 
  btGLDebugDrawer_drawTriangle'_ a1' a2' a3' a4' a5' a6' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#23>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_drawTriangle' :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ alpha
 -> IO ((Vec3), (Vec3), (Vec3), (Vec3))
btGLDebugDrawer_drawTriangle' a1 a6 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  allocaVec3 $ \a5' -> 
  let {a6' = realToFrac a6} in 
  btGLDebugDrawer_drawTriangle''_ a1' a2' a3' a4' a5' a6' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#21>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_drawBox :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ boxMin
 -> (Vec3) -- ^ boxMax
 -> (Vec3) -- ^ color
 -> (Float) -- ^ alpha
 -> IO ((Vec3), (Vec3), (Vec3))
btGLDebugDrawer_drawBox a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  let {a5' = realToFrac a5} in 
  btGLDebugDrawer_drawBox'_ a1' a2' a3' a4' a5' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#21>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_drawBox' :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ alpha
 -> IO ((Vec3), (Vec3), (Vec3))
btGLDebugDrawer_drawBox' a1 a5 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  allocaVec3 $ \a4' -> 
  let {a5' = realToFrac a5} in 
  btGLDebugDrawer_drawBox''_ a1' a2' a3' a4' a5' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#25>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_drawContactPoint :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ PointOnB
 -> (Vec3) -- ^ normalOnB
 -> (Float) -- ^ distance
 -> (Int) -- ^ lifeTime
 -> (Vec3) -- ^ color
 -> IO ((Vec3), (Vec3), (Vec3))
btGLDebugDrawer_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' -> 
  btGLDebugDrawer_drawContactPoint'_ a1' a2' a3' a4' a5' a6' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a2'', a3'', a6'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#25>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_drawContactPoint' :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ distance
 -> (Int) -- ^ lifeTime
 -> IO ((Vec3), (Vec3), (Vec3))
btGLDebugDrawer_drawContactPoint' a1 a4 a5 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  allocaVec3 $ \a3' -> 
  let {a4' = realToFrac a4} in 
  let {a5' = fromIntegral a5} in 
  allocaVec3 $ \a6' -> 
  btGLDebugDrawer_drawContactPoint''_ a1' a2' a3' a4' a5' a6' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a6'>>= \a6'' -> 
  return (a2'', a3'', a6'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#16>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_drawLine :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ from
 -> (Vec3) -- ^ to
 -> (Vec3) -- ^ fromColor
 -> (Vec3) -- ^ toColor
 -> IO ((Vec3), (Vec3), (Vec3), (Vec3))
btGLDebugDrawer_drawLine a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btGLDebugDrawer_drawLine'_ a1' a2' a3' a4' a5' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')

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

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

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#16>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_drawLine0 :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ from
 -> (Vec3) -- ^ to
 -> (Vec3) -- ^ fromColor
 -> (Vec3) -- ^ toColor
 -> IO ((Vec3), (Vec3), (Vec3), (Vec3))
btGLDebugDrawer_drawLine0 a1 a2 a3 a4 a5 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  withVec3 a5 $ \a5' -> 
  btGLDebugDrawer_drawLine0'_ a1' a2' a3' a4' a5' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  peekVec3  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')

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

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

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#18>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_drawLine1 :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ from
 -> (Vec3) -- ^ to
 -> (Vec3) -- ^ color
 -> IO ((Vec3), (Vec3), (Vec3))
btGLDebugDrawer_drawLine1 a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withVec3 a3 $ \a3' -> 
  withVec3 a4 $ \a4' -> 
  btGLDebugDrawer_drawLine1'_ a1' a2' a3' a4' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a3'>>= \a3'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')

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

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

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#27>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_reportErrorWarning :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (String) -- ^ warningString
 -> IO ()
btGLDebugDrawer_reportErrorWarning a1 a2 =
  withBt a1 $ \a1' -> 
  C2HSImp.withCString a2 $ \a2' -> 
  btGLDebugDrawer_reportErrorWarning'_ a1' a2' >>
  return ()

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

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

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#31>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_setDebugMode :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (Int) -- ^ debugMode
 -> IO ()
btGLDebugDrawer_setDebugMode a1 a2 =
  withBt a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  btGLDebugDrawer_setDebugMode'_ a1' a2' >>
  return ()

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#20>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_drawSphere :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (Vec3) -- ^ p
 -> (Float) -- ^ radius
 -> (Vec3) -- ^ color
 -> IO ((Vec3), (Vec3))
btGLDebugDrawer_drawSphere a1 a2 a3 a4 =
  withBt a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  withVec3 a4 $ \a4' -> 
  btGLDebugDrawer_drawSphere'_ a1' a2' a3' a4' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a4'')

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

{- | <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.h?r=2223#20>
     <http://code.google.com/p/bullet/source/browse/trunk/src/GLDebugDrawer.cpp?r=2223>
-}
btGLDebugDrawer_drawSphere' :: ( BtGLDebugDrawerClass bc ) => (bc) -- ^ 
 -> (Float) -- ^ radius
 -> IO ((Vec3), (Vec3))
btGLDebugDrawer_drawSphere' a1 a3 =
  withBt a1 $ \a1' -> 
  allocaVec3 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  allocaVec3 $ \a4' -> 
  btGLDebugDrawer_drawSphere''_ a1' a2' a3' a4' >>
  peekVec3  a2'>>= \a2'' -> 
  peekVec3  a4'>>= \a4'' -> 
  return (a2'', a4'')

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


foreign import ccall safe "Physics/Bullet/Raw.chs.h btGLDebugDrawer_new"
  btGLDebugDrawer'_ :: (IO (C2HSImp.Ptr ()))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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