bitmaps-0.2.5.1: Bitmap library

Data.Bitmap.Class

Contents

Synopsis

Documentation

class (Integral (BIndexType bmp), Pixel (BPixelType bmp)) => Bitmap bmp whereSource

Bitmap class

Pixels are indexed by (row, column), where (0, 0) represents the upper-left-most corner of the bitmap. Instances of this class are not required to support empty bitmaps.

The encoding and decoding lists contain functions that can encode and decode or return a string containing information about why it could not be decoded in that format. The order is important: When a function tries multiple or any decoder, it will use or return the one(s) closest to the head of the list. There are lists of generic functions that are defined by default. Normally, if an implementation of a bitmap type overrides the default instance, it will only need to replace one or a few decoders, not touching the rest of the default decoders or the order of the decoders; thus the function updateIdentifiableElements is defined and exported.

Instances *must* support every serialization format.

Associated Types

type BIndexType bmp Source

type BPixelType bmp Source

Methods

depthSource

Arguments

:: bmp 
-> Depth

The color depth of the bitmap in bits

dimensionsSource

Arguments

:: bmp 
-> Dimensions (BIndexType bmp)

Return the width and height of the bitmap in pixels

getPixelSource

Arguments

:: bmp 
-> Coordinates (BIndexType bmp) 
-> BPixelType bmp

Get a pixel; indexing starts at 0

Implementations can assume that the coordinates are within the bounds of the bitmap. Thus callers of this function should always ensure that the coordinates are within the bounds of the bitmap.

constructPixelsSource

Arguments

:: (Coordinates (BIndexType bmp) -> BPixelType bmp) 
-> Dimensions (BIndexType bmp) 
-> bmp

Construct a bitmap with a function that returns a pixel for each coordinate with the given dimensions

The function should return the same type of pixel for each coordinate.

Implementations are not required to call the function in any particular order, and are not even required to guarantee that the function will be called for each pixel, which might be true for a bitmap that is evaluated lazily as needed.

convertInternalFormatSource

Arguments

:: bmp 
-> bmp 
-> bmp

Construct a new bitmap from the bitmap passed as the second argument but storing it in the bitmap of the meta-bitmap passed as the first argument

The purpose of this function is efficiency. Some bitmap types have multiple possible internal representations of bitmaps. For these bitmap types, it is often more efficient when performing operations on multiple bitmaps for them be stored in the same format. Instances might even always convert the bitmaps if their formats differ.

Implementations are not required to define this function to store the second bitmap in another format, or even in the same format as the first bitmap; this is only used for efficiency. They should, however, return a bitmap that represents the same bitmap as what the main bitmap (passed as the second argument) represents. The default behaviour of this function is to return the main bitmap (passed second) verbatim.

As an example application of this function, consider a program that regularly captures the screen and searches for any of several bitmaps which are read from the filesystem. The programmer chooses the type that is most efficient for the format that the screen capture is in, and uses it as the main type. As the screen is expected to change, it would be inefficient to convert each capture into another internal format each time, especially since screen dumps can be very large. The bitmaps, however, are generally static (and much smaller), so they could be converted once using this function, convertInternalFormat, to the format that screen captures are represented in, and reused. If the formats would otherwise differ, this is much more efficient than converting the format of every sub-bitmap every time a search or operation is needed.

NB: again, the format of the first argument is used along with the image of the second argument to return (possibly) a bitmap with the image of the second argument and with the format of the first argument.

completeEncodersSource

Arguments

:: [(CompleteBitmapFormat, CompleteEncoder bmp)]

Bitmap encoders; default definition is based on defaultCompleteEncoders

As the head of the list might be best suited for writing to files or generating text strings but not both, it is suggested that this function is used only when it does not matter whether the result is writable to a file or is generally human readable.

completeDecodersSource

Arguments

:: [(CompleteBitmapFormat, CompleteDecoder bmp)]

Bitmap decodes; extra bytes after the end should be ignored by them; default definition is based on defaultCompleteDecoders

imageEncodersSource

Arguments

:: [(ImageBitmapFormat, ImageEncoder bmp)]

Bitmap encoders; the meta-information is lost; default definition is based on defaultImageEncoders

imageDecodersSource

Arguments

:: [(ImageBitmapFormat, ImageDecoder bmp)]

Decode the bitmap; the meta-information from the given bitmap is used (see ImageDecoder); default definition is based on defaultImageDecoders

convertBitmap :: (Bitmap a, Bitmap b) => a -> bSource

Convert one bitmap type to another

Polymorphic type wrappers

newtype CompleteEncoder bmp Source

Constructors

CompleteEncoder 

Fields

unwrapCompleteEncoder :: StringCells s => bmp -> s
 

newtype CompleteDecoder bmp Source

Constructors

CompleteDecoder 

newtype ImageEncoder bmp Source

Constructors

ImageEncoder 

Fields

unwrapImageEncoder :: StringCells s => bmp -> s
 

newtype ImageDecoder bmp Source

Constructors

ImageDecoder 

Fields

unwrapImageDecoder :: StringCells s => bmp -> s -> Either String bmp
 

Bitmap serialization

updateIdentifiableElements :: Eq k => [(k, v)] -> [(k, v)] -> [(k, v)]Source

Update identifiable elements

updateIdentifiableElements orig new returns orig with each matching pair updated; extraneous replacements in new are ignored.

encodeCBF_BMPIU :: (StringCells s, Bitmap bmp) => bmp -> sSource

encodeCBF_BMPIUU :: (StringCells s, Bitmap bmp) => bmp -> sSource

encodeIBF_IDRGB24Z64 :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> sSource

encodeIBF_IDBGR24R2RZ64 :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> sSource

encodeIBF_IDBGR24HZH :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> sSource

encodeIBF_IDRGB32Z64 :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> sSource

encodeIBF_BGR24H :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> sSource

encodeIBF_BGR24A4VR :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> sSource

encodeIBF_BGRU32VR :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> sSource

encodeIBF_BGRU32 :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> sSource

encodeIBF_RGB24A4VR :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> sSource

encodeIBF_RGB24A4 :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> sSource

encodeIBF_RGB32 :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> sSource

encodeIBF_RGB32Z64 :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> sSource

tryIBF_IDRGB24Z64 :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> s -> Either String bmpSource

tryIBF_IDBGR24R2RZ64 :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> s -> Either String bmpSource

tryIBF_IDBGR24HZH :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> s -> Either String bmpSource

tryIBF_IDRGB32Z64 :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> s -> Either String bmpSource

tryIBF_BGR24H :: forall s bmp. (StringCells s, Bitmap bmp) => bmp -> s -> Either String bmpSource

tryIBF_BGR24A4VR :: (StringCells s, Bitmap bmp) => bmp -> s -> Either String bmpSource

tryIBF_BGRU32VR :: (StringCells s, Bitmap bmp) => bmp -> s -> Either String bmpSource

tryIBF_BGRU32 :: (StringCells s, Bitmap bmp) => bmp -> s -> Either String bmpSource

tryIBF_RGB24A4VR :: (StringCells s, Bitmap bmp) => bmp -> s -> Either String bmpSource

tryIBF_RGB24A4 :: (StringCells s, Bitmap bmp) => bmp -> s -> Either String bmpSource

tryIBF_RGB32 :: (StringCells s, Bitmap bmp) => bmp -> s -> Either String bmpSource

tryIBF_RGB32Z64 :: (StringCells s, Bitmap bmp) => bmp -> s -> Either String bmpSource

encodeComplete :: (StringCells s, Bitmap bmp) => bmp -> sSource

Encode a bitmap

An implementation can choose the most efficient or appropriate format by placing its encoder first in its list of encoders.

decodeComplete :: (StringCells s, Bitmap bmp) => s -> Maybe (CompleteBitmapFormat, bmp)Source

Decode a bitmap

The result of first decoder of the implementation that succeeds will be returned. If none succeed, Nothing is returned.

encodeImage :: (StringCells s, Bitmap bmp) => bmp -> sSource

Encode the pixels of a bitmap

An implementation can choose the most efficient or appropriate format by placing its encoder first in its list of encoders.

decodeImage :: (StringCells s, Bitmap bmp) => bmp -> s -> Maybe (ImageBitmapFormat, bmp)Source

Decode the pixels of a bitmap

The result of first decoder of the implementation that succeeds will be returned. If none succeed, Nothing is returned.

encodeCompleteFmt :: (StringCells s, Bitmap bmp) => CompleteBitmapFormat -> bmp -> sSource

Encode a bitmap in a particular format

decodeCompleteFmt :: (StringCells s, Bitmap bmp) => CompleteBitmapFormat -> s -> Either String bmpSource

Decode a bitmap in a particular format

encodeImageFmt :: (StringCells s, Bitmap bmp) => ImageBitmapFormat -> bmp -> sSource

Encode the pixels of a bitmap in a particular format

decodeImageFmt :: (StringCells s, Bitmap bmp) => ImageBitmapFormat -> bmp -> s -> Either String bmpSource

Decode the pixels of a bitmap in a particular format

decodeImageDimensions :: (StringCells s, Bitmap bmp) => Dimensions (BIndexType bmp) -> s -> Maybe (ImageBitmapFormat, bmp)Source

Decode an image with the given dimensions

This is only guaranteed to work on implementations and formats that only need dimensions in addition to the raw pixel data. This is convenient because most often the dimensions are all that is needed.

Currently, this function works by constructing a bitmap with the given dimensions and with each pixel set to the least intensity. Thus it is significantly more efficient if this is used with a bitmap that doesn't strictly evaluate the entire pixel data when the structure is first constructed (not necessarily when any pixel is accessed) (currently none of the bitmap types exported in this library are so strict), as the bitmap will not need to be fully evaluated; only the dimensions will be used.

decodeImageDimensionsFmt :: (StringCells s, Bitmap bmp) => ImageBitmapFormat -> Dimensions (BIndexType bmp) -> s -> Either String bmpSource

Decode an image with the given dimensions as decodeImageDimensions does it, but in a specific format

Utility functions

dimensionsFit :: Integral a => Dimensions a -> Dimensions a -> BoolSource

Determine whether the seconds dimensions passed can fit within the first dimensions passed

If the width or height of the second dimensions exceeds those of first dimensions, False is returned.

bitmapWidth :: Bitmap bmp => bmp -> BIndexType bmpSource

Returns the width of a bitmap

bitmapHeight :: Bitmap bmp => bmp -> BIndexType bmpSource

Returns the height of a bitmap