gloss-1.12.0.0: Painless 2D vector graphics, animations and simulations.

Safe HaskellNone
LanguageHaskell98

Graphics.Gloss.Data.Bitmap

Description

Functions to load bitmap data from various places.

Synopsis

Documentation

data BitmapData :: * #

Abstract 32-bit RGBA bitmap data.

Instances

Eq BitmapData 
Data BitmapData 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BitmapData -> c BitmapData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BitmapData #

toConstr :: BitmapData -> Constr #

dataTypeOf :: BitmapData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BitmapData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BitmapData) #

gmapT :: (forall b. Data b => b -> b) -> BitmapData -> BitmapData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BitmapData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BitmapData -> r #

gmapQ :: (forall d. Data d => d -> u) -> BitmapData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BitmapData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BitmapData -> m BitmapData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BitmapData -> m BitmapData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BitmapData -> m BitmapData #

Show BitmapData 

data BitmapFormat :: * #

Description of how the bitmap is layed out in memory.

  • Prior version of Gloss assumed `BitmapFormat BottomToTop PxAGBR`

Instances

Eq BitmapFormat 
Data BitmapFormat 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BitmapFormat -> c BitmapFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BitmapFormat #

toConstr :: BitmapFormat -> Constr #

dataTypeOf :: BitmapFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BitmapFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BitmapFormat) #

gmapT :: (forall b. Data b => b -> b) -> BitmapFormat -> BitmapFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BitmapFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BitmapFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> BitmapFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BitmapFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BitmapFormat -> m BitmapFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BitmapFormat -> m BitmapFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BitmapFormat -> m BitmapFormat #

Ord BitmapFormat 
Show BitmapFormat 

data RowOrder :: * #

Order of rows in an image are either:

  • TopToBottom - the top row, followed by the next-lower row and so on.
  • BottomToTop - the bottom row followed by the next-higher row and so on.

Constructors

TopToBottom 
BottomToTop 

Instances

Bounded RowOrder 
Enum RowOrder 
Eq RowOrder 
Data RowOrder 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RowOrder -> c RowOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RowOrder #

toConstr :: RowOrder -> Constr #

dataTypeOf :: RowOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RowOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowOrder) #

gmapT :: (forall b. Data b => b -> b) -> RowOrder -> RowOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RowOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RowOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> RowOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RowOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RowOrder -> m RowOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RowOrder -> m RowOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RowOrder -> m RowOrder #

Ord RowOrder 
Show RowOrder 

data PixelFormat :: * #

Pixel formats describe the order of the color channels in memory.

Constructors

PxRGBA 
PxABGR 

Instances

Bounded PixelFormat 
Enum PixelFormat 
Eq PixelFormat 
Data PixelFormat 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PixelFormat -> c PixelFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PixelFormat #

toConstr :: PixelFormat -> Constr #

dataTypeOf :: PixelFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PixelFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PixelFormat) #

gmapT :: (forall b. Data b => b -> b) -> PixelFormat -> PixelFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PixelFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PixelFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> PixelFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PixelFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PixelFormat -> m PixelFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PixelFormat -> m PixelFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PixelFormat -> m PixelFormat #

Ord PixelFormat 
Show PixelFormat 

bitmapOfForeignPtr :: Int -> Int -> BitmapFormat -> ForeignPtr Word8 -> Bool -> Picture #

O(1). Use a ForeignPtr of RGBA data as a bitmap with the given width and height.

The boolean flag controls whether Gloss should cache the data between frames for speed. If you are programatically generating the image for each frame then use False. If you have loaded it from a file then use True.

bitmapOfByteString :: Int -> Int -> BitmapFormat -> ByteString -> Bool -> Picture #

O(size). Copy a ByteString of RGBA data into a bitmap with the given width and height.

The boolean flag controls whether Gloss should cache the data between frames for speed. If you are programatically generating the image for each frame then use False. If you have loaded it from a file then use True.

bitmapOfBMP :: BMP -> Picture #

O(size). Copy a BMP file into a bitmap.

loadBMP :: FilePath -> IO Picture #

Load an uncompressed 24 or 32bit RGBA BMP file as a bitmap.