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

Safe HaskellNone

Codec.Picture.Types

Contents

Description

Module providing the basic types for image manipulation in the library. Defining the types used to store all those _Juicy Pixels_

Synopsis

Types

Image types

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 Word8

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

Instances

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

mutableImageWidth :: !Int

Width of the image in pixels

mutableImageHeight :: !Int

Height of the image in pixels.

mutableImageData :: STVector s Word8

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.

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

Pixel types

type Pixel8 = Word8Source

Simple alias for greyscale value in 8 bits.

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.

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

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

Methods

dropTransparency :: a -> bSource

Just return the opaque pixel value

Helper functions

canConvertTo :: (Pixel a, Pixel b) => a -> b -> BoolSource

Tell if you can convert between two pixel types, both arguments are unused.

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.

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

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.

data PlaneRed Source

Define the plane for the red color component

Constructors

PlaneRed 

data PlaneGreen Source

Define the plane for the green color component

Constructors

PlaneGreen 

data PlaneBlue Source

Define the plane for the blue color component

Constructors

PlaneBlue 

data PlaneAlpha Source

Define the plane for the alpha (transparency) component

Constructors

PlaneAlpha 

data PlaneLuma Source

Define the plane for the luma component

Constructors

PlaneLuma 

data PlaneCr Source

Define the plane for the Cr component

Constructors

PlaneCr 

data PlaneCb Source

Define the plane for the Cb component

Constructors

PlaneCb 

extractComponent :: forall px plane. (Pixel px, ColorPlane px plane) => plane -> Image px -> Image Pixel8Source

Extract a color plane from an image given a present plane in the image examples :

  extractRedPlane :: Image PixelRGB8-> Image Pixel8
  extractRedPlane = extractComponent PlaneRed

unsafeExtractComponentSource

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. If you ask a component out of bound, the error function will be called