The full, mutable API in the IO monad.
- module Data.Bitmap.Base
- newBitmap :: forall t. PixelComponent t => Size -> NChn -> Maybe Alignment -> IO (Bitmap t)
- newBitmapUninitialized :: forall t. PixelComponent t => Size -> NChn -> Maybe Alignment -> IO (Bitmap t)
- createSingleChannelBitmap :: forall t. PixelComponent t => Size -> Maybe Alignment -> (Int -> Int -> t) -> IO (Bitmap t)
- copyBitmapFromPtr :: forall t. PixelComponent t => Size -> NChn -> Padding -> Ptr t -> Maybe Alignment -> IO (Bitmap t)
- bitmapFromForeignPtrUnsafe :: forall t. PixelComponent t => Size -> NChn -> Alignment -> Padding -> ForeignPtr t -> Bitmap t
- withBitmap :: PixelComponent t => Bitmap t -> (Size -> NChn -> Padding -> Ptr t -> IO a) -> IO a
- componentMap :: PixelComponent s => (s -> s) -> Bitmap s -> IO (Bitmap s)
- componentMap' :: (PixelComponent s, PixelComponent t) => (s -> t) -> Bitmap s -> Maybe Alignment -> IO (Bitmap t)
- componentMapInPlace :: PixelComponent s => (s -> s) -> Bitmap s -> IO ()
- copySubImage :: PixelComponent t => Bitmap t -> Offset -> Size -> IO (Bitmap t)
- copySubImage' :: PixelComponent t => Bitmap t -> Offset -> Size -> Size -> Offset -> IO (Bitmap t)
- copySubImageInto :: PixelComponent t => Bitmap t -> Offset -> Size -> Bitmap t -> Offset -> IO ()
- combineChannels :: forall t. PixelComponent t => [Bitmap t] -> Maybe Alignment -> IO (Bitmap t)
- extractChannels :: PixelComponent t => Bitmap t -> Maybe Alignment -> IO [Bitmap t]
- extractSingleChannel :: PixelComponent t => Bitmap t -> Maybe Alignment -> Int -> IO (Bitmap t)
- extractChannelInto :: forall t. PixelComponent t => Bitmap t -> Int -> Bitmap t -> Int -> IO ()
- bilinearResample :: PixelComponent t => Bitmap t -> Size -> Maybe Alignment -> IO (Bitmap t)
- bilinearResampleChannel :: PixelComponent t => Bitmap t -> Int -> Size -> Maybe Alignment -> IO (Bitmap t)
- bilinearResampleChannelInto :: forall t. PixelComponent t => Bitmap t -> Int -> Bitmap t -> Int -> IO ()
- blendBitmaps :: PixelComponent t => Float -> Float -> Bitmap t -> Bitmap t -> Maybe Alignment -> IO (Bitmap t)
- blendChannels :: PixelComponent t => Float -> Float -> Bitmap t -> Int -> Bitmap t -> Int -> Maybe Alignment -> IO (Bitmap t)
- blendChannelsInto :: forall t. PixelComponent t => Float -> Float -> Bitmap t -> Int -> Bitmap t -> Int -> Bitmap t -> Int -> IO ()
- powerlawGammaCorrection :: forall t. PixelComponent t => Float -> Bitmap t -> Maybe Alignment -> IO (Bitmap t)
- powerlawGammaCorrectionChannel :: PixelComponent t => Float -> Bitmap t -> Int -> Maybe Alignment -> IO (Bitmap t)
- powerlawGammaCorrectionChannelInto :: forall t. PixelComponent t => Float -> Bitmap t -> Int -> Bitmap t -> Int -> IO ()
- copyBitmapToByteString :: PixelComponent t => Bitmap t -> IO ByteString
- copyBitmapFromByteString :: forall t. PixelComponent t => ByteString -> Size -> NChn -> Padding -> IO (Bitmap t)
- withComponentPtr :: forall t a. PixelComponent t => Bitmap t -> Offset -> Int -> (Ptr t -> IO a) -> IO a
- unsafeReadComponent :: PixelComponent t => Bitmap t -> Offset -> Int -> IO t
- unsafeWriteComponent :: PixelComponent t => Bitmap t -> Offset -> Int -> t -> IO ()
- unsafeReadComponents :: PixelComponent t => Bitmap t -> Offset -> Int -> Int -> IO [t]
- unsafeWriteComponents :: PixelComponent t => Bitmap t -> Offset -> Int -> [t] -> IO ()
- unsafeReadPixel :: PixelComponent t => Bitmap t -> Offset -> IO [t]
- unsafeReadPixel1 :: PixelComponent t => Bitmap t -> Offset -> IO t
- unsafeReadPixel2 :: PixelComponent t => Bitmap t -> Offset -> IO (t, t)
- unsafeReadPixel3 :: PixelComponent t => Bitmap t -> Offset -> IO (t, t, t)
- unsafeReadPixel4 :: PixelComponent t => Bitmap t -> Offset -> IO (t, t, t, t)
- unsafeWritePixel1 :: PixelComponent t => Bitmap t -> Offset -> t -> IO ()
- unsafeWritePixel2 :: PixelComponent t => Bitmap t -> Offset -> (t, t) -> IO ()
- unsafeWritePixel3 :: PixelComponent t => Bitmap t -> Offset -> (t, t, t) -> IO ()
- unsafeWritePixel4 :: PixelComponent t => Bitmap t -> Offset -> (t, t, t, t) -> IO ()
Documentation
module Data.Bitmap.Base
Creating and accessing bitmaps
:: 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.
newBitmapUninitialized :: forall t. PixelComponent t => Size -> NChn -> Maybe Alignment -> IO (Bitmap t)Source
createSingleChannelBitmapSource
:: 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!
bitmapFromForeignPtrUnsafe :: forall t. PixelComponent t => Size -> NChn -> Alignment -> Padding -> ForeignPtr t -> Bitmap tSource
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.
:: (PixelComponent s, PixelComponent t) | |
=> (s -> t) | |
-> Bitmap s | source bitmap |
-> Maybe Alignment | row alignment of the resulting bitmap |
-> IO (Bitmap t) |
componentMapInPlace :: PixelComponent s => (s -> s) -> Bitmap s -> IO ()Source
Cropping and extending
:: 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.
:: 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.
:: 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
combineChannels :: forall t. PixelComponent t => [Bitmap t] -> Maybe Alignment -> IO (Bitmap t)Source
extractChannels :: PixelComponent t => Bitmap t -> Maybe Alignment -> IO [Bitmap t]Source
Bilinear resampling
Blending
:: 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.
Gamma correction
:: 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.
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
:: 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)
:: 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.
:: 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.
:: 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.
:: 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...)
unsafeReadPixel2 :: PixelComponent t => Bitmap t -> Offset -> IO (t, t)Source
unsafeReadPixel3 :: PixelComponent t => Bitmap t -> Offset -> IO (t, t, t)Source
unsafeReadPixel4 :: PixelComponent t => Bitmap t -> Offset -> IO (t, t, t, t)Source
unsafeWritePixel1 :: PixelComponent t => Bitmap t -> Offset -> t -> IO ()Source
unsafeWritePixel2 :: PixelComponent t => Bitmap t -> Offset -> (t, t) -> IO ()Source
unsafeWritePixel3 :: PixelComponent t => Bitmap t -> Offset -> (t, t, t) -> IO ()Source
unsafeWritePixel4 :: PixelComponent t => Bitmap t -> Offset -> (t, t, t, t) -> IO ()Source