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

Safe HaskellNone

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)Source

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

decodeImage :: ByteString -> Either String DynamicImageSource

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 succeed will return the decoded image in it's own colorspace

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)

generateImageSource

Arguments

:: forall a . Pixel a 
=> (Int -> Int -> a)

Generating function, with x and y params.

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

generateFoldImageSource

Arguments

:: 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).

withImageSource

Arguments

:: 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).

Generic image writing

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

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

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

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

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

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

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

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

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

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

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 Source

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

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

Write an image in a file use the bitmap format.

encodeBitmap :: forall pixel. BmpEncodable pixel => Image pixel -> ByteStringSource

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

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

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

decodeBitmap :: ByteString -> Either String DynamicImageSource

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

  • PixelRGB8

encodeDynamicBitmap :: DynamicImage -> Either String ByteStringSource

Encode a dynamic image in bmp if possible, supported pixel type are :

  • RGB8
  • RGBA8
  • Y8

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

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)Source

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

readGifImages :: FilePath -> IO (Either String [Image PixelRGB8])Source

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

decodeGif :: ByteString -> Either String DynamicImageSource

Transform a raw gif image to an image, witout modifying the pixels. This function can output the following pixel types :

  • PixelRGB8

decodeGifImages :: ByteString -> Either String [Image PixelRGB8]Source

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

encodeGifImage :: Image Pixel8 -> ByteStringSource

Encode a greyscale image to a bytestring.

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

Write a greyscale in a gif file on the disk.

encodeGifImageWithPalette :: Image Pixel8 -> Palette -> Either String ByteStringSource

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

Write a gif image with a palette to a file.

  • A palette must have between 1 and 256 colors

encodeColorReducedGifImage :: Image PixelRGB8 -> Either String ByteStringSource

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

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

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

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

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

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 = IntSource

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

data GifLooping Source

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 ByteStringSource

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

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

Jpeg handling

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

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 DynamicImageSource

Try to decompress 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 convertImage from the ColorSpaceConvertible typeclass.

This function can output the following pixel types :

  • PixelY8
  • PixelYCbCr8

encodeJpeg :: Image PixelYCbCr8 -> ByteStringSource

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

encodeJpegAtQualitySource

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 whereSource

Encode an image into a png if possible.

Methods

encodePng :: Image a -> ByteStringSource

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

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

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

decodePng :: ByteString -> Either String DynamicImageSource

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 pixel types :

  • PixelY8
  • PixelY16
  • PixelYA8
  • PixelYA16
  • PixelRGB8
  • PixelRGB16
  • PixelRGBA8
  • PixelRGBA16

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

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

encodePalettedPng :: Palette -> Image Pixel8 -> Either String ByteStringSource

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

encodeDynamicPng :: DynamicImage -> Either String ByteStringSource

Encode a dynamic image in bmp if possible, supported pixel type are :

  • Y8
  • Y16
  • YA8
  • YA16
  • RGB8
  • RGB16
  • RGBA8
  • RGBA16

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

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

Tiff handling

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

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

decodeTiff :: ByteString -> Either String DynamicImageSource

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

This function can output the following pixel types :

  • PixelY8
  • PixelY16
  • PixelRGB8
  • PixelRGB16
  • PixelCMYK8
  • PixelCMYK16

encodeTiff :: forall px. TiffSaveable px => Image px -> ByteStringSource

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

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

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

HDR (Radiance/RGBE) handling

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

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

decodeHDR :: ByteString -> Either String DynamicImageSource

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

  • PixelRGBF

encodeHDR :: Image PixelRGBF -> ByteStringSource

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

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

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

Color Quantization

data PaletteCreationMethod Source

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 Source

To specify how the palette will be created.

Constructors

PaletteOptions 

Fields

paletteCreationMethod :: PaletteCreationMethod

Algorithm used to find the palette

enableImageDithering :: Bool

Do we want to apply the dithering to the image. Enabling it often reduce compression ratio but enhance the perceived quality of the final image.

paletteColorCount :: Int

Maximum number of color we want in the palette

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

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 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.

Constructors

Image 

Fields

imageWidth :: !Int

Width of the image in pixels

imageHeight :: !Int

Height of the image in pixels.

imageData :: Vector (PixelBaseComponent a)

The real image, to extract pixels at some position you should use the helpers functions.

Instances

data DynamicImage Source

Type allowing the loading of an image with different pixel structures

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

Instances

type Palette = Image PixelRGB8Source

Type for the palette used in Gif & PNG files.

Pixels

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).

Associated Types

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

Methods

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

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)

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

type Pixel8 = Word8Source

Simple alias for greyscale value in 8 bits.

type Pixel16 = Word16Source

Simple alias for greyscale value in 16 bits.

type PixelF = FloatSource

Floating greyscale value, the 0 to 255 8 bit range maps to 0 to 1 in this floating version

data PixelYA16 Source

Pixel type storing Luminance (Y) and alpha information on 16 bits. Value are stored in the following order :

  • Luminance
  • Alpha

Constructors

PixelYA16 !Pixel16 !Pixel16 

Foreign unsafe import

imageFromUnsafePtrSource

Arguments

:: forall px . (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