| Safe Haskell | Safe-Infered | 
|---|
Codec.Picture.Types
Description
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 Word8
 
- data MutableImage s a = MutableImage {}
- data  DynamicImage - = ImageY8 (Image Pixel8)
- | ImageYA8 (Image PixelYA8)
- | ImageRGB8 (Image PixelRGB8)
- | ImageRGBA8 (Image PixelRGBA8)
- | ImageYCbCr8 (Image PixelYCbCr8)
 
- data PixelType
- type Pixel8 = Word8
- data PixelYA8 = PixelYA8 !Word8 !Word8
- data PixelRGB8 = PixelRGB8 !Word8 !Word8 !Word8
- data PixelRGBA8 = PixelRGBA8 !Word8 !Word8 !Word8 !Word8
- data PixelYCbCr8 = PixelYCbCr8 !Word8 !Word8 !Word8
- class (Pixel a, Pixel b) => ColorConvertible a b  where- promotePixel :: a -> b
- promoteImage :: Image a -> Image b
 
- class Serialize a => Pixel a  where- canPromoteTo :: a -> PixelType -> Bool
- componentCount :: a -> Int
- pixelBaseIndex :: Image a -> Int -> Int -> Int
- mutablePixelBaseIndex :: MutableImage s a -> Int -> Int -> Int
- promotionType :: a -> PixelType
- pixelAt :: Image a -> Int -> Int -> a
- readPixel :: MutableImage s a -> Int -> Int -> ST s a
- writePixel :: MutableImage s a -> Int -> Int -> a -> ST s ()
 
- class (Pixel a, Pixel b) => ColorSpaceConvertible a b  where- convertPixel :: a -> b
- convertImage :: Image a -> Image b
 
- class Pixel a => LumaPlaneExtractable a  where- computeLuma :: a -> Pixel8
- extractLumaPlane :: Image a -> Image Pixel8
 
- class (Pixel a, Pixel b) => TransparentPixel a b | a -> b where- dropTransparency :: a -> b
 
- canConvertTo :: (Pixel a, Pixel b) => a -> b -> Bool
- extractComponent :: forall a. Pixel a => Int -> Image a -> Image Pixel8
- pixelMap :: forall a b. (Pixel a, Pixel b) => (a -> b) -> Image a -> Image b
- dropAlphaLayer :: TransparentPixel a b => Image a -> Image b
- 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)
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.
Constructors
| Image | |
| Fields 
 | |
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.
Constructors
| MutableImage | |
| Fields 
 | |
Instances
| NFData (MutableImage s a) | 
data DynamicImage Source
Type allowing the loading of an image with different pixel structures
Constructors
| ImageY8 (Image Pixel8) | A greyscale image. | 
| ImageYA8 (Image PixelYA8) | An image in greyscale with an alpha channel. | 
| ImageRGB8 (Image PixelRGB8) | An image in true color. | 
| ImageRGBA8 (Image PixelRGBA8) | An image in true color and an alpha channel. | 
| ImageYCbCr8 (Image PixelYCbCr8) | An image in the colorspace used by Jpeg images. | 
Instances
Describe pixel kind at runtime
Constructors
| PixelMonochromatic | For 2 bits pixels | 
| PixelGreyscale | |
| PixelGreyscaleAlpha | |
| PixelRedGreenBlue8 | |
| PixelRedGreenBlueAlpha8 | |
| PixelYChromaRChromaB8 | 
Pixel types
Pixel type storing Luminance (Y) and alpha information on 8 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
Instances
data PixelRGBA8 Source
Pixel type storing a classic pixel, with an alpha component. Values are stored in the following order
- Red
- Green
- Blue
- Alpha
Constructors
| PixelRGBA8 !Word8 !Word8 !Word8 !Word8 | 
data PixelYCbCr8 Source
Pixel storing data in the YCbCr colorspace, value are stored in the following order :
- Y (luminance)
- Cr
- Cb
Constructors
| PixelYCbCr8 !Word8 !Word8 !Word8 | 
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
Methods
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.
Instances
| Pixel a => ColorConvertible a a | Free promotion for identic pixel types | 
| ColorConvertible PixelRGB8 PixelRGBA8 | |
| ColorConvertible PixelYA8 PixelRGBA8 | |
| ColorConvertible PixelYA8 PixelRGB8 | |
| ColorConvertible Pixel8 PixelRGBA8 | |
| ColorConvertible Pixel8 PixelRGB8 | |
| ColorConvertible Pixel8 PixelYA8 | 
class Serialize a => Pixel a whereSource
Typeclass used to query a type about it's properties regarding casting to other pixel types
Methods
canPromoteTo :: a -> PixelType -> BoolSource
Tell if a pixel can be converted to another pixel,
 the first value should not be used, and undefined can
 be used as a valid value.
componentCount :: a -> IntSource
Return the number of component of the 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
promotionType :: a -> PixelTypeSource
Return the constructor associated to the type, again the value in the first parameter is not used, so you can use undefined
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 :: MutableImage s a -> Int -> Int -> ST s aSource
Same as pixelAt but for mutable images.
writePixel :: MutableImage s a -> Int -> Int -> a -> ST s ()Source
Write a pixel in a mutable image at position x y
Instances
class (Pixel a, Pixel b) => ColorSpaceConvertible a b whereSource
This class abstract colorspace conversion. This conversion can be lossy, which ColorConvertible cannot
Methods
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 => LumaPlaneExtractable a whereSource
Helper class to help extract a luma plane out of an image or a pixel
Methods
computeLuma :: a -> Pixel8Source
Compute the luminance part of a pixel
extractLumaPlane :: Image a -> Image Pixel8Source
Extract a luma plane out of an image. This method is in the typeclass to help performant implementation.
class (Pixel a, Pixel b) => TransparentPixel a b | a -> b whereSource
Class modeling transparent pixel, should provide a method to combine transparent pixels
Helper functions
canConvertTo :: (Pixel a, Pixel b) => a -> b -> BoolSource
Tell if you can convert between two pixel types, both arguments are unused.
Arguments
| :: forall a . Pixel a | |
| => Int | The component index, beginning at 0 ending at (componentCount - 1) | 
| -> Image a | Source image | 
| -> Image Pixel8 | 
Extract an image plane of an image, returning an image which can be represented by a gray scale image.
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)
dropAlphaLayer :: TransparentPixel a b => Image a -> Image bSource
For any image with an alpha component (transparency), drop it, returning a pure opaque image.
Arguments
| :: 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