gloss-1.13.0.1: 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 Rectangle #

Represents a rectangular section in a bitmap

Constructors

Rectangle 

Fields

Instances
Eq Rectangle 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Data Rectangle 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Methods

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

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

toConstr :: Rectangle -> Constr #

dataTypeOf :: Rectangle -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Rectangle 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Read Rectangle 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Show Rectangle 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

data BitmapData #

Abstract 32-bit RGBA bitmap data.

Instances
Eq BitmapData 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Data BitmapData 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

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 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

bitmapSize :: BitmapData -> (Int, Int) #

width, height in pixels

data BitmapFormat #

Description of how the bitmap is layed out in memory.

  • Prior version of Gloss assumed `BitmapFormat BottomToTop PxAGBR`
Instances
Eq BitmapFormat 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Data BitmapFormat 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

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 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Show BitmapFormat 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

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 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Enum RowOrder 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Eq RowOrder 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Data RowOrder 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

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 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Show RowOrder 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

data PixelFormat #

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

Constructors

PxRGBA 
PxABGR 
Instances
Bounded PixelFormat 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Enum PixelFormat 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Eq PixelFormat 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Data PixelFormat 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

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 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

Show PixelFormat 
Instance details

Defined in Graphics.Gloss.Internals.Rendering.Bitmap

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.

bitmapDataOfBMP :: BMP -> BitmapData #

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.