Safe Haskell | None |
---|
Module providing the basic types for image manipulation in the library. Defining the types used to store all those _Juicy Pixels_
- data Image a = Image {
- imageWidth :: !Int
- imageHeight :: !Int
- imageData :: Vector (PixelBaseComponent a)
- data MutableImage s a = MutableImage {
- mutableImageWidth :: !Int
- mutableImageHeight :: !Int
- mutableImageData :: STVector s (PixelBaseComponent a)
- data DynamicImage
- = ImageY8 (Image Pixel8)
- | ImageY16 (Image Pixel16)
- | ImageYF (Image PixelF)
- | ImageYA8 (Image PixelYA8)
- | ImageYA16 (Image PixelYA16)
- | ImageRGB8 (Image PixelRGB8)
- | ImageRGB16 (Image PixelRGB16)
- | ImageRGBF (Image PixelRGBF)
- | ImageRGBA8 (Image PixelRGBA8)
- | ImageRGBA16 (Image PixelRGBA16)
- | ImageYCbCr8 (Image PixelYCbCr8)
- | ImageCMYK8 (Image PixelCMYK8)
- | ImageCMYK16 (Image PixelCMYK16)
- freezeImage :: (Storable (PixelBaseComponent a), PrimMonad m) => MutableImage (PrimState m) a -> m (Image a)
- unsafeFreezeImage :: (Storable (PixelBaseComponent a), PrimMonad m) => MutableImage (PrimState m) a -> m (Image a)
- type Pixel8 = Word8
- type Pixel16 = Word16
- type PixelF = Float
- data PixelYA8 = PixelYA8 !Pixel8 !Pixel8
- data PixelYA16 = PixelYA16 !Pixel16 !Pixel16
- data PixelRGB8 = PixelRGB8 !Pixel8 !Pixel8 !Pixel8
- data PixelRGB16 = PixelRGB16 !Pixel16 !Pixel16 !Pixel16
- data PixelRGBF = PixelRGBF !PixelF !PixelF !PixelF
- data PixelRGBA8 = PixelRGBA8 !Pixel8 !Pixel8 !Pixel8 !Pixel8
- data PixelRGBA16 = PixelRGBA16 !Pixel16 !Pixel16 !Pixel16 !Pixel16
- data PixelCMYK8 = PixelCMYK8 !Pixel8 !Pixel8 !Pixel8 !Pixel8
- data PixelCMYK16 = PixelCMYK16 !Pixel16 !Pixel16 !Pixel16 !Pixel16
- data PixelYCbCr8 = PixelYCbCr8 !Pixel8 !Pixel8 !Pixel8
- class (Pixel a, Pixel b) => ColorConvertible a b where
- promotePixel :: a -> b
- promoteImage :: Image a -> Image b
- class (Storable (PixelBaseComponent a), Num (PixelBaseComponent a), Eq a) => Pixel a where
- type PixelBaseComponent a :: *
- componentCount :: a -> Int
- colorMap :: (PixelBaseComponent a -> PixelBaseComponent a) -> a -> a
- pixelBaseIndex :: Image a -> Int -> Int -> Int
- mutablePixelBaseIndex :: MutableImage s a -> Int -> Int -> Int
- pixelAt :: Image a -> Int -> Int -> a
- readPixel :: PrimMonad m => MutableImage (PrimState m) a -> Int -> Int -> m a
- writePixel :: PrimMonad m => MutableImage (PrimState m) a -> Int -> Int -> a -> m ()
- unsafePixelAt :: Vector (PixelBaseComponent a) -> Int -> a
- unsafeReadPixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent a) -> Int -> m a
- unsafeWritePixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent a) -> Int -> a -> m ()
- class (Pixel a, Pixel b) => ColorSpaceConvertible a b where
- convertPixel :: a -> b
- convertImage :: Image a -> Image b
- class (Pixel a, Pixel (PixelBaseComponent a)) => LumaPlaneExtractable a where
- computeLuma :: a -> PixelBaseComponent a
- extractLumaPlane :: Image a -> Image (PixelBaseComponent a)
- class (Pixel a, Pixel b) => TransparentPixel a b | a -> b where
- dropTransparency :: a -> b
- dynamicMap :: (forall pixel. Pixel pixel => Image pixel -> a) -> DynamicImage -> a
- pixelMap :: forall a b. (Pixel a, Pixel b) => (a -> b) -> Image a -> Image b
- pixelFold :: Pixel pixel => (acc -> Int -> Int -> pixel -> acc) -> acc -> Image pixel -> acc
- dropAlphaLayer :: TransparentPixel a b => Image a -> Image b
- withImage :: forall m pixel. (Pixel pixel, PrimMonad m) => Int -> Int -> (Int -> Int -> m pixel) -> m (Image pixel)
- generateImage :: forall a. Pixel a => (Int -> Int -> a) -> Int -> Int -> Image a
- generateFoldImage :: forall a acc. Pixel a => (acc -> Int -> Int -> (acc, a)) -> acc -> Int -> Int -> (acc, Image a)
- gammaCorrection :: PixelF -> Image PixelRGBF -> Image PixelRGBF
- toneMapping :: PixelF -> Image PixelRGBF -> Image PixelRGBF
- class ColorPlane pixel planeToken
- data PlaneRed = PlaneRed
- data PlaneGreen = PlaneGreen
- data PlaneBlue = PlaneBlue
- data PlaneAlpha = PlaneAlpha
- data PlaneLuma = PlaneLuma
- data PlaneCr = PlaneCr
- data PlaneCb = PlaneCb
- data PlaneCyan = PlaneCyan
- data PlaneMagenta = PlaneMagenta
- data PlaneYellow = PlaneYellow
- data PlaneBlack = PlaneBlack
- extractComponent :: forall px plane. (Pixel px, Pixel (PixelBaseComponent px), PixelBaseComponent (PixelBaseComponent px) ~ PixelBaseComponent px, ColorPlane px plane) => plane -> Image px -> Image (PixelBaseComponent px)
- unsafeExtractComponent :: forall a. (Pixel a, Pixel (PixelBaseComponent a), PixelBaseComponent (PixelBaseComponent a) ~ PixelBaseComponent a) => Int -> Image a -> Image (PixelBaseComponent a)
Types
Image types
Image or pixel buffer, the coordinates are assumed to start from the upper-left corner of the image, with the horizontal position first, then the vertical one.
Image | |
|
data MutableImage s a Source
Image or pixel buffer, the coordinates are assumed to start from the upper-left corner of the image, with the horizontal position first, then the vertical one. The image can be transformed in place.
MutableImage | |
|
NFData (MutableImage s a) |
data DynamicImage Source
Type allowing the loading of an image with different pixel structures
ImageY8 (Image Pixel8) | A greyscale image. |
ImageY16 (Image Pixel16) | A greyscale image with 16bit components |
ImageYF (Image PixelF) | A greyscale HDR image |
ImageYA8 (Image PixelYA8) | An image in greyscale with an alpha channel. |
ImageYA16 (Image PixelYA16) | An image in greyscale with alpha channel on 16 bits. |
ImageRGB8 (Image PixelRGB8) | An image in true color. |
ImageRGB16 (Image PixelRGB16) | An image in true color with 16bit depth. |
ImageRGBF (Image PixelRGBF) | An image with HDR pixels |
ImageRGBA8 (Image PixelRGBA8) | An image in true color and an alpha channel. |
ImageRGBA16 (Image PixelRGBA16) | A true color image with alpha on 16 bits. |
ImageYCbCr8 (Image PixelYCbCr8) | An image in the colorspace used by Jpeg images. |
ImageCMYK8 (Image PixelCMYK8) | An image in the colorspace CMYK |
ImageCMYK16 (Image PixelCMYK16) | An image in the colorspace CMYK and 16 bots precision |
Image functions
freezeImage :: (Storable (PixelBaseComponent a), PrimMonad m) => MutableImage (PrimState m) a -> m (Image a)Source
`O(n)` Yield an immutable copy of an image by making a copy of it
unsafeFreezeImage :: (Storable (PixelBaseComponent a), PrimMonad m) => MutableImage (PrimState m) a -> m (Image a)Source
`O(1)` Unsafe convert a mutable image to an immutable one without copying. The mutable image may not be used after this operation.
Pixel types
Floating greyscale value, the 0 to 255 8 bit range maps to 0 to 1 in this floating version
Pixel type storing Luminance (Y) and alpha information on 8 bits. Value are stored in the following order :
- Luminance
- Alpha
Pixel type storing Luminance (Y) and alpha information on 16 bits. Value are stored in the following order :
- Luminance
- Alpha
Pixel type storing classic pixel on 8 bits Value are stored in the following order :
- Red
- Green
- Blue
data PixelRGB16 Source
Pixel type storing pixels on 16 bits Value are stored in the following order :
- Red
- Green
- Blue
Pixel type storing HDR pixel on 32 bits float Value are stored in the following order :
- Red
- Green
- Blue
data PixelRGBA8 Source
Pixel type storing a classic pixel, with an alpha component. Values are stored in the following order
- Red
- Green
- Blue
- Alpha
data PixelRGBA16 Source
Pixel type storing a RGB information with an alpha channel on 16 bits. Values are stored in the following order
- Red
- Green
- Blue
- Alpha
data PixelCMYK8 Source
Pixel storing data in the CMYK colorspace. value are stored in the following order :
- Cyan
- Magenta
- Yellow
- Black
data PixelCMYK16 Source
Pixel storing data in the CMYK colorspace. value are stored in the following order :
- Cyan
- Magenta
- Yellow
- Black
data PixelYCbCr8 Source
Pixel storing data in the YCbCr colorspace, value are stored in the following order :
- Y (luminance)
- Cr
- Cb
Type classes
class (Pixel a, Pixel b) => ColorConvertible a b whereSource
Implement upcasting for pixel types
Minimal declaration declaration promotePixel
It is strongly recommanded to overload promoteImage to keep
performance acceptable
promotePixel :: a -> bSource
Convert a pixel type to another pixel type. This operation should never loss any data.
promoteImage :: Image a -> Image bSource
Change the underlying pixel type of an image by performing a full copy of it.
class (Storable (PixelBaseComponent a), Num (PixelBaseComponent a), Eq a) => Pixel a whereSource
Definition of pixels used in images. Each pixel has a color space, and a representative component (Word8 or Float).
type PixelBaseComponent a :: *Source
Type of the pixel component, classical images would have Word8 type as their PixelBaseComponent, HDR image would have Float for instance
componentCount :: a -> IntSource
Return the number of component of the pixel
colorMap :: (PixelBaseComponent a -> PixelBaseComponent a) -> a -> aSource
Apply a function to all color component of a pixel.
pixelBaseIndex :: Image a -> Int -> Int -> IntSource
Calculate the index for the begining of the pixel
mutablePixelBaseIndex :: MutableImage s a -> Int -> Int -> IntSource
Calculate theindex for the begining of the pixel at position x y
pixelAt :: Image a -> Int -> Int -> aSource
Extract a pixel at a given position, (x, y), the origin is assumed to be at the corner top left, positive y to the bottom of the image
readPixel :: PrimMonad m => MutableImage (PrimState m) a -> Int -> Int -> m aSource
Same as pixelAt but for mutable images.
writePixel :: PrimMonad m => MutableImage (PrimState m) a -> Int -> Int -> a -> m ()Source
Write a pixel in a mutable image at position x y
unsafePixelAt :: Vector (PixelBaseComponent a) -> Int -> aSource
Unsafe version of pixelAt, read a pixel at the given index without bound checking (if possible). The index is expressed in number (PixelBaseComponent a)
unsafeReadPixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent a) -> Int -> m aSource
Unsafe version of readPixel, read a pixel at the given position without bound checking (if possible). The index is expressed in number (PixelBaseComponent a)
unsafeWritePixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent a) -> Int -> a -> m ()Source
Unsafe version of writePixel, write a pixel at the given position without bound checking. This can be _really_ unsafe. The index is expressed in number (PixelBaseComponent a)
The following graph describe the differents way to convert between pixel types,
- Nodes describe pixel type
- Arrows describe functions
class (Pixel a, Pixel b) => ColorSpaceConvertible a b whereSource
This class abstract colorspace conversion. This conversion can be lossy, which ColorConvertible cannot
convertPixel :: a -> bSource
Pass a pixel from a colorspace (say RGB) to the second one (say YCbCr)
convertImage :: Image a -> Image bSource
Helper function to convert a whole image by taking a copy it.
class (Pixel a, Pixel (PixelBaseComponent a)) => LumaPlaneExtractable a whereSource
Helper class to help extract a luma plane out of an image or a pixel
computeLuma :: a -> PixelBaseComponent aSource
Compute the luminance part of a pixel
extractLumaPlane :: Image a -> Image (PixelBaseComponent a)Source
Extract a luma plane out of an image. This method is in the typeclass to help performant implementation.
jpegToGrayScale :: FilePath -> FilePath -> IO () jpegToGrayScale source dest
class (Pixel a, Pixel b) => TransparentPixel a b | a -> b whereSource
Class modeling transparent pixel, should provide a method to combine transparent pixels
dropTransparency :: a -> bSource
Just return the opaque pixel value
Helper functions
dynamicMap :: (forall pixel. Pixel pixel => Image pixel -> a) -> DynamicImage -> aSource
Helper function to help extract information from dynamic image. To get the width of an dynamic image, you can use the following snippet :
dynWidth :: DynamicImage -> Int dynWidth img = dynamicMap imageWidth img
pixelMap :: forall a b. (Pixel a, Pixel b) => (a -> b) -> Image a -> Image bSource
map
equivalent for an image, working at the pixel level.
Little example : a brightness function for an rgb image
brightnessRGB8 :: Int -> Image PixelRGB8 -> Image PixelRGB8 brightnessRGB8 add = pixelMap brightFunction where up v = fromIntegral (fromIntegral v + add) brightFunction (PixelRGB8 r g b) = PixelRGB8 (up r) (up g) (up b)
pixelFold :: Pixel pixel => (acc -> Int -> Int -> pixel -> acc) -> acc -> Image pixel -> accSource
Fold over the pixel of an image with a raster scan order : from top to bottom, left to right
dropAlphaLayer :: TransparentPixel a b => Image a -> Image bSource
For any image with an alpha component (transparency), drop it, returning a pure opaque image.
:: forall m pixel . (Pixel pixel, PrimMonad m) | |
=> Int | Image width |
-> Int | Image height |
-> (Int -> Int -> m pixel) | Generating functions |
-> m (Image pixel) |
Create an image using a monadic initializer function. The function will receive value from 0 to width-1 for the x parameter and 0 to height-1 for the y parameter. The coordinate 0,0 is the upper left corner of the image, and (width-1, height-1) the lower right corner.
The function is called for each pixel in the line from left to right (0 to width - 1) and for each line (0 to height - 1).
:: forall a . Pixel a | |
=> (Int -> Int -> a) | Generating function, with |
-> Int | Width in pixels |
-> Int | Height in pixels |
-> Image a |
Create an image given a function to generate pixels. The function will receive value from 0 to width-1 for the x parameter and 0 to height-1 for the y parameter. The coordinate 0,0 is the upper left corner of the image, and (width-1, height-1) the lower right corner.
for example, to create a small gradient image :
imageCreator :: String -> Image PixelRGB8 imageCreator path = writePng path $ generateImage pixelRenderer 250 300 where pixelRenderer x y = PixelRGB8 x y 128
:: forall a acc . Pixel a | |
=> (acc -> Int -> Int -> (acc, a)) | Function taking the state, x and y |
-> acc | Initial state |
-> Int | Width in pixels |
-> Int | Height in pixels |
-> (acc, Image a) |
Create an image given a function to generate pixels. The function will receive value from 0 to width-1 for the x parameter and 0 to height-1 for the y parameter. The coordinate 0,0 is the upper left corner of the image, and (width-1, height-1) the lower right corner.
the acc parameter is a user defined one.
The function is called for each pixel in the line from left to right (0 to width - 1) and for each line (0 to height - 1).
:: PixelF | Gamma value, should be between 0.5 and 3.0 |
-> Image PixelRGBF | Image to treat. |
-> Image PixelRGBF |
Perform a gamma correction for an image with HDR pixels.
Perform a tone mapping operation on an High dynamic range image.
Color plane extraction
class ColorPlane pixel planeToken Source
Class used to describle plane present in the pixel type. If a pixel has a plane description associated, you can use the plane name to extract planes independently.
Define the plane for the red color component
data PlaneGreen Source
Define the plane for the green color component
Define the plane for the blue color component
data PlaneAlpha Source
Define the plane for the alpha (transparency) component
Define the plane for the luma component
Define plane for the cyan component of the CMYK color space.
data PlaneMagenta Source
Define plane for the magenta component of the CMYK color space.
data PlaneYellow Source
Define plane for the yellow component of the CMYK color space.
data PlaneBlack Source
Define plane for the black component of the CMYK color space.
extractComponent :: forall px plane. (Pixel px, Pixel (PixelBaseComponent px), PixelBaseComponent (PixelBaseComponent px) ~ PixelBaseComponent px, ColorPlane px plane) => plane -> Image px -> Image (PixelBaseComponent px)Source
Extract a color plane from an image given a present plane in the image examples :
extractRedPlane :: Image PixelRGB8-> Image Pixel8 extractRedPlane = extractComponent PlaneRed
:: forall a . (Pixel a, Pixel (PixelBaseComponent a), PixelBaseComponent (PixelBaseComponent a) ~ PixelBaseComponent a) | |
=> Int | The component index, beginning at 0 ending at (componentCount - 1) |
-> Image a | Source image |
-> Image (PixelBaseComponent a) |
Extract an image plane of an image, returning an image which
can be represented by a gray scale image.
If you ask a component out of bound, the error
function will
be called