JuicyPixels-repa-0.6: Convenience functions to obtain array representations of images.

Safe HaskellNone

Codec.Picture.Repa

Contents

Synopsis

Primitive types and operations

data Img a Source

Img a is an image where the phantom type a indicates the image format

All images are held in a three dimensional repa array. If the image format is only two dimensional (ex: R, G, or B) then the shape is Z :. y :. x :. 1.

convertImage :: ConvertImage a b => a -> Img bSource

Converts from JuicyPixels type (Usually Image or DynamicImage to the repa-based Img type.

Generic interface

readImage :: DecodeImage a => FilePath -> IO (Either String (Img a))Source

decodeImage :: DecodeImage a => ByteString -> Either String (Img a)Source

Monomorphic image decoding functions

Image Representations (Phantom Types)

data RGBA Source

A 32-bit image with full red, green, blue and alpha channels.

The image is stored as Height x Width x ColorChannel.

The color channel is stored in RGBA order. For the common OpenGL ordering users might want to use reverseColorChannel.

Instances

DecodeImage RGBA 
ConvertImage DynamicImage RGBA 
Collapsable RGBA (Word8, Word8, Word8) 
Collapsable RGBA (Word8, Word8, Word8, Word8) 
(ToRGBAChannels a, Pixel a) => ConvertImage (Image a) RGBA 

data RGB Source

A 24-bit image with red, green and blue channels

Instances

DecodeImage RGB 
ConvertImage DynamicImage RGB 
(ToRGBAChannels a, Pixel a) => ConvertImage (Image a) RGB 

data R Source

An all-red image

Instances

DecodeImage R 
ConvertImage DynamicImage R 
(ToRGBAChannels a, Pixel a) => ConvertImage (Image a) R 

data G Source

An all-green image

Instances

DecodeImage G 
ConvertImage DynamicImage G 
(ToRGBAChannels a, Pixel a) => ConvertImage (Image a) G 

data B Source

An all-blue image

Instances

DecodeImage B 
ConvertImage DynamicImage B 
(ToRGBAChannels a, Pixel a) => ConvertImage (Image a) B 

Helper Functions (useful for OpenGL etc.)

toForeignPtr :: Img RGBA -> (ForeignPtr Word8, Int, Int)Source

O(n) returning (pointer, length, offset)

toByteString :: Img a -> ByteStringSource

toByteString arr converts images to bytestrings, which is often useful for Gloss.

toUnboxed :: Img a -> Vector Word8Source

O(n) Convert to an unboxed vector

class Collapsable a t whereSource

Methods

collapseColorChannel :: Img a -> Array D DIM2 tSource

Converts the color channel into a tuple:

reverseColorChannel :: Img a -> Img aSource

By default, the color channel for RGBA indexes 0 -> R, 1 -> G, 2 -> B, 3 -> A. This is the AGBR byte ordering in OpenGL. For rendering with OpenGL's RGBA PixelFormat be sure to call reverseColorChannel before converting to a Vector.

Internal Functionallity (exported for advanced uses)