module Graphics.Gloss.Internals.Rendering.Bitmap
        ( BitmapData(..)
        , BitmapFormat(..), PixelFormat(..), RowOrder(..)
        , bitmapPath
        , freeBitmapData)
where
import Data.Data
import Foreign
data BitmapData
        = BitmapData
        { bitmapDataLength :: Int  
        , bitmapFormat     :: BitmapFormat
        , bitmapPointer    :: (ForeignPtr Word8) } 
        deriving (Eq, Data, Typeable)
data BitmapFormat
        = BitmapFormat 
        { rowOrder    :: RowOrder
        , pixelFormat :: PixelFormat }
        deriving (Eq, Data, Typeable, Show, Ord)
data RowOrder
        = TopToBottom 
        | BottomToTop
        deriving (Eq, Data, Typeable, Show, Ord, Enum, Bounded)
data PixelFormat
        = PxRGBA | PxABGR
        deriving (Eq, Data, Typeable, Show, Ord, Enum, Bounded)
instance Show BitmapData where
 show _ = "BitmapData"
bitmapPath :: Float -> Float -> [(Float, Float)]
bitmapPath width height
 = [(width', height'), (width', height'), (width', height'), (width', height')]
 where  width'  = width  / 2
        height' = height / 2
freeBitmapData :: Ptr Word8 -> IO ()
freeBitmapData p = free p