| Safe Haskell | Safe-Infered | 
|---|
Data.Bitmap.IO
Contents
Description
The full, mutable API in the IO monad.
- module Data.Bitmap.Base
- data IOBitmap t
- data IOBitmapChannel t
- unsafeFreezeBitmap :: IOBitmap t -> Bitmap t
- unsafeThawBitmap :: Bitmap t -> IOBitmap t
- emptyBitmap :: PixelComponent t => Size -> NChn -> Maybe Alignment -> IO (IOBitmap t)
- cloneBitmap :: PixelComponent t => IOBitmap t -> Maybe Alignment -> IO (IOBitmap t)
- emptyCloneBitmap :: PixelComponent t => IOBitmap t -> Maybe Alignment -> IO (IOBitmap t)
- createSingleChannelBitmap :: PixelComponent t => Size -> Maybe Alignment -> (Int -> Int -> t) -> IO (IOBitmap t)
- newIOBitmap :: PixelComponent t => Size -> NChn -> Maybe Alignment -> IO (IOBitmap t)
- newIOBitmapUninitialized :: PixelComponent t => Size -> NChn -> Maybe Alignment -> IO (IOBitmap t)
- copyBitmapFromPtr :: PixelComponent t => Size -> NChn -> Padding -> Ptr t -> Maybe Alignment -> IO (IOBitmap t)
- ioBitmapFromForeignPtrUnsafe :: PixelComponent t => Size -> NChn -> Alignment -> Padding -> ForeignPtr t -> IOBitmap t
- withIOBitmap :: PixelComponent t => IOBitmap t -> (Size -> NChn -> Padding -> Ptr t -> IO a) -> IO a
- componentMap :: PixelComponent s => (s -> s) -> IOBitmap s -> IO (IOBitmap s)
- componentMap' :: (PixelComponent s, PixelComponent t) => (s -> t) -> IOBitmap s -> Maybe Alignment -> IO (IOBitmap t)
- componentMapInPlace :: PixelComponent s => (s -> s) -> IOBitmap s -> IO ()
- copySubImage :: PixelComponent t => IOBitmap t -> Offset -> Size -> IO (IOBitmap t)
- copySubImage' :: PixelComponent t => IOBitmap t -> Offset -> Size -> Size -> Offset -> IO (IOBitmap t)
- copySubImageInto :: PixelComponent t => IOBitmap t -> Offset -> Size -> IOBitmap t -> Offset -> IO ()
- flipBitmap :: PixelComponent t => IOBitmap t -> Maybe Alignment -> IO (IOBitmap t)
- flipBitmapInPlace :: PixelComponent t => IOBitmap t -> IO ()
- mirrorBitmap :: PixelComponent t => IOBitmap t -> Maybe Alignment -> IO (IOBitmap t)
- mirrorBitmapInPlace :: PixelComponent t => IOBitmap t -> IO ()
- castBitmap :: (PixelComponent s, PixelComponent t) => IOBitmap s -> Maybe Alignment -> IO (IOBitmap t)
- combineChannels :: PixelComponent t => [IOBitmap t] -> Maybe Alignment -> IO (IOBitmap t)
- extractChannels :: PixelComponent t => IOBitmap t -> Maybe Alignment -> IO [IOBitmap t]
- extractSingleChannel :: PixelComponent t => IOBitmap t -> Maybe Alignment -> Int -> IO (IOBitmap t)
- extractChannelInto :: PixelComponent t => IOBitmap t -> Int -> IOBitmap t -> Int -> IO ()
- bilinearResample :: PixelComponent t => IOBitmap t -> Size -> Maybe Alignment -> IO (IOBitmap t)
- bilinearResampleChannel :: PixelComponent t => IOBitmap t -> Int -> Size -> Maybe Alignment -> IO (IOBitmap t)
- bilinearResampleChannelInto :: PixelComponent t => IOBitmap t -> Int -> IOBitmap t -> Int -> IO ()
- blendBitmaps :: PixelComponent t => Float -> Float -> IOBitmap t -> IOBitmap t -> Maybe Alignment -> IO (IOBitmap t)
- blendChannels :: PixelComponent t => Float -> Float -> IOBitmap t -> Int -> IOBitmap t -> Int -> Maybe Alignment -> IO (IOBitmap t)
- blendChannelsInto :: PixelComponent t => Float -> Float -> IOBitmap t -> Int -> IOBitmap t -> Int -> IOBitmap t -> Int -> IO ()
- powerlawGammaCorrection :: PixelComponent t => Float -> IOBitmap t -> Maybe Alignment -> IO (IOBitmap t)
- powerlawGammaCorrectionChannel :: PixelComponent t => Float -> IOBitmap t -> Int -> Maybe Alignment -> IO (IOBitmap t)
- powerlawGammaCorrectionChannelInto :: PixelComponent t => Float -> IOBitmap t -> Int -> IOBitmap t -> Int -> IO ()
Documentation
module Data.Bitmap.Base
Mutable bitmap type
A mutable Bitmap in the IO Monad. Only the content is mutable, the shape isn't.
Instances
data IOBitmapChannel t Source
unsafeFreezeBitmap :: IOBitmap t -> Bitmap tSource
unsafeThawBitmap :: Bitmap t -> IOBitmap tSource
Creating and accessing bitmaps
Arguments
| :: PixelComponent t | |
| => Size | (width,height) | 
| -> NChn | number of channels (components/pixel) | 
| -> Maybe Alignment | the row alignment of the new image | 
| -> IO (IOBitmap t) | 
Synonym for newIOBitmap
Arguments
| :: PixelComponent t | |
| => IOBitmap t | source image | 
| -> Maybe Alignment | target alignment | 
| -> IO (IOBitmap t) | 
Clones a bitmap.
Arguments
| :: PixelComponent t | |
| => IOBitmap t | source (only dimensions and such is used) | 
| -> Maybe Alignment | target alignment | 
| -> IO (IOBitmap t) | new empty bitmap | 
Creates an empty bitmap with the same properties as the source.
createSingleChannelBitmapSource
Arguments
| :: 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 (IOBitmap t) | 
Creates a new single-channel bitmap, using the given function to compute the pixel values. Warning, this is probably slow!
Arguments
| :: PixelComponent t | |
| => Size | (width,height) | 
| -> NChn | number of channels (components/pixel) | 
| -> Maybe Alignment | the row alignment of the new image | 
| -> IO (IOBitmap 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.
newIOBitmapUninitialized :: PixelComponent t => Size -> NChn -> Maybe Alignment -> IO (IOBitmap t)Source
ioBitmapFromForeignPtrUnsafe :: PixelComponent t => Size -> NChn -> Alignment -> Padding -> ForeignPtr t -> IOBitmap tSource
Using bitmaps
withIOBitmap :: PixelComponent t => IOBitmap t -> (Size -> NChn -> Padding -> Ptr t -> IO a) -> IO aSource
withIOBitmap bitmap $ \(w,h) nchn padding ptr -> ...
Mapping over bitmaps
componentMap :: PixelComponent s => (s -> s) -> IOBitmap s -> IO (IOBitmap 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.
Arguments
| :: (PixelComponent s, PixelComponent t) | |
| => (s -> t) | |
| -> IOBitmap s | source bitmap | 
| -> Maybe Alignment | row alignment of the resulting bitmap | 
| -> IO (IOBitmap t) | 
componentMapInPlace :: PixelComponent s => (s -> s) -> IOBitmap s -> IO ()Source
Cropping and extending
Arguments
| :: PixelComponent t | |
| => IOBitmap t | source image | 
| -> Offset | source rectangle offset | 
| -> Size | source rectangle size | 
| -> IO (IOBitmap t) | 
Copies a subrectangle of the source image into a new image.
Arguments
| :: PixelComponent t | |
| => IOBitmap t | source image | 
| -> Offset | source rectangle offset | 
| -> Size | source rectangle size | 
| -> Size | target image size | 
| -> Offset | target rectangle offset | 
| -> IO (IOBitmap t) | 
Copy into a new "black" bitmap; common generalization of crop and extend.
Arguments
| :: PixelComponent t | |
| => IOBitmap t | source image | 
| -> Offset | source rectangle offset | 
| -> Size | source rectangle size | 
| -> IOBitmap 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.
Flipping and mirroring
Arguments
| :: PixelComponent t | |
| => IOBitmap t | source image | 
| -> Maybe Alignment | target image row alignment | 
| -> IO (IOBitmap t) | 
Flips the bitmap vertically.
Arguments
| :: PixelComponent t | |
| => IOBitmap t | source image | 
| -> IO () | 
Arguments
| :: PixelComponent t | |
| => IOBitmap t | source image | 
| -> Maybe Alignment | target image row alignment | 
| -> IO (IOBitmap t) | 
Flips the bitmap horizontally.
Arguments
| :: PixelComponent t | |
| => IOBitmap t | source image | 
| -> IO () | 
Cast
Arguments
| :: (PixelComponent s, PixelComponent t) | |
| => IOBitmap s | source image | 
| -> Maybe Alignment | target image row alignment | 
| -> IO (IOBitmap t) | 
Convert a bitmap to one with a different component type.
Manipulating channels
combineChannels :: PixelComponent t => [IOBitmap t] -> Maybe Alignment -> IO (IOBitmap t)Source
extractChannels :: PixelComponent t => IOBitmap t -> Maybe Alignment -> IO [IOBitmap t]Source
Bilinear resampling
Blending
Arguments
| :: PixelComponent t | |
| => Float | weight1 | 
| -> Float | weight2 | 
| -> IOBitmap t | source1 image | 
| -> IOBitmap t | source2 image | 
| -> Maybe Alignment | target alignment | 
| -> IO (IOBitmap 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.
Gamma correction
Arguments
| :: PixelComponent t | |
| => Float | gamma | 
| -> IOBitmap t | source bitmap | 
| -> Maybe Alignment | target alignment | 
| -> IO (IOBitmap t) | 
This is equivalent to componentMap (c -> c^gamma), except that
 (^) is defined only for integral exponents; but should be faster anyway.