module Graphics.UI.SDL.Rect where
import Foreign (Storable(poke, sizeOf, alignment, peekByteOff, pokeByteOff,
                         peek))
import Data.Word (Word16)
import Data.Int (Int16)
data Rect
    = Rect
    { rectX, rectY :: Int,  
      rectW, rectH :: Int } 
    deriving (Show,Eq,Ord)
instance Storable Rect where
    sizeOf = const (8)
    alignment = const 2
    peek ptr
        = do x <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr :: IO Int16
             y <- (\hsc_ptr -> peekByteOff hsc_ptr 2) ptr :: IO Int16
             w <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr :: IO Word16
             h <- (\hsc_ptr -> peekByteOff hsc_ptr 6) ptr :: IO Word16
             return $! Rect (fromIntegral x) (fromIntegral y) (fromIntegral w) (fromIntegral h)
    poke ptr (Rect x y w h)
        = do (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr (fromIntegral x :: Int16)
             (\hsc_ptr -> pokeByteOff hsc_ptr 2) ptr (fromIntegral y :: Int16)
             (\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr (fromIntegral w :: Word16)
             (\hsc_ptr -> pokeByteOff hsc_ptr 6) ptr (fromIntegral h :: Word16)