{-# LINE 1 "src/Chiphunk/Low/Types.chs" #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
module Chiphunk.Low.Types
( Vect (..)
, VectPtr
, BB (..)
, BBPtr
, DataPtr
, Body (..)
, BodyType (..)
, Space (..)
, Shape (..)
, Constraint (..)
, Arbiter (..)
, Transform (..)
, TransformPtr
, CollisionType
, CPBool
, mkStateVar
, Polyline(..)
, PolylinePtr
, PolylineSet(..)
, PolylineSetPtr
, withPolylinePtr
, peekPolylineSet
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp
import Data.Cross
import Data.Hashable
import Data.StateVar
import Data.VectorSpace
import Foreign
import GHC.Generics (Generic)
data Vect = Vect
{ Vect -> Double
vX :: !Double, Vect -> Double
vY :: !Double
} deriving (Vect -> Vect -> Bool
(Vect -> Vect -> Bool) -> (Vect -> Vect -> Bool) -> Eq Vect
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Vect -> Vect -> Bool
$c/= :: Vect -> Vect -> Bool
== :: Vect -> Vect -> Bool
$c== :: Vect -> Vect -> Bool
Eq, Int -> Vect -> ShowS
[Vect] -> ShowS
Vect -> String
(Int -> Vect -> ShowS)
-> (Vect -> String) -> ([Vect] -> ShowS) -> Show Vect
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Vect] -> ShowS
$cshowList :: [Vect] -> ShowS
show :: Vect -> String
$cshow :: Vect -> String
showsPrec :: Int -> Vect -> ShowS
$cshowsPrec :: Int -> Vect -> ShowS
Show, Eq Vect
Eq Vect
-> (Vect -> Vect -> Ordering)
-> (Vect -> Vect -> Bool)
-> (Vect -> Vect -> Bool)
-> (Vect -> Vect -> Bool)
-> (Vect -> Vect -> Bool)
-> (Vect -> Vect -> Vect)
-> (Vect -> Vect -> Vect)
-> Ord Vect
Vect -> Vect -> Bool
Vect -> Vect -> Ordering
Vect -> Vect -> Vect
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Vect -> Vect -> Vect
$cmin :: Vect -> Vect -> Vect
max :: Vect -> Vect -> Vect
$cmax :: Vect -> Vect -> Vect
>= :: Vect -> Vect -> Bool
$c>= :: Vect -> Vect -> Bool
> :: Vect -> Vect -> Bool
$c> :: Vect -> Vect -> Bool
<= :: Vect -> Vect -> Bool
$c<= :: Vect -> Vect -> Bool
< :: Vect -> Vect -> Bool
$c< :: Vect -> Vect -> Bool
compare :: Vect -> Vect -> Ordering
$ccompare :: Vect -> Vect -> Ordering
$cp1Ord :: Eq Vect
Ord, (forall x. Vect -> Rep Vect x)
-> (forall x. Rep Vect x -> Vect) -> Generic Vect
forall x. Rep Vect x -> Vect
forall x. Vect -> Rep Vect x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Vect x -> Vect
$cfrom :: forall x. Vect -> Rep Vect x
Generic)
instance Hashable Vect
instance AdditiveGroup Vect where
zeroV :: Vect
zeroV = Double -> Double -> Vect
Vect Double
0 Double
0
negateV :: Vect -> Vect
negateV (Vect Double
x Double
y) = Double -> Double -> Vect
Vect (-Double
x) (-Double
y)
Vect Double
x1 Double
y1 ^+^ :: Vect -> Vect -> Vect
^+^ Vect Double
x2 Double
y2 = Double -> Double -> Vect
Vect (Double
x1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
x2) (Double
y1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
y2)
Vect Double
x1 Double
y1 ^-^ :: Vect -> Vect -> Vect
^-^ Vect Double
x2 Double
y2 = Double -> Double -> Vect
Vect (Double
x1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
x2) (Double
y1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
y2)
instance VectorSpace Vect where
type Scalar Vect = Double
Scalar Vect
f *^ :: Scalar Vect -> Vect -> Vect
*^ Vect Double
x Double
y = Double -> Double -> Vect
Vect (Double
Scalar Vect
f Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
x) (Double
Scalar Vect
f Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
y)
instance InnerSpace Vect where
Vect Double
x1 Double
y1 <.> :: Vect -> Vect -> Scalar Vect
<.> Vect Double
x2 Double
y2 = Double
x1 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
x2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
y1 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
y2
instance HasCross2 Vect where
cross2 (Vect x y) = Vect (-y) x
instance Storable Vect where
sizeOf :: Vect -> Int
sizeOf Vect
_ = Int
16
{-# LINE 65 "src/Chiphunk/Low/Types.chs" #-}
alignment _ = 8
{-# LINE 66 "src/Chiphunk/Low/Types.chs" #-}
poke p (Vect x y) = do
(\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: C2HSImp.CDouble)}) p $ realToFrac x
(\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CDouble)}) p $ realToFrac y
peek p = Vect <$> (realToFrac <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CDouble}) p)
<*> (realToFrac <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CDouble}) p)
type VectPtr = C2HSImp.Ptr (Vect)
{-# LINE 74 "src/Chiphunk/Low/Types.chs" #-}
data BB = BB
{ BB -> Double
bbL :: !Double, BB -> Double
bbB :: !Double, BB -> Double
bbR :: !Double, BB -> Double
bbT :: !Double
} deriving (Int -> BB -> ShowS
[BB] -> ShowS
BB -> String
(Int -> BB -> ShowS)
-> (BB -> String) -> ([BB] -> ShowS) -> Show BB
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BB] -> ShowS
$cshowList :: [BB] -> ShowS
show :: BB -> String
$cshow :: BB -> String
showsPrec :: Int -> BB -> ShowS
$cshowsPrec :: Int -> BB -> ShowS
Show, BB -> BB -> Bool
(BB -> BB -> Bool) -> (BB -> BB -> Bool) -> Eq BB
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BB -> BB -> Bool
$c/= :: BB -> BB -> Bool
== :: BB -> BB -> Bool
$c== :: BB -> BB -> Bool
Eq, Eq BB
Eq BB
-> (BB -> BB -> Ordering)
-> (BB -> BB -> Bool)
-> (BB -> BB -> Bool)
-> (BB -> BB -> Bool)
-> (BB -> BB -> Bool)
-> (BB -> BB -> BB)
-> (BB -> BB -> BB)
-> Ord BB
BB -> BB -> Bool
BB -> BB -> Ordering
BB -> BB -> BB
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BB -> BB -> BB
$cmin :: BB -> BB -> BB
max :: BB -> BB -> BB
$cmax :: BB -> BB -> BB
>= :: BB -> BB -> Bool
$c>= :: BB -> BB -> Bool
> :: BB -> BB -> Bool
$c> :: BB -> BB -> Bool
<= :: BB -> BB -> Bool
$c<= :: BB -> BB -> Bool
< :: BB -> BB -> Bool
$c< :: BB -> BB -> Bool
compare :: BB -> BB -> Ordering
$ccompare :: BB -> BB -> Ordering
$cp1Ord :: Eq BB
Ord, (forall x. BB -> Rep BB x)
-> (forall x. Rep BB x -> BB) -> Generic BB
forall x. Rep BB x -> BB
forall x. BB -> Rep BB x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BB x -> BB
$cfrom :: forall x. BB -> Rep BB x
Generic)
instance Hashable BB
instance Storable BB where
sizeOf :: BB -> Int
sizeOf BB
_ = Int
32
{-# LINE 84 "src/Chiphunk/Low/Types.chs" #-}
alignment _ = 8
{-# LINE 85 "src/Chiphunk/Low/Types.chs" #-}
poke p (BB l b r t) = do
(\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: C2HSImp.CDouble)}) p $ realToFrac l
(\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CDouble)}) p $ realToFrac b
(\ptr val -> do {C2HSImp.pokeByteOff ptr 16 (val :: C2HSImp.CDouble)}) p $ realToFrac r
(\ptr val -> do {C2HSImp.pokeByteOff ptr 24 (val :: C2HSImp.CDouble)}) p $ realToFrac t
peek :: Ptr BB -> IO BB
peek Ptr BB
p = Double -> Double -> Double -> Double -> BB
BB (Double -> Double -> Double -> Double -> BB)
-> IO Double -> IO (Double -> Double -> Double -> BB)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CDouble -> Double) -> IO CDouble -> IO Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr BB
ptr -> do {Ptr BB -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr BB
ptr Int
0 :: IO C2HSImp.CDouble}) Ptr BB
p)
IO (Double -> Double -> Double -> BB)
-> IO Double -> IO (Double -> Double -> BB)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CDouble -> Double) -> IO CDouble -> IO Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr BB
ptr -> do {Ptr BB -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr BB
ptr Int
8 :: IO C2HSImp.CDouble}) Ptr BB
p)
IO (Double -> Double -> BB) -> IO Double -> IO (Double -> BB)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CDouble -> Double) -> IO CDouble -> IO Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr BB
ptr -> do {Ptr BB -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr BB
ptr Int
16 :: IO C2HSImp.CDouble}) Ptr BB
p)
IO (Double -> BB) -> IO Double -> IO BB
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CDouble -> Double) -> IO CDouble -> IO Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr BB
ptr -> do {Ptr BB -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr BB
ptr Int
24 :: IO C2HSImp.CDouble}) Ptr BB
p)
type BBPtr = C2HSImp.Ptr (BB)
{-# LINE 97 "src/Chiphunk/Low/Types.chs" #-}
type DataPtr = C2HSImp.Ptr (())
{-# LINE 100 "src/Chiphunk/Low/Types.chs" #-}
newtype Body = Body (C2HSImp.Ptr (Body))
{-# LINE 103 "src/Chiphunk/Low/Types.chs" #-}
deriving (Eq, Ord, Generic)
instance Hashable Body
instance Storable Body where
sizeOf :: Body -> Int
sizeOf (Body Ptr Body
p) = Ptr Body -> Int
forall a. Storable a => a -> Int
sizeOf Ptr Body
p
alignment :: Body -> Int
alignment (Body Ptr Body
p) = Ptr Body -> Int
forall a. Storable a => a -> Int
alignment Ptr Body
p
poke :: Ptr Body -> Body -> IO ()
poke Ptr Body
p (Body Ptr Body
b) = Ptr (Ptr Body) -> Ptr Body -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Body -> Ptr (Ptr Body)
forall a b. Ptr a -> Ptr b
castPtr Ptr Body
p) Ptr Body
b
peek :: Ptr Body -> IO Body
peek Ptr Body
p = Ptr Body -> Body
Body (Ptr Body -> Body) -> IO (Ptr Body) -> IO Body
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr (Ptr Body) -> IO (Ptr Body)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Body -> Ptr (Ptr Body)
forall a b. Ptr a -> Ptr b
castPtr Ptr Body
p)
data BodyType =
BodyTypeDynamic
| BodyTypeKimenatic
| BodyTypeStatic
deriving (Int -> BodyType
BodyType -> Int
BodyType -> [BodyType]
BodyType -> BodyType
BodyType -> BodyType -> [BodyType]
BodyType -> BodyType -> BodyType -> [BodyType]
(BodyType -> BodyType)
-> (BodyType -> BodyType)
-> (Int -> BodyType)
-> (BodyType -> Int)
-> (BodyType -> [BodyType])
-> (BodyType -> BodyType -> [BodyType])
-> (BodyType -> BodyType -> [BodyType])
-> (BodyType -> BodyType -> BodyType -> [BodyType])
-> Enum BodyType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: BodyType -> BodyType -> BodyType -> [BodyType]
$cenumFromThenTo :: BodyType -> BodyType -> BodyType -> [BodyType]
enumFromTo :: BodyType -> BodyType -> [BodyType]
$cenumFromTo :: BodyType -> BodyType -> [BodyType]
enumFromThen :: BodyType -> BodyType -> [BodyType]
$cenumFromThen :: BodyType -> BodyType -> [BodyType]
enumFrom :: BodyType -> [BodyType]
$cenumFrom :: BodyType -> [BodyType]
fromEnum :: BodyType -> Int
$cfromEnum :: BodyType -> Int
toEnum :: Int -> BodyType
$ctoEnum :: Int -> BodyType
pred :: BodyType -> BodyType
$cpred :: BodyType -> BodyType
succ :: BodyType -> BodyType
$csucc :: BodyType -> BodyType
Enum)
{-# LINE 146 "src/Chiphunk/Low/Types.chs" #-}
deriving instance Show BodyType
newtype Space = Space (C2HSImp.Ptr (Space))
{-# LINE 152 "src/Chiphunk/Low/Types.chs" #-}
deriving (Eq, Ord, Generic)
instance Hashable Space
instance Storable Space where
sizeOf :: Space -> Int
sizeOf (Space Ptr Space
p) = Ptr Space -> Int
forall a. Storable a => a -> Int
sizeOf Ptr Space
p
alignment :: Space -> Int
alignment (Space Ptr Space
p) = Ptr Space -> Int
forall a. Storable a => a -> Int
alignment Ptr Space
p
poke :: Ptr Space -> Space -> IO ()
poke Ptr Space
p (Space Ptr Space
b) = Ptr (Ptr Space) -> Ptr Space -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Space -> Ptr (Ptr Space)
forall a b. Ptr a -> Ptr b
castPtr Ptr Space
p) Ptr Space
b
peek :: Ptr Space -> IO Space
peek Ptr Space
p = Ptr Space -> Space
Space (Ptr Space -> Space) -> IO (Ptr Space) -> IO Space
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr (Ptr Space) -> IO (Ptr Space)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Space -> Ptr (Ptr Space)
forall a b. Ptr a -> Ptr b
castPtr Ptr Space
p)
newtype Shape = Shape (C2HSImp.Ptr (Shape))
{-# LINE 175 "src/Chiphunk/Low/Types.chs" #-}
deriving (Eq, Ord, Generic)
instance Hashable Shape
instance Storable Shape where
sizeOf :: Shape -> Int
sizeOf (Shape Ptr Shape
p) = Ptr Shape -> Int
forall a. Storable a => a -> Int
sizeOf Ptr Shape
p
alignment :: Shape -> Int
alignment (Shape Ptr Shape
p) = Ptr Shape -> Int
forall a. Storable a => a -> Int
alignment Ptr Shape
p
poke :: Ptr Shape -> Shape -> IO ()
poke Ptr Shape
p (Shape Ptr Shape
b) = Ptr (Ptr Shape) -> Ptr Shape -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Shape -> Ptr (Ptr Shape)
forall a b. Ptr a -> Ptr b
castPtr Ptr Shape
p) Ptr Shape
b
peek :: Ptr Shape -> IO Shape
peek Ptr Shape
p = Ptr Shape -> Shape
Shape (Ptr Shape -> Shape) -> IO (Ptr Shape) -> IO Shape
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr (Ptr Shape) -> IO (Ptr Shape)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Shape -> Ptr (Ptr Shape)
forall a b. Ptr a -> Ptr b
castPtr Ptr Shape
p)
newtype Constraint = Constraint (C2HSImp.Ptr (Constraint))
{-# LINE 189 "src/Chiphunk/Low/Types.chs" #-}
deriving (Eq, Ord, Generic)
instance Hashable Constraint
instance Storable Constraint where
sizeOf :: Constraint -> Int
sizeOf (Constraint Ptr Constraint
p) = Ptr Constraint -> Int
forall a. Storable a => a -> Int
sizeOf Ptr Constraint
p
alignment :: Constraint -> Int
alignment (Constraint Ptr Constraint
p) = Ptr Constraint -> Int
forall a. Storable a => a -> Int
alignment Ptr Constraint
p
poke :: Ptr Constraint -> Constraint -> IO ()
poke Ptr Constraint
p (Constraint Ptr Constraint
b) = Ptr (Ptr Constraint) -> Ptr Constraint -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Constraint -> Ptr (Ptr Constraint)
forall a b. Ptr a -> Ptr b
castPtr Ptr Constraint
p) Ptr Constraint
b
peek :: Ptr Constraint -> IO Constraint
peek Ptr Constraint
p = Ptr Constraint -> Constraint
Constraint (Ptr Constraint -> Constraint)
-> IO (Ptr Constraint) -> IO Constraint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr (Ptr Constraint) -> IO (Ptr Constraint)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Constraint -> Ptr (Ptr Constraint)
forall a b. Ptr a -> Ptr b
castPtr Ptr Constraint
p)
newtype Arbiter = Arbiter (C2HSImp.Ptr (Arbiter))
{-# LINE 209 "src/Chiphunk/Low/Types.chs" #-}
deriving (Eq, Ord, Generic)
instance Hashable Arbiter
instance Storable Arbiter where
sizeOf :: Arbiter -> Int
sizeOf (Arbiter Ptr Arbiter
p) = Ptr Arbiter -> Int
forall a. Storable a => a -> Int
sizeOf Ptr Arbiter
p
alignment :: Arbiter -> Int
alignment (Arbiter Ptr Arbiter
p) = Ptr Arbiter -> Int
forall a. Storable a => a -> Int
alignment Ptr Arbiter
p
poke :: Ptr Arbiter -> Arbiter -> IO ()
poke Ptr Arbiter
p (Arbiter Ptr Arbiter
b) = Ptr (Ptr Arbiter) -> Ptr Arbiter -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Arbiter -> Ptr (Ptr Arbiter)
forall a b. Ptr a -> Ptr b
castPtr Ptr Arbiter
p) Ptr Arbiter
b
peek :: Ptr Arbiter -> IO Arbiter
peek Ptr Arbiter
p = Ptr Arbiter -> Arbiter
Arbiter (Ptr Arbiter -> Arbiter) -> IO (Ptr Arbiter) -> IO Arbiter
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr (Ptr Arbiter) -> IO (Ptr Arbiter)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Arbiter -> Ptr (Ptr Arbiter)
forall a b. Ptr a -> Ptr b
castPtr Ptr Arbiter
p)
data Transform = Transform
{ Transform -> Double
tA :: !Double, Transform -> Double
tB :: !Double, Transform -> Double
tC :: !Double, Transform -> Double
tD :: !Double, Transform -> Double
tTx :: !Double, Transform -> Double
tTy :: !Double
} deriving (Int -> Transform -> ShowS
[Transform] -> ShowS
Transform -> String
(Int -> Transform -> ShowS)
-> (Transform -> String)
-> ([Transform] -> ShowS)
-> Show Transform
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Transform] -> ShowS
$cshowList :: [Transform] -> ShowS
show :: Transform -> String
$cshow :: Transform -> String
showsPrec :: Int -> Transform -> ShowS
$cshowsPrec :: Int -> Transform -> ShowS
Show, Transform -> Transform -> Bool
(Transform -> Transform -> Bool)
-> (Transform -> Transform -> Bool) -> Eq Transform
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Transform -> Transform -> Bool
$c/= :: Transform -> Transform -> Bool
== :: Transform -> Transform -> Bool
$c== :: Transform -> Transform -> Bool
Eq)
instance Storable Transform where
sizeOf :: Transform -> Int
sizeOf Transform
_ = Int
48
{-# LINE 226 "src/Chiphunk/Low/Types.chs" #-}
alignment _ = 8
{-# LINE 227 "src/Chiphunk/Low/Types.chs" #-}
poke p (Transform a b c d tx ty) = do
(\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: C2HSImp.CDouble)}) p $ realToFrac a
(\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CDouble)}) p $ realToFrac b
(\ptr val -> do {C2HSImp.pokeByteOff ptr 16 (val :: C2HSImp.CDouble)}) p $ realToFrac c
(\ptr val -> do {C2HSImp.pokeByteOff ptr 24 (val :: C2HSImp.CDouble)}) p $ realToFrac d
(\ptr val -> do {C2HSImp.pokeByteOff ptr 32 (val :: C2HSImp.CDouble)}) p $ realToFrac tx
(\ptr val -> do {C2HSImp.pokeByteOff ptr 40 (val :: C2HSImp.CDouble)}) p $ realToFrac ty
peek :: Ptr Transform -> IO Transform
peek Ptr Transform
p = Double
-> Double -> Double -> Double -> Double -> Double -> Transform
Transform (Double
-> Double -> Double -> Double -> Double -> Double -> Transform)
-> IO Double
-> IO (Double -> Double -> Double -> Double -> Double -> Transform)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CDouble -> Double) -> IO CDouble -> IO Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr Transform
ptr -> do {Ptr Transform -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Transform
ptr Int
0 :: IO C2HSImp.CDouble}) Ptr Transform
p)
IO (Double -> Double -> Double -> Double -> Double -> Transform)
-> IO Double
-> IO (Double -> Double -> Double -> Double -> Transform)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CDouble -> Double) -> IO CDouble -> IO Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr Transform
ptr -> do {Ptr Transform -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Transform
ptr Int
8 :: IO C2HSImp.CDouble}) Ptr Transform
p)
IO (Double -> Double -> Double -> Double -> Transform)
-> IO Double -> IO (Double -> Double -> Double -> Transform)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CDouble -> Double) -> IO CDouble -> IO Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr Transform
ptr -> do {Ptr Transform -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Transform
ptr Int
16 :: IO C2HSImp.CDouble}) Ptr Transform
p)
IO (Double -> Double -> Double -> Transform)
-> IO Double -> IO (Double -> Double -> Transform)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CDouble -> Double) -> IO CDouble -> IO Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr Transform
ptr -> do {Ptr Transform -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Transform
ptr Int
24 :: IO C2HSImp.CDouble}) Ptr Transform
p)
IO (Double -> Double -> Transform)
-> IO Double -> IO (Double -> Transform)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CDouble -> Double) -> IO CDouble -> IO Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr Transform
ptr -> do {Ptr Transform -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Transform
ptr Int
32 :: IO C2HSImp.CDouble}) Ptr Transform
p)
IO (Double -> Transform) -> IO Double -> IO Transform
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CDouble -> Double) -> IO CDouble -> IO Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr Transform
ptr -> do {Ptr Transform -> Int -> IO CDouble
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Transform
ptr Int
40 :: IO C2HSImp.CDouble}) Ptr Transform
p)
type TransformPtr = C2HSImp.Ptr (Transform)
{-# LINE 243 "src/Chiphunk/Low/Types.chs" #-}
type CollisionType = WordPtr
type CPBool = (C2HSImp.CUChar)
{-# LINE 248 "src/Chiphunk/Low/Types.chs" #-}
mkStateVar :: (a -> IO b) -> (a -> b -> IO ()) -> a -> StateVar b
mkStateVar :: (a -> IO b) -> (a -> b -> IO ()) -> a -> StateVar b
mkStateVar a -> IO b
g a -> b -> IO ()
s a
i = IO b -> (b -> IO ()) -> StateVar b
forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar (a -> IO b
g a
i) (a -> b -> IO ()
s a
i)
type PolylinePtr = C2HSImp.Ptr (Polyline)
{-# LINE 254 "src/Chiphunk/Low/Types.chs" #-}
newtype Polyline = Polyline { unPolyline :: [Vect] }
foreign import ccall w_cpPolylineVerts :: Ptr Polyline -> Ptr Vect
withPolylinePtr :: Polyline -> (Ptr Polyline -> IO a) -> IO a
withPolylinePtr :: Polyline -> (Ptr Polyline -> IO a) -> IO a
withPolylinePtr (Polyline [Vect]
verts) Ptr Polyline -> IO a
fn = do
Int -> (Ptr Polyline -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Vect -> Int
forall a. Storable a => a -> Int
sizeOf (Vect
forall a. HasCallStack => a
undefined :: Vect) Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
countInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
10)) ((Ptr Polyline -> IO a) -> IO a) -> (Ptr Polyline -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr Polyline
p -> do
(\Ptr Polyline
ptr CInt
val -> do {Ptr Polyline -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr Polyline
ptr Int
0 (CInt
val :: C2HSImp.CInt)}) Ptr Polyline
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
count
(\Ptr Polyline
ptr CInt
val -> do {Ptr Polyline -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr Polyline
ptr Int
4 (CInt
val :: C2HSImp.CInt)}) Ptr Polyline
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
count
let vp :: Ptr Vect
vp = Ptr Polyline -> Int -> Ptr Vect
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Polyline
p (Int
8)
{-# LINE 265 "src/Chiphunk/Low/Types.chs" #-}
pokeArray vp verts
Ptr Polyline -> IO a
fn Ptr Polyline
p
where
count :: Int
count = [Vect] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Vect]
verts
peekPolyline :: Ptr Polyline -> IO Polyline
peekPolyline :: Ptr Polyline -> IO Polyline
peekPolyline Ptr Polyline
p = do
Int
count <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr Polyline
ptr -> do {Ptr Polyline -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr Polyline
ptr Int
0 :: IO C2HSImp.CInt}) Ptr Polyline
p
let vp :: Ptr Vect
vp = Ptr Polyline -> Ptr Vect
w_cpPolylineVerts Ptr Polyline
p
[Vect] -> Polyline
Polyline ([Vect] -> Polyline) -> IO [Vect] -> IO Polyline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Ptr Vect -> IO [Vect]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
count Ptr Vect
vp
type PolylineSetPtr = C2HSImp.Ptr (PolylineSet)
{-# LINE 277 "src/Chiphunk/Low/Types.chs" #-}
data PolylineSet = PolylineSet { PolylineSet -> [Polyline]
unPolylineSet :: [Polyline] }
peekPolylineSet :: Ptr PolylineSet -> IO PolylineSet
peekPolylineSet :: Ptr PolylineSet -> IO PolylineSet
peekPolylineSet Ptr PolylineSet
p = do
Int
count <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr PolylineSet
ptr -> do {Ptr PolylineSet -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr PolylineSet
ptr Int
0 :: IO C2HSImp.CInt}) Ptr PolylineSet
p
Ptr (Ptr Polyline)
lp <- (\Ptr PolylineSet
ptr -> do {Ptr PolylineSet -> Int -> IO (Ptr (Ptr Polyline))
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr PolylineSet
ptr Int
8 :: IO (C2HSImp.Ptr (PolylinePtr))}) Ptr PolylineSet
p
[Polyline] -> PolylineSet
PolylineSet ([Polyline] -> PolylineSet) -> IO [Polyline] -> IO PolylineSet
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Ptr Polyline -> IO Polyline) -> [Ptr Polyline] -> IO [Polyline]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Ptr Polyline -> IO Polyline
peekPolyline ([Ptr Polyline] -> IO [Polyline])
-> IO [Ptr Polyline] -> IO [Polyline]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Int -> Ptr (Ptr Polyline) -> IO [Ptr Polyline]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
count Ptr (Ptr Polyline)
lp)