module Graphics.Gloss.Internals.Render.Bitmap
( BitmapData(..)
, reverseRGBA
, bitmapPath
, freeBitmapData
)
where
import Foreign
data BitmapData
= BitmapData
Int
(ForeignPtr Word8)
deriving (Eq)
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
reverseRGBA :: BitmapData -> IO ()
reverseRGBA (BitmapData length8 fptr)
= withForeignPtr fptr (reverseRGBA_ptr length8)
reverseRGBA_ptr :: Int -> Ptr Word8 -> IO ()
reverseRGBA_ptr length8 ptr8
= go (length8 `div` 4) (castPtr ptr8) 0
where
go :: Int -> Ptr Word32 -> Int -> IO ()
go len ptr count
| count < len
= do curr <- peekElemOff ptr count
let byte0 = shift (isolateByte0 curr) 24
let byte1 = shift (isolateByte1 curr) 8
let byte2 = shift (isolateByte2 curr) (8)
let byte3 = shift (isolateByte3 curr) (24)
pokeElemOff ptr count (byte0 .|. byte1 .|. byte2 .|. byte3)
go len ptr (count + 1)
| otherwise
= return ()
freeBitmapData :: Ptr Word8 -> IO ()
freeBitmapData p = free p
isolateByte0 :: Word32 -> Word32
isolateByte0 word =
word .&. (255 :: Word32)
isolateByte1 :: Word32 -> Word32
isolateByte1 word =
word .&. (65280 :: Word32)
isolateByte2 :: Word32 -> Word32
isolateByte2 word =
word .&. (16711680 :: Word32)
isolateByte3 :: Word32 -> Word32
isolateByte3 word =
word .&. (4278190080 :: Word32)