Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- readImage :: FilePath -> IO (Either String DynamicImage)
- readImageWithMetadata :: FilePath -> IO (Either String (DynamicImage, Metadatas))
- decodeImage :: ByteString -> Either String DynamicImage
- decodeImageWithMetadata :: ByteString -> Either String (DynamicImage, Metadatas)
- decodeImageWithPaletteAndMetadata :: ByteString -> Either String (PalettedImage, Metadatas)
- pixelMap :: forall a b. (Pixel a, Pixel b) => (a -> b) -> Image a -> Image b
- dynamicMap :: (forall pixel. Pixel pixel => Image pixel -> a) -> DynamicImage -> a
- dynamicPixelMap :: (forall pixel. Pixel pixel => Image pixel -> Image pixel) -> DynamicImage -> DynamicImage
- generateImage :: forall px. Pixel px => (Int -> Int -> px) -> Int -> Int -> Image px
- generateFoldImage :: forall a acc. Pixel a => (acc -> Int -> Int -> (acc, a)) -> acc -> Int -> Int -> (acc, Image a)
- withImage :: forall m pixel. (Pixel pixel, PrimMonad m) => Int -> Int -> (Int -> Int -> m pixel) -> m (Image pixel)
- palettedToTrueColor :: PalettedImage -> DynamicImage
- convertRGB8 :: DynamicImage -> Image PixelRGB8
- convertRGB16 :: DynamicImage -> Image PixelRGB16
- convertRGBA8 :: DynamicImage -> Image PixelRGBA8
- type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t
- imagePixels :: forall pxa pxb. (Pixel pxa, Pixel pxb) => Traversal (Image pxa) (Image pxb) pxa pxb
- imageIPixels :: forall pxa pxb. (Pixel pxa, Pixel pxb) => Traversal (Image pxa) (Image pxb) (Int, Int, pxa) pxb
- saveBmpImage :: FilePath -> DynamicImage -> IO ()
- saveJpgImage :: Int -> FilePath -> DynamicImage -> IO ()
- saveGifImage :: FilePath -> DynamicImage -> Either String (IO ())
- savePngImage :: FilePath -> DynamicImage -> IO ()
- saveTiffImage :: FilePath -> DynamicImage -> IO ()
- saveRadianceImage :: FilePath -> DynamicImage -> IO ()
- class BmpEncodable pixel
- writeBitmap :: BmpEncodable pixel => FilePath -> Image pixel -> IO ()
- encodeBitmap :: forall pixel. BmpEncodable pixel => Image pixel -> ByteString
- readBitmap :: FilePath -> IO (Either String DynamicImage)
- decodeBitmap :: ByteString -> Either String DynamicImage
- encodeDynamicBitmap :: DynamicImage -> Either String ByteString
- writeDynamicBitmap :: FilePath -> DynamicImage -> IO (Either String Bool)
- readGif :: FilePath -> IO (Either String DynamicImage)
- readGifImages :: FilePath -> IO (Either String [DynamicImage])
- decodeGif :: ByteString -> Either String DynamicImage
- decodeGifImages :: ByteString -> Either String [DynamicImage]
- encodeGifImage :: Image Pixel8 -> ByteString
- writeGifImage :: FilePath -> Image Pixel8 -> IO ()
- encodeGifImageWithPalette :: Image Pixel8 -> Palette -> Either String ByteString
- writeGifImageWithPalette :: FilePath -> Image Pixel8 -> Palette -> Either String (IO ())
- encodeColorReducedGifImage :: Image PixelRGB8 -> Either String ByteString
- writeColorReducedGifImage :: FilePath -> Image PixelRGB8 -> Either String (IO ())
- encodeGifImages :: GifLooping -> [(Palette, GifDelay, Image Pixel8)] -> Either String ByteString
- writeGifImages :: FilePath -> GifLooping -> [(Palette, GifDelay, Image Pixel8)] -> Either String (IO ())
- type GifDelay = Int
- data GifLooping
- encodeGifAnimation :: GifDelay -> GifLooping -> [Image PixelRGB8] -> Either String ByteString
- writeGifAnimation :: FilePath -> GifDelay -> GifLooping -> [Image PixelRGB8] -> Either String (IO ())
- readJpeg :: FilePath -> IO (Either String DynamicImage)
- decodeJpeg :: ByteString -> Either String DynamicImage
- encodeJpeg :: Image PixelYCbCr8 -> ByteString
- encodeJpegAtQuality :: Word8 -> Image PixelYCbCr8 -> ByteString
- class PngSavable a where
- encodePng :: Image a -> ByteString
- encodePngWithMetadata :: Metadatas -> Image a -> ByteString
- readPng :: FilePath -> IO (Either String DynamicImage)
- decodePng :: ByteString -> Either String DynamicImage
- writePng :: PngSavable pixel => FilePath -> Image pixel -> IO ()
- encodePalettedPng :: PngPaletteSaveable a => Image a -> Image Pixel8 -> Either String ByteString
- encodeDynamicPng :: DynamicImage -> Either String ByteString
- writeDynamicPng :: FilePath -> DynamicImage -> IO (Either String Bool)
- readTGA :: FilePath -> IO (Either String DynamicImage)
- decodeTga :: ByteString -> Either String DynamicImage
- class TgaSaveable a
- encodeTga :: TgaSaveable px => Image px -> ByteString
- writeTga :: TgaSaveable pixel => FilePath -> Image pixel -> IO ()
- readTiff :: FilePath -> IO (Either String DynamicImage)
- class Pixel px => TiffSaveable px
- decodeTiff :: ByteString -> Either String DynamicImage
- encodeTiff :: forall px. TiffSaveable px => Image px -> ByteString
- writeTiff :: TiffSaveable pixel => FilePath -> Image pixel -> IO ()
- readHDR :: FilePath -> IO (Either String DynamicImage)
- decodeHDR :: ByteString -> Either String DynamicImage
- encodeHDR :: Image PixelRGBF -> ByteString
- writeHDR :: FilePath -> Image PixelRGBF -> IO ()
- data PaletteCreationMethod
- data PaletteOptions = PaletteOptions {}
- palettize :: PaletteOptions -> Image PixelRGB8 -> (Image Pixel8, Palette)
- data Image a = Image {
- imageWidth :: !Int
- imageHeight :: !Int
- imageData :: Vector (PixelBaseComponent a)
- data DynamicImage
- = ImageY8 (Image Pixel8)
- | ImageY16 (Image Pixel16)
- | ImageY32 (Image Pixel32)
- | ImageYF (Image PixelF)
- | ImageYA8 (Image PixelYA8)
- | ImageYA16 (Image PixelYA16)
- | ImageRGB8 (Image PixelRGB8)
- | ImageRGB16 (Image PixelRGB16)
- | ImageRGBF (Image PixelRGBF)
- | ImageRGBA8 (Image PixelRGBA8)
- | ImageRGBA16 (Image PixelRGBA16)
- | ImageYCbCr8 (Image PixelYCbCr8)
- | ImageCMYK8 (Image PixelCMYK8)
- | ImageCMYK16 (Image PixelCMYK16)
- type Palette = Image PixelRGB8
- class (Storable (PixelBaseComponent a), Num (PixelBaseComponent a), Eq a) => Pixel a where
- type PixelBaseComponent a :: *
- mixWith :: (Int -> PixelBaseComponent a -> PixelBaseComponent a -> PixelBaseComponent a) -> a -> a -> a
- mixWithAlpha :: (Int -> PixelBaseComponent a -> PixelBaseComponent a -> PixelBaseComponent a) -> (PixelBaseComponent a -> PixelBaseComponent a -> PixelBaseComponent a) -> a -> a -> a
- pixelOpacity :: a -> PixelBaseComponent a
- componentCount :: a -> Int
- colorMap :: (PixelBaseComponent a -> PixelBaseComponent a) -> a -> a
- pixelBaseIndex :: Image a -> Int -> Int -> Int
- mutablePixelBaseIndex :: MutableImage s a -> Int -> Int -> Int
- pixelAt :: Image a -> Int -> Int -> a
- readPixel :: PrimMonad m => MutableImage (PrimState m) a -> Int -> Int -> m a
- writePixel :: PrimMonad m => MutableImage (PrimState m) a -> Int -> Int -> a -> m ()
- unsafePixelAt :: Vector (PixelBaseComponent a) -> Int -> a
- unsafeReadPixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent a) -> Int -> m a
- unsafeWritePixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent a) -> Int -> a -> m ()
- type Pixel8 = Word8
- type Pixel16 = Word16
- type Pixel32 = Word32
- type PixelF = Float
- data PixelYA8 = PixelYA8 !Pixel8 !Pixel8
- data PixelYA16 = PixelYA16 !Pixel16 !Pixel16
- data PixelRGB8 = PixelRGB8 !Pixel8 !Pixel8 !Pixel8
- data PixelRGB16 = PixelRGB16 !Pixel16 !Pixel16 !Pixel16
- data PixelRGBF = PixelRGBF !PixelF !PixelF !PixelF
- data PixelRGBA8 = PixelRGBA8 !Pixel8 !Pixel8 !Pixel8 !Pixel8
- data PixelRGBA16 = PixelRGBA16 !Pixel16 !Pixel16 !Pixel16 !Pixel16
- data PixelYCbCr8 = PixelYCbCr8 !Pixel8 !Pixel8 !Pixel8
- data PixelCMYK8 = PixelCMYK8 !Pixel8 !Pixel8 !Pixel8 !Pixel8
- data PixelCMYK16 = PixelCMYK16 !Pixel16 !Pixel16 !Pixel16 !Pixel16
- imageFromUnsafePtr :: forall px. (Pixel px, PixelBaseComponent px ~ Word8) => Int -> Int -> ForeignPtr Word8 -> Image px
Generic functions
readImage :: FilePath -> IO (Either String DynamicImage) Source #
Load an image file without even thinking about it, it does everything
as decodeImage
readImageWithMetadata :: FilePath -> IO (Either String (DynamicImage, Metadatas)) Source #
Equivalent to readImage
but also providing metadatas.
decodeImage :: ByteString -> Either String DynamicImage Source #
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) Source #
Equivalent to decodeImage
, but also provide potential metadatas
present in the given file.
decodeImageWithPaletteAndMetadata :: ByteString -> Either String (PalettedImage, Metadatas) Source #
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 Source #
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)
dynamicMap :: (forall pixel. Pixel pixel => Image pixel -> a) -> DynamicImage -> a Source #
Helper function to help extract information from dynamic image. To get the width of a dynamic image, you can use the following snippet:
dynWidth :: DynamicImage -> Int dynWidth img = dynamicMap imageWidth img
dynamicPixelMap :: (forall pixel. Pixel pixel => Image pixel -> Image pixel) -> DynamicImage -> DynamicImage Source #
Equivalent of the pixelMap
function for the dynamic images.
You can perform pixel colorspace independant operations with this
function.
For instance, if you want to extract a square crop of any image, without caring about colorspace, you can use the following snippet.
dynSquare :: DynamicImage -> DynamicImage dynSquare = dynamicPixelMap squareImage squareImage :: Pixel a => Image a -> Image a squareImage img = generateImage (\x y -> pixelAt img x y) edge edge where edge = min (imageWidth img) (imageHeight img)
:: Pixel px | |
=> (Int -> Int -> px) | Generating function, with |
-> 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
:: 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).
:: (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 Source #
Flatten a PalettedImage to a DynamicImage
RGB helper functions
convertRGB8 :: DynamicImage -> Image PixelRGB8 Source #
Convert by any means 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
convertRGB16 :: DynamicImage -> Image PixelRGB16 Source #
Convert by any means possible a dynamic image to an image in RGB. The process can lose precision while converting from 32bits pixels or Floating point pixels. Any alpha layer will be dropped
convertRGBA8 :: DynamicImage -> Image PixelRGBA8 Source #
Convert by any means 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 Source #
Traversal type matching the definition in the Lens package.
imagePixels :: forall pxa pxb. (Pixel pxa, Pixel pxb) => Traversal (Image pxa) (Image pxb) pxa pxb Source #
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 Source #
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 () 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.
bitsPerPixel, bmpEncode, hasAlpha
Instances
BmpEncodable PixelRGBA8 Source # | |
Defined in Codec.Picture.Bitmap bitsPerPixel :: PixelRGBA8 -> Int bmpEncode :: Image PixelRGBA8 -> Put hasAlpha :: Image PixelRGBA8 -> Bool defaultPalette :: PixelRGBA8 -> BmpPalette | |
BmpEncodable PixelRGB8 Source # | |
Defined in Codec.Picture.Bitmap | |
BmpEncodable Pixel8 Source # | |
Defined in Codec.Picture.Bitmap |
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 -> ByteString Source #
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, RGBA or Y.
decodeBitmap :: ByteString -> Either String DynamicImage Source #
Try to decode a bitmap image. Right now this function can output the following image:
encodeDynamicBitmap :: DynamicImage -> Either String ByteString Source #
Encode a dynamic image in BMP if possible, supported images are:
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 [DynamicImage]) Source #
Helper function trying to load all the images of an animated gif file.
decodeGif :: ByteString -> Either String DynamicImage Source #
Transform a raw gif image to an image, without modifying the pixels. This function can output the following images:
decodeGifImages :: ByteString -> Either String [DynamicImage] Source #
Transform a raw gif to a list of images, representing all the images of an animation.
encodeGifImage :: Image Pixel8 -> ByteString Source #
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 ByteString Source #
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 ByteString Source #
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 ByteString Source #
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
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.
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 Source #
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 animation 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 DynamicImage Source #
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 Source #
Encode an image in jpeg at a reasonnable quality level.
If you want better quality or reduced file size, you should
use encodeJpegAtQuality
:: 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 Source #
Encode an image into a png if possible.
encodePng :: Image a -> ByteString Source #
Transform an image into a png encoded bytestring, ready to be written as a file.
encodePngWithMetadata :: Metadatas -> Image a -> ByteString Source #
Encode a png using some metadatas. The following metadata keys will
be stored in a tEXt
field :
Title
Description
Author
Copyright
Software
Comment
Disclaimer
Source
Warning
Unknown
using the key present in the constructor.
the followings metadata will bes tored in the gAMA
chunk.
The followings metadata will be stored in a pHYs
chunk
Instances
readPng :: FilePath -> IO (Either String DynamicImage) Source #
Helper function trying to load a png file from a file on disk.
decodePng :: ByteString -> Either String DynamicImage Source #
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 () Source #
Helper function to directly write an image as a png on disk.
encodePalettedPng :: PngPaletteSaveable a => Image a -> Image Pixel8 -> Either String ByteString Source #
Encode a paletted image as a color indexed 8-bit PNG.
the palette must have between 1 and 256 values in it.
Accepts PixelRGB8
and PixelRGBA8
as palette pixel type
encodeDynamicPng :: DynamicImage -> Either String ByteString Source #
Encode a dynamic image in PNG if possible, supported images are:
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.
TGA handling
decodeTga :: ByteString -> Either String DynamicImage Source #
Transform a raw tga image to an image, without modifying the underlying pixel type.
This function can output the following images:
class TgaSaveable a Source #
This typeclass determine if a pixel can be saved in the TGA format.
tgaDataOfImage, tgaPixelDepthOfImage, tgaTypeOfImage
Instances
TgaSaveable PixelRGBA8 Source # | |
Defined in Codec.Picture.Tga tgaDataOfImage :: Image PixelRGBA8 -> ByteString tgaPixelDepthOfImage :: Image PixelRGBA8 -> Word8 tgaTypeOfImage :: Image PixelRGBA8 -> TgaImageType | |
TgaSaveable PixelRGB8 Source # | |
Defined in Codec.Picture.Tga tgaDataOfImage :: Image PixelRGB8 -> ByteString tgaPixelDepthOfImage :: Image PixelRGB8 -> Word8 tgaTypeOfImage :: Image PixelRGB8 -> TgaImageType | |
TgaSaveable Pixel8 Source # | |
Defined in Codec.Picture.Tga tgaDataOfImage :: Image Pixel8 -> ByteString tgaPixelDepthOfImage :: Image Pixel8 -> Word8 tgaTypeOfImage :: Image Pixel8 -> TgaImageType |
encodeTga :: TgaSaveable px => Image px -> ByteString Source #
Transform a compatible image to a raw bytestring representing a Targa file.
writeTga :: TgaSaveable pixel => FilePath -> Image pixel -> IO () Source #
Helper function to directly write an image a tga on disk.
Tiff handling
readTiff :: FilePath -> IO (Either String DynamicImage) Source #
Helper function trying to load tiff file from a file on disk.
class Pixel px => TiffSaveable px Source #
Class defining which pixel types can be serialized in a Tiff file.
colorSpaceOfPixel
Instances
TiffSaveable PixelRGBA16 Source # | |
Defined in Codec.Picture.Tiff | |
TiffSaveable PixelRGBA8 Source # | |
Defined in Codec.Picture.Tiff | |
TiffSaveable PixelCMYK16 Source # | |
Defined in Codec.Picture.Tiff | |
TiffSaveable PixelCMYK8 Source # | |
Defined in Codec.Picture.Tiff | |
TiffSaveable PixelYCbCr8 Source # | |
Defined in Codec.Picture.Tiff | |
TiffSaveable PixelRGB16 Source # | |
Defined in Codec.Picture.Tiff | |
TiffSaveable PixelRGB8 Source # | |
Defined in Codec.Picture.Tiff | |
TiffSaveable PixelYA16 Source # | |
Defined in Codec.Picture.Tiff | |
TiffSaveable PixelYA8 Source # | |
Defined in Codec.Picture.Tiff | |
TiffSaveable PixelF Source # | |
Defined in Codec.Picture.Tiff | |
TiffSaveable Pixel32 Source # | |
Defined in Codec.Picture.Tiff | |
TiffSaveable Pixel16 Source # | |
Defined in Codec.Picture.Tiff | |
TiffSaveable Pixel8 Source # | |
Defined in Codec.Picture.Tiff |
decodeTiff :: ByteString -> Either String DynamicImage Source #
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 Source #
Transform an image into a Tiff encoded bytestring, ready 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 DynamicImage Source #
Decode an HDR (radiance) image, the resulting image can be:
encodeHDR :: Image PixelRGBF -> ByteString Source #
Encode an High dynamic range image into a radiance image file format. Alias for encodeRawHDR
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.
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.
PaletteOptions | |
|
palettize :: PaletteOptions -> Image PixelRGB8 -> (Image Pixel8, Palette) Source #
Reduces an image to a color palette according to PaletteOptions
and
returns the indices image along with its Palette
.
Image types and pixel types
Image
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.
Image | |
|
data DynamicImage Source #
Image type enumerating all predefined pixel types. It enables loading and use of images of different pixel types.
ImageY8 (Image Pixel8) | A greyscale image. |
ImageY16 (Image Pixel16) | A greyscale image with 16bit components |
ImageY32 (Image Pixel32) | A greyscale image with 32bit 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
Eq DynamicImage Source # | |
Defined in Codec.Picture.Types (==) :: DynamicImage -> DynamicImage -> Bool # (/=) :: DynamicImage -> DynamicImage -> Bool # | |
NFData DynamicImage Source # | |
Defined in Codec.Picture.Types rnf :: DynamicImage -> () # |
Pixels
class (Storable (PixelBaseComponent a), Num (PixelBaseComponent a), Eq a) => Pixel a where Source #
Definition of pixels used in images. Each pixel has a color space, and a representative component (Word8 or Float).
mixWith, pixelOpacity, componentCount, colorMap, pixelAt, readPixel, writePixel, unsafePixelAt, unsafeReadPixel, unsafeWritePixel
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
mixWith :: (Int -> PixelBaseComponent a -> PixelBaseComponent a -> PixelBaseComponent a) -> a -> a -> a Source #
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)
:: (Int -> PixelBaseComponent a -> PixelBaseComponent a -> PixelBaseComponent a) | Function for color component |
-> (PixelBaseComponent a -> PixelBaseComponent a -> PixelBaseComponent a) | Function for alpha component |
-> 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 Source #
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 Source #
Return the number of components of the pixel
colorMap :: (PixelBaseComponent a -> PixelBaseComponent a) -> a -> a Source #
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 Source #
Calculate the index for the begining of the pixel
mutablePixelBaseIndex :: MutableImage s a -> Int -> Int -> Int Source #
Calculate theindex for the begining of the pixel at position x y
pixelAt :: Image a -> Int -> Int -> a Source #
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 Source #
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 -> a Source #
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 Source #
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)
Instances
Type alias for 8bit greyscale pixels. For simplicity, greyscale pixels use plain numbers instead of a separate type.
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]
Pixel type storing 8bit Luminance (Y) and alpha (A) information. Values are stored in the following order:
- Luminance
- Alpha
Instances
Pixel type storing 16bit Luminance (Y) and alpha (A) information. Values are stored in the following order:
- Luminance
- Alpha
Instances
Classic pixel type storing 8bit red, green and blue (RGB) information. Values are stored in the following order:
- Red
- Green
- Blue
Instances
data PixelRGB16 Source #
Pixel type storing 16bit red, green and blue (RGB) information. Values are stored in the following order:
- Red
- Green
- Blue
Instances
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
Instances
data PixelRGBA8 Source #
Classical pixel type storing 8bit red, green, blue and alpha (RGBA) information. Values are stored in the following order:
- Red
- Green
- Blue
- Alpha
Instances
data PixelRGBA16 Source #
Pixel type storing 16bit red, green, blue and alpha (RGBA) information. Values are stored in the following order:
- Red
- Green
- Blue
- Alpha
Instances
data PixelYCbCr8 Source #
Pixel type storing 8bit luminance, blue difference and red difference (YCbCr) information. Values are stored in the following order:
- Y (luminance)
- Cb
- Cr
Instances
data PixelCMYK8 Source #
Pixel type storing 8bit cyan, magenta, yellow and black (CMYK) information. Values are stored in the following order:
- Cyan
- Magenta
- Yellow
- Black
Instances
data PixelCMYK16 Source #
Pixel type storing 16bit cyan, magenta, yellow and black (CMYK) information. Values are stored in the following order:
- Cyan
- Magenta
- Yellow
- Black
Instances
Foreign unsafe import
:: (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