{-# LINE 1 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
{-#LANGUAGE ForeignFunctionInterface#-}
module Physics.Bullet.Raw.BulletCollision.NarrowPhaseCollision (
module Physics.Bullet.Raw.BulletCollision.NarrowPhaseCollision
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Marshal.Utils as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import Control.Monad
import Foreign.Marshal.Alloc
import Foreign.ForeignPtr.Unsafe
import Foreign.Ptr
import Physics.Bullet.Raw.C2HS
import Physics.Bullet.Raw.Types
import Physics.Bullet.Raw.Class
btDiscreteCollisionDetectorInterface_ClosestPointInput :: IO ((BtDiscreteCollisionDetectorInterface_ClosestPointInput))
btDiscreteCollisionDetectorInterface_ClosestPointInput =
btDiscreteCollisionDetectorInterface_ClosestPointInput'_ >>= \res ->
mkBtDiscreteCollisionDetectorInterface_ClosestPointInput res >>= \res' ->
return (res')
{-# LINE 17 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_ClosestPointInput_free :: ( BtDiscreteCollisionDetectorInterface_ClosestPointInputClass bc ) => (bc) -> IO ()
btDiscreteCollisionDetectorInterface_ClosestPointInput_free a1 =
withBt a1 $ \a1' ->
btDiscreteCollisionDetectorInterface_ClosestPointInput_free'_ a1' >>
return ()
{-# LINE 18 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformA_set :: ( BtDiscreteCollisionDetectorInterface_ClosestPointInputClass bc ) => (bc) -> (Transform) -> IO ()
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformA_set a1 a2 =
withBt a1 $ \a1' ->
withTransform a2 $ \a2' ->
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformA_set'_ a1' a2' >>
return ()
{-# LINE 22 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformA_get :: ( BtDiscreteCollisionDetectorInterface_ClosestPointInputClass bc ) => (bc) -> IO ((Transform))
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformA_get a1 =
withBt a1 $ \a1' ->
allocaTransform $ \a2' ->
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformA_get'_ a1' a2' >>
peekTransform a2'>>= \a2'' ->
return (a2'')
{-# LINE 26 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformB_set :: ( BtDiscreteCollisionDetectorInterface_ClosestPointInputClass bc ) => (bc) -> (Transform) -> IO ()
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformB_set a1 a2 =
withBt a1 $ \a1' ->
withTransform a2 $ \a2' ->
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformB_set'_ a1' a2' >>
return ()
{-# LINE 30 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformB_get :: ( BtDiscreteCollisionDetectorInterface_ClosestPointInputClass bc ) => (bc) -> IO ((Transform))
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformB_get a1 =
withBt a1 $ \a1' ->
allocaTransform $ \a2' ->
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformB_get'_ a1' a2' >>
peekTransform a2'>>= \a2'' ->
return (a2'')
{-# LINE 34 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_maximumDistanceSquared_set :: ( BtDiscreteCollisionDetectorInterface_ClosestPointInputClass bc ) => (bc) -> (Float) -> IO ()
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_maximumDistanceSquared_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_maximumDistanceSquared_set'_ a1' a2' >>
return ()
{-# LINE 38 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_maximumDistanceSquared_get :: ( BtDiscreteCollisionDetectorInterface_ClosestPointInputClass bc ) => (bc) -> IO ((Float))
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_maximumDistanceSquared_get a1 =
withBt a1 $ \a1' ->
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_maximumDistanceSquared_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 42 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_stackAlloc_set :: ( BtDiscreteCollisionDetectorInterface_ClosestPointInputClass bc , BtStackAllocClass a ) => (bc) -> (a) -> IO ()
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_stackAlloc_set a1 a2 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_stackAlloc_set'_ a1' a2' >>
return ()
{-# LINE 46 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_stackAlloc_get :: ( BtDiscreteCollisionDetectorInterface_ClosestPointInputClass bc ) => (bc) -> IO ((BtStackAlloc))
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_stackAlloc_get a1 =
withBt a1 $ \a1' ->
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_stackAlloc_get'_ a1' >>= \res ->
mkBtStackAlloc res >>= \res' ->
return (res')
{-# LINE 50 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_Result_setShapeIdentifiersB :: ( BtDiscreteCollisionDetectorInterface_ResultClass bc ) => (bc)
-> (Int)
-> (Int)
-> IO ()
btDiscreteCollisionDetectorInterface_Result_setShapeIdentifiersB a1 a2 a3 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
btDiscreteCollisionDetectorInterface_Result_setShapeIdentifiersB'_ a1' a2' a3' >>
return ()
{-# LINE 58 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_Result_setShapeIdentifiersA :: ( BtDiscreteCollisionDetectorInterface_ResultClass bc ) => (bc)
-> (Int)
-> (Int)
-> IO ()
btDiscreteCollisionDetectorInterface_Result_setShapeIdentifiersA a1 a2 a3 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
btDiscreteCollisionDetectorInterface_Result_setShapeIdentifiersA'_ a1' a2' a3' >>
return ()
{-# LINE 65 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_Result_addContactPoint :: ( BtDiscreteCollisionDetectorInterface_ResultClass bc ) => (bc)
-> (Vec3)
-> (Vec3)
-> (Float)
-> IO ((Vec3), (Vec3))
btDiscreteCollisionDetectorInterface_Result_addContactPoint a1 a2 a3 a4 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
withVec3 a3 $ \a3' ->
let {a4' = realToFrac a4} in
btDiscreteCollisionDetectorInterface_Result_addContactPoint'_ a1' a2' a3' a4' >>
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
return (a2'', a3'')
{-# LINE 73 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_Result_addContactPoint' :: ( BtDiscreteCollisionDetectorInterface_ResultClass bc ) => (bc)
-> (Float)
-> IO ((Vec3), (Vec3))
btDiscreteCollisionDetectorInterface_Result_addContactPoint' a1 a4 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
allocaVec3 $ \a3' ->
let {a4' = realToFrac a4} in
btDiscreteCollisionDetectorInterface_Result_addContactPoint''_ a1' a2' a3' a4' >>
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
return (a2'', a3'')
{-# LINE 81 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btConstraintRow :: IO ((BtConstraintRow))
btConstraintRow =
btConstraintRow'_ >>= \res ->
mkBtConstraintRow res >>= \res' ->
return (res')
{-# LINE 86 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btConstraintRow_free :: ( BtConstraintRowClass bc ) => (bc) -> IO ()
btConstraintRow_free a1 =
withBt a1 $ \a1' ->
btConstraintRow_free'_ a1' >>
return ()
{-# LINE 87 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btConstraintRow_m_rhs_set :: ( BtConstraintRowClass bc ) => (bc) -> (Float) -> IO ()
btConstraintRow_m_rhs_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btConstraintRow_m_rhs_set'_ a1' a2' >>
return ()
{-# LINE 91 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btConstraintRow_m_rhs_get :: ( BtConstraintRowClass bc ) => (bc) -> IO ((Float))
btConstraintRow_m_rhs_get a1 =
withBt a1 $ \a1' ->
btConstraintRow_m_rhs_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 95 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btConstraintRow_m_jacDiagInv_set :: ( BtConstraintRowClass bc ) => (bc) -> (Float) -> IO ()
btConstraintRow_m_jacDiagInv_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btConstraintRow_m_jacDiagInv_set'_ a1' a2' >>
return ()
{-# LINE 99 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btConstraintRow_m_jacDiagInv_get :: ( BtConstraintRowClass bc ) => (bc) -> IO ((Float))
btConstraintRow_m_jacDiagInv_get a1 =
withBt a1 $ \a1' ->
btConstraintRow_m_jacDiagInv_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 103 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btConstraintRow_m_lowerLimit_set :: ( BtConstraintRowClass bc ) => (bc) -> (Float) -> IO ()
btConstraintRow_m_lowerLimit_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btConstraintRow_m_lowerLimit_set'_ a1' a2' >>
return ()
{-# LINE 107 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btConstraintRow_m_lowerLimit_get :: ( BtConstraintRowClass bc ) => (bc) -> IO ((Float))
btConstraintRow_m_lowerLimit_get a1 =
withBt a1 $ \a1' ->
btConstraintRow_m_lowerLimit_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 111 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btConstraintRow_m_upperLimit_set :: ( BtConstraintRowClass bc ) => (bc) -> (Float) -> IO ()
btConstraintRow_m_upperLimit_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btConstraintRow_m_upperLimit_set'_ a1' a2' >>
return ()
{-# LINE 115 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btConstraintRow_m_upperLimit_get :: ( BtConstraintRowClass bc ) => (bc) -> IO ((Float))
btConstraintRow_m_upperLimit_get a1 =
withBt a1 $ \a1' ->
btConstraintRow_m_upperLimit_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 119 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btConstraintRow_m_accumImpulse_set :: ( BtConstraintRowClass bc ) => (bc) -> (Float) -> IO ()
btConstraintRow_m_accumImpulse_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btConstraintRow_m_accumImpulse_set'_ a1' a2' >>
return ()
{-# LINE 123 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btConstraintRow_m_accumImpulse_get :: ( BtConstraintRowClass bc ) => (bc) -> IO ((Float))
btConstraintRow_m_accumImpulse_get a1 =
withBt a1 $ \a1' ->
btConstraintRow_m_accumImpulse_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 127 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btDiscreteCollisionDetectorInterface_getClosestPoints :: ( BtDiscreteCollisionDetectorInterfaceClass bc , BtDiscreteCollisionDetectorInterface_ClosestPointInputClass p0 , BtDiscreteCollisionDetectorInterface_ResultClass p1 , BtIDebugDrawClass p2 ) => (bc)
-> (p0)
-> (p1)
-> (p2)
-> (Bool)
-> IO ()
btDiscreteCollisionDetectorInterface_getClosestPoints a1 a2 a3 a4 a5 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
withBt a3 $ \a3' ->
withBt a4 $ \a4' ->
let {a5' = C2HSImp.fromBool a5} in
btDiscreteCollisionDetectorInterface_getClosestPoints'_ a1' a2' a3' a4' a5' >>
return ()
{-# LINE 137 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2 :: IO ((BtGjkEpaSolver2))
btGjkEpaSolver2 =
btGjkEpaSolver2'_ >>= \res ->
mkBtGjkEpaSolver2 res >>= \res' ->
return (res')
{-# LINE 142 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_free :: ( BtGjkEpaSolver2Class bc ) => (bc) -> IO ()
btGjkEpaSolver2_free a1 =
withBt a1 $ \a1' ->
btGjkEpaSolver2_free'_ a1' >>
return ()
{-# LINE 143 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_StackSizeRequirement :: ( ) => IO ((Int))
btGjkEpaSolver2_StackSizeRequirement =
btGjkEpaSolver2_StackSizeRequirement'_ >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 147 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_Distance :: ( BtConvexShapeClass p0 , BtConvexShapeClass p2 , BtGjkEpaSolver2_sResultsClass p5 ) => (p0)
-> (Transform)
-> (p2)
-> (Transform)
-> (Vec3)
-> (p5)
-> IO ((Bool), (Transform), (Transform), (Vec3))
btGjkEpaSolver2_Distance a1 a2 a3 a4 a5 a6 =
withBt a1 $ \a1' ->
withTransform a2 $ \a2' ->
withBt a3 $ \a3' ->
withTransform a4 $ \a4' ->
withVec3 a5 $ \a5' ->
withBt a6 $ \a6' ->
btGjkEpaSolver2_Distance'_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekTransform a2'>>= \a2'' ->
peekTransform a4'>>= \a4'' ->
peekVec3 a5'>>= \a5'' ->
return (res', a2'', a4'', a5'')
{-# LINE 157 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_Distance' :: ( BtConvexShapeClass p0 , BtConvexShapeClass p2 , BtGjkEpaSolver2_sResultsClass p5 ) => (p0)
-> (p2)
-> (p5)
-> IO ((Bool), (Transform), (Transform), (Vec3))
btGjkEpaSolver2_Distance' a1 a3 a6 =
withBt a1 $ \a1' ->
allocaTransform $ \a2' ->
withBt a3 $ \a3' ->
allocaTransform $ \a4' ->
allocaVec3 $ \a5' ->
withBt a6 $ \a6' ->
btGjkEpaSolver2_Distance''_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekTransform a2'>>= \a2'' ->
peekTransform a4'>>= \a4'' ->
peekVec3 a5'>>= \a5'' ->
return (res', a2'', a4'', a5'')
{-# LINE 167 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_Penetration :: ( BtConvexShapeClass p0 , BtConvexShapeClass p2 , BtGjkEpaSolver2_sResultsClass p5 ) => (p0)
-> (Transform)
-> (p2)
-> (Transform)
-> (Vec3)
-> (p5)
-> (Bool)
-> IO ((Bool), (Transform), (Transform), (Vec3))
btGjkEpaSolver2_Penetration a1 a2 a3 a4 a5 a6 a7 =
withBt a1 $ \a1' ->
withTransform a2 $ \a2' ->
withBt a3 $ \a3' ->
withTransform a4 $ \a4' ->
withVec3 a5 $ \a5' ->
withBt a6 $ \a6' ->
let {a7' = C2HSImp.fromBool a7} in
btGjkEpaSolver2_Penetration'_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekTransform a2'>>= \a2'' ->
peekTransform a4'>>= \a4'' ->
peekVec3 a5'>>= \a5'' ->
return (res', a2'', a4'', a5'')
{-# LINE 178 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_Penetration' :: ( BtConvexShapeClass p0 , BtConvexShapeClass p2 , BtGjkEpaSolver2_sResultsClass p5 ) => (p0)
-> (p2)
-> (p5)
-> (Bool)
-> IO ((Bool), (Transform), (Transform), (Vec3))
btGjkEpaSolver2_Penetration' a1 a3 a6 a7 =
withBt a1 $ \a1' ->
allocaTransform $ \a2' ->
withBt a3 $ \a3' ->
allocaTransform $ \a4' ->
allocaVec3 $ \a5' ->
withBt a6 $ \a6' ->
let {a7' = C2HSImp.fromBool a7} in
btGjkEpaSolver2_Penetration''_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekTransform a2'>>= \a2'' ->
peekTransform a4'>>= \a4'' ->
peekVec3 a5'>>= \a5'' ->
return (res', a2'', a4'', a5'')
{-# LINE 189 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_SignedDistance :: ( BtConvexShapeClass p2 , BtGjkEpaSolver2_sResultsClass p4 ) => (Vec3)
-> (Float)
-> (p2)
-> (Transform)
-> (p4)
-> IO ((Float), (Vec3), (Transform))
btGjkEpaSolver2_SignedDistance a1 a2 a3 a4 a5 =
withVec3 a1 $ \a1' ->
let {a2' = realToFrac a2} in
withBt a3 $ \a3' ->
withTransform a4 $ \a4' ->
withBt a5 $ \a5' ->
btGjkEpaSolver2_SignedDistance'_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = realToFrac res} in
peekVec3 a1'>>= \a1'' ->
peekTransform a4'>>= \a4'' ->
return (res', a1'', a4'')
{-# LINE 198 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_SignedDistance' :: ( BtConvexShapeClass p2 , BtGjkEpaSolver2_sResultsClass p4 ) => (Float)
-> (p2)
-> (p4)
-> IO ((Float), (Vec3), (Transform))
btGjkEpaSolver2_SignedDistance' a2 a3 a5 =
allocaVec3 $ \a1' ->
let {a2' = realToFrac a2} in
withBt a3 $ \a3' ->
allocaTransform $ \a4' ->
withBt a5 $ \a5' ->
btGjkEpaSolver2_SignedDistance''_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = realToFrac res} in
peekVec3 a1'>>= \a1'' ->
peekTransform a4'>>= \a4'' ->
return (res', a1'', a4'')
{-# LINE 207 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_SignedDistance0 :: ( BtConvexShapeClass p2 , BtGjkEpaSolver2_sResultsClass p4 ) => (Vec3)
-> (Float)
-> (p2)
-> (Transform)
-> (p4)
-> IO ((Float), (Vec3), (Transform))
btGjkEpaSolver2_SignedDistance0 a1 a2 a3 a4 a5 =
withVec3 a1 $ \a1' ->
let {a2' = realToFrac a2} in
withBt a3 $ \a3' ->
withTransform a4 $ \a4' ->
withBt a5 $ \a5' ->
btGjkEpaSolver2_SignedDistance0'_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = realToFrac res} in
peekVec3 a1'>>= \a1'' ->
peekTransform a4'>>= \a4'' ->
return (res', a1'', a4'')
{-# LINE 216 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_SignedDistance0' :: ( BtConvexShapeClass p2 , BtGjkEpaSolver2_sResultsClass p4 ) => (Float)
-> (p2)
-> (p4)
-> IO ((Float), (Vec3), (Transform))
btGjkEpaSolver2_SignedDistance0' a2 a3 a5 =
allocaVec3 $ \a1' ->
let {a2' = realToFrac a2} in
withBt a3 $ \a3' ->
allocaTransform $ \a4' ->
withBt a5 $ \a5' ->
btGjkEpaSolver2_SignedDistance0''_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = realToFrac res} in
peekVec3 a1'>>= \a1'' ->
peekTransform a4'>>= \a4'' ->
return (res', a1'', a4'')
{-# LINE 225 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_SignedDistance1 :: ( BtConvexShapeClass p0 , BtConvexShapeClass p2 , BtGjkEpaSolver2_sResultsClass p5 ) => (p0)
-> (Transform)
-> (p2)
-> (Transform)
-> (Vec3)
-> (p5)
-> IO ((Bool), (Transform), (Transform), (Vec3))
btGjkEpaSolver2_SignedDistance1 a1 a2 a3 a4 a5 a6 =
withBt a1 $ \a1' ->
withTransform a2 $ \a2' ->
withBt a3 $ \a3' ->
withTransform a4 $ \a4' ->
withVec3 a5 $ \a5' ->
withBt a6 $ \a6' ->
btGjkEpaSolver2_SignedDistance1'_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekTransform a2'>>= \a2'' ->
peekTransform a4'>>= \a4'' ->
peekVec3 a5'>>= \a5'' ->
return (res', a2'', a4'', a5'')
{-# LINE 235 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_SignedDistance1' :: ( BtConvexShapeClass p0 , BtConvexShapeClass p2 , BtGjkEpaSolver2_sResultsClass p5 ) => (p0)
-> (p2)
-> (p5)
-> IO ((Bool), (Transform), (Transform), (Vec3))
btGjkEpaSolver2_SignedDistance1' a1 a3 a6 =
withBt a1 $ \a1' ->
allocaTransform $ \a2' ->
withBt a3 $ \a3' ->
allocaTransform $ \a4' ->
allocaVec3 $ \a5' ->
withBt a6 $ \a6' ->
btGjkEpaSolver2_SignedDistance1''_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekTransform a2'>>= \a2'' ->
peekTransform a4'>>= \a4'' ->
peekVec3 a5'>>= \a5'' ->
return (res', a2'', a4'', a5'')
{-# LINE 245 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_free :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ()
btGjkPairDetector_free a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_free'_ a1' >>
return ()
{-# LINE 247 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_setCachedSeperatingAxis :: ( BtGjkPairDetectorClass bc ) => (bc)
-> (Vec3)
-> IO ((Vec3))
btGjkPairDetector_setCachedSeperatingAxis a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btGjkPairDetector_setCachedSeperatingAxis'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 253 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_setCachedSeperatingAxis' :: ( BtGjkPairDetectorClass bc ) => (bc)
-> IO ((Vec3))
btGjkPairDetector_setCachedSeperatingAxis' a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btGjkPairDetector_setCachedSeperatingAxis''_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 259 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_getCachedSeparatingAxis :: ( BtGjkPairDetectorClass bc ) => (bc)
-> IO ((Vec3))
btGjkPairDetector_getCachedSeparatingAxis a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btGjkPairDetector_getCachedSeparatingAxis'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 265 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_getClosestPoints :: ( BtGjkPairDetectorClass bc , BtDiscreteCollisionDetectorInterface_ClosestPointInputClass p0 , BtDiscreteCollisionDetectorInterface_ResultClass p1 , BtIDebugDrawClass p2 ) => (bc)
-> (p0)
-> (p1)
-> (p2)
-> (Bool)
-> IO ()
btGjkPairDetector_getClosestPoints a1 a2 a3 a4 a5 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
withBt a3 $ \a3' ->
withBt a4 $ \a4' ->
let {a5' = C2HSImp.fromBool a5} in
btGjkPairDetector_getClosestPoints'_ a1' a2' a3' a4' a5' >>
return ()
{-# LINE 274 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_setMinkowskiA :: ( BtGjkPairDetectorClass bc , BtConvexShapeClass p0 ) => (bc)
-> (p0)
-> IO ()
btGjkPairDetector_setMinkowskiA a1 a2 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
btGjkPairDetector_setMinkowskiA'_ a1' a2' >>
return ()
{-# LINE 280 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_setMinkowskiB :: ( BtGjkPairDetectorClass bc , BtConvexShapeClass p0 ) => (bc)
-> (p0)
-> IO ()
btGjkPairDetector_setMinkowskiB a1 a2 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
btGjkPairDetector_setMinkowskiB'_ a1' a2' >>
return ()
{-# LINE 286 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_setIgnoreMargin :: ( BtGjkPairDetectorClass bc ) => (bc)
-> (Bool)
-> IO ()
btGjkPairDetector_setIgnoreMargin a1 a2 =
withBt a1 $ \a1' ->
let {a2' = C2HSImp.fromBool a2} in
btGjkPairDetector_setIgnoreMargin'_ a1' a2' >>
return ()
{-# LINE 292 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_getClosestPointsNonVirtual :: ( BtGjkPairDetectorClass bc , BtDiscreteCollisionDetectorInterface_ClosestPointInputClass p0 , BtDiscreteCollisionDetectorInterface_ResultClass p1 , BtIDebugDrawClass p2 ) => (bc)
-> (p0)
-> (p1)
-> (p2)
-> IO ()
btGjkPairDetector_getClosestPointsNonVirtual a1 a2 a3 a4 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
withBt a3 $ \a3' ->
withBt a4 $ \a4' ->
btGjkPairDetector_getClosestPointsNonVirtual'_ a1' a2' a3' a4' >>
return ()
{-# LINE 300 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_getCachedSeparatingDistance :: ( BtGjkPairDetectorClass bc ) => (bc)
-> IO ((Float))
btGjkPairDetector_getCachedSeparatingDistance a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_getCachedSeparatingDistance'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 305 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_cachedSeparatingAxis_set :: ( BtGjkPairDetectorClass bc ) => (bc) -> (Vec3) -> IO ()
btGjkPairDetector_m_cachedSeparatingAxis_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btGjkPairDetector_m_cachedSeparatingAxis_set'_ a1' a2' >>
return ()
{-# LINE 309 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_cachedSeparatingAxis_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((Vec3))
btGjkPairDetector_m_cachedSeparatingAxis_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btGjkPairDetector_m_cachedSeparatingAxis_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 313 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_simplexSolver_set :: ( BtGjkPairDetectorClass bc , BtVoronoiSimplexSolverClass a ) => (bc) -> (a) -> IO ()
btGjkPairDetector_m_simplexSolver_set a1 a2 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
btGjkPairDetector_m_simplexSolver_set'_ a1' a2' >>
return ()
{-# LINE 317 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_simplexSolver_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((BtVoronoiSimplexSolver))
btGjkPairDetector_m_simplexSolver_get a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_m_simplexSolver_get'_ a1' >>= \res ->
mkBtVoronoiSimplexSolver res >>= \res' ->
return (res')
{-# LINE 321 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_minkowskiA_set :: ( BtGjkPairDetectorClass bc , BtConvexShapeClass a ) => (bc) -> (a) -> IO ()
btGjkPairDetector_m_minkowskiA_set a1 a2 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
btGjkPairDetector_m_minkowskiA_set'_ a1' a2' >>
return ()
{-# LINE 325 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_minkowskiA_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((BtConvexShape))
btGjkPairDetector_m_minkowskiA_get a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_m_minkowskiA_get'_ a1' >>= \res ->
mkBtConvexShape res >>= \res' ->
return (res')
{-# LINE 329 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_minkowskiB_set :: ( BtGjkPairDetectorClass bc , BtConvexShapeClass a ) => (bc) -> (a) -> IO ()
btGjkPairDetector_m_minkowskiB_set a1 a2 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
btGjkPairDetector_m_minkowskiB_set'_ a1' a2' >>
return ()
{-# LINE 333 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_minkowskiB_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((BtConvexShape))
btGjkPairDetector_m_minkowskiB_get a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_m_minkowskiB_get'_ a1' >>= \res ->
mkBtConvexShape res >>= \res' ->
return (res')
{-# LINE 337 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_shapeTypeA_set :: ( BtGjkPairDetectorClass bc ) => (bc) -> (Int) -> IO ()
btGjkPairDetector_m_shapeTypeA_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btGjkPairDetector_m_shapeTypeA_set'_ a1' a2' >>
return ()
{-# LINE 341 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_shapeTypeA_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((Int))
btGjkPairDetector_m_shapeTypeA_get a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_m_shapeTypeA_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 345 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_shapeTypeB_set :: ( BtGjkPairDetectorClass bc ) => (bc) -> (Int) -> IO ()
btGjkPairDetector_m_shapeTypeB_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btGjkPairDetector_m_shapeTypeB_set'_ a1' a2' >>
return ()
{-# LINE 349 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_shapeTypeB_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((Int))
btGjkPairDetector_m_shapeTypeB_get a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_m_shapeTypeB_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 353 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_marginA_set :: ( BtGjkPairDetectorClass bc ) => (bc) -> (Float) -> IO ()
btGjkPairDetector_m_marginA_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btGjkPairDetector_m_marginA_set'_ a1' a2' >>
return ()
{-# LINE 357 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_marginA_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((Float))
btGjkPairDetector_m_marginA_get a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_m_marginA_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 361 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_marginB_set :: ( BtGjkPairDetectorClass bc ) => (bc) -> (Float) -> IO ()
btGjkPairDetector_m_marginB_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btGjkPairDetector_m_marginB_set'_ a1' a2' >>
return ()
{-# LINE 365 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_marginB_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((Float))
btGjkPairDetector_m_marginB_get a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_m_marginB_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 369 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_ignoreMargin_set :: ( BtGjkPairDetectorClass bc ) => (bc) -> (Bool) -> IO ()
btGjkPairDetector_m_ignoreMargin_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = C2HSImp.fromBool a2} in
btGjkPairDetector_m_ignoreMargin_set'_ a1' a2' >>
return ()
{-# LINE 373 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_ignoreMargin_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((Bool))
btGjkPairDetector_m_ignoreMargin_get a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_m_ignoreMargin_get'_ a1' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
{-# LINE 377 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_cachedSeparatingDistance_set :: ( BtGjkPairDetectorClass bc ) => (bc) -> (Float) -> IO ()
btGjkPairDetector_m_cachedSeparatingDistance_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btGjkPairDetector_m_cachedSeparatingDistance_set'_ a1' a2' >>
return ()
{-# LINE 381 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_cachedSeparatingDistance_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((Float))
btGjkPairDetector_m_cachedSeparatingDistance_get a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_m_cachedSeparatingDistance_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 385 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_lastUsedMethod_set :: ( BtGjkPairDetectorClass bc ) => (bc) -> (Int) -> IO ()
btGjkPairDetector_m_lastUsedMethod_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btGjkPairDetector_m_lastUsedMethod_set'_ a1' a2' >>
return ()
{-# LINE 389 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_lastUsedMethod_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((Int))
btGjkPairDetector_m_lastUsedMethod_get a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_m_lastUsedMethod_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 393 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_curIter_set :: ( BtGjkPairDetectorClass bc ) => (bc) -> (Int) -> IO ()
btGjkPairDetector_m_curIter_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btGjkPairDetector_m_curIter_set'_ a1' a2' >>
return ()
{-# LINE 397 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_curIter_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((Int))
btGjkPairDetector_m_curIter_get a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_m_curIter_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 401 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_degenerateSimplex_set :: ( BtGjkPairDetectorClass bc ) => (bc) -> (Int) -> IO ()
btGjkPairDetector_m_degenerateSimplex_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btGjkPairDetector_m_degenerateSimplex_set'_ a1' a2' >>
return ()
{-# LINE 405 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_degenerateSimplex_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((Int))
btGjkPairDetector_m_degenerateSimplex_get a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_m_degenerateSimplex_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 409 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_catchDegeneracies_set :: ( BtGjkPairDetectorClass bc ) => (bc) -> (Int) -> IO ()
btGjkPairDetector_m_catchDegeneracies_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btGjkPairDetector_m_catchDegeneracies_set'_ a1' a2' >>
return ()
{-# LINE 413 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkPairDetector_m_catchDegeneracies_get :: ( BtGjkPairDetectorClass bc ) => (bc) -> IO ((Int))
btGjkPairDetector_m_catchDegeneracies_get a1 =
withBt a1 $ \a1' ->
btGjkPairDetector_m_catchDegeneracies_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 417 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint0 :: IO ((BtManifoldPoint))
btManifoldPoint0 =
btManifoldPoint0'_ >>= \res ->
mkBtManifoldPoint res >>= \res' ->
return (res')
{-# LINE 422 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint1 :: (Vec3) -> (Vec3) -> (Vec3) -> (Float) -> IO ((BtManifoldPoint))
btManifoldPoint1 a1 a2 a3 a4 =
withVec3 a1 $ \a1' ->
withVec3 a2 $ \a2' ->
withVec3 a3 $ \a3' ->
let {a4' = realToFrac a4} in
btManifoldPoint1'_ a1' a2' a3' a4' >>= \res ->
mkBtManifoldPoint res >>= \res' ->
return (res')
{-# LINE 426 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_free :: ( BtManifoldPointClass bc ) => (bc) -> IO ()
btManifoldPoint_free a1 =
withBt a1 $ \a1' ->
btManifoldPoint_free'_ a1' >>
return ()
{-# LINE 427 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_setDistance :: ( BtManifoldPointClass bc ) => (bc)
-> (Float)
-> IO ()
btManifoldPoint_setDistance a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btManifoldPoint_setDistance'_ a1' a2' >>
return ()
{-# LINE 433 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_getLifeTime :: ( BtManifoldPointClass bc ) => (bc)
-> IO ((Int))
btManifoldPoint_getLifeTime a1 =
withBt a1 $ \a1' ->
btManifoldPoint_getLifeTime'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 438 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_getDistance :: ( BtManifoldPointClass bc ) => (bc)
-> IO ((Float))
btManifoldPoint_getDistance a1 =
withBt a1 $ \a1' ->
btManifoldPoint_getDistance'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 443 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_getPositionWorldOnB :: ( BtManifoldPointClass bc ) => (bc)
-> IO ((Vec3))
btManifoldPoint_getPositionWorldOnB a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btManifoldPoint_getPositionWorldOnB'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 449 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_getAppliedImpulse :: ( BtManifoldPointClass bc ) => (bc)
-> IO ((Float))
btManifoldPoint_getAppliedImpulse a1 =
withBt a1 $ \a1' ->
btManifoldPoint_getAppliedImpulse'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 454 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_getPositionWorldOnA :: ( BtManifoldPointClass bc ) => (bc)
-> IO ((Vec3))
btManifoldPoint_getPositionWorldOnA a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btManifoldPoint_getPositionWorldOnA'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 460 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_appliedImpulse_set :: ( BtManifoldPointClass bc ) => (bc) -> (Float) -> IO ()
btManifoldPoint_m_appliedImpulse_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btManifoldPoint_m_appliedImpulse_set'_ a1' a2' >>
return ()
{-# LINE 464 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_appliedImpulse_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Float))
btManifoldPoint_m_appliedImpulse_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_appliedImpulse_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 468 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_appliedImpulseLateral1_set :: ( BtManifoldPointClass bc ) => (bc) -> (Float) -> IO ()
btManifoldPoint_m_appliedImpulseLateral1_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btManifoldPoint_m_appliedImpulseLateral1_set'_ a1' a2' >>
return ()
{-# LINE 472 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_appliedImpulseLateral1_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Float))
btManifoldPoint_m_appliedImpulseLateral1_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_appliedImpulseLateral1_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 476 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_appliedImpulseLateral2_set :: ( BtManifoldPointClass bc ) => (bc) -> (Float) -> IO ()
btManifoldPoint_m_appliedImpulseLateral2_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btManifoldPoint_m_appliedImpulseLateral2_set'_ a1' a2' >>
return ()
{-# LINE 480 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_appliedImpulseLateral2_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Float))
btManifoldPoint_m_appliedImpulseLateral2_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_appliedImpulseLateral2_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 484 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_combinedFriction_set :: ( BtManifoldPointClass bc ) => (bc) -> (Float) -> IO ()
btManifoldPoint_m_combinedFriction_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btManifoldPoint_m_combinedFriction_set'_ a1' a2' >>
return ()
{-# LINE 488 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_combinedFriction_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Float))
btManifoldPoint_m_combinedFriction_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_combinedFriction_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 492 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_combinedRestitution_set :: ( BtManifoldPointClass bc ) => (bc) -> (Float) -> IO ()
btManifoldPoint_m_combinedRestitution_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btManifoldPoint_m_combinedRestitution_set'_ a1' a2' >>
return ()
{-# LINE 496 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_combinedRestitution_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Float))
btManifoldPoint_m_combinedRestitution_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_combinedRestitution_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 500 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_contactCFM1_set :: ( BtManifoldPointClass bc ) => (bc) -> (Float) -> IO ()
btManifoldPoint_m_contactCFM1_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btManifoldPoint_m_contactCFM1_set'_ a1' a2' >>
return ()
{-# LINE 504 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_contactCFM1_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Float))
btManifoldPoint_m_contactCFM1_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_contactCFM1_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 508 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_contactCFM2_set :: ( BtManifoldPointClass bc ) => (bc) -> (Float) -> IO ()
btManifoldPoint_m_contactCFM2_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btManifoldPoint_m_contactCFM2_set'_ a1' a2' >>
return ()
{-# LINE 512 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_contactCFM2_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Float))
btManifoldPoint_m_contactCFM2_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_contactCFM2_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 516 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_contactMotion1_set :: ( BtManifoldPointClass bc ) => (bc) -> (Float) -> IO ()
btManifoldPoint_m_contactMotion1_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btManifoldPoint_m_contactMotion1_set'_ a1' a2' >>
return ()
{-# LINE 520 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_contactMotion1_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Float))
btManifoldPoint_m_contactMotion1_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_contactMotion1_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 524 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_contactMotion2_set :: ( BtManifoldPointClass bc ) => (bc) -> (Float) -> IO ()
btManifoldPoint_m_contactMotion2_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btManifoldPoint_m_contactMotion2_set'_ a1' a2' >>
return ()
{-# LINE 528 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_contactMotion2_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Float))
btManifoldPoint_m_contactMotion2_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_contactMotion2_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 532 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_distance1_set :: ( BtManifoldPointClass bc ) => (bc) -> (Float) -> IO ()
btManifoldPoint_m_distance1_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btManifoldPoint_m_distance1_set'_ a1' a2' >>
return ()
{-# LINE 536 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_distance1_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Float))
btManifoldPoint_m_distance1_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_distance1_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 540 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_index0_set :: ( BtManifoldPointClass bc ) => (bc) -> (Int) -> IO ()
btManifoldPoint_m_index0_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btManifoldPoint_m_index0_set'_ a1' a2' >>
return ()
{-# LINE 544 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_index0_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Int))
btManifoldPoint_m_index0_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_index0_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 548 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_index1_set :: ( BtManifoldPointClass bc ) => (bc) -> (Int) -> IO ()
btManifoldPoint_m_index1_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btManifoldPoint_m_index1_set'_ a1' a2' >>
return ()
{-# LINE 552 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_index1_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Int))
btManifoldPoint_m_index1_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_index1_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 556 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_lateralFrictionDir1_set :: ( BtManifoldPointClass bc ) => (bc) -> (Vec3) -> IO ()
btManifoldPoint_m_lateralFrictionDir1_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btManifoldPoint_m_lateralFrictionDir1_set'_ a1' a2' >>
return ()
{-# LINE 560 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_lateralFrictionDir1_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Vec3))
btManifoldPoint_m_lateralFrictionDir1_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btManifoldPoint_m_lateralFrictionDir1_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 564 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_lateralFrictionDir2_set :: ( BtManifoldPointClass bc ) => (bc) -> (Vec3) -> IO ()
btManifoldPoint_m_lateralFrictionDir2_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btManifoldPoint_m_lateralFrictionDir2_set'_ a1' a2' >>
return ()
{-# LINE 568 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_lateralFrictionDir2_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Vec3))
btManifoldPoint_m_lateralFrictionDir2_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btManifoldPoint_m_lateralFrictionDir2_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 572 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_lateralFrictionInitialized_set :: ( BtManifoldPointClass bc ) => (bc) -> (Bool) -> IO ()
btManifoldPoint_m_lateralFrictionInitialized_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = C2HSImp.fromBool a2} in
btManifoldPoint_m_lateralFrictionInitialized_set'_ a1' a2' >>
return ()
{-# LINE 576 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_lateralFrictionInitialized_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Bool))
btManifoldPoint_m_lateralFrictionInitialized_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_lateralFrictionInitialized_get'_ a1' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
{-# LINE 580 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_lifeTime_set :: ( BtManifoldPointClass bc ) => (bc) -> (Int) -> IO ()
btManifoldPoint_m_lifeTime_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btManifoldPoint_m_lifeTime_set'_ a1' a2' >>
return ()
{-# LINE 584 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_lifeTime_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Int))
btManifoldPoint_m_lifeTime_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_lifeTime_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 588 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_localPointA_set :: ( BtManifoldPointClass bc ) => (bc) -> (Vec3) -> IO ()
btManifoldPoint_m_localPointA_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btManifoldPoint_m_localPointA_set'_ a1' a2' >>
return ()
{-# LINE 592 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_localPointA_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Vec3))
btManifoldPoint_m_localPointA_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btManifoldPoint_m_localPointA_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 596 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_localPointB_set :: ( BtManifoldPointClass bc ) => (bc) -> (Vec3) -> IO ()
btManifoldPoint_m_localPointB_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btManifoldPoint_m_localPointB_set'_ a1' a2' >>
return ()
{-# LINE 600 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_localPointB_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Vec3))
btManifoldPoint_m_localPointB_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btManifoldPoint_m_localPointB_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 604 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_normalWorldOnB_set :: ( BtManifoldPointClass bc ) => (bc) -> (Vec3) -> IO ()
btManifoldPoint_m_normalWorldOnB_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btManifoldPoint_m_normalWorldOnB_set'_ a1' a2' >>
return ()
{-# LINE 608 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_normalWorldOnB_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Vec3))
btManifoldPoint_m_normalWorldOnB_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btManifoldPoint_m_normalWorldOnB_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 612 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_partId0_set :: ( BtManifoldPointClass bc ) => (bc) -> (Int) -> IO ()
btManifoldPoint_m_partId0_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btManifoldPoint_m_partId0_set'_ a1' a2' >>
return ()
{-# LINE 616 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_partId0_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Int))
btManifoldPoint_m_partId0_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_partId0_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 620 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_partId1_set :: ( BtManifoldPointClass bc ) => (bc) -> (Int) -> IO ()
btManifoldPoint_m_partId1_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btManifoldPoint_m_partId1_set'_ a1' a2' >>
return ()
{-# LINE 624 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_partId1_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Int))
btManifoldPoint_m_partId1_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_partId1_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 628 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_positionWorldOnA_set :: ( BtManifoldPointClass bc ) => (bc) -> (Vec3) -> IO ()
btManifoldPoint_m_positionWorldOnA_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btManifoldPoint_m_positionWorldOnA_set'_ a1' a2' >>
return ()
{-# LINE 632 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_positionWorldOnA_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Vec3))
btManifoldPoint_m_positionWorldOnA_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btManifoldPoint_m_positionWorldOnA_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 636 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_positionWorldOnB_set :: ( BtManifoldPointClass bc ) => (bc) -> (Vec3) -> IO ()
btManifoldPoint_m_positionWorldOnB_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btManifoldPoint_m_positionWorldOnB_set'_ a1' a2' >>
return ()
{-# LINE 640 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_positionWorldOnB_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((Vec3))
btManifoldPoint_m_positionWorldOnB_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btManifoldPoint_m_positionWorldOnB_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 644 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_userPersistentData_set :: ( BtManifoldPointClass bc ) => (bc) -> (VoidPtr) -> IO ()
btManifoldPoint_m_userPersistentData_set a1 a2 =
withBt a1 $ \a1' ->
withVoidPtr a2 $ \a2' ->
btManifoldPoint_m_userPersistentData_set'_ a1' a2' >>
return ()
{-# LINE 648 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btManifoldPoint_m_userPersistentData_get :: ( BtManifoldPointClass bc ) => (bc) -> IO ((VoidPtr))
btManifoldPoint_m_userPersistentData_get a1 =
withBt a1 $ \a1' ->
btManifoldPoint_m_userPersistentData_get'_ a1' >>= \res ->
mkVoidPtr res >>= \res' ->
return (res')
{-# LINE 652 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold0 :: IO ((BtPersistentManifold))
btPersistentManifold0 =
btPersistentManifold0'_ >>= \res ->
mkBtPersistentManifold res >>= \res' ->
return (res')
{-# LINE 657 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold1 :: (VoidPtr) -> (VoidPtr) -> (Int) -> (Float) -> (Float) -> IO ((BtPersistentManifold))
btPersistentManifold1 a1 a2 a3 a4 a5 =
withVoidPtr a1 $ \a1' ->
withVoidPtr a2 $ \a2' ->
let {a3' = fromIntegral a3} in
let {a4' = realToFrac a4} in
let {a5' = realToFrac a5} in
btPersistentManifold1'_ a1' a2' a3' a4' a5' >>= \res ->
mkBtPersistentManifold res >>= \res' ->
return (res')
{-# LINE 661 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_free :: ( BtPersistentManifoldClass bc ) => (bc) -> IO ()
btPersistentManifold_free a1 =
withBt a1 $ \a1' ->
btPersistentManifold_free'_ a1' >>
return ()
{-# LINE 662 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_setBodies :: ( BtPersistentManifoldClass bc ) => (bc)
-> (VoidPtr)
-> (VoidPtr)
-> IO ()
btPersistentManifold_setBodies a1 a2 a3 =
withBt a1 $ \a1' ->
withVoidPtr a2 $ \a2' ->
withVoidPtr a3 $ \a3' ->
btPersistentManifold_setBodies'_ a1' a2' a3' >>
return ()
{-# LINE 669 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_replaceContactPoint :: ( BtPersistentManifoldClass bc , BtManifoldPointClass p0 ) => (bc)
-> (p0)
-> (Int)
-> IO ()
btPersistentManifold_replaceContactPoint a1 a2 a3 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
let {a3' = fromIntegral a3} in
btPersistentManifold_replaceContactPoint'_ a1' a2' a3' >>
return ()
{-# LINE 676 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_clearUserCache :: ( BtPersistentManifoldClass bc , BtManifoldPointClass p0 ) => (bc)
-> (p0)
-> IO ()
btPersistentManifold_clearUserCache a1 a2 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
btPersistentManifold_clearUserCache'_ a1' a2' >>
return ()
{-# LINE 682 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_getBody1 :: ( BtPersistentManifoldClass bc ) => (bc)
-> IO ((VoidPtr))
btPersistentManifold_getBody1 a1 =
withBt a1 $ \a1' ->
btPersistentManifold_getBody1'_ a1' >>= \res ->
mkVoidPtr res >>= \res' ->
return (res')
{-# LINE 687 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_getBody10 :: ( BtPersistentManifoldClass bc ) => (bc)
-> IO ((VoidPtr))
btPersistentManifold_getBody10 a1 =
withBt a1 $ \a1' ->
btPersistentManifold_getBody10'_ a1' >>= \res ->
mkVoidPtr res >>= \res' ->
return (res')
{-# LINE 692 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_getContactProcessingThreshold :: ( BtPersistentManifoldClass bc ) => (bc)
-> IO ((Float))
btPersistentManifold_getContactProcessingThreshold a1 =
withBt a1 $ \a1' ->
btPersistentManifold_getContactProcessingThreshold'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 697 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_clearManifold :: ( BtPersistentManifoldClass bc ) => (bc)
-> IO ()
btPersistentManifold_clearManifold a1 =
withBt a1 $ \a1' ->
btPersistentManifold_clearManifold'_ a1' >>
return ()
{-# LINE 702 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_getNumContacts :: ( BtPersistentManifoldClass bc ) => (bc)
-> IO ((Int))
btPersistentManifold_getNumContacts a1 =
withBt a1 $ \a1' ->
btPersistentManifold_getNumContacts'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 707 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_getBody0 :: ( BtPersistentManifoldClass bc ) => (bc)
-> IO ((VoidPtr))
btPersistentManifold_getBody0 a1 =
withBt a1 $ \a1' ->
btPersistentManifold_getBody0'_ a1' >>= \res ->
mkVoidPtr res >>= \res' ->
return (res')
{-# LINE 712 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_getBody00 :: ( BtPersistentManifoldClass bc ) => (bc)
-> IO ((VoidPtr))
btPersistentManifold_getBody00 a1 =
withBt a1 $ \a1' ->
btPersistentManifold_getBody00'_ a1' >>= \res ->
mkVoidPtr res >>= \res' ->
return (res')
{-# LINE 717 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_addManifoldPoint :: ( BtPersistentManifoldClass bc , BtManifoldPointClass p0 ) => (bc)
-> (p0)
-> IO ((Int))
btPersistentManifold_addManifoldPoint a1 a2 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
btPersistentManifold_addManifoldPoint'_ a1' a2' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 723 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_getCacheEntry :: ( BtPersistentManifoldClass bc , BtManifoldPointClass p0 ) => (bc)
-> (p0)
-> IO ((Int))
btPersistentManifold_getCacheEntry a1 a2 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
btPersistentManifold_getCacheEntry'_ a1' a2' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 729 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_validContactDistance :: ( BtPersistentManifoldClass bc , BtManifoldPointClass p0 ) => (bc)
-> (p0)
-> IO ((Bool))
btPersistentManifold_validContactDistance a1 a2 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
btPersistentManifold_validContactDistance'_ a1' a2' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
{-# LINE 735 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_removeContactPoint :: ( BtPersistentManifoldClass bc ) => (bc)
-> (Int)
-> IO ()
btPersistentManifold_removeContactPoint a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btPersistentManifold_removeContactPoint'_ a1' a2' >>
return ()
{-# LINE 741 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_getContactPoint :: ( BtPersistentManifoldClass bc ) => (bc)
-> (Int)
-> IO ((BtManifoldPoint))
btPersistentManifold_getContactPoint a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btPersistentManifold_getContactPoint'_ a1' a2' >>= \res ->
mkBtManifoldPoint res >>= \res' ->
return (res')
{-# LINE 747 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_getContactPoint0 :: ( BtPersistentManifoldClass bc ) => (bc)
-> (Int)
-> IO ((BtManifoldPoint))
btPersistentManifold_getContactPoint0 a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btPersistentManifold_getContactPoint0'_ a1' a2' >>= \res ->
mkBtManifoldPoint res >>= \res' ->
return (res')
{-# LINE 753 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_getContactPoint1 :: ( BtPersistentManifoldClass bc ) => (bc)
-> (Int)
-> IO ((BtManifoldPoint))
btPersistentManifold_getContactPoint1 a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btPersistentManifold_getContactPoint1'_ a1' a2' >>= \res ->
mkBtManifoldPoint res >>= \res' ->
return (res')
{-# LINE 759 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_refreshContactPoints :: ( BtPersistentManifoldClass bc ) => (bc)
-> (Transform)
-> (Transform)
-> IO ((Transform), (Transform))
btPersistentManifold_refreshContactPoints a1 a2 a3 =
withBt a1 $ \a1' ->
withTransform a2 $ \a2' ->
withTransform a3 $ \a3' ->
btPersistentManifold_refreshContactPoints'_ a1' a2' a3' >>
peekTransform a2'>>= \a2'' ->
peekTransform a3'>>= \a3'' ->
return (a2'', a3'')
{-# LINE 766 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_refreshContactPoints' :: ( BtPersistentManifoldClass bc ) => (bc)
-> IO ((Transform), (Transform))
btPersistentManifold_refreshContactPoints' a1 =
withBt a1 $ \a1' ->
allocaTransform $ \a2' ->
allocaTransform $ \a3' ->
btPersistentManifold_refreshContactPoints''_ a1' a2' a3' >>
peekTransform a2'>>= \a2'' ->
peekTransform a3'>>= \a3'' ->
return (a2'', a3'')
{-# LINE 773 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_getContactBreakingThreshold :: ( BtPersistentManifoldClass bc ) => (bc)
-> IO ((Float))
btPersistentManifold_getContactBreakingThreshold a1 =
withBt a1 $ \a1' ->
btPersistentManifold_getContactBreakingThreshold'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 778 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_m_companionIdA_set :: ( BtPersistentManifoldClass bc ) => (bc) -> (Int) -> IO ()
btPersistentManifold_m_companionIdA_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btPersistentManifold_m_companionIdA_set'_ a1' a2' >>
return ()
{-# LINE 782 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_m_companionIdA_get :: ( BtPersistentManifoldClass bc ) => (bc) -> IO ((Int))
btPersistentManifold_m_companionIdA_get a1 =
withBt a1 $ \a1' ->
btPersistentManifold_m_companionIdA_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 786 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_m_companionIdB_set :: ( BtPersistentManifoldClass bc ) => (bc) -> (Int) -> IO ()
btPersistentManifold_m_companionIdB_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btPersistentManifold_m_companionIdB_set'_ a1' a2' >>
return ()
{-# LINE 790 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_m_companionIdB_get :: ( BtPersistentManifoldClass bc ) => (bc) -> IO ((Int))
btPersistentManifold_m_companionIdB_get a1 =
withBt a1 $ \a1' ->
btPersistentManifold_m_companionIdB_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 794 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_m_index1a_set :: ( BtPersistentManifoldClass bc ) => (bc) -> (Int) -> IO ()
btPersistentManifold_m_index1a_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btPersistentManifold_m_index1a_set'_ a1' a2' >>
return ()
{-# LINE 798 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btPersistentManifold_m_index1a_get :: ( BtPersistentManifoldClass bc ) => (bc) -> IO ((Int))
btPersistentManifold_m_index1a_get a1 =
withBt a1 $ \a1' ->
btPersistentManifold_m_index1a_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 802 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btStorageResult_addContactPoint :: ( BtStorageResultClass bc ) => (bc)
-> (Vec3)
-> (Vec3)
-> (Float)
-> IO ((Vec3), (Vec3))
btStorageResult_addContactPoint a1 a2 a3 a4 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
withVec3 a3 $ \a3' ->
let {a4' = realToFrac a4} in
btStorageResult_addContactPoint'_ a1' a2' a3' a4' >>
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
return (a2'', a3'')
{-# LINE 811 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btStorageResult_addContactPoint' :: ( BtStorageResultClass bc ) => (bc)
-> (Float)
-> IO ((Vec3), (Vec3))
btStorageResult_addContactPoint' a1 a4 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
allocaVec3 $ \a3' ->
let {a4' = realToFrac a4} in
btStorageResult_addContactPoint''_ a1' a2' a3' a4' >>
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
return (a2'', a3'')
{-# LINE 819 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btStorageResult_m_normalOnSurfaceB_set :: ( BtStorageResultClass bc ) => (bc) -> (Vec3) -> IO ()
btStorageResult_m_normalOnSurfaceB_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btStorageResult_m_normalOnSurfaceB_set'_ a1' a2' >>
return ()
{-# LINE 823 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btStorageResult_m_normalOnSurfaceB_get :: ( BtStorageResultClass bc ) => (bc) -> IO ((Vec3))
btStorageResult_m_normalOnSurfaceB_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btStorageResult_m_normalOnSurfaceB_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 827 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btStorageResult_m_closestPointInB_set :: ( BtStorageResultClass bc ) => (bc) -> (Vec3) -> IO ()
btStorageResult_m_closestPointInB_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btStorageResult_m_closestPointInB_set'_ a1' a2' >>
return ()
{-# LINE 831 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btStorageResult_m_closestPointInB_get :: ( BtStorageResultClass bc ) => (bc) -> IO ((Vec3))
btStorageResult_m_closestPointInB_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btStorageResult_m_closestPointInB_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 835 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btStorageResult_m_distance_set :: ( BtStorageResultClass bc ) => (bc) -> (Float) -> IO ()
btStorageResult_m_distance_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btStorageResult_m_distance_set'_ a1' a2' >>
return ()
{-# LINE 839 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btStorageResult_m_distance_get :: ( BtStorageResultClass bc ) => (bc) -> IO ((Float))
btStorageResult_m_distance_get a1 =
withBt a1 $ \a1' ->
btStorageResult_m_distance_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 843 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btSubSimplexClosestResult :: IO ((BtSubSimplexClosestResult))
btSubSimplexClosestResult =
btSubSimplexClosestResult'_ >>= \res ->
mkBtSubSimplexClosestResult res >>= \res' ->
return (res')
{-# LINE 848 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btSubSimplexClosestResult_free :: ( BtSubSimplexClosestResultClass bc ) => (bc) -> IO ()
btSubSimplexClosestResult_free a1 =
withBt a1 $ \a1' ->
btSubSimplexClosestResult_free'_ a1' >>
return ()
{-# LINE 849 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btSubSimplexClosestResult_reset :: ( BtSubSimplexClosestResultClass bc ) => (bc)
-> IO ()
btSubSimplexClosestResult_reset a1 =
withBt a1 $ \a1' ->
btSubSimplexClosestResult_reset'_ a1' >>
return ()
{-# LINE 854 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btSubSimplexClosestResult_isValid :: ( BtSubSimplexClosestResultClass bc ) => (bc)
-> IO ((Bool))
btSubSimplexClosestResult_isValid a1 =
withBt a1 $ \a1' ->
btSubSimplexClosestResult_isValid'_ a1' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
{-# LINE 859 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btSubSimplexClosestResult_setBarycentricCoordinates :: ( BtSubSimplexClosestResultClass bc ) => (bc)
-> (Float)
-> (Float)
-> (Float)
-> (Float)
-> IO ()
btSubSimplexClosestResult_setBarycentricCoordinates 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
btSubSimplexClosestResult_setBarycentricCoordinates'_ a1' a2' a3' a4' a5' >>
return ()
{-# LINE 868 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btSubSimplexClosestResult_m_closestPointOnSimplex_set :: ( BtSubSimplexClosestResultClass bc ) => (bc) -> (Vec3) -> IO ()
btSubSimplexClosestResult_m_closestPointOnSimplex_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btSubSimplexClosestResult_m_closestPointOnSimplex_set'_ a1' a2' >>
return ()
{-# LINE 872 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btSubSimplexClosestResult_m_closestPointOnSimplex_get :: ( BtSubSimplexClosestResultClass bc ) => (bc) -> IO ((Vec3))
btSubSimplexClosestResult_m_closestPointOnSimplex_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btSubSimplexClosestResult_m_closestPointOnSimplex_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 876 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btSubSimplexClosestResult_m_usedVertices_set :: ( BtSubSimplexClosestResultClass bc , BtUsageBitfieldClass a ) => (bc) -> (a) -> IO ()
btSubSimplexClosestResult_m_usedVertices_set a1 a2 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
btSubSimplexClosestResult_m_usedVertices_set'_ a1' a2' >>
return ()
{-# LINE 880 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btSubSimplexClosestResult_m_usedVertices_get :: ( BtSubSimplexClosestResultClass bc ) => (bc) -> IO ((BtUsageBitfield))
btSubSimplexClosestResult_m_usedVertices_get a1 =
withBt a1 $ \a1' ->
btSubSimplexClosestResult_m_usedVertices_get'_ a1' >>= \res ->
mkBtUsageBitfield res >>= \res' ->
return (res')
{-# LINE 884 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btSubSimplexClosestResult_m_degenerate_set :: ( BtSubSimplexClosestResultClass bc ) => (bc) -> (Bool) -> IO ()
btSubSimplexClosestResult_m_degenerate_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = C2HSImp.fromBool a2} in
btSubSimplexClosestResult_m_degenerate_set'_ a1' a2' >>
return ()
{-# LINE 888 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btSubSimplexClosestResult_m_degenerate_get :: ( BtSubSimplexClosestResultClass bc ) => (bc) -> IO ((Bool))
btSubSimplexClosestResult_m_degenerate_get a1 =
withBt a1 $ \a1' ->
btSubSimplexClosestResult_m_degenerate_get'_ a1' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
{-# LINE 892 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield :: IO ((BtUsageBitfield))
btUsageBitfield =
btUsageBitfield'_ >>= \res ->
mkBtUsageBitfield res >>= \res' ->
return (res')
{-# LINE 897 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_free :: ( BtUsageBitfieldClass bc ) => (bc) -> IO ()
btUsageBitfield_free a1 =
withBt a1 $ \a1' ->
btUsageBitfield_free'_ a1' >>
return ()
{-# LINE 898 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_reset :: ( BtUsageBitfieldClass bc ) => (bc)
-> IO ()
btUsageBitfield_reset a1 =
withBt a1 $ \a1' ->
btUsageBitfield_reset'_ a1' >>
return ()
{-# LINE 903 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_unused1_set :: ( BtUsageBitfieldClass bc ) => (bc) -> (Int) -> IO ()
btUsageBitfield_unused1_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btUsageBitfield_unused1_set'_ a1' a2' >>
return ()
{-# LINE 907 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_unused1_get :: ( BtUsageBitfieldClass bc ) => (bc) -> IO ((Int))
btUsageBitfield_unused1_get a1 =
withBt a1 $ \a1' ->
btUsageBitfield_unused1_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 911 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_unused2_set :: ( BtUsageBitfieldClass bc ) => (bc) -> (Int) -> IO ()
btUsageBitfield_unused2_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btUsageBitfield_unused2_set'_ a1' a2' >>
return ()
{-# LINE 915 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_unused2_get :: ( BtUsageBitfieldClass bc ) => (bc) -> IO ((Int))
btUsageBitfield_unused2_get a1 =
withBt a1 $ \a1' ->
btUsageBitfield_unused2_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 919 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_unused3_set :: ( BtUsageBitfieldClass bc ) => (bc) -> (Int) -> IO ()
btUsageBitfield_unused3_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btUsageBitfield_unused3_set'_ a1' a2' >>
return ()
{-# LINE 923 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_unused3_get :: ( BtUsageBitfieldClass bc ) => (bc) -> IO ((Int))
btUsageBitfield_unused3_get a1 =
withBt a1 $ \a1' ->
btUsageBitfield_unused3_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 927 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_unused4_set :: ( BtUsageBitfieldClass bc ) => (bc) -> (Int) -> IO ()
btUsageBitfield_unused4_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btUsageBitfield_unused4_set'_ a1' a2' >>
return ()
{-# LINE 931 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_unused4_get :: ( BtUsageBitfieldClass bc ) => (bc) -> IO ((Int))
btUsageBitfield_unused4_get a1 =
withBt a1 $ \a1' ->
btUsageBitfield_unused4_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 935 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_usedVertexA_set :: ( BtUsageBitfieldClass bc ) => (bc) -> (Int) -> IO ()
btUsageBitfield_usedVertexA_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btUsageBitfield_usedVertexA_set'_ a1' a2' >>
return ()
{-# LINE 939 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_usedVertexA_get :: ( BtUsageBitfieldClass bc ) => (bc) -> IO ((Int))
btUsageBitfield_usedVertexA_get a1 =
withBt a1 $ \a1' ->
btUsageBitfield_usedVertexA_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 943 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_usedVertexB_set :: ( BtUsageBitfieldClass bc ) => (bc) -> (Int) -> IO ()
btUsageBitfield_usedVertexB_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btUsageBitfield_usedVertexB_set'_ a1' a2' >>
return ()
{-# LINE 947 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_usedVertexB_get :: ( BtUsageBitfieldClass bc ) => (bc) -> IO ((Int))
btUsageBitfield_usedVertexB_get a1 =
withBt a1 $ \a1' ->
btUsageBitfield_usedVertexB_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 951 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_usedVertexC_set :: ( BtUsageBitfieldClass bc ) => (bc) -> (Int) -> IO ()
btUsageBitfield_usedVertexC_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btUsageBitfield_usedVertexC_set'_ a1' a2' >>
return ()
{-# LINE 955 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_usedVertexC_get :: ( BtUsageBitfieldClass bc ) => (bc) -> IO ((Int))
btUsageBitfield_usedVertexC_get a1 =
withBt a1 $ \a1' ->
btUsageBitfield_usedVertexC_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 959 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_usedVertexD_set :: ( BtUsageBitfieldClass bc ) => (bc) -> (Int) -> IO ()
btUsageBitfield_usedVertexD_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btUsageBitfield_usedVertexD_set'_ a1' a2' >>
return ()
{-# LINE 963 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btUsageBitfield_usedVertexD_get :: ( BtUsageBitfieldClass bc ) => (bc) -> IO ((Int))
btUsageBitfield_usedVertexD_get a1 =
withBt a1 $ \a1' ->
btUsageBitfield_usedVertexD_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 967 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver :: IO ((BtVoronoiSimplexSolver))
btVoronoiSimplexSolver =
btVoronoiSimplexSolver'_ >>= \res ->
mkBtVoronoiSimplexSolver res >>= \res' ->
return (res')
{-# LINE 972 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_free :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> IO ()
btVoronoiSimplexSolver_free a1 =
withBt a1 $ \a1' ->
btVoronoiSimplexSolver_free'_ a1' >>
return ()
{-# LINE 973 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_reset :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> IO ()
btVoronoiSimplexSolver_reset a1 =
withBt a1 $ \a1' ->
btVoronoiSimplexSolver_reset'_ a1' >>
return ()
{-# LINE 978 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_updateClosestVectorAndPoints :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> IO ((Bool))
btVoronoiSimplexSolver_updateClosestVectorAndPoints a1 =
withBt a1 $ \a1' ->
btVoronoiSimplexSolver_updateClosestVectorAndPoints'_ a1' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
{-# LINE 983 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_setEqualVertexThreshold :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> (Float)
-> IO ()
btVoronoiSimplexSolver_setEqualVertexThreshold a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btVoronoiSimplexSolver_setEqualVertexThreshold'_ a1' a2' >>
return ()
{-# LINE 989 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_inSimplex :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> (Vec3)
-> IO ((Bool), (Vec3))
btVoronoiSimplexSolver_inSimplex a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btVoronoiSimplexSolver_inSimplex'_ a1' a2' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekVec3 a2'>>= \a2'' ->
return (res', a2'')
{-# LINE 995 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_inSimplex' :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> IO ((Bool), (Vec3))
btVoronoiSimplexSolver_inSimplex' a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btVoronoiSimplexSolver_inSimplex''_ a1' a2' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekVec3 a2'>>= \a2'' ->
return (res', a2'')
{-# LINE 1001 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_closest :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> (Vec3)
-> IO ((Bool), (Vec3))
btVoronoiSimplexSolver_closest a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btVoronoiSimplexSolver_closest'_ a1' a2' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekVec3 a2'>>= \a2'' ->
return (res', a2'')
{-# LINE 1007 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_closest' :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> IO ((Bool), (Vec3))
btVoronoiSimplexSolver_closest' a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btVoronoiSimplexSolver_closest''_ a1' a2' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekVec3 a2'>>= \a2'' ->
return (res', a2'')
{-# LINE 1013 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_closestPtPointTetrahedron :: ( BtVoronoiSimplexSolverClass bc , BtSubSimplexClosestResultClass p5 ) => (bc)
-> (Vec3)
-> (Vec3)
-> (Vec3)
-> (Vec3)
-> (Vec3)
-> (p5)
-> IO ((Bool), (Vec3), (Vec3), (Vec3), (Vec3), (Vec3))
btVoronoiSimplexSolver_closestPtPointTetrahedron a1 a2 a3 a4 a5 a6 a7 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
withVec3 a3 $ \a3' ->
withVec3 a4 $ \a4' ->
withVec3 a5 $ \a5' ->
withVec3 a6 $ \a6' ->
withBt a7 $ \a7' ->
btVoronoiSimplexSolver_closestPtPointTetrahedron'_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
peekVec3 a4'>>= \a4'' ->
peekVec3 a5'>>= \a5'' ->
peekVec3 a6'>>= \a6'' ->
return (res', a2'', a3'', a4'', a5'', a6'')
{-# LINE 1024 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_closestPtPointTetrahedron' :: ( BtVoronoiSimplexSolverClass bc , BtSubSimplexClosestResultClass p5 ) => (bc)
-> (p5)
-> IO ((Bool), (Vec3), (Vec3), (Vec3), (Vec3), (Vec3))
btVoronoiSimplexSolver_closestPtPointTetrahedron' a1 a7 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
allocaVec3 $ \a3' ->
allocaVec3 $ \a4' ->
allocaVec3 $ \a5' ->
allocaVec3 $ \a6' ->
withBt a7 $ \a7' ->
btVoronoiSimplexSolver_closestPtPointTetrahedron''_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
peekVec3 a4'>>= \a4'' ->
peekVec3 a5'>>= \a5'' ->
peekVec3 a6'>>= \a6'' ->
return (res', a2'', a3'', a4'', a5'', a6'')
{-# LINE 1035 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_closestPtPointTriangle :: ( BtVoronoiSimplexSolverClass bc , BtSubSimplexClosestResultClass p4 ) => (bc)
-> (Vec3)
-> (Vec3)
-> (Vec3)
-> (Vec3)
-> (p4)
-> IO ((Bool), (Vec3), (Vec3), (Vec3), (Vec3))
btVoronoiSimplexSolver_closestPtPointTriangle a1 a2 a3 a4 a5 a6 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
withVec3 a3 $ \a3' ->
withVec3 a4 $ \a4' ->
withVec3 a5 $ \a5' ->
withBt a6 $ \a6' ->
btVoronoiSimplexSolver_closestPtPointTriangle'_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
peekVec3 a4'>>= \a4'' ->
peekVec3 a5'>>= \a5'' ->
return (res', a2'', a3'', a4'', a5'')
{-# LINE 1045 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_closestPtPointTriangle' :: ( BtVoronoiSimplexSolverClass bc , BtSubSimplexClosestResultClass p4 ) => (bc)
-> (p4)
-> IO ((Bool), (Vec3), (Vec3), (Vec3), (Vec3))
btVoronoiSimplexSolver_closestPtPointTriangle' a1 a6 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
allocaVec3 $ \a3' ->
allocaVec3 $ \a4' ->
allocaVec3 $ \a5' ->
withBt a6 $ \a6' ->
btVoronoiSimplexSolver_closestPtPointTriangle''_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = C2HSImp.toBool res} in
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
peekVec3 a4'>>= \a4'' ->
peekVec3 a5'>>= \a5'' ->
return (res', a2'', a3'', a4'', a5'')
{-# LINE 1055 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_pointOutsideOfPlane :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> (Vec3)
-> (Vec3)
-> (Vec3)
-> (Vec3)
-> (Vec3)
-> IO ((Int), (Vec3), (Vec3), (Vec3), (Vec3), (Vec3))
btVoronoiSimplexSolver_pointOutsideOfPlane a1 a2 a3 a4 a5 a6 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
withVec3 a3 $ \a3' ->
withVec3 a4 $ \a4' ->
withVec3 a5 $ \a5' ->
withVec3 a6 $ \a6' ->
btVoronoiSimplexSolver_pointOutsideOfPlane'_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = fromIntegral res} in
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
peekVec3 a4'>>= \a4'' ->
peekVec3 a5'>>= \a5'' ->
peekVec3 a6'>>= \a6'' ->
return (res', a2'', a3'', a4'', a5'', a6'')
{-# LINE 1065 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_pointOutsideOfPlane' :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> IO ((Int), (Vec3), (Vec3), (Vec3), (Vec3), (Vec3))
btVoronoiSimplexSolver_pointOutsideOfPlane' a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
allocaVec3 $ \a3' ->
allocaVec3 $ \a4' ->
allocaVec3 $ \a5' ->
allocaVec3 $ \a6' ->
btVoronoiSimplexSolver_pointOutsideOfPlane''_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = fromIntegral res} in
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
peekVec3 a4'>>= \a4'' ->
peekVec3 a5'>>= \a5'' ->
peekVec3 a6'>>= \a6'' ->
return (res', a2'', a3'', a4'', a5'', a6'')
{-# LINE 1075 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_emptySimplex :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> IO ((Bool))
btVoronoiSimplexSolver_emptySimplex a1 =
withBt a1 $ \a1' ->
btVoronoiSimplexSolver_emptySimplex'_ a1' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
{-# LINE 1080 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_maxVertex :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> IO ((Float))
btVoronoiSimplexSolver_maxVertex a1 =
withBt a1 $ \a1' ->
btVoronoiSimplexSolver_maxVertex'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 1085 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_addVertex :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> (Vec3)
-> (Vec3)
-> (Vec3)
-> IO ((Vec3), (Vec3), (Vec3))
btVoronoiSimplexSolver_addVertex a1 a2 a3 a4 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
withVec3 a3 $ \a3' ->
withVec3 a4 $ \a4' ->
btVoronoiSimplexSolver_addVertex'_ a1' a2' a3' a4' >>
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
peekVec3 a4'>>= \a4'' ->
return (a2'', a3'', a4'')
{-# LINE 1093 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_addVertex' :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> IO ((Vec3), (Vec3), (Vec3))
btVoronoiSimplexSolver_addVertex' a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
allocaVec3 $ \a3' ->
allocaVec3 $ \a4' ->
btVoronoiSimplexSolver_addVertex''_ a1' a2' a3' a4' >>
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
peekVec3 a4'>>= \a4'' ->
return (a2'', a3'', a4'')
{-# LINE 1101 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_reduceVertices :: ( BtVoronoiSimplexSolverClass bc , BtUsageBitfieldClass p0 ) => (bc)
-> (p0)
-> IO ()
btVoronoiSimplexSolver_reduceVertices a1 a2 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
btVoronoiSimplexSolver_reduceVertices'_ a1' a2' >>
return ()
{-# LINE 1107 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_backup_closest :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> (Vec3)
-> IO ((Vec3))
btVoronoiSimplexSolver_backup_closest a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btVoronoiSimplexSolver_backup_closest'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 1113 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_backup_closest' :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> IO ((Vec3))
btVoronoiSimplexSolver_backup_closest' a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btVoronoiSimplexSolver_backup_closest''_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 1119 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_removeVertex :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> (Int)
-> IO ()
btVoronoiSimplexSolver_removeVertex a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btVoronoiSimplexSolver_removeVertex'_ a1' a2' >>
return ()
{-# LINE 1125 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_getEqualVertexThreshold :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> IO ((Float))
btVoronoiSimplexSolver_getEqualVertexThreshold a1 =
withBt a1 $ \a1' ->
btVoronoiSimplexSolver_getEqualVertexThreshold'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 1130 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_compute_points :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> (Vec3)
-> (Vec3)
-> IO ((Vec3), (Vec3))
btVoronoiSimplexSolver_compute_points a1 a2 a3 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
withVec3 a3 $ \a3' ->
btVoronoiSimplexSolver_compute_points'_ a1' a2' a3' >>
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
return (a2'', a3'')
{-# LINE 1137 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_compute_points' :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> IO ((Vec3), (Vec3))
btVoronoiSimplexSolver_compute_points' a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
allocaVec3 $ \a3' ->
btVoronoiSimplexSolver_compute_points''_ a1' a2' a3' >>
peekVec3 a2'>>= \a2'' ->
peekVec3 a3'>>= \a3'' ->
return (a2'', a3'')
{-# LINE 1144 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_fullSimplex :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> IO ((Bool))
btVoronoiSimplexSolver_fullSimplex a1 =
withBt a1 $ \a1' ->
btVoronoiSimplexSolver_fullSimplex'_ a1' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
{-# LINE 1149 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_numVertices :: ( BtVoronoiSimplexSolverClass bc ) => (bc)
-> IO ((Int))
btVoronoiSimplexSolver_numVertices a1 =
withBt a1 $ \a1' ->
btVoronoiSimplexSolver_numVertices'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 1154 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_cachedBC_set :: ( BtVoronoiSimplexSolverClass bc , BtSubSimplexClosestResultClass a ) => (bc) -> (a) -> IO ()
btVoronoiSimplexSolver_m_cachedBC_set a1 a2 =
withBt a1 $ \a1' ->
withBt a2 $ \a2' ->
btVoronoiSimplexSolver_m_cachedBC_set'_ a1' a2' >>
return ()
{-# LINE 1158 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_cachedBC_get :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> IO ((BtSubSimplexClosestResult))
btVoronoiSimplexSolver_m_cachedBC_get a1 =
withBt a1 $ \a1' ->
btVoronoiSimplexSolver_m_cachedBC_get'_ a1' >>= \res ->
mkBtSubSimplexClosestResult res >>= \res' ->
return (res')
{-# LINE 1162 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_cachedP1_set :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> (Vec3) -> IO ()
btVoronoiSimplexSolver_m_cachedP1_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btVoronoiSimplexSolver_m_cachedP1_set'_ a1' a2' >>
return ()
{-# LINE 1166 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_cachedP1_get :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> IO ((Vec3))
btVoronoiSimplexSolver_m_cachedP1_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btVoronoiSimplexSolver_m_cachedP1_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 1170 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_cachedP2_set :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> (Vec3) -> IO ()
btVoronoiSimplexSolver_m_cachedP2_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btVoronoiSimplexSolver_m_cachedP2_set'_ a1' a2' >>
return ()
{-# LINE 1174 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_cachedP2_get :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> IO ((Vec3))
btVoronoiSimplexSolver_m_cachedP2_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btVoronoiSimplexSolver_m_cachedP2_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 1178 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_cachedV_set :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> (Vec3) -> IO ()
btVoronoiSimplexSolver_m_cachedV_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btVoronoiSimplexSolver_m_cachedV_set'_ a1' a2' >>
return ()
{-# LINE 1182 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_cachedV_get :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> IO ((Vec3))
btVoronoiSimplexSolver_m_cachedV_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btVoronoiSimplexSolver_m_cachedV_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 1186 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_cachedValidClosest_set :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> (Bool) -> IO ()
btVoronoiSimplexSolver_m_cachedValidClosest_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = C2HSImp.fromBool a2} in
btVoronoiSimplexSolver_m_cachedValidClosest_set'_ a1' a2' >>
return ()
{-# LINE 1190 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_cachedValidClosest_get :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> IO ((Bool))
btVoronoiSimplexSolver_m_cachedValidClosest_get a1 =
withBt a1 $ \a1' ->
btVoronoiSimplexSolver_m_cachedValidClosest_get'_ a1' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
{-# LINE 1194 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_equalVertexThreshold_set :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> (Float) -> IO ()
btVoronoiSimplexSolver_m_equalVertexThreshold_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btVoronoiSimplexSolver_m_equalVertexThreshold_set'_ a1' a2' >>
return ()
{-# LINE 1198 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_equalVertexThreshold_get :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> IO ((Float))
btVoronoiSimplexSolver_m_equalVertexThreshold_get a1 =
withBt a1 $ \a1' ->
btVoronoiSimplexSolver_m_equalVertexThreshold_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 1202 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_lastW_set :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> (Vec3) -> IO ()
btVoronoiSimplexSolver_m_lastW_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btVoronoiSimplexSolver_m_lastW_set'_ a1' a2' >>
return ()
{-# LINE 1206 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_lastW_get :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> IO ((Vec3))
btVoronoiSimplexSolver_m_lastW_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btVoronoiSimplexSolver_m_lastW_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 1210 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_needsUpdate_set :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> (Bool) -> IO ()
btVoronoiSimplexSolver_m_needsUpdate_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = C2HSImp.fromBool a2} in
btVoronoiSimplexSolver_m_needsUpdate_set'_ a1' a2' >>
return ()
{-# LINE 1214 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_needsUpdate_get :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> IO ((Bool))
btVoronoiSimplexSolver_m_needsUpdate_get a1 =
withBt a1 $ \a1' ->
btVoronoiSimplexSolver_m_needsUpdate_get'_ a1' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
{-# LINE 1218 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_numVertices_set :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> (Int) -> IO ()
btVoronoiSimplexSolver_m_numVertices_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = fromIntegral a2} in
btVoronoiSimplexSolver_m_numVertices_set'_ a1' a2' >>
return ()
{-# LINE 1222 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btVoronoiSimplexSolver_m_numVertices_get :: ( BtVoronoiSimplexSolverClass bc ) => (bc) -> IO ((Int))
btVoronoiSimplexSolver_m_numVertices_get a1 =
withBt a1 $ \a1' ->
btVoronoiSimplexSolver_m_numVertices_get'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 1226 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_sResults :: IO ((BtGjkEpaSolver2_sResults))
btGjkEpaSolver2_sResults =
btGjkEpaSolver2_sResults'_ >>= \res ->
mkBtGjkEpaSolver2_sResults res >>= \res' ->
return (res')
{-# LINE 1231 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_sResults_free :: ( BtGjkEpaSolver2_sResultsClass bc ) => (bc) -> IO ()
btGjkEpaSolver2_sResults_free a1 =
withBt a1 $ \a1' ->
btGjkEpaSolver2_sResults_free'_ a1' >>
return ()
{-# LINE 1232 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_sResults_distance_set :: ( BtGjkEpaSolver2_sResultsClass bc ) => (bc) -> (Float) -> IO ()
btGjkEpaSolver2_sResults_distance_set a1 a2 =
withBt a1 $ \a1' ->
let {a2' = realToFrac a2} in
btGjkEpaSolver2_sResults_distance_set'_ a1' a2' >>
return ()
{-# LINE 1236 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_sResults_distance_get :: ( BtGjkEpaSolver2_sResultsClass bc ) => (bc) -> IO ((Float))
btGjkEpaSolver2_sResults_distance_get a1 =
withBt a1 $ \a1' ->
btGjkEpaSolver2_sResults_distance_get'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 1240 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_sResults_normal_set :: ( BtGjkEpaSolver2_sResultsClass bc ) => (bc) -> (Vec3) -> IO ()
btGjkEpaSolver2_sResults_normal_set a1 a2 =
withBt a1 $ \a1' ->
withVec3 a2 $ \a2' ->
btGjkEpaSolver2_sResults_normal_set'_ a1' a2' >>
return ()
{-# LINE 1244 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
btGjkEpaSolver2_sResults_normal_get :: ( BtGjkEpaSolver2_sResultsClass bc ) => (bc) -> IO ((Vec3))
btGjkEpaSolver2_sResults_normal_get a1 =
withBt a1 $ \a1' ->
allocaVec3 $ \a2' ->
btGjkEpaSolver2_sResults_normal_get'_ a1' a2' >>
peekVec3 a2'>>= \a2'' ->
return (a2'')
{-# LINE 1248 "./Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs" #-}
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_ClosestPointInput_new"
btDiscreteCollisionDetectorInterface_ClosestPointInput'_ :: (IO (C2HSImp.Ptr ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_ClosestPointInput_free"
btDiscreteCollisionDetectorInterface_ClosestPointInput_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformA_set"
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformA_get"
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformA_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformB_set"
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformB_get"
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_transformB_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_ClosestPointInput_m_maximumDistanceSquared_set"
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_maximumDistanceSquared_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_ClosestPointInput_m_maximumDistanceSquared_get"
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_maximumDistanceSquared_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_ClosestPointInput_m_stackAlloc_set"
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_stackAlloc_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_ClosestPointInput_m_stackAlloc_get"
btDiscreteCollisionDetectorInterface_ClosestPointInput_m_stackAlloc_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_Result_setShapeIdentifiersB"
btDiscreteCollisionDetectorInterface_Result_setShapeIdentifiersB'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_Result_setShapeIdentifiersA"
btDiscreteCollisionDetectorInterface_Result_setShapeIdentifiersA'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_Result_addContactPoint"
btDiscreteCollisionDetectorInterface_Result_addContactPoint'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO ())))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_Result_addContactPoint"
btDiscreteCollisionDetectorInterface_Result_addContactPoint''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO ())))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btConstraintRow_new"
btConstraintRow'_ :: (IO (C2HSImp.Ptr ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btConstraintRow_free"
btConstraintRow_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btConstraintRow_m_rhs_set"
btConstraintRow_m_rhs_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btConstraintRow_m_rhs_get"
btConstraintRow_m_rhs_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btConstraintRow_m_jacDiagInv_set"
btConstraintRow_m_jacDiagInv_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btConstraintRow_m_jacDiagInv_get"
btConstraintRow_m_jacDiagInv_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btConstraintRow_m_lowerLimit_set"
btConstraintRow_m_lowerLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btConstraintRow_m_lowerLimit_get"
btConstraintRow_m_lowerLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btConstraintRow_m_upperLimit_set"
btConstraintRow_m_upperLimit_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btConstraintRow_m_upperLimit_get"
btConstraintRow_m_upperLimit_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btConstraintRow_m_accumImpulse_set"
btConstraintRow_m_accumImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btConstraintRow_m_accumImpulse_get"
btConstraintRow_m_accumImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btDiscreteCollisionDetectorInterface_getClosestPoints"
btDiscreteCollisionDetectorInterface_getClosestPoints'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ()))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_new"
btGjkEpaSolver2'_ :: (IO (C2HSImp.Ptr ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_free"
btGjkEpaSolver2_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_StackSizeRequirement"
btGjkEpaSolver2_StackSizeRequirement'_ :: (IO C2HSImp.CInt)
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_Distance"
btGjkEpaSolver2_Distance'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_Distance"
btGjkEpaSolver2_Distance''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_Penetration"
btGjkEpaSolver2_Penetration'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_Penetration"
btGjkEpaSolver2_Penetration''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_SignedDistance0"
btGjkEpaSolver2_SignedDistance'_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_SignedDistance0"
btGjkEpaSolver2_SignedDistance''_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_SignedDistance0"
btGjkEpaSolver2_SignedDistance0'_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_SignedDistance0"
btGjkEpaSolver2_SignedDistance0''_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_SignedDistance1"
btGjkEpaSolver2_SignedDistance1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_SignedDistance1"
btGjkEpaSolver2_SignedDistance1''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_free"
btGjkPairDetector_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_setCachedSeperatingAxis"
btGjkPairDetector_setCachedSeperatingAxis'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_setCachedSeperatingAxis"
btGjkPairDetector_setCachedSeperatingAxis''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_getCachedSeparatingAxis"
btGjkPairDetector_getCachedSeparatingAxis'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_getClosestPoints"
btGjkPairDetector_getClosestPoints'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ()))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_setMinkowskiA"
btGjkPairDetector_setMinkowskiA'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_setMinkowskiB"
btGjkPairDetector_setMinkowskiB'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_setIgnoreMargin"
btGjkPairDetector_setIgnoreMargin'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_getClosestPointsNonVirtual"
btGjkPairDetector_getClosestPointsNonVirtual'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_getCachedSeparatingDistance"
btGjkPairDetector_getCachedSeparatingDistance'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_cachedSeparatingAxis_set"
btGjkPairDetector_m_cachedSeparatingAxis_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_cachedSeparatingAxis_get"
btGjkPairDetector_m_cachedSeparatingAxis_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_simplexSolver_set"
btGjkPairDetector_m_simplexSolver_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_simplexSolver_get"
btGjkPairDetector_m_simplexSolver_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_minkowskiA_set"
btGjkPairDetector_m_minkowskiA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_minkowskiA_get"
btGjkPairDetector_m_minkowskiA_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_minkowskiB_set"
btGjkPairDetector_m_minkowskiB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_minkowskiB_get"
btGjkPairDetector_m_minkowskiB_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_shapeTypeA_set"
btGjkPairDetector_m_shapeTypeA_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_shapeTypeA_get"
btGjkPairDetector_m_shapeTypeA_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_shapeTypeB_set"
btGjkPairDetector_m_shapeTypeB_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_shapeTypeB_get"
btGjkPairDetector_m_shapeTypeB_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_marginA_set"
btGjkPairDetector_m_marginA_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_marginA_get"
btGjkPairDetector_m_marginA_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_marginB_set"
btGjkPairDetector_m_marginB_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_marginB_get"
btGjkPairDetector_m_marginB_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_ignoreMargin_set"
btGjkPairDetector_m_ignoreMargin_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_ignoreMargin_get"
btGjkPairDetector_m_ignoreMargin_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_cachedSeparatingDistance_set"
btGjkPairDetector_m_cachedSeparatingDistance_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_cachedSeparatingDistance_get"
btGjkPairDetector_m_cachedSeparatingDistance_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_lastUsedMethod_set"
btGjkPairDetector_m_lastUsedMethod_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_lastUsedMethod_get"
btGjkPairDetector_m_lastUsedMethod_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_curIter_set"
btGjkPairDetector_m_curIter_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_curIter_get"
btGjkPairDetector_m_curIter_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_degenerateSimplex_set"
btGjkPairDetector_m_degenerateSimplex_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_degenerateSimplex_get"
btGjkPairDetector_m_degenerateSimplex_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_catchDegeneracies_set"
btGjkPairDetector_m_catchDegeneracies_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkPairDetector_m_catchDegeneracies_get"
btGjkPairDetector_m_catchDegeneracies_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_new0"
btManifoldPoint0'_ :: (IO (C2HSImp.Ptr ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_new1"
btManifoldPoint1'_ :: ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO (C2HSImp.Ptr ()))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_free"
btManifoldPoint_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_setDistance"
btManifoldPoint_setDistance'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_getLifeTime"
btManifoldPoint_getLifeTime'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_getDistance"
btManifoldPoint_getDistance'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_getPositionWorldOnB"
btManifoldPoint_getPositionWorldOnB'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_getAppliedImpulse"
btManifoldPoint_getAppliedImpulse'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_getPositionWorldOnA"
btManifoldPoint_getPositionWorldOnA'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_appliedImpulse_set"
btManifoldPoint_m_appliedImpulse_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_appliedImpulse_get"
btManifoldPoint_m_appliedImpulse_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_appliedImpulseLateral1_set"
btManifoldPoint_m_appliedImpulseLateral1_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_appliedImpulseLateral1_get"
btManifoldPoint_m_appliedImpulseLateral1_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_appliedImpulseLateral2_set"
btManifoldPoint_m_appliedImpulseLateral2_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_appliedImpulseLateral2_get"
btManifoldPoint_m_appliedImpulseLateral2_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_combinedFriction_set"
btManifoldPoint_m_combinedFriction_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_combinedFriction_get"
btManifoldPoint_m_combinedFriction_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_combinedRestitution_set"
btManifoldPoint_m_combinedRestitution_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_combinedRestitution_get"
btManifoldPoint_m_combinedRestitution_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_contactCFM1_set"
btManifoldPoint_m_contactCFM1_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_contactCFM1_get"
btManifoldPoint_m_contactCFM1_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_contactCFM2_set"
btManifoldPoint_m_contactCFM2_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_contactCFM2_get"
btManifoldPoint_m_contactCFM2_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_contactMotion1_set"
btManifoldPoint_m_contactMotion1_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_contactMotion1_get"
btManifoldPoint_m_contactMotion1_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_contactMotion2_set"
btManifoldPoint_m_contactMotion2_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_contactMotion2_get"
btManifoldPoint_m_contactMotion2_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_distance1_set"
btManifoldPoint_m_distance1_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_distance1_get"
btManifoldPoint_m_distance1_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_index0_set"
btManifoldPoint_m_index0_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_index0_get"
btManifoldPoint_m_index0_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_index1_set"
btManifoldPoint_m_index1_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_index1_get"
btManifoldPoint_m_index1_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_lateralFrictionDir1_set"
btManifoldPoint_m_lateralFrictionDir1_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_lateralFrictionDir1_get"
btManifoldPoint_m_lateralFrictionDir1_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_lateralFrictionDir2_set"
btManifoldPoint_m_lateralFrictionDir2_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_lateralFrictionDir2_get"
btManifoldPoint_m_lateralFrictionDir2_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_lateralFrictionInitialized_set"
btManifoldPoint_m_lateralFrictionInitialized_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_lateralFrictionInitialized_get"
btManifoldPoint_m_lateralFrictionInitialized_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_lifeTime_set"
btManifoldPoint_m_lifeTime_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_lifeTime_get"
btManifoldPoint_m_lifeTime_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_localPointA_set"
btManifoldPoint_m_localPointA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_localPointA_get"
btManifoldPoint_m_localPointA_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_localPointB_set"
btManifoldPoint_m_localPointB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_localPointB_get"
btManifoldPoint_m_localPointB_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_normalWorldOnB_set"
btManifoldPoint_m_normalWorldOnB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_normalWorldOnB_get"
btManifoldPoint_m_normalWorldOnB_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_partId0_set"
btManifoldPoint_m_partId0_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_partId0_get"
btManifoldPoint_m_partId0_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_partId1_set"
btManifoldPoint_m_partId1_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_partId1_get"
btManifoldPoint_m_partId1_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_positionWorldOnA_set"
btManifoldPoint_m_positionWorldOnA_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_positionWorldOnA_get"
btManifoldPoint_m_positionWorldOnA_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_positionWorldOnB_set"
btManifoldPoint_m_positionWorldOnB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_positionWorldOnB_get"
btManifoldPoint_m_positionWorldOnB_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_userPersistentData_set"
btManifoldPoint_m_userPersistentData_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btManifoldPoint_m_userPersistentData_get"
btManifoldPoint_m_userPersistentData_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_new0"
btPersistentManifold0'_ :: (IO (C2HSImp.Ptr ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_new1"
btPersistentManifold1'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO (C2HSImp.Ptr ())))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_free"
btPersistentManifold_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_setBodies"
btPersistentManifold_setBodies'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ()))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_replaceContactPoint"
btPersistentManifold_replaceContactPoint'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ()))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_clearUserCache"
btPersistentManifold_clearUserCache'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_getBody10"
btPersistentManifold_getBody1'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_getBody10"
btPersistentManifold_getBody10'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_getContactProcessingThreshold"
btPersistentManifold_getContactProcessingThreshold'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_clearManifold"
btPersistentManifold_clearManifold'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_getNumContacts"
btPersistentManifold_getNumContacts'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_getBody00"
btPersistentManifold_getBody0'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_getBody00"
btPersistentManifold_getBody00'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_addManifoldPoint"
btPersistentManifold_addManifoldPoint'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_getCacheEntry"
btPersistentManifold_getCacheEntry'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_validContactDistance"
btPersistentManifold_validContactDistance'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_removeContactPoint"
btPersistentManifold_removeContactPoint'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_getContactPoint0"
btPersistentManifold_getContactPoint'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ()))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_getContactPoint0"
btPersistentManifold_getContactPoint0'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ()))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_getContactPoint1"
btPersistentManifold_getContactPoint1'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ()))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_refreshContactPoints"
btPersistentManifold_refreshContactPoints'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_refreshContactPoints"
btPersistentManifold_refreshContactPoints''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_getContactBreakingThreshold"
btPersistentManifold_getContactBreakingThreshold'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_m_companionIdA_set"
btPersistentManifold_m_companionIdA_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_m_companionIdA_get"
btPersistentManifold_m_companionIdA_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_m_companionIdB_set"
btPersistentManifold_m_companionIdB_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_m_companionIdB_get"
btPersistentManifold_m_companionIdB_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_m_index1a_set"
btPersistentManifold_m_index1a_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btPersistentManifold_m_index1a_get"
btPersistentManifold_m_index1a_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btStorageResult_addContactPoint"
btStorageResult_addContactPoint'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO ())))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btStorageResult_addContactPoint"
btStorageResult_addContactPoint''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (C2HSImp.CFloat -> (IO ())))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btStorageResult_m_normalOnSurfaceB_set"
btStorageResult_m_normalOnSurfaceB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btStorageResult_m_normalOnSurfaceB_get"
btStorageResult_m_normalOnSurfaceB_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btStorageResult_m_closestPointInB_set"
btStorageResult_m_closestPointInB_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btStorageResult_m_closestPointInB_get"
btStorageResult_m_closestPointInB_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btStorageResult_m_distance_set"
btStorageResult_m_distance_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btStorageResult_m_distance_get"
btStorageResult_m_distance_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btSubSimplexClosestResult_new"
btSubSimplexClosestResult'_ :: (IO (C2HSImp.Ptr ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btSubSimplexClosestResult_free"
btSubSimplexClosestResult_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btSubSimplexClosestResult_reset"
btSubSimplexClosestResult_reset'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btSubSimplexClosestResult_isValid"
btSubSimplexClosestResult_isValid'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btSubSimplexClosestResult_setBarycentricCoordinates"
btSubSimplexClosestResult_setBarycentricCoordinates'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (IO ()))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btSubSimplexClosestResult_m_closestPointOnSimplex_set"
btSubSimplexClosestResult_m_closestPointOnSimplex_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btSubSimplexClosestResult_m_closestPointOnSimplex_get"
btSubSimplexClosestResult_m_closestPointOnSimplex_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btSubSimplexClosestResult_m_usedVertices_set"
btSubSimplexClosestResult_m_usedVertices_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btSubSimplexClosestResult_m_usedVertices_get"
btSubSimplexClosestResult_m_usedVertices_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btSubSimplexClosestResult_m_degenerate_set"
btSubSimplexClosestResult_m_degenerate_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btSubSimplexClosestResult_m_degenerate_get"
btSubSimplexClosestResult_m_degenerate_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_new"
btUsageBitfield'_ :: (IO (C2HSImp.Ptr ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_free"
btUsageBitfield_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_reset"
btUsageBitfield_reset'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_unused1_set"
btUsageBitfield_unused1_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUShort -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_unused1_get"
btUsageBitfield_unused1_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUShort))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_unused2_set"
btUsageBitfield_unused2_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUShort -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_unused2_get"
btUsageBitfield_unused2_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUShort))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_unused3_set"
btUsageBitfield_unused3_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUShort -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_unused3_get"
btUsageBitfield_unused3_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUShort))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_unused4_set"
btUsageBitfield_unused4_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUShort -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_unused4_get"
btUsageBitfield_unused4_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUShort))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_usedVertexA_set"
btUsageBitfield_usedVertexA_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUShort -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_usedVertexA_get"
btUsageBitfield_usedVertexA_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUShort))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_usedVertexB_set"
btUsageBitfield_usedVertexB_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUShort -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_usedVertexB_get"
btUsageBitfield_usedVertexB_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUShort))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_usedVertexC_set"
btUsageBitfield_usedVertexC_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUShort -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_usedVertexC_get"
btUsageBitfield_usedVertexC_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUShort))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_usedVertexD_set"
btUsageBitfield_usedVertexD_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUShort -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btUsageBitfield_usedVertexD_get"
btUsageBitfield_usedVertexD_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUShort))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_new"
btVoronoiSimplexSolver'_ :: (IO (C2HSImp.Ptr ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_free"
btVoronoiSimplexSolver_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_reset"
btVoronoiSimplexSolver_reset'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_updateClosestVectorAndPoints"
btVoronoiSimplexSolver_updateClosestVectorAndPoints'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_setEqualVertexThreshold"
btVoronoiSimplexSolver_setEqualVertexThreshold'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_inSimplex"
btVoronoiSimplexSolver_inSimplex'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CInt)))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_inSimplex"
btVoronoiSimplexSolver_inSimplex''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CInt)))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_closest"
btVoronoiSimplexSolver_closest'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CInt)))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_closest"
btVoronoiSimplexSolver_closest''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CInt)))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_closestPtPointTetrahedron"
btVoronoiSimplexSolver_closestPtPointTetrahedron'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_closestPtPointTetrahedron"
btVoronoiSimplexSolver_closestPtPointTetrahedron''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_closestPtPointTriangle"
btVoronoiSimplexSolver_closestPtPointTriangle'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_closestPtPointTriangle"
btVoronoiSimplexSolver_closestPtPointTriangle''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_pointOutsideOfPlane"
btVoronoiSimplexSolver_pointOutsideOfPlane'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_pointOutsideOfPlane"
btVoronoiSimplexSolver_pointOutsideOfPlane''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_emptySimplex"
btVoronoiSimplexSolver_emptySimplex'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_maxVertex"
btVoronoiSimplexSolver_maxVertex'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_addVertex"
btVoronoiSimplexSolver_addVertex'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_addVertex"
btVoronoiSimplexSolver_addVertex''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_reduceVertices"
btVoronoiSimplexSolver_reduceVertices'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_backup_closest"
btVoronoiSimplexSolver_backup_closest'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_backup_closest"
btVoronoiSimplexSolver_backup_closest''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_removeVertex"
btVoronoiSimplexSolver_removeVertex'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_getEqualVertexThreshold"
btVoronoiSimplexSolver_getEqualVertexThreshold'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_compute_points"
btVoronoiSimplexSolver_compute_points'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_compute_points"
btVoronoiSimplexSolver_compute_points''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ()))))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_fullSimplex"
btVoronoiSimplexSolver_fullSimplex'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_numVertices"
btVoronoiSimplexSolver_numVertices'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_cachedBC_set"
btVoronoiSimplexSolver_m_cachedBC_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_cachedBC_get"
btVoronoiSimplexSolver_m_cachedBC_get'_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_cachedP1_set"
btVoronoiSimplexSolver_m_cachedP1_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_cachedP1_get"
btVoronoiSimplexSolver_m_cachedP1_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_cachedP2_set"
btVoronoiSimplexSolver_m_cachedP2_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_cachedP2_get"
btVoronoiSimplexSolver_m_cachedP2_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_cachedV_set"
btVoronoiSimplexSolver_m_cachedV_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_cachedV_get"
btVoronoiSimplexSolver_m_cachedV_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_cachedValidClosest_set"
btVoronoiSimplexSolver_m_cachedValidClosest_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_cachedValidClosest_get"
btVoronoiSimplexSolver_m_cachedValidClosest_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_equalVertexThreshold_set"
btVoronoiSimplexSolver_m_equalVertexThreshold_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_equalVertexThreshold_get"
btVoronoiSimplexSolver_m_equalVertexThreshold_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_lastW_set"
btVoronoiSimplexSolver_m_lastW_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_lastW_get"
btVoronoiSimplexSolver_m_lastW_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_needsUpdate_set"
btVoronoiSimplexSolver_m_needsUpdate_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_needsUpdate_get"
btVoronoiSimplexSolver_m_needsUpdate_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_numVertices_set"
btVoronoiSimplexSolver_m_numVertices_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btVoronoiSimplexSolver_m_numVertices_get"
btVoronoiSimplexSolver_m_numVertices_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_sResults_new"
btGjkEpaSolver2_sResults'_ :: (IO (C2HSImp.Ptr ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_sResults_free"
btGjkEpaSolver2_sResults_free'_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_sResults_distance_set"
btGjkEpaSolver2_sResults_distance_set'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CFloat -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_sResults_distance_get"
btGjkEpaSolver2_sResults_distance_get'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CFloat))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_sResults_normal_set"
btGjkEpaSolver2_sResults_normal_set'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))
foreign import ccall safe "Physics/Bullet/Raw/BulletCollision/NarrowPhaseCollision.chs.h btGjkEpaSolver2_sResults_normal_get"
btGjkEpaSolver2_sResults_normal_get'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CFloat) -> (IO ())))