JuicyPixels-3.2.8.1: Picture loading/serialization (in png, jpeg, bitmap, gif, tga, tiff and radiance)

Safe HaskellNone
LanguageHaskell2010

Codec.Picture

Contents

Description

Main module for image import/export into various image formats.

To use the library without thinking about it, look after decodeImage and readImage.

Generally, the read* functions read the images from a file and try to decode it, and the decode* functions try to decode a bytestring.

For an easy image writing use the saveBmpImage, saveJpgImage & savePngImage functions

Synopsis

Generic functions

readImage :: FilePath -> IO (Either String DynamicImage) #

Load an image file without even thinking about it, it does everything as decodeImage

readImageWithMetadata :: FilePath -> IO (Either String (DynamicImage, Metadatas)) #

Equivalent to readImage but also providing metadatas.

decodeImage :: ByteString -> Either String DynamicImage #

If you want to decode an image in a bytestring without even thinking in term of format or whatever, this is the function to use. It will try to decode in each known format and if one decoding succeeds, it will return the decoded image in it's own colorspace.

decodeImageWithMetadata :: ByteString -> Either String (DynamicImage, Metadatas) #

Equivalent to decodeImage, but also provide potential metadatas present in the given file.

decodeImageWithPaletteAndMetadata :: ByteString -> Either String (PalettedImage, Metadatas) #

Equivalent to decodeImage, but also provide potential metadatas present in the given file and the palettes if the format provides them.

pixelMap :: forall a b. (Pixel a, Pixel b) => (a -> b) -> Image a -> Image b #

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)

generateImage #

Arguments

:: Pixel px 
=> (Int -> Int -> px)

Generating function, with x and y params.

-> Int

Width in pixels

-> Int

Height in pixels

-> Image px 

Create an image given a function to generate pixels. The function will receive values from 0 to width-1 for the x parameter and 0 to height-1 for the y parameter. The coordinates 0,0 are 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 -> IO ()
imageCreator path = writePng path $ generateImage pixelRenderer 250 300
   where pixelRenderer x y = PixelRGB8 (fromIntegral x) (fromIntegral y) 128

generateFoldImage #

Arguments

:: 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 values from 0 to width-1 for the x parameter and 0 to height-1 for the y parameter. The coordinates 0,0 are 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).

withImage #

Arguments

:: (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 values from 0 to width-1 for the x parameter and 0 to height-1 for the y parameter. The coordinates 0,0 are 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).

palettedToTrueColor :: PalettedImage -> DynamicImage #

Flatten a PalettedImage to a DynamicImage

RGB helper functions

convertRGB8 :: DynamicImage -> Image PixelRGB8 #

Convert by any mean possible a dynamic image to an image in RGB. The process can lose precision while converting from 16bits pixels or Floating point pixels. Any alpha layer will be dropped

convertRGBA8 :: DynamicImage -> Image PixelRGBA8 #

Convert by any mean possible a dynamic image to an image in RGBA. The process can lose precision while converting from 16bits pixels or Floating point pixels.

Lens compatibility

type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t #

Traversal type matching the definition in the Lens package.

imagePixels :: forall pxa pxb. (Pixel pxa, Pixel pxb) => Traversal (Image pxa) (Image pxb) pxa pxb #

Traversal in "raster" order, from left to right the top to bottom. This traversal is matching pixelMap in spirit.

Since 3.2.4

imageIPixels :: forall pxa pxb. (Pixel pxa, Pixel pxb) => Traversal (Image pxa) (Image pxb) (Int, Int, pxa) pxb #

Traversal providing the pixel position with it's value. The traversal in raster order, from lef to right, then top to bottom. The traversal match pixelMapXY in spirit.

Since 3.2.4

Generic image writing

saveBmpImage :: FilePath -> DynamicImage -> IO () #

Save an image to a '.bmp' file, will do everything it can to save an image.

saveJpgImage :: Int -> FilePath -> DynamicImage -> IO () #

Save an image to a '.jpg' file, will do everything it can to save an image.

saveGifImage :: FilePath -> DynamicImage -> Either String (IO ()) #

Save an image to a '.gif' file, will do everything it can to save it.

savePngImage :: FilePath -> DynamicImage -> IO () #

Save an image to a '.png' file, will do everything it can to save an image. For example, a simple transcoder to png

transcodeToPng :: FilePath -> FilePath -> IO ()
transcodeToPng pathIn pathOut = do
   eitherImg <- readImage pathIn
   case eitherImg of
       Left _ -> return ()
       Right img -> savePngImage pathOut img

saveTiffImage :: FilePath -> DynamicImage -> IO () #

Save an image to a '.tiff' file, will do everything it can to save an image.

saveRadianceImage :: FilePath -> DynamicImage -> IO () #

Save an image to a '.hdr' file, will do everything it can to save an image.

Specific image format functions

Bitmap handling

class BmpEncodable pixel #

All the instance of this class can be written as a bitmap file using this library.

Minimal complete definition

bitsPerPixel, bmpEncode

writeBitmap :: BmpEncodable pixel => FilePath -> Image pixel -> IO () #

Write an image in a file use the bitmap format.

encodeBitmap :: forall pixel. BmpEncodable pixel => Image pixel -> ByteString #

Encode an image into a bytestring in .bmp format ready to be written on disk.

readBitmap :: FilePath -> IO (Either String DynamicImage) #

Try to load a .bmp file. The colorspace would be RGB, RGBA or Y.

decodeBitmap :: ByteString -> Either String DynamicImage #

Try to decode a bitmap image. Right now this function can output the following image:

encodeDynamicBitmap :: DynamicImage -> Either String ByteString #

Encode a dynamic image in BMP if possible, supported images are:

writeDynamicBitmap :: FilePath -> DynamicImage -> IO (Either String Bool) #

Write a dynamic image in a .bmp image file if possible. The same restriction as encodeDynamicBitmap apply.

Gif handling

readGif :: FilePath -> IO (Either String DynamicImage) #

Helper function trying to load a gif file from a file on disk.

readGifImages :: FilePath -> IO (Either String [DynamicImage]) #

Helper function trying to load all the images of an animated gif file.

decodeGif :: ByteString -> Either String DynamicImage #

Transform a raw gif image to an image, without modifying the pixels. This function can output the following images:

decodeGifImages :: ByteString -> Either String [DynamicImage] #

Transform a raw gif to a list of images, representing all the images of an animation.

encodeGifImage :: Image Pixel8 -> ByteString #

Encode a greyscale image to a bytestring.

writeGifImage :: FilePath -> Image Pixel8 -> IO () #

Write a greyscale in a gif file on the disk.

encodeGifImageWithPalette :: Image Pixel8 -> Palette -> Either String ByteString #

Encode an image with a given palette. Can return errors if the palette is ill-formed.

  • A palette must have between 1 and 256 colors

writeGifImageWithPalette :: FilePath -> Image Pixel8 -> Palette -> Either String (IO ()) #

Write a gif image with a palette to a file.

  • A palette must have between 1 and 256 colors

encodeColorReducedGifImage :: Image PixelRGB8 -> Either String ByteString #

Encode a full color image to a gif by applying a color quantization algorithm on it.

writeColorReducedGifImage :: FilePath -> Image PixelRGB8 -> Either String (IO ()) #

Write a full color image to a gif by applying a color quantization algorithm on it.

encodeGifImages :: GifLooping -> [(Palette, GifDelay, Image Pixel8)] -> Either String ByteString #

Encode a gif animation to a bytestring.

  • Every image must have the same size
  • Every palette must have between one and 256 colors.

writeGifImages :: FilePath -> GifLooping -> [(Palette, GifDelay, Image Pixel8)] -> Either String (IO ()) #

Write a list of images as a gif animation in a file.

  • Every image must have the same size
  • Every palette must have between one and 256 colors.

Gif animation

type GifDelay = Int #

Delay to wait before showing the next Gif image. The delay is expressed in 100th of seconds.

data GifLooping #

Help to control the behaviour of GIF animation looping.

Constructors

LoopingNever

The animation will stop once the end is reached

LoopingForever

The animation will restart once the end is reached

LoopingRepeat Word16

The animation will repeat n times before stoping

encodeGifAnimation :: GifDelay -> GifLooping -> [Image PixelRGB8] -> Either String ByteString #

Helper function to create a gif animation. All the images of the animation are separated by the same delay.

writeGifAnimation :: FilePath -> GifDelay -> GifLooping -> [Image PixelRGB8] -> Either String (IO ()) #

Helper function to write a gif animation on disk. See encodeGifAnimation

Jpeg handling

readJpeg :: FilePath -> IO (Either String DynamicImage) #

Try to load a jpeg file and decompress. The colorspace is still YCbCr if you want to perform computation on the luma part. You can convert it to RGB using colorSpaceConversion.

decodeJpeg :: ByteString -> Either String DynamicImage #

Try to decompress and decode a jpeg file. The colorspace is still YCbCr if you want to perform computation on the luma part. You can convert it to RGB using convertImage from the ColorSpaceConvertible typeclass.

This function can output the following images:

encodeJpeg :: Image PixelYCbCr8 -> ByteString #

Encode an image in jpeg at a reasonnable quality level. If you want better quality or reduced file size, you should use encodeJpegAtQuality

encodeJpegAtQuality #

Arguments

:: Word8

Quality factor

-> Image PixelYCbCr8

Image to encode

-> ByteString

Encoded JPEG

Function to call to encode an image to jpeg. The quality factor should be between 0 and 100 (100 being the best quality).

Png handling

class PngSavable a where #

Encode an image into a png if possible.

Minimal complete definition

encodePngWithMetadata

Methods

encodePng :: Image a -> ByteString #

Transform an image into a png encoded bytestring, ready to be written as a file.

encodePngWithMetadata :: Metadatas -> Image a -> ByteString #

Encode a png using some metadatas. The following metadata keys will be stored in a tEXt field :

the followings metadata will bes tored in the gAMA chunk.

The followings metadata will be stored in a pHYs chunk

readPng :: FilePath -> IO (Either String DynamicImage) #

Helper function trying to load a png file from a file on disk.

decodePng :: ByteString -> Either String DynamicImage #

Transform a raw png image to an image, without modifying the underlying pixel type. If the image is greyscale and < 8 bits, a transformation to RGBA8 is performed. This should change in the future. The resulting image let you manage the pixel types.

This function can output the following images:

writePng :: PngSavable pixel => FilePath -> Image pixel -> IO () #

Helper function to directly write an image as a png on disk.

encodePalettedPng :: Palette -> Image Pixel8 -> Either String ByteString #

Encode a paletted image as a color indexed 8-bit PNG. the palette must have between 1 and 256 values in it.

writeDynamicPng :: FilePath -> DynamicImage -> IO (Either String Bool) #

Write a dynamic image in a .png image file if possible. The same restriction as encodeDynamicPng apply.

TGA handling

readTGA :: FilePath -> IO (Either String DynamicImage) #

Try to load a .tga file from disk.

decodeTga :: ByteString -> Either String DynamicImage #

Transform a raw tga image to an image, without modifying the underlying pixel type.

This function can output the following images:

class TgaSaveable a #

This typeclass determine if a pixel can be saved in the TGA format.

Minimal complete definition

tgaDataOfImage, tgaPixelDepthOfImage, tgaTypeOfImage

encodeTga :: TgaSaveable px => Image px -> ByteString #

Transform a compatible image to a raw bytestring representing a Targa file.

writeTga :: TgaSaveable pixel => FilePath -> Image pixel -> IO () #

Helper function to directly write an image a tga on disk.

Tiff handling

readTiff :: FilePath -> IO (Either String DynamicImage) #

Helper function trying to load tiff file from a file on disk.

class Pixel px => TiffSaveable px #

Class defining which pixel types can be serialized in a Tiff file.

Minimal complete definition

colorSpaceOfPixel

Instances

TiffSaveable PixelRGBA16 # 
TiffSaveable PixelRGBA8 # 
TiffSaveable PixelCMYK16 # 
TiffSaveable PixelCMYK8 # 
TiffSaveable PixelYCbCr8 # 
TiffSaveable PixelRGB16 # 
TiffSaveable PixelRGB8 # 
TiffSaveable PixelYA16 # 
TiffSaveable PixelYA8 # 
TiffSaveable Pixel16 # 
TiffSaveable Pixel8 # 

decodeTiff :: ByteString -> Either String DynamicImage #

Decode a tiff encoded image while preserving the underlying pixel type (except for Y32 which is truncated to 16 bits).

This function can output the following images:

encodeTiff :: forall px. TiffSaveable px => Image px -> ByteString #

Transform an image into a Tiff encoded bytestring, ready to be written as a file.

writeTiff :: TiffSaveable pixel => FilePath -> Image pixel -> IO () #

Helper function to directly write an image as a tiff on disk.

HDR (Radiance/RGBE) handling

readHDR :: FilePath -> IO (Either String DynamicImage) #

Try to load a .pic file. The colorspace can only be RGB with floating point precision.

decodeHDR :: ByteString -> Either String DynamicImage #

Decode an HDR (radiance) image, the resulting image can be:

encodeHDR :: Image PixelRGBF -> ByteString #

Encode an High dynamic range image into a radiance image file format. Alias for encodeRawHDR

writeHDR :: FilePath -> Image PixelRGBF -> IO () #

Write an High dynamic range image into a radiance image file on disk.

Color Quantization

data PaletteCreationMethod #

Define which palette creation method is used.

Constructors

MedianMeanCut

MedianMeanCut method, provide the best results (visualy) at the cost of increased calculations.

Uniform

Very fast algorithm (one pass), doesn't provide good looking results.

data PaletteOptions #

To specify how the palette will be created.

Constructors

PaletteOptions 

Fields

palettize :: PaletteOptions -> Image PixelRGB8 -> (Image Pixel8, Palette) #

Reduces an image to a color palette according to PaletteOpts and returns the indices image along with its Palette.

Image types and pixel types

Image

data Image a #

The main type of this package, one that most functions work on, is Image.

Parameterized by the underlying pixel format it forms a rigid type. If you wish to store images of different or unknown pixel formats use DynamicImage.

Image is essentially a rectangular pixel buffer of specified width and height. The coordinates are assumed to start from the upper-left corner of the image, with the horizontal position first and vertical second.

Constructors

Image 

Fields

  • imageWidth :: !Int

    Width of the image in pixels

  • imageHeight :: !Int

    Height of the image in pixels.

  • imageData :: Vector (PixelBaseComponent a)

    Image pixel data. To extract pixels at a given position you should use the helper functions.

    Internally pixel data is stored as consecutively packed lines from top to bottom, scanned from left to right within individual lines, from first to last color component within each pixel.

Instances

NFData (Image a) # 

Methods

rnf :: Image a -> () #

data DynamicImage #

Image type enumerating all predefined pixel types. It enables loading and use of images of different pixel types.

Constructors

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 bits precision

Instances

type Palette = Image PixelRGB8 #

Type for the palette used in Gif & PNG files.

Pixels

class (Storable (PixelBaseComponent a), Num (PixelBaseComponent a), Eq a) => Pixel a where #

Definition of pixels used in images. Each pixel has a color space, and a representative component (Word8 or Float).

Associated Types

type PixelBaseComponent a :: * #

Type of the pixel component, "classical" images would have Word8 type as their PixelBaseComponent, HDR image would have Float for instance

Methods

mixWith :: (Int -> PixelBaseComponent a -> PixelBaseComponent a -> PixelBaseComponent a) -> a -> a -> a #

Call the function for every component of the pixels. For example for RGB pixels mixWith is declared like this:

mixWith f (PixelRGB8 ra ga ba) (PixelRGB8 rb gb bb) =
   PixelRGB8 (f 0 ra rb) (f 1 ga gb) (f 2 ba bb)

mixWithAlpha :: (Int -> PixelBaseComponent a -> PixelBaseComponent a -> PixelBaseComponent a) -> (PixelBaseComponent a -> PixelBaseComponent a -> PixelBaseComponent a) -> a -> a -> a #

Extension of the mixWith which separate the treatment of the color components of the alpha value (transparency component). For pixel without alpha components, it is equivalent to mixWith.

mixWithAlpha f fa (PixelRGBA8 ra ga ba aa) (PixelRGB8 rb gb bb ab) =
   PixelRGBA8 (f 0 ra rb) (f 1 ga gb) (f 2 ba bb) (fa aa ab)

pixelOpacity :: a -> PixelBaseComponent a #

Return the opacity of a pixel, if the pixel has an alpha layer, return the alpha value. If the pixel doesn't have an alpha value, return a value representing the opaqueness.

componentCount :: a -> Int #

Return the number of components of the pixel

colorMap :: (PixelBaseComponent a -> PixelBaseComponent a) -> a -> a #

Apply a function to each component of a pixel. If the color type possess an alpha (transparency channel), it is treated like the other color components.

pixelBaseIndex :: Image a -> Int -> Int -> Int #

Calculate the index for the begining of the pixel

mutablePixelBaseIndex :: MutableImage s a -> Int -> Int -> Int #

Calculate theindex for the begining of the pixel at position x y

pixelAt :: Image a -> Int -> Int -> a #

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 a #

Same as pixelAt but for mutable images.

writePixel :: PrimMonad m => MutableImage (PrimState m) a -> Int -> Int -> a -> m () #

Write a pixel in a mutable image at position x y

unsafePixelAt :: Vector (PixelBaseComponent a) -> Int -> a #

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 a #

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 () #

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)

Instances

Pixel PixelRGBA16 # 
Pixel PixelRGBA8 # 
Pixel PixelCMYK16 # 
Pixel PixelCMYK8 # 
Pixel PixelYCbCr8 # 
Pixel PixelRGBF # 
Pixel PixelRGB16 # 
Pixel PixelYCbCrK8 # 
Pixel PixelRGB8 # 
Pixel PixelYA16 # 
Pixel PixelYA8 # 
Pixel PixelF # 
Pixel Pixel32 # 
Pixel Pixel16 # 
Pixel Pixel8 # 

type Pixel8 = Word8 #

Type alias for 8bit greyscale pixels. For simplicity, greyscale pixels use plain numbers instead of a separate type.

type Pixel16 = Word16 #

Type alias for 16bit greyscale pixels.

type PixelF = Float #

Type alias for 32bit floating point greyscale pixels. The standard bounded value range is mapped to the closed interval [0,1] i.e.

map promotePixel [0, 1 .. 255 :: Pixel8] == [0/255, 1/255 .. 1.0 :: PixelF]

data PixelYA8 #

Pixel type storing 8bit Luminance (Y) and alpha (A) information. Values are stored in the following order:

  • Luminance
  • Alpha

Constructors

PixelYA8 !Pixel8 !Pixel8 

Instances

Eq PixelYA8 # 
Ord PixelYA8 # 
Show PixelYA8 # 
PackeablePixel PixelYA8 # 
LumaPlaneExtractable PixelYA8 # 
Pixel PixelYA8 # 
PngSavable PixelYA8 # 
TiffSaveable PixelYA8 # 
ColorConvertible PixelYA8 PixelRGBA8 # 
ColorConvertible PixelYA8 PixelRGB8 # 
ColorConvertible Pixel8 PixelYA8 # 
TransparentPixel PixelYA8 Pixel8 # 
ColorPlane PixelYA8 PlaneLuma # 
ColorPlane PixelYA8 PlaneAlpha # 
type PackedRepresentation PixelYA8 # 
type PixelBaseComponent PixelYA8 # 

data PixelYA16 #

Pixel type storing 16bit Luminance (Y) and alpha (A) information. Values are stored in the following order:

  • Luminance
  • Alpha

Constructors

PixelYA16 !Pixel16 !Pixel16 

Instances

Eq PixelYA16 # 
Ord PixelYA16 # 
Show PixelYA16 # 
PackeablePixel PixelYA16 # 
Pixel PixelYA16 # 
PngSavable PixelYA16 # 
TiffSaveable PixelYA16 # 
ColorConvertible PixelYA16 PixelRGBA16 # 
ColorConvertible Pixel16 PixelYA16 # 
TransparentPixel PixelYA16 Pixel16 # 
ColorPlane PixelYA16 PlaneLuma # 
ColorPlane PixelYA16 PlaneAlpha # 
type PackedRepresentation PixelYA16 # 
type PixelBaseComponent PixelYA16 # 

data PixelRGB8 #

Classic pixel type storing 8bit red, green and blue (RGB) information. Values are stored in the following order:

  • Red
  • Green
  • Blue

Constructors

PixelRGB8 !Pixel8 !Pixel8 !Pixel8 

Instances

Eq PixelRGB8 # 
Ord PixelRGB8 # 
Show PixelRGB8 # 
LumaPlaneExtractable PixelRGB8 # 
Pixel PixelRGB8 # 
PngSavable PixelRGB8 # 
TgaSaveable PixelRGB8 # 
BmpEncodable PixelRGB8 # 
JpgEncodable PixelRGB8 # 

Methods

additionalBlocks :: Image PixelRGB8 -> [JpgFrame]

componentsOfColorSpace :: Image PixelRGB8 -> [JpgComponent]

encodingState :: Int -> Image PixelRGB8 -> Vector EncoderState

imageHuffmanTables :: Image PixelRGB8 -> [(JpgHuffmanTableSpec, HuffmanPackedTree)]

scanSpecificationOfColorSpace :: Image PixelRGB8 -> [JpgScanSpecification]

quantTableSpec :: Image PixelRGB8 -> Int -> [JpgQuantTableSpec]

maximumSubSamplingOf :: Image PixelRGB8 -> Int

TiffSaveable PixelRGB8 # 
ColorSpaceConvertible PixelCMYK8 PixelRGB8 # 
ColorSpaceConvertible PixelYCbCr8 PixelRGB8 # 
ColorSpaceConvertible PixelYCbCrK8 PixelRGB8 # 
ColorSpaceConvertible PixelRGB8 PixelCMYK8 # 
ColorSpaceConvertible PixelRGB8 PixelYCbCr8 # 
ColorConvertible PixelRGB8 PixelRGBA16 # 
ColorConvertible PixelRGB8 PixelRGBA8 # 
ColorConvertible PixelRGB8 PixelRGBF # 
ColorConvertible PixelRGB8 PixelRGB16 # 
ColorConvertible PixelYA8 PixelRGB8 # 
ColorConvertible Pixel8 PixelRGB8 # 
TransparentPixel PixelRGBA8 PixelRGB8 # 
ColorPlane PixelRGB8 PlaneBlue # 
ColorPlane PixelRGB8 PlaneGreen # 
ColorPlane PixelRGB8 PlaneRed # 
type PixelBaseComponent PixelRGB8 # 

data PixelRGB16 #

Pixel type storing 16bit red, green and blue (RGB) information. Values are stored in the following order:

  • Red
  • Green
  • Blue

Instances

Eq PixelRGB16 # 
Ord PixelRGB16 # 
Show PixelRGB16 # 
LumaPlaneExtractable PixelRGB16 # 
Pixel PixelRGB16 # 
PngSavable PixelRGB16 # 
TiffSaveable PixelRGB16 # 
ColorSpaceConvertible PixelCMYK16 PixelRGB16 # 
ColorSpaceConvertible PixelRGB16 PixelCMYK16 # 
ColorConvertible PixelRGB16 PixelRGBA16 # 
ColorConvertible PixelRGB8 PixelRGB16 # 
ColorConvertible Pixel16 PixelRGB16 # 
TransparentPixel PixelRGBA16 PixelRGB16 # 
ColorPlane PixelRGB16 PlaneBlue # 
ColorPlane PixelRGB16 PlaneGreen # 
ColorPlane PixelRGB16 PlaneRed # 
type PixelBaseComponent PixelRGB16 # 

data PixelRGBF #

HDR pixel type storing floating point 32bit red, green and blue (RGB) information. Same value range and comments apply as for PixelF. Values are stored in the following order:

  • Red
  • Green
  • Blue

Constructors

PixelRGBF !PixelF !PixelF !PixelF 

Instances

Eq PixelRGBF # 
Ord PixelRGBF # 
Show PixelRGBF # 
LumaPlaneExtractable PixelRGBF # 
Pixel PixelRGBF # 
ColorConvertible PixelRGB8 PixelRGBF # 
ColorConvertible PixelF PixelRGBF # 
ColorPlane PixelRGBF PlaneBlue # 
ColorPlane PixelRGBF PlaneGreen # 
ColorPlane PixelRGBF PlaneRed # 
type PixelBaseComponent PixelRGBF # 

data PixelRGBA8 #

Classical pixel type storing 8bit red, green, blue and alpha (RGBA) information. Values are stored in the following order:

  • Red
  • Green
  • Blue
  • Alpha

Instances

Eq PixelRGBA8 # 
Ord PixelRGBA8 # 
Show PixelRGBA8 # 
PackeablePixel PixelRGBA8 # 
LumaPlaneExtractable PixelRGBA8 # 
Pixel PixelRGBA8 # 
PngSavable PixelRGBA8 # 
TgaSaveable PixelRGBA8 # 
BmpEncodable PixelRGBA8 # 
TiffSaveable PixelRGBA8 # 
ColorConvertible PixelRGBA8 PixelRGBA16 # 
ColorConvertible PixelRGB8 PixelRGBA8 # 
ColorConvertible PixelYA8 PixelRGBA8 # 
ColorConvertible Pixel8 PixelRGBA8 # 
TransparentPixel PixelRGBA8 PixelRGB8 # 
ColorPlane PixelRGBA8 PlaneAlpha # 
ColorPlane PixelRGBA8 PlaneBlue # 
ColorPlane PixelRGBA8 PlaneGreen # 
ColorPlane PixelRGBA8 PlaneRed # 
type PackedRepresentation PixelRGBA8 # 
type PixelBaseComponent PixelRGBA8 # 

data PixelRGBA16 #

Pixel type storing 16bit red, green, blue and alpha (RGBA) information. Values are stored in the following order:

  • Red
  • Green
  • Blue
  • Alpha

Instances

Eq PixelRGBA16 # 
Ord PixelRGBA16 # 
Show PixelRGBA16 # 
PackeablePixel PixelRGBA16 # 
Pixel PixelRGBA16 # 
PngSavable PixelRGBA16 # 
TiffSaveable PixelRGBA16 # 
ColorConvertible PixelRGBA8 PixelRGBA16 # 
ColorConvertible PixelRGB16 PixelRGBA16 # 
ColorConvertible PixelRGB8 PixelRGBA16 # 
ColorConvertible PixelYA16 PixelRGBA16 # 
ColorConvertible Pixel16 PixelRGBA16 # 
TransparentPixel PixelRGBA16 PixelRGB16 # 
ColorPlane PixelRGBA16 PlaneAlpha # 
ColorPlane PixelRGBA16 PlaneBlue # 
ColorPlane PixelRGBA16 PlaneGreen # 
ColorPlane PixelRGBA16 PlaneRed # 
type PackedRepresentation PixelRGBA16 # 
type PixelBaseComponent PixelRGBA16 # 

data PixelYCbCr8 #

Pixel type storing 8bit luminance, blue difference and red difference (YCbCr) information. Values are stored in the following order:

  • Y (luminance)
  • Cb
  • Cr

Constructors

PixelYCbCr8 !Pixel8 !Pixel8 !Pixel8 

Instances

Eq PixelYCbCr8 # 
Ord PixelYCbCr8 # 
Show PixelYCbCr8 # 
LumaPlaneExtractable PixelYCbCr8 # 
Pixel PixelYCbCr8 # 
JpgEncodable PixelYCbCr8 # 

Methods

additionalBlocks :: Image PixelYCbCr8 -> [JpgFrame]

componentsOfColorSpace :: Image PixelYCbCr8 -> [JpgComponent]

encodingState :: Int -> Image PixelYCbCr8 -> Vector EncoderState

imageHuffmanTables :: Image PixelYCbCr8 -> [(JpgHuffmanTableSpec, HuffmanPackedTree)]

scanSpecificationOfColorSpace :: Image PixelYCbCr8 -> [JpgScanSpecification]

quantTableSpec :: Image PixelYCbCr8 -> Int -> [JpgQuantTableSpec]

maximumSubSamplingOf :: Image PixelYCbCr8 -> Int

TiffSaveable PixelYCbCr8 # 
ColorSpaceConvertible PixelYCbCr8 PixelRGB8 # 
ColorSpaceConvertible PixelRGB8 PixelYCbCr8 # 
ColorPlane PixelYCbCr8 PlaneCb # 
ColorPlane PixelYCbCr8 PlaneCr # 
ColorPlane PixelYCbCr8 PlaneLuma # 
type PixelBaseComponent PixelYCbCr8 # 

data PixelCMYK8 #

Pixel type storing 8bit cyan, magenta, yellow and black (CMYK) information. Values are stored in the following order:

  • Cyan
  • Magenta
  • Yellow
  • Black

Instances

Eq PixelCMYK8 # 
Ord PixelCMYK8 # 
Show PixelCMYK8 # 
PackeablePixel PixelCMYK8 # 
Pixel PixelCMYK8 # 
JpgEncodable PixelCMYK8 # 

Methods

additionalBlocks :: Image PixelCMYK8 -> [JpgFrame]

componentsOfColorSpace :: Image PixelCMYK8 -> [JpgComponent]

encodingState :: Int -> Image PixelCMYK8 -> Vector EncoderState

imageHuffmanTables :: Image PixelCMYK8 -> [(JpgHuffmanTableSpec, HuffmanPackedTree)]

scanSpecificationOfColorSpace :: Image PixelCMYK8 -> [JpgScanSpecification]

quantTableSpec :: Image PixelCMYK8 -> Int -> [JpgQuantTableSpec]

maximumSubSamplingOf :: Image PixelCMYK8 -> Int

TiffSaveable PixelCMYK8 # 
ColorSpaceConvertible PixelCMYK8 PixelRGB8 # 
ColorSpaceConvertible PixelYCbCrK8 PixelCMYK8 # 
ColorSpaceConvertible PixelRGB8 PixelCMYK8 # 
ColorPlane PixelCMYK8 PlaneBlack # 
ColorPlane PixelCMYK8 PlaneYellow # 
ColorPlane PixelCMYK8 PlaneMagenta # 
ColorPlane PixelCMYK8 PlaneCyan # 
type PackedRepresentation PixelCMYK8 # 
type PixelBaseComponent PixelCMYK8 # 

data PixelCMYK16 #

Pixel type storing 16bit cyan, magenta, yellow and black (CMYK) information. Values are stored in the following order:

  • Cyan
  • Magenta
  • Yellow
  • Black

Instances

Eq PixelCMYK16 # 
Ord PixelCMYK16 # 
Show PixelCMYK16 # 
PackeablePixel PixelCMYK16 # 
Pixel PixelCMYK16 # 
TiffSaveable PixelCMYK16 # 
ColorSpaceConvertible PixelCMYK16 PixelRGB16 # 
ColorSpaceConvertible PixelRGB16 PixelCMYK16 # 
ColorPlane PixelCMYK16 PlaneBlack # 
ColorPlane PixelCMYK16 PlaneYellow # 
ColorPlane PixelCMYK16 PlaneMagenta # 
ColorPlane PixelCMYK16 PlaneCyan # 
type PackedRepresentation PixelCMYK16 # 
type PixelBaseComponent PixelCMYK16 # 

Foreign unsafe import

imageFromUnsafePtr #

Arguments

:: (Pixel px, PixelBaseComponent px ~ Word8) 
=> Int

Width in pixels

-> Int

Height in pixels

-> ForeignPtr Word8

Pointer to the raw data

-> Image px 

Import a image from an unsafe pointer The pointer must have a size of width * height * componentCount px