{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# OPTIONS_HADDOCK hide #-}
module Graphics.Gloss.Internals.Data.Picture
( Point
, Vector
, Path
, Picture(..)
, Rectangle(..)
, BitmapData, PixelFormat(..), BitmapFormat(..), RowOrder(..)
, bitmapSize
, bitmapOfForeignPtr
, bitmapDataOfForeignPtr
, bitmapOfByteString
, bitmapDataOfByteString
, bitmapOfBMP
, bitmapDataOfBMP
, loadBMP
, rectAtOrigin )
where
import Graphics.Gloss.Internals.Data.Color
import Graphics.Gloss.Internals.Rendering.Bitmap
import Codec.BMP
import Foreign.ForeignPtr
import Foreign.Marshal.Alloc
import Foreign.Marshal.Utils
import Foreign.Ptr
import Data.Word
import Data.Monoid
import Data.ByteString
import Data.Data
import System.IO.Unsafe
import qualified Data.ByteString.Unsafe as BSU
import Prelude hiding (map)
#if __GLASGOW_HASKELL__ >= 800
import Data.Semigroup
import Data.List.NonEmpty
#endif
type Point = (Float, Float)
type Vector = Point
type Path = [Point]
data Picture
= Blank
| Polygon Path
| Line Path
| Circle Float
| ThickCircle Float Float
| Arc Float Float Float
| ThickArc Float Float Float Float
| Text String
| Bitmap BitmapData
| BitmapSection Rectangle BitmapData
| Color Color Picture
| Translate Float Float Picture
| Rotate Float Picture
| Scale Float Float Picture
| Pictures [Picture]
deriving (Show, Eq, Data, Typeable)
instance Monoid Picture where
mempty = Blank
mappend a b = Pictures [a, b]
mconcat = Pictures
#if __GLASGOW_HASKELL__ >= 800
instance Semigroup Picture where
a <> b = Pictures [a, b]
sconcat = Pictures . toList
stimes = stimesIdempotent
#endif
bitmapOfForeignPtr :: Int -> Int -> BitmapFormat -> ForeignPtr Word8 -> Bool -> Picture
bitmapOfForeignPtr width height fmt fptr cacheMe =
Bitmap $
bitmapDataOfForeignPtr width height fmt fptr cacheMe
bitmapDataOfForeignPtr :: Int -> Int -> BitmapFormat -> ForeignPtr Word8 -> Bool -> BitmapData
bitmapDataOfForeignPtr width height fmt fptr cacheMe
= let len = width * height * 4
in BitmapData len fmt (width,height) cacheMe fptr
bitmapOfByteString :: Int -> Int -> BitmapFormat -> ByteString -> Bool -> Picture
bitmapOfByteString width height fmt bs cacheMe =
Bitmap $
bitmapDataOfByteString width height fmt bs cacheMe
bitmapDataOfByteString :: Int -> Int -> BitmapFormat -> ByteString -> Bool -> BitmapData
bitmapDataOfByteString width height fmt bs cacheMe
= unsafePerformIO
$ do let len = width * height * 4
ptr <- mallocBytes len
fptr <- newForeignPtr finalizerFree ptr
BSU.unsafeUseAsCString bs
$ \cstr -> copyBytes ptr (castPtr cstr) len
return $ BitmapData len fmt (width, height) cacheMe fptr
{-# NOINLINE bitmapDataOfByteString #-}
bitmapOfBMP :: BMP -> Picture
bitmapOfBMP bmp
= Bitmap $ bitmapDataOfBMP bmp
bitmapDataOfBMP :: BMP -> BitmapData
bitmapDataOfBMP bmp
= unsafePerformIO
$ do let (width, height) = bmpDimensions bmp
let bs = unpackBMPToRGBA32 bmp
let len = width * height * 4
ptr <- mallocBytes len
fptr <- newForeignPtr finalizerFree ptr
BSU.unsafeUseAsCString bs
$ \cstr -> copyBytes ptr (castPtr cstr) len
return $ BitmapData len (BitmapFormat BottomToTop PxRGBA) (width,height) True fptr
{-# NOINLINE bitmapDataOfBMP #-}
loadBMP :: FilePath -> IO Picture
loadBMP filePath
= do ebmp <- readBMP filePath
case ebmp of
Left err -> error $ show err
Right bmp -> return $ bitmapOfBMP bmp
rectAtOrigin :: Int -> Int -> Rectangle
rectAtOrigin w h = Rectangle (0,0) (w,h)