bitmap-0.0.1: A library for handling and manipulating bitmaps.

Data.Bitmap.IO

Contents

Description

The full, mutable API in the IO monad.

Synopsis

Documentation

Creating and accessing bitmaps

newBitmapSource

Arguments

:: forall t . PixelComponent t 
=> Size

(width,height)

-> NChn

number of channels (components/pixel)

-> Maybe Alignment

the row alignment of the new image

-> IO (Bitmap t) 

Note: we cannot guarantee the alignment of the memory block (but typically it is aligned at least to machine word boundary), but what we can guarantee is that the rows are properly padded.

At the moment, the default alignment is 4, valid alignments are 1, 2, 4, 8 and 16, and the padding method is compatible with the OpenGL one (that is, the padding is the smallest multiple of a component size such that the next row is aligned).

The resulting new bitmap is filled with zeros.

createSingleChannelBitmapSource

Arguments

:: forall t . PixelComponent t 
=> Size

(width,height)

-> Maybe Alignment

the row alignment of the new image

-> (Int -> Int -> t)

the function we will use to fill the bitmap

-> IO (Bitmap t) 

Creates a new single-channel bitmap, using the given function to compute the pixel values. Warning, this is probably slow!

copyBitmapFromPtrSource

Arguments

:: forall t . PixelComponent t 
=> Size

(width,height) of the source

-> NChn

number of channels in the source

-> Padding

source padding

-> Ptr t

the source

-> Maybe Alignment

target alignment

-> IO (Bitmap t) 

withBitmap :: PixelComponent t => Bitmap t -> (Size -> NChn -> Padding -> Ptr t -> IO a) -> IO aSource

withBitmap bitmap $ \(w,h) nchn padding ptr -> ...

Mapping over bitmaps

componentMap :: PixelComponent s => (s -> s) -> Bitmap s -> IO (Bitmap s)Source

Maps a function over each component of each pixel. Warning: this is probably slow! Use a specialized function if there is one for your task.

componentMap'Source

Arguments

:: (PixelComponent s, PixelComponent t) 
=> (s -> t) 
-> Bitmap s

source bitmap

-> Maybe Alignment

row alignment of the resulting bitmap

-> IO (Bitmap t) 

Cropping and extending

copySubImageSource

Arguments

:: PixelComponent t 
=> Bitmap t

source image

-> Offset

source rectangle offset

-> Size

source rectangle size

-> IO (Bitmap t) 

Copies a subrectangle of the source image into a new image.

copySubImage'Source

Arguments

:: PixelComponent t 
=> Bitmap t

source image

-> Offset

source rectangle offset

-> Size

source rectangle size

-> Size

target image size

-> Offset

target rectangle offset

-> IO (Bitmap t) 

Copy into a new "black" bitmap; common generalization of crop and extend.

copySubImageIntoSource

Arguments

:: PixelComponent t 
=> Bitmap t

source image

-> Offset

source rectangle offset

-> Size

source rectangle size

-> Bitmap t

target image

-> Offset

target rectangle offset

-> IO () 

The source rectangle may be arbitrary, may or may not intersect the source image in any way. We only copy the intersection of the rectangle with the image.

Manipulating channels

extractSingleChannelSource

Arguments

:: PixelComponent t 
=> Bitmap t

source image

-> Maybe Alignment

target image row alignment

-> Int

source channel index

-> IO (Bitmap t) 

extractChannelIntoSource

Arguments

:: forall t . PixelComponent t 
=> Bitmap t

source image

-> Int

source channel index

-> Bitmap t

target image

-> Int

target channel index

-> IO () 

Bilinear resampling

bilinearResampleSource

Arguments

:: PixelComponent t 
=> Bitmap t

source image

-> Size

target image size

-> Maybe Alignment

target image alignment

-> IO (Bitmap t) 

bilinearResampleChannelSource

Arguments

:: PixelComponent t 
=> Bitmap t

source image

-> Int

source channel index

-> Size

target image size

-> Maybe Alignment

target image alignment

-> IO (Bitmap t) 

bilinearResampleChannelIntoSource

Arguments

:: forall t . PixelComponent t 
=> Bitmap t

source image

-> Int

source channel index

-> Bitmap t

target image

-> Int

target channel index

-> IO () 

Blending

blendBitmapsSource

Arguments

:: PixelComponent t 
=> Float

weight1

-> Float

weight2

-> Bitmap t

source1 image

-> Bitmap t

source2 image

-> Maybe Alignment

target alignment

-> IO (Bitmap t) 

Blends two bitmaps with the given weights; that is, the result is the specified linear combination. If the values are outside the allowed range (this can happen with the Word8, Word16, Word32 types and weights whose sum is bigger than 1, or with a negative weight), then they are clipped. The clipping does not happen with the Float component type.

blendChannelsSource

Arguments

:: PixelComponent t 
=> Float

weight1

-> Float

weight2

-> Bitmap t

source1 image

-> Int

source1 channel index

-> Bitmap t

source2 image

-> Int

source2 channel index

-> Maybe Alignment

target alignment

-> IO (Bitmap t) 

blendChannelsIntoSource

Arguments

:: forall t . PixelComponent t 
=> Float

weight1

-> Float

weight2

-> Bitmap t

source1 image

-> Int

source1 channel index

-> Bitmap t

source2 image

-> Int

source2 channel index

-> Bitmap t

target image

-> Int

target channel index

-> IO () 

Gamma correction

powerlawGammaCorrectionSource

Arguments

:: forall t . PixelComponent t 
=> Float

gamma

-> Bitmap t

source bitmap

-> Maybe Alignment

target alignment

-> IO (Bitmap t) 

This is equivalent to componentMap (c -> c^gamma), except that (^) is defined only for integral exponents; but should be faster anyway.

powerlawGammaCorrectionChannelSource

Arguments

:: PixelComponent t 
=> Float

gamma

-> Bitmap t

source image

-> Int

source channel index

-> Maybe Alignment

target image alignment

-> IO (Bitmap t) 

powerlawGammaCorrectionChannelIntoSource

Arguments

:: forall t . PixelComponent t 
=> Float

gamma

-> Bitmap t

source image

-> Int

source channel index

-> Bitmap t

target image

-> Int

target channel index

-> IO () 

Conversion to/from ByteString

copyBitmapToByteString :: PixelComponent t => Bitmap t -> IO ByteStringSource

The data is copied, not shared. Note that the resulting ByteString is encoded using the host machine's endianness, so it may be not compatible across different architectures!

copyBitmapFromByteString :: forall t. PixelComponent t => ByteString -> Size -> NChn -> Padding -> IO (Bitmap t)Source

The data is copied, not shared. Note that we expect the ByteString to be encoded encoded using the host machine's endianness.

Reading and writing pixels

withComponentPtrSource

Arguments

:: forall t a . PixelComponent t 
=> Bitmap t

the bitmap

-> Offset

position (x,y)

-> Int

channel index {0,1,...,nchannels-1}

-> (Ptr t -> IO a)

user action

-> IO a 

Note that the resulting pointer is valid only within a line (because of the padding)

unsafeReadComponentSource

Arguments

:: PixelComponent t 
=> Bitmap t

the bitmap

-> Offset

position (x,y)

-> Int

channel index {0,1,...,nchannels-1}

-> IO t 

It is not very efficient to read/write lots of pixels this way.

unsafeWriteComponentSource

Arguments

:: PixelComponent t 
=> Bitmap t

the bitmap

-> Offset

position (x,y)

-> Int

channel index {0,1,...,nchannels-1}

-> t

the value to write

-> IO () 

unsafeReadComponentsSource

Arguments

:: PixelComponent t 
=> Bitmap t

the bitmap

-> Offset

position (x,y)

-> Int

channel index {0,1,...,nchannels-1}

-> Int

the number of components to read

-> IO [t] 

Please note that the component array to read shouldn't cross the boundary between lines.

unsafeWriteComponentsSource

Arguments

:: PixelComponent t 
=> Bitmap t

the bitmap

-> Offset

position (x,y)

-> Int

channel index {0,1,...,nchannels-1}

-> [t]

the components to write

-> IO () 

Please note that the component array to write shouldn't cross the boundary between lines.

unsafeReadPixelSource

Arguments

:: PixelComponent t 
=> Bitmap t

the bitmap

-> Offset

position (x,y)

-> IO [t] 

unsafeReadPixel1 :: PixelComponent t => Bitmap t -> Offset -> IO tSource

These functions assume that the number of channels of the bitmap agrees with the number suffix of the function.

(Maybe I should put the number of components into the Bitmap type? But that would cause different problems...)

unsafeWritePixel4 :: PixelComponent t => Bitmap t -> Offset -> (t, t, t, t) -> IO ()Source