Safe Haskell | None |
---|
Codec.Picture.Repa
Contents
- data Img a
- imgData :: Img a -> Array F DIM3 Word8
- convertImage :: ConvertImage a b => a -> Img b
- readImage :: DecodeImage a => FilePath -> IO (Either String (Img a))
- decodeImage :: DecodeImage a => ByteString -> Either String (Img a)
- readImageRGBA :: FilePath -> IO (Either String (Img RGBA))
- readImageRGB :: FilePath -> IO (Either String (Img RGB))
- readImageR :: FilePath -> IO (Either String (Img R))
- readImageG :: FilePath -> IO (Either String (Img G))
- readImageB :: FilePath -> IO (Either String (Img B))
- decodeImageRGBA :: ByteString -> Either String (Img RGBA)
- decodeImageRGB :: ByteString -> Either String (Img RGB)
- decodeImageR :: ByteString -> Either String (Img R)
- decodeImageG :: ByteString -> Either String (Img G)
- decodeImageB :: ByteString -> Either String (Img B)
- data RGBA
- data RGB
- data R
- data G
- data B
- toForeignPtr :: Img RGBA -> (ForeignPtr Word8, Int, Int)
- toByteString :: Img a -> ByteString
- onImg :: (Array F DIM3 Word8 -> Array F DIM3 Word8) -> Img a -> Img a
- reverseColorChannel :: Img a -> Img a
- flipHorizontally :: Array F DIM3 Word8 -> Array F DIM3 Word8
- flipVertically :: Array F DIM3 Word8 -> Array F DIM3 Word8
- vConcat :: [Array F DIM3 Word8] -> Array F DIM3 Word8
- hConcat :: [Array F DIM3 Word8] -> Array F DIM3 Word8
- class ToRGBAChannels a where
- toRGBAChannels :: a -> PixelRGBA8
Primitive types and operations
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
decodeImage :: DecodeImage a => ByteString -> Either String (Img a)Source
Monomorphic image decoding functions
decodeImageRGBA :: ByteString -> Either String (Img RGBA)Source
decodeImageRGB :: ByteString -> Either String (Img RGB)Source
decodeImageR :: ByteString -> Either String (Img R)Source
decodeImageG :: ByteString -> Either String (Img G)Source
decodeImageB :: ByteString -> Either String (Img B)Source
Image Representations (Phantom Types)
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 | |
(ToRGBAChannels a, Pixel a) => ConvertImage (Image a) RGBA |
A 24-bit image with red, green and blue channels
Instances
DecodeImage RGB | |
ConvertImage DynamicImage RGB | |
(ToRGBAChannels a, Pixel a) => ConvertImage (Image a) RGB |
An all-red image
Instances
DecodeImage R | |
ConvertImage DynamicImage R | |
(ToRGBAChannels a, Pixel a) => ConvertImage (Image a) R |
An all-green image
Instances
DecodeImage G | |
ConvertImage DynamicImage G | |
(ToRGBAChannels a, Pixel a) => ConvertImage (Image a) G |
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.
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 (or directly to
bytestring via 'repa-bytestring').
Internal Functionallity (exported for advanced uses)
class ToRGBAChannels a whereSource
Methods
toRGBAChannels :: a -> PixelRGBA8Source