{-# LINE 1 "src/Chiphunk/Low/Shape.chs" #-}
module Chiphunk.Low.Shape
( Shape
, shapeBody
, shapeBB
, shapeSensor
, shapeElasticity
, shapeFriction
, shapeSurfaceVelocity
, shapeCollisionType
, shapeMass
, shapeDensity
, ShapeFilter (..)
, ShapeFilterPtr
, shapeFilter
, shapeSpace
, shapeUserData
, shapeFree
, shapeCacheBB
, shapeUpdate
, circleShapeNew
, segmentShapeNew
, segmentShapeNeighbors
, polyShapeNew
, polyShapeNewRaw
, boxShapeNew
, boxShapeNew2
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Marshal.Utils as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp
import Foreign
import Chiphunk.Low.Internal
import Data.StateVar
import Chiphunk.Low.Types
{-# LINE 36 "src/Chiphunk/Low/Shape.chs" #-}
cpShapeGetBody :: (Shape) -> IO ((Body))
cpShapeGetBody a1 =
let {a1' = id a1} in
cpShapeGetBody'_ a1' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 41 "src/Chiphunk/Low/Shape.chs" #-}
cpShapeSetBody :: (Shape) -> (Body) -> IO ()
cpShapeSetBody a1 a2 =
let {a1' = id a1} in
let {a2' = id a2} in
cpShapeSetBody'_ a1' a2' >>
return ()
{-# LINE 43 "src/Chiphunk/Low/Shape.chs" #-}
shapeBody :: Shape -> StateVar Body
shapeBody = mkStateVar cpShapeGetBody cpShapeSetBody
w_cpShapeGetBB :: (Shape) -> IO ((BB))
w_cpShapeGetBB :: Shape -> IO BB
w_cpShapeGetBB Shape
a1 =
let {a1' :: Shape
a1' = Shape -> Shape
forall a. a -> a
id Shape
a1} in
(Ptr BB -> IO BB) -> IO BB
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr BB -> IO BB) -> IO BB) -> (Ptr BB -> IO BB) -> IO BB
forall a b. (a -> b) -> a -> b
$ \Ptr BB
a2' ->
Shape -> Ptr BB -> IO ()
w_cpShapeGetBB'_ Shape
a1' Ptr BB
a2' IO () -> IO BB -> IO BB
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
Ptr BB -> IO BB
forall a. Storable a => Ptr a -> IO a
peek Ptr BB
a2'IO BB -> (BB -> IO BB) -> IO BB
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \BB
a2'' ->
BB -> IO BB
forall (m :: * -> *) a. Monad m => a -> m a
return (BB
a2'')
{-# LINE 50 "src/Chiphunk/Low/Shape.chs" #-}
shapeBB :: Shape -> GettableStateVar BB
shapeBB = makeGettableStateVar . w_cpShapeGetBB
cpShapeGetSensor :: (Shape) -> IO ((Bool))
cpShapeGetSensor :: Shape -> IO Bool
cpShapeGetSensor Shape
a1 =
let {a1' :: Shape
a1' = Shape -> Shape
forall a. a -> a
id Shape
a1} in
Shape -> IO CUChar
cpShapeGetSensor'_ Shape
a1' IO CUChar -> (CUChar -> IO Bool) -> IO Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CUChar
res ->
let {res' :: Bool
res' = CUChar -> Bool
forall a. (Eq a, Num a) => a -> Bool
C2HSImp.toBool CUChar
res} in
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
res')
{-# LINE 59 "src/Chiphunk/Low/Shape.chs" #-}
cpShapeSetSensor :: (Shape) -> (Bool) -> IO ()
cpShapeSetSensor a1 a2 =
let {a1' = id a1} in
let {a2' = C2HSImp.fromBool a2} in
cpShapeSetSensor'_ a1' a2' >>
return ()
{-# LINE 61 "src/Chiphunk/Low/Shape.chs" #-}
shapeSensor :: Shape -> StateVar Bool
shapeSensor = mkStateVar cpShapeGetSensor cpShapeSetSensor
cpShapeGetElasticity :: (Shape) -> IO ((Double))
cpShapeGetElasticity :: Shape -> IO Double
cpShapeGetElasticity Shape
a1 =
let {a1' :: Shape
a1' = Shape -> Shape
forall a. a -> a
id Shape
a1} in
Shape -> IO CDouble
cpShapeGetElasticity'_ Shape
a1' IO CDouble -> (CDouble -> IO Double) -> IO Double
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CDouble
res ->
let {res' :: Double
res' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
res} in
Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return (Double
res')
{-# LINE 68 "src/Chiphunk/Low/Shape.chs" #-}
cpShapeSetElasticity :: (Shape) -> (Double) -> IO ()
cpShapeSetElasticity a1 a2 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
cpShapeSetElasticity'_ a1' a2' >>
return ()
{-# LINE 70 "src/Chiphunk/Low/Shape.chs" #-}
shapeElasticity :: Shape -> StateVar Double
shapeElasticity :: Shape -> StateVar Double
shapeElasticity = (Shape -> IO Double)
-> (Shape -> Double -> IO ()) -> Shape -> StateVar Double
forall a b. (a -> IO b) -> (a -> b -> IO ()) -> a -> StateVar b
mkStateVar Shape -> IO Double
cpShapeGetElasticity Shape -> Double -> IO ()
cpShapeSetElasticity
cpShapeGetFriction :: (Shape) -> IO ((Double))
cpShapeGetFriction :: Shape -> IO Double
cpShapeGetFriction Shape
a1 =
let {a1' :: Shape
a1' = Shape -> Shape
forall a. a -> a
id Shape
a1} in
Shape -> IO CDouble
cpShapeGetFriction'_ Shape
a1' IO CDouble -> (CDouble -> IO Double) -> IO Double
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CDouble
res ->
let {res' :: Double
res' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
res} in
Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return (Double
res')
{-# LINE 80 "src/Chiphunk/Low/Shape.chs" #-}
cpShapeSetFriction :: (Shape) -> (Double) -> IO ()
cpShapeSetFriction a1 a2 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
cpShapeSetFriction'_ a1' a2' >>
return ()
{-# LINE 82 "src/Chiphunk/Low/Shape.chs" #-}
shapeFriction :: Shape -> StateVar Double
shapeFriction :: Shape -> StateVar Double
shapeFriction = (Shape -> IO Double)
-> (Shape -> Double -> IO ()) -> Shape -> StateVar Double
forall a b. (a -> IO b) -> (a -> b -> IO ()) -> a -> StateVar b
mkStateVar Shape -> IO Double
cpShapeGetFriction Shape -> Double -> IO ()
cpShapeSetFriction
w_cpShapeGetSurfaceVelocity :: (Shape) -> IO ((Vect))
w_cpShapeGetSurfaceVelocity :: Shape -> IO Vect
w_cpShapeGetSurfaceVelocity Shape
a1 =
let {a1' :: Shape
a1' = Shape -> Shape
forall a. a -> a
id Shape
a1} in
(Ptr Vect -> IO Vect) -> IO Vect
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Vect -> IO Vect) -> IO Vect)
-> (Ptr Vect -> IO Vect) -> IO Vect
forall a b. (a -> b) -> a -> b
$ \Ptr Vect
a2' ->
Shape -> Ptr Vect -> IO ()
w_cpShapeGetSurfaceVelocity'_ Shape
a1' Ptr Vect
a2' IO () -> IO Vect -> IO Vect
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
Ptr Vect -> IO Vect
forall a. Storable a => Ptr a -> IO a
peek Ptr Vect
a2'IO Vect -> (Vect -> IO Vect) -> IO Vect
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Vect
a2'' ->
Vect -> IO Vect
forall (m :: * -> *) a. Monad m => a -> m a
return (Vect
a2'')
{-# LINE 92 "src/Chiphunk/Low/Shape.chs" #-}
cpShapeSetSurfaceVelocity :: (Shape) -> (Vect) -> IO ()
cpShapeSetSurfaceVelocity a1 a2 =
let {a1' = id a1} in
with a2 $ \a2' ->
cpShapeSetSurfaceVelocity'_ a1' a2' >>
return ()
{-# LINE 94 "src/Chiphunk/Low/Shape.chs" #-}
shapeSurfaceVelocity :: Shape -> StateVar Vect
shapeSurfaceVelocity = mkStateVar w_cpShapeGetSurfaceVelocity cpShapeSetSurfaceVelocity
cpShapeGetCollisionType :: (Shape) -> IO ((CollisionType))
cpShapeGetCollisionType :: Shape -> IO CollisionType
cpShapeGetCollisionType Shape
a1 =
let {a1' :: Shape
a1' = Shape -> Shape
forall a. a -> a
id Shape
a1} in
Shape -> IO CULong
cpShapeGetCollisionType'_ Shape
a1' IO CULong -> (CULong -> IO CollisionType) -> IO CollisionType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CULong
res ->
let {res' :: CollisionType
res' = CULong -> CollisionType
forall a b. (Integral a, Num b) => a -> b
fromIntegral CULong
res} in
CollisionType -> IO CollisionType
forall (m :: * -> *) a. Monad m => a -> m a
return (CollisionType
res')
{-# LINE 102 "src/Chiphunk/Low/Shape.chs" #-}
cpShapeSetCollisionType :: (Shape) -> (CollisionType) -> IO ()
cpShapeSetCollisionType a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
cpShapeSetCollisionType'_ a1' a2' >>
return ()
{-# LINE 104 "src/Chiphunk/Low/Shape.chs" #-}
shapeCollisionType :: Shape -> StateVar CollisionType
shapeCollisionType = mkStateVar cpShapeGetCollisionType cpShapeSetCollisionType
cpShapeGetMass :: (Shape) -> IO ((Double))
cpShapeGetMass :: Shape -> IO Double
cpShapeGetMass Shape
a1 =
let {a1' :: Shape
a1' = Shape -> Shape
forall a. a -> a
id Shape
a1} in
Shape -> IO CDouble
cpShapeGetMass'_ Shape
a1' IO CDouble -> (CDouble -> IO Double) -> IO Double
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CDouble
res ->
let {res' :: Double
res' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
res} in
return (res')
{-# LINE 113 "src/Chiphunk/Low/Shape.chs" #-}
cpShapeSetMass :: (Shape) -> (Double) -> IO ()
cpShapeSetMass a1 a2 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
cpShapeSetMass'_ a1' a2' >>
return ()
{-# LINE 115 "src/Chiphunk/Low/Shape.chs" #-}
shapeMass :: Shape -> StateVar Double
shapeMass = mkStateVar cpShapeGetMass cpShapeSetMass
cpShapeGetDensity :: (Shape) -> IO ((Double))
cpShapeGetDensity a1 =
let {a1' = id a1} in
cpShapeGetDensity'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 120 "src/Chiphunk/Low/Shape.chs" #-}
cpShapeSetDensity :: (Shape) -> (Double) -> IO ()
cpShapeSetDensity a1 a2 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
cpShapeSetDensity'_ a1' a2' >>
return ()
{-# LINE 122 "src/Chiphunk/Low/Shape.chs" #-}
shapeDensity :: Shape -> StateVar Double
shapeDensity = mkStateVar cpShapeGetDensity cpShapeSetDensity
data ShapeFilter = ShapeFilter
{ sfGroup :: !WordPtr
, sfCategories :: !Word32
, sfMask :: !Word32
} deriving Show
instance Storable ShapeFilter where
sizeOf :: ShapeFilter -> Int
sizeOf ShapeFilter
_ = Int
16
{-# LINE 136 "src/Chiphunk/Low/Shape.chs" #-}
alignment _ = 8
{-# LINE 137 "src/Chiphunk/Low/Shape.chs" #-}
poke p (ShapeFilter g c m) = do
(\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: C2HSImp.CULong)}) p $ fromIntegral g
(\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CUInt)}) p $ fromIntegral c
(\ptr val -> do {C2HSImp.pokeByteOff ptr 12 (val :: C2HSImp.CUInt)}) p $ fromIntegral m
peek :: Ptr ShapeFilter -> IO ShapeFilter
peek Ptr ShapeFilter
p = CollisionType -> Word32 -> Word32 -> ShapeFilter
ShapeFilter (CollisionType -> Word32 -> Word32 -> ShapeFilter)
-> IO CollisionType -> IO (Word32 -> Word32 -> ShapeFilter)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CULong -> CollisionType
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CULong -> CollisionType) -> IO CULong -> IO CollisionType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr ShapeFilter
ptr -> do {Ptr ShapeFilter -> Int -> IO CULong
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr ShapeFilter
ptr Int
0 :: IO C2HSImp.CULong}) Ptr ShapeFilter
p)
IO (Word32 -> Word32 -> ShapeFilter)
-> IO Word32 -> IO (Word32 -> ShapeFilter)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CUInt -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Word32) -> IO CUInt -> IO Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr ShapeFilter
ptr -> do {Ptr ShapeFilter -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr ShapeFilter
ptr Int
8 :: IO C2HSImp.CUInt}) Ptr ShapeFilter
p)
IO (Word32 -> ShapeFilter) -> IO Word32 -> IO ShapeFilter
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CUInt -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Word32) -> IO CUInt -> IO Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr ShapeFilter
ptr -> do {Ptr ShapeFilter -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr ShapeFilter
ptr Int
12 :: IO C2HSImp.CUInt}) Ptr ShapeFilter
p)
type ShapeFilterPtr = C2HSImp.Ptr (ShapeFilter)
{-# LINE 147 "src/Chiphunk/Low/Shape.chs" #-}
w_cpShapeGetFilter :: (Shape) -> IO ((ShapeFilter))
w_cpShapeGetFilter :: Shape -> IO ShapeFilter
w_cpShapeGetFilter Shape
a1 =
let {a1' :: Shape
a1' = Shape -> Shape
forall a. a -> a
id Shape
a1} in
(Ptr ShapeFilter -> IO ShapeFilter) -> IO ShapeFilter
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr ShapeFilter -> IO ShapeFilter) -> IO ShapeFilter)
-> (Ptr ShapeFilter -> IO ShapeFilter) -> IO ShapeFilter
forall a b. (a -> b) -> a -> b
$ \Ptr ShapeFilter
a2' ->
Shape -> Ptr ShapeFilter -> IO ()
w_cpShapeGetFilter'_ Shape
a1' Ptr ShapeFilter
a2' IO () -> IO ShapeFilter -> IO ShapeFilter
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
Ptr ShapeFilter -> IO ShapeFilter
ShapeFilter -> (Ptr ShapeFilter -> IO ()) -> IO ()
forall a. Storable a => Ptr a -> IO a
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with :: forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
peek :: forall a. Storable a => Ptr a -> IO a
peek Ptr ShapeFilter
a2'IO ShapeFilter -> (ShapeFilter -> IO ShapeFilter) -> IO ShapeFilter
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ShapeFilter
a2'' ->
return (a2'')
{-# LINE 149 "src/Chiphunk/Low/Shape.chs" #-}
cpShapeSetFilter :: (Shape) -> (ShapeFilter) -> IO ()
cpShapeSetFilter a1 a2 =
let {a1' = id a1} in
with a2 $ \a2' ->
cpShapeSetFilter'_ a1' a2' >>
return ()
{-# LINE 151 "src/Chiphunk/Low/Shape.chs" #-}
shapeFilter :: Shape -> StateVar ShapeFilter
shapeFilter = mkStateVar w_cpShapeGetFilter cpShapeSetFilter
cpShapeGetSpace :: (Shape) -> IO ((Space))
cpShapeGetSpace a1 =
let {a1' = id a1} in
cpShapeGetSpace'_ a1' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 157 "src/Chiphunk/Low/Shape.chs" #-}
shapeSpace :: Shape -> GettableStateVar Space
shapeSpace = makeGettableStateVar . cpShapeGetSpace
cpShapeGetUserData :: (Shape) -> IO ((DataPtr))
cpShapeGetUserData a1 =
let {a1' = id a1} in
cpShapeGetUserData'_ a1' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 163 "src/Chiphunk/Low/Shape.chs" #-}
cpShapeSetUserData :: (Shape) -> (DataPtr) -> IO ()
cpShapeSetUserData a1 a2 =
let {a1' = id a1} in
let {a2' = id a2} in
cpShapeSetUserData'_ a1' a2' >>
return ()
{-# LINE 165 "src/Chiphunk/Low/Shape.chs" #-}
shapeUserData :: Shape -> StateVar DataPtr
shapeUserData = mkStateVar cpShapeGetUserData cpShapeSetUserData
shapeFree :: (Shape) -> IO ()
shapeFree :: Shape -> IO ()
shapeFree Shape
a1 =
let {a1' :: Shape
a1' = Shape -> Shape
forall a. a -> a
id Shape
a1} in
Shape -> IO ()
shapeFree'_ Shape
a1' IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# LINE 174 "src/Chiphunk/Low/Shape.chs" #-}
shapeCacheBB :: (Shape)
-> IO ((BB))
shapeCacheBB a1 =
let {a1' = id a1} in
alloca $ \a2' ->
shapeCacheBB'_ a1' a2' >>
peek a2'>>= \a2'' ->
return (a2'')
{-# LINE 181 "src/Chiphunk/Low/Shape.chs" #-}
shapeUpdate :: (Shape)
-> (Transform) -> IO ((BB))
shapeUpdate a1 a2 =
let {a1' = id a1} in
with a2 $ \a2' ->
alloca $ \a3' ->
shapeUpdate'_ a1' a2' a3' >>
peek a3'>>= \a3'' ->
return (a3'')
{-# LINE 188 "src/Chiphunk/Low/Shape.chs" #-}
circleShapeNew :: (Body)
-> (Double)
-> (Vect)
-> IO ((Shape))
circleShapeNew :: Body -> Double -> Vect -> IO Shape
circleShapeNew Body
a1 Double
a2 Vect
a3 =
let {a1' :: Body
a1' = Body -> Body
forall a. a -> a
id Body
a1} in
let {a2' :: CDouble
a2' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
a2} in
Vect -> (Ptr Vect -> IO Shape) -> IO Shape
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Vect
a3 ((Ptr Vect -> IO Shape) -> IO Shape)
-> (Ptr Vect -> IO Shape) -> IO Shape
forall a b. (a -> b) -> a -> b
$ \Ptr Vect
a3' ->
Body -> CDouble -> Ptr Vect -> IO Shape
circleShapeNew'_ Body
a1' CDouble
a2' Ptr Vect
a3' IO Shape -> (Shape -> IO Shape) -> IO Shape
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Shape
res ->
let {res' :: Shape
res' = Shape -> Shape
forall a. a -> a
id Shape
res} in
Shape -> IO Shape
forall (m :: * -> *) a. Monad m => a -> m a
return (Shape
res')
{-# LINE 195 "src/Chiphunk/Low/Shape.chs" #-}
segmentShapeNew :: (Body)
-> (Vect)
-> (Vect)
-> (Double)
-> IO ((Shape))
segmentShapeNew a1 a2 a3 a4 =
let {a1' = id a1} in
with a2 $ \a2' ->
with a3 $ \a3' ->
let {a4' = realToFrac a4} in
segmentShapeNew'_ a1' a2' a3' a4' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 203 "src/Chiphunk/Low/Shape.chs" #-}
cpSegmentShapeSetNeighbors :: (Shape) -> (Vect) -> (Vect) -> IO ()
cpSegmentShapeSetNeighbors a1 a2 a3 =
let {a1' = id a1} in
with a2 $ \a2' ->
with a3 $ \a3' ->
cpSegmentShapeSetNeighbors'_ a1' a2' a3' >>
return ()
{-# LINE 205 "src/Chiphunk/Low/Shape.chs" #-}
segmentShapeNeighbors :: Shape -> SettableStateVar (Vect, Vect)
segmentShapeNeighbors shape =
makeSettableStateVar $ \(v1, v2) ->
cpSegmentShapeSetNeighbors shape v1 v2
polyShapeNew :: (Body)
-> ([Vect])
-> (Transform)
-> (Double)
-> IO ((Shape))
polyShapeNew :: Body -> [Vect] -> Transform -> Double -> IO Shape
polyShapeNew Body
a1 [Vect]
a2 Transform
a3 Double
a4 =
let {a1' :: Body
a1' = Body -> Body
forall a. a -> a
id Body
a1} in
[Vect] -> ((CInt, Ptr Vect) -> IO Shape) -> IO Shape
forall a b. Storable a => [a] -> ((CInt, Ptr a) -> IO b) -> IO b
withList [Vect]
a2 (((CInt, Ptr Vect) -> IO Shape) -> IO Shape)
-> ((CInt, Ptr Vect) -> IO Shape) -> IO Shape
forall a b. (a -> b) -> a -> b
$ \(CInt
a2'1, Ptr Vect
a2'2) ->
Transform -> (Ptr Transform -> IO Shape) -> IO Shape
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Transform
a3 ((Ptr Transform -> IO Shape) -> IO Shape)
-> (Ptr Transform -> IO Shape) -> IO Shape
forall a b. (a -> b) -> a -> b
$ \Ptr Transform
a3' ->
let {a4' :: CDouble
a4' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
a4} in
Body -> CInt -> Ptr Vect -> Ptr Transform -> CDouble -> IO Shape
polyShapeNew'_ Body
a1' CInt
a2'1 Ptr Vect
a2'2 Ptr Transform
a3' CDouble
a4' IO Shape -> (Shape -> IO Shape) -> IO Shape
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Shape
res ->
let {res' :: Shape
res' = Shape -> Shape
forall a. a -> a
id Shape
res} in
Shape -> IO Shape
forall (m :: * -> *) a. Monad m => a -> m a
return (Shape
res')
{-# LINE 223 "src/Chiphunk/Low/Shape.chs" #-}
polyShapeNewRaw :: (Body) -> ([Vect]) -> (Double) -> IO ((Shape))
polyShapeNewRaw a1 a2 a3 =
let {a1' = id a1} in
withList a2 $ \(a2'1, a2'2) ->
let {a3' = realToFrac a3} in
polyShapeNewRaw'_ a1' a2'1 a2'2 a3' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 227 "src/Chiphunk/Low/Shape.chs" #-}
boxShapeNew :: (Body)
-> (Double)
-> (Double)
-> (Double)
-> IO ((Shape))
boxShapeNew a1 a2 a3 a4 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
let {a3' = realToFrac a3} in
let {a4' = realToFrac a4} in
boxShapeNew'_ a1' a2' a3' a4' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 235 "src/Chiphunk/Low/Shape.chs" #-}
boxShapeNew2 :: (Body)
-> (BB)
-> (Double)
-> IO ((Shape))
boxShapeNew2 a1 a2 a3 =
let {a1' = id a1} in
with a2 $ \a2' ->
let {a3' = realToFrac a3} in
boxShapeNew2'_ a1' a2' a3' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 242 "src/Chiphunk/Low/Shape.chs" #-}
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeGetBody"
cpShapeGetBody'_ :: ((Shape) -> (IO (Body)))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeSetBody"
cpShapeSetBody'_ :: ((Shape) -> ((Body) -> (IO ())))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h w_cpShapeGetBB"
w_cpShapeGetBB'_ :: ((Shape) -> ((BBPtr) -> (IO ())))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeGetSensor"
cpShapeGetSensor'_ :: ((Shape) -> (IO C2HSImp.CUChar))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeSetSensor"
cpShapeSetSensor'_ :: ((Shape) -> (C2HSImp.CUChar -> (IO ())))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeGetElasticity"
cpShapeGetElasticity'_ :: ((Shape) -> (IO C2HSImp.CDouble))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeSetElasticity"
cpShapeSetElasticity'_ :: ((Shape) -> (C2HSImp.CDouble -> (IO ())))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeGetFriction"
cpShapeGetFriction'_ :: ((Shape) -> (IO C2HSImp.CDouble))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeSetFriction"
cpShapeSetFriction'_ :: ((Shape) -> (C2HSImp.CDouble -> (IO ())))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h w_cpShapeGetSurfaceVelocity"
w_cpShapeGetSurfaceVelocity'_ :: ((Shape) -> ((VectPtr) -> (IO ())))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h __c2hs_wrapped__cpShapeSetSurfaceVelocity"
cpShapeSetSurfaceVelocity'_ :: ((Shape) -> ((VectPtr) -> (IO ())))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeGetCollisionType"
cpShapeGetCollisionType'_ :: ((Shape) -> (IO C2HSImp.CULong))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeSetCollisionType"
cpShapeSetCollisionType'_ :: ((Shape) -> (C2HSImp.CULong -> (IO ())))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeGetMass"
cpShapeGetMass'_ :: ((Shape) -> (IO C2HSImp.CDouble))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeSetMass"
cpShapeSetMass'_ :: ((Shape) -> (C2HSImp.CDouble -> (IO ())))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeGetDensity"
cpShapeGetDensity'_ :: ((Shape) -> (IO C2HSImp.CDouble))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeSetDensity"
cpShapeSetDensity'_ :: ((Shape) -> (C2HSImp.CDouble -> (IO ())))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h w_cpShapeGetFilter"
w_cpShapeGetFilter'_ :: ((Shape) -> ((ShapeFilterPtr) -> (IO ())))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h __c2hs_wrapped__cpShapeSetFilter"
cpShapeSetFilter'_ :: ((Shape) -> ((ShapeFilterPtr) -> (IO ())))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeGetSpace"
cpShapeGetSpace'_ :: ((Shape) -> (IO (Space)))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeGetUserData"
cpShapeGetUserData'_ :: ((Shape) -> (IO (DataPtr)))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpShapeSetUserData"
cpShapeSetUserData'_ :: ((Shape) -> ((DataPtr) -> (IO ())))
foreign import ccall safe "Chiphunk/Low/Shape.chs.h cpShapeFree"
shapeFree'_ :: ((Shape) -> (IO ()))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h w_cpShapeCacheBB"
shapeCacheBB'_ :: ((Shape) -> ((BBPtr) -> (IO ())))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h __c2hs_wrapped__w_cpShapeUpdate"
shapeUpdate'_ :: ((Shape) -> ((TransformPtr) -> ((BBPtr) -> (IO ()))))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h __c2hs_wrapped__cpCircleShapeNew"
circleShapeNew'_ :: ((Body) -> (C2HSImp.CDouble -> ((VectPtr) -> (IO (Shape)))))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h __c2hs_wrapped__cpSegmentShapeNew"
segmentShapeNew'_ :: ((Body) -> ((VectPtr) -> ((VectPtr) -> (C2HSImp.CDouble -> (IO (Shape))))))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h __c2hs_wrapped__cpSegmentShapeSetNeighbors"
cpSegmentShapeSetNeighbors'_ :: ((Shape) -> ((VectPtr) -> ((VectPtr) -> (IO ()))))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h __c2hs_wrapped__cpPolyShapeNew"
polyShapeNew'_ :: ((Body) -> (C2HSImp.CInt -> ((VectPtr) -> ((TransformPtr) -> (C2HSImp.CDouble -> (IO (Shape)))))))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpPolyShapeNewRaw"
polyShapeNewRaw'_ :: ((Body) -> (C2HSImp.CInt -> ((VectPtr) -> (C2HSImp.CDouble -> (IO (Shape))))))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h cpBoxShapeNew"
boxShapeNew'_ :: ((Body) -> (C2HSImp.CDouble -> (C2HSImp.CDouble -> (C2HSImp.CDouble -> (IO (Shape))))))
foreign import ccall unsafe "Chiphunk/Low/Shape.chs.h __c2hs_wrapped__cpBoxShapeNew2"
boxShapeNew2'_ :: ((Body) -> ((BBPtr) -> (C2HSImp.CDouble -> (IO (Shape)))))