Safe Haskell | None |
---|---|
Language | Haskell2010 |
Codec.Picture
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
- 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 :: (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 :: Pixel px => (Int -> Int -> px) -> Int -> Int -> Image px
- generateFoldImage :: 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 :: Type -> Type). Applicative f => (a -> f b) -> s -> f t
- imagePixels :: (Pixel pxa, Pixel pxb) => Traversal (Image pxa) (Image pxb) pxa pxb
- imageIPixels :: (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 :: 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 :: 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 :: (Pixel px, PixelBaseComponent px ~ Word8) => Int -> Int -> ForeignPtr Word8 -> Image px
Generic functions
readImage :: FilePath -> IO (Either String DynamicImage) #
Load an image file without even thinking about it, it does everything
as decodeImage
readImageWithMetadata :: FilePath -> IO (Either String (DynamicImage, Metadatas)) #
Equivalent to readImage
but also providing metadatas.
decodeImage :: ByteString -> Either String DynamicImage #
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) #
Equivalent to decodeImage
, but also provide potential metadatas
present in the given file.
decodeImageWithPaletteAndMetadata :: ByteString -> Either String (PalettedImage, Metadatas) #
Equivalent to decodeImage
, but also provide potential metadatas
present in the given file and the palettes if the format provides them.
pixelMap :: (Pixel a, Pixel b) => (a -> b) -> Image a -> Image b #
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 #
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 #
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)
Arguments
:: 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
Arguments
:: 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).
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 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 #
Flatten a PalettedImage to a DynamicImage
RGB helper functions
convertRGB8 :: DynamicImage -> Image PixelRGB8 #
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 #
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 #
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 :: Type -> Type). Applicative f => (a -> f b) -> s -> f t #
Traversal type matching the definition in the Lens package.
imagePixels :: (Pixel pxa, Pixel pxb) => Traversal (Image pxa) (Image pxb) pxa pxb #
Traversal in "raster" order, from left to right the top to bottom. This traversal is matching pixelMap in spirit.
Since 3.2.4
imageIPixels :: (Pixel pxa, Pixel pxb) => Traversal (Image pxa) (Image pxb) (Int, Int, pxa) pxb #
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 () #
Save an image to a '.bmp' file, will do everything it can to save an image.
saveJpgImage :: Int -> FilePath -> DynamicImage -> IO () #
Save an image to a '.jpg' file, will do everything it can to save an image.
saveGifImage :: FilePath -> DynamicImage -> Either String (IO ()) #
Save an image to a '.gif' file, will do everything it can to save it.
savePngImage :: FilePath -> DynamicImage -> IO () #
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 () #
Save an image to a '.tiff' file, will do everything it can to save an image.
saveRadianceImage :: FilePath -> DynamicImage -> IO () #
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 #
All the instance of this class can be written as a bitmap file using this library.
Minimal complete definition
bitsPerPixel, bmpEncode, hasAlpha
Instances
BmpEncodable Pixel8 # | |
Defined in Codec.Picture.Bitmap | |
BmpEncodable PixelRGB8 # | |
Defined in Codec.Picture.Bitmap | |
BmpEncodable PixelRGBA8 # | |
Defined in Codec.Picture.Bitmap Methods bitsPerPixel :: PixelRGBA8 -> Int bmpEncode :: Image PixelRGBA8 -> Put hasAlpha :: Image PixelRGBA8 -> Bool defaultPalette :: PixelRGBA8 -> BmpPalette |
writeBitmap :: BmpEncodable pixel => FilePath -> Image pixel -> IO () #
Write an image in a file use the bitmap format.
encodeBitmap :: BmpEncodable pixel => Image pixel -> ByteString #
Encode an image into a bytestring in .bmp format ready to be written on disk.
readBitmap :: FilePath -> IO (Either String DynamicImage) #
Try to load a .bmp file. The colorspace would be RGB, RGBA or Y.
decodeBitmap :: ByteString -> Either String DynamicImage #
Try to decode a bitmap image. Right now this function can output the following image:
encodeDynamicBitmap :: DynamicImage -> Either String ByteString #
Encode a dynamic image in BMP if possible, supported images are:
writeDynamicBitmap :: FilePath -> DynamicImage -> IO (Either String Bool) #
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) #
Helper function trying to load a gif file from a file on disk.
readGifImages :: FilePath -> IO (Either String [DynamicImage]) #
Helper function trying to load all the images of an animated gif file.
decodeGif :: ByteString -> Either String DynamicImage #
Transform a raw gif image to an image, without modifying the pixels. This function can output the following images:
decodeGifImages :: ByteString -> Either String [DynamicImage] #
Transform a raw gif to a list of images, representing all the images of an animation.
encodeGifImage :: Image Pixel8 -> ByteString #
Encode a greyscale image to a bytestring.
encodeGifImageWithPalette :: Image Pixel8 -> Palette -> Either String ByteString #
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 ()) #
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 #
Encode a full color image to a gif by applying a color quantization algorithm on it.
writeColorReducedGifImage :: FilePath -> Image PixelRGB8 -> Either String (IO ()) #
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 #
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 ()) #
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 #
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 ByteString #
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 ()) #
Helper function to write a gif animation on disk. See encodeGifAnimation
Jpeg handling
readJpeg :: FilePath -> IO (Either String DynamicImage) #
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 #
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 #
Encode an image in jpeg at a reasonnable quality level.
If you want better quality or reduced file size, you should
use encodeJpegAtQuality
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 where #
Encode an image into a png if possible.
Minimal complete definition
Methods
encodePng :: Image a -> ByteString #
Transform an image into a png encoded bytestring, ready to be written as a file.
encodePngWithMetadata :: Metadatas -> Image a -> ByteString #
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 be stored in the gAMA
chunk.
The followings metadata will be stored in a pHYs
chunk
Instances
readPng :: FilePath -> IO (Either String DynamicImage) #
Helper function trying to load a png file from a file on disk.
decodePng :: ByteString -> Either String DynamicImage #
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 () #
Helper function to directly write an image as a png on disk.
encodePalettedPng :: PngPaletteSaveable a => Image a -> Image Pixel8 -> Either String ByteString #
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 #
Encode a dynamic image in PNG if possible, supported images are:
writeDynamicPng :: FilePath -> DynamicImage -> IO (Either String Bool) #
Write a dynamic image in a .png image file if possible. The same restriction as encodeDynamicPng apply.
TGA handling
decodeTga :: ByteString -> Either String DynamicImage #
Transform a raw tga image to an image, without modifying the underlying pixel type.
This function can output the following images:
class TgaSaveable a #
This typeclass determine if a pixel can be saved in the TGA format.
Minimal complete definition
tgaDataOfImage, tgaPixelDepthOfImage, tgaTypeOfImage
Instances
TgaSaveable Pixel8 # | |
Defined in Codec.Picture.Tga Methods tgaDataOfImage :: Image Pixel8 -> ByteString tgaPixelDepthOfImage :: Image Pixel8 -> Word8 tgaTypeOfImage :: Image Pixel8 -> TgaImageType | |
TgaSaveable PixelRGB8 # | |
Defined in Codec.Picture.Tga Methods tgaDataOfImage :: Image PixelRGB8 -> ByteString tgaPixelDepthOfImage :: Image PixelRGB8 -> Word8 tgaTypeOfImage :: Image PixelRGB8 -> TgaImageType | |
TgaSaveable PixelRGBA8 # | |
Defined in Codec.Picture.Tga Methods tgaDataOfImage :: Image PixelRGBA8 -> ByteString tgaPixelDepthOfImage :: Image PixelRGBA8 -> Word8 tgaTypeOfImage :: Image PixelRGBA8 -> TgaImageType |
encodeTga :: TgaSaveable px => Image px -> ByteString #
Transform a compatible image to a raw bytestring representing a Targa file.
writeTga :: TgaSaveable pixel => FilePath -> Image pixel -> IO () #
Helper function to directly write an image a tga on disk.
Tiff handling
readTiff :: FilePath -> IO (Either String DynamicImage) #
Helper function trying to load tiff file from a file on disk.
class Pixel px => TiffSaveable px #
Class defining which pixel types can be serialized in a Tiff file.
Minimal complete definition
colorSpaceOfPixel
Instances
decodeTiff :: ByteString -> Either String DynamicImage #
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 :: TiffSaveable px => Image px -> ByteString #
Transform an image into a Tiff encoded bytestring, ready to be written as a file.
writeTiff :: TiffSaveable pixel => FilePath -> Image pixel -> IO () #
Helper function to directly write an image as a tiff on disk.
HDR (Radiance/RGBE) handling
readHDR :: FilePath -> IO (Either String DynamicImage) #
Try to load a .pic file. The colorspace can only be RGB with floating point precision.
decodeHDR :: ByteString -> Either String DynamicImage #
Decode an HDR (radiance) image, the resulting image can be:
encodeHDR :: Image PixelRGBF -> ByteString #
Encode an High dynamic range image into a radiance image file format. Alias for encodeRawHDR
writeHDR :: FilePath -> Image PixelRGBF -> IO () #
Write an High dynamic range image into a radiance image file on disk.
Color Quantization
data PaletteCreationMethod #
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 #
To specify how the palette will be created.
Constructors
PaletteOptions | |
Fields
|
palettize :: PaletteOptions -> Image PixelRGB8 -> (Image Pixel8, Palette) #
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.
Constructors
Image | |
Fields
|
data DynamicImage #
Image type enumerating all predefined pixel types. It enables loading and use of images of different pixel types.
Constructors
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
NFData DynamicImage # | |
Defined in Codec.Picture.Types Methods rnf :: DynamicImage -> () # | |
Eq DynamicImage # | |
Defined in Codec.Picture.Types |
Pixels
class (Storable (PixelBaseComponent a), Num (PixelBaseComponent a), Eq a) => Pixel a where #
Definition of pixels used in images. Each pixel has a color space, and a representative component (Word8 or Float).
Minimal complete definition
mixWith, pixelOpacity, componentCount, colorMap, pixelAt, readPixel, writePixel, unsafePixelAt, unsafeReadPixel, unsafeWritePixel
Associated Types
type PixelBaseComponent a #
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 -> a #
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)
Arguments
:: (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 #
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 #
Return the number of components of the pixel
colorMap :: (PixelBaseComponent a -> PixelBaseComponent a) -> a -> a #
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 #
Calculate the index for the begining of the pixel
mutablePixelBaseIndex :: MutableImage s a -> Int -> Int -> Int #
Calculate theindex for the begining of the pixel at position x y
pixelAt :: Image a -> Int -> Int -> a #
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 #
Same as pixelAt but for mutable images.
writePixel :: PrimMonad m => MutableImage (PrimState m) a -> Int -> Int -> a -> m () #
Write a pixel in a mutable image at position x y
unsafePixelAt :: Vector (PixelBaseComponent a) -> Int -> a #
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 #
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 () #
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
PngSavable PixelYA8 # | |||||
Defined in Codec.Picture.Png.Internal.Export Methods encodePng :: Image PixelYA8 -> ByteString # encodePngWithMetadata :: Metadatas -> Image PixelYA8 -> ByteString # | |||||
TiffSaveable PixelYA8 # | |||||
Defined in Codec.Picture.Tiff Methods colorSpaceOfPixel :: PixelYA8 -> TiffColorspace extraSampleCodeOfPixel :: PixelYA8 -> Maybe ExtraSample subSamplingInfo :: PixelYA8 -> Vector Word32 sampleFormat :: PixelYA8 -> [TiffSampleFormat] | |||||
LumaPlaneExtractable PixelYA8 # | |||||
Defined in Codec.Picture.Types Methods computeLuma :: PixelYA8 -> PixelBaseComponent PixelYA8 # extractLumaPlane :: Image PixelYA8 -> Image (PixelBaseComponent PixelYA8) # | |||||
PackeablePixel PixelYA8 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods | |||||
Pixel PixelYA8 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods mixWith :: (Int -> PixelBaseComponent PixelYA8 -> PixelBaseComponent PixelYA8 -> PixelBaseComponent PixelYA8) -> PixelYA8 -> PixelYA8 -> PixelYA8 # mixWithAlpha :: (Int -> PixelBaseComponent PixelYA8 -> PixelBaseComponent PixelYA8 -> PixelBaseComponent PixelYA8) -> (PixelBaseComponent PixelYA8 -> PixelBaseComponent PixelYA8 -> PixelBaseComponent PixelYA8) -> PixelYA8 -> PixelYA8 -> PixelYA8 # pixelOpacity :: PixelYA8 -> PixelBaseComponent PixelYA8 # componentCount :: PixelYA8 -> Int # colorMap :: (PixelBaseComponent PixelYA8 -> PixelBaseComponent PixelYA8) -> PixelYA8 -> PixelYA8 # pixelBaseIndex :: Image PixelYA8 -> Int -> Int -> Int # mutablePixelBaseIndex :: MutableImage s PixelYA8 -> Int -> Int -> Int # pixelAt :: Image PixelYA8 -> Int -> Int -> PixelYA8 # readPixel :: PrimMonad m => MutableImage (PrimState m) PixelYA8 -> Int -> Int -> m PixelYA8 # writePixel :: PrimMonad m => MutableImage (PrimState m) PixelYA8 -> Int -> Int -> PixelYA8 -> m () # unsafePixelAt :: Vector (PixelBaseComponent PixelYA8) -> Int -> PixelYA8 # unsafeReadPixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelYA8) -> Int -> m PixelYA8 # unsafeWritePixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelYA8) -> Int -> PixelYA8 -> m () # | |||||
Show PixelYA8 # | |||||
Eq PixelYA8 # | |||||
Ord PixelYA8 # | |||||
Defined in Codec.Picture.Types | |||||
ColorConvertible Pixel8 PixelYA8 # | |||||
Defined in Codec.Picture.Types | |||||
ColorConvertible PixelYA8 PixelRGB16 # | |||||
Defined in Codec.Picture.Types | |||||
ColorConvertible PixelYA8 PixelRGB8 # | |||||
Defined in Codec.Picture.Types | |||||
ColorConvertible PixelYA8 PixelRGBA8 # | |||||
Defined in Codec.Picture.Types | |||||
ColorPlane PixelYA8 PlaneAlpha # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelYA8 -> PlaneAlpha -> Int | |||||
ColorPlane PixelYA8 PlaneLuma # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelYA8 -> PlaneLuma -> Int | |||||
TransparentPixel PixelYA8 Pixel8 # | |||||
Defined in Codec.Picture.Types Methods dropTransparency :: PixelYA8 -> Pixel8 # getTransparency :: PixelYA8 -> PixelBaseComponent PixelYA8 # | |||||
type PackedRepresentation PixelYA8 # | |||||
Defined in Codec.Picture.Types | |||||
type PixelBaseComponent PixelYA8 # | |||||
Defined in Codec.Picture.Types |
Pixel type storing 16bit Luminance (Y) and alpha (A) information. Values are stored in the following order:
- Luminance
- Alpha
Instances
PngSavable PixelYA16 # | |||||
Defined in Codec.Picture.Png.Internal.Export Methods encodePng :: Image PixelYA16 -> ByteString # encodePngWithMetadata :: Metadatas -> Image PixelYA16 -> ByteString # | |||||
TiffSaveable PixelYA16 # | |||||
Defined in Codec.Picture.Tiff Methods colorSpaceOfPixel :: PixelYA16 -> TiffColorspace extraSampleCodeOfPixel :: PixelYA16 -> Maybe ExtraSample subSamplingInfo :: PixelYA16 -> Vector Word32 sampleFormat :: PixelYA16 -> [TiffSampleFormat] | |||||
PackeablePixel PixelYA16 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods packPixel :: PixelYA16 -> PackedRepresentation PixelYA16 # unpackPixel :: PackedRepresentation PixelYA16 -> PixelYA16 # | |||||
Pixel PixelYA16 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods mixWith :: (Int -> PixelBaseComponent PixelYA16 -> PixelBaseComponent PixelYA16 -> PixelBaseComponent PixelYA16) -> PixelYA16 -> PixelYA16 -> PixelYA16 # mixWithAlpha :: (Int -> PixelBaseComponent PixelYA16 -> PixelBaseComponent PixelYA16 -> PixelBaseComponent PixelYA16) -> (PixelBaseComponent PixelYA16 -> PixelBaseComponent PixelYA16 -> PixelBaseComponent PixelYA16) -> PixelYA16 -> PixelYA16 -> PixelYA16 # pixelOpacity :: PixelYA16 -> PixelBaseComponent PixelYA16 # componentCount :: PixelYA16 -> Int # colorMap :: (PixelBaseComponent PixelYA16 -> PixelBaseComponent PixelYA16) -> PixelYA16 -> PixelYA16 # pixelBaseIndex :: Image PixelYA16 -> Int -> Int -> Int # mutablePixelBaseIndex :: MutableImage s PixelYA16 -> Int -> Int -> Int # pixelAt :: Image PixelYA16 -> Int -> Int -> PixelYA16 # readPixel :: PrimMonad m => MutableImage (PrimState m) PixelYA16 -> Int -> Int -> m PixelYA16 # writePixel :: PrimMonad m => MutableImage (PrimState m) PixelYA16 -> Int -> Int -> PixelYA16 -> m () # unsafePixelAt :: Vector (PixelBaseComponent PixelYA16) -> Int -> PixelYA16 # unsafeReadPixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelYA16) -> Int -> m PixelYA16 # unsafeWritePixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelYA16) -> Int -> PixelYA16 -> m () # | |||||
Show PixelYA16 # | |||||
Eq PixelYA16 # | |||||
Ord PixelYA16 # | |||||
ColorConvertible Pixel16 PixelYA16 # | |||||
Defined in Codec.Picture.Types | |||||
ColorConvertible PixelYA16 PixelRGB16 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelYA16 -> PixelRGB16 # promoteImage :: Image PixelYA16 -> Image PixelRGB16 # | |||||
ColorConvertible PixelYA16 PixelRGBA16 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelYA16 -> PixelRGBA16 # promoteImage :: Image PixelYA16 -> Image PixelRGBA16 # | |||||
ColorPlane PixelYA16 PlaneAlpha # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelYA16 -> PlaneAlpha -> Int | |||||
ColorPlane PixelYA16 PlaneLuma # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelYA16 -> PlaneLuma -> Int | |||||
TransparentPixel PixelYA16 Pixel16 # | |||||
Defined in Codec.Picture.Types Methods dropTransparency :: PixelYA16 -> Pixel16 # getTransparency :: PixelYA16 -> PixelBaseComponent PixelYA16 # | |||||
type PackedRepresentation PixelYA16 # | |||||
Defined in Codec.Picture.Types | |||||
type PixelBaseComponent PixelYA16 # | |||||
Defined in Codec.Picture.Types |
Classic pixel type storing 8bit red, green and blue (RGB) information. Values are stored in the following order:
- Red
- Green
- Blue
Instances
BmpEncodable PixelRGB8 # | |||||
Defined in Codec.Picture.Bitmap | |||||
JpgEncodable PixelRGB8 # | |||||
Defined in Codec.Picture.Jpg Methods additionalBlocks :: Image PixelRGB8 -> [JpgFrame] componentsOfColorSpace :: Image PixelRGB8 -> [JpgComponent] encodingState :: Int -> Image PixelRGB8 -> Vector EncoderState imageHuffmanTables :: Image PixelRGB8 -> [(JpgHuffmanTableSpec, HuffmanPackedTree)] scanSpecificationOfColorSpace :: Image PixelRGB8 -> [JpgScanSpecification] quantTableSpec :: Image PixelRGB8 -> Int -> [JpgQuantTableSpec] | |||||
PngPaletteSaveable PixelRGB8 # | |||||
Defined in Codec.Picture.Png.Internal.Export Methods encodePalettedPng :: Image PixelRGB8 -> Image Pixel8 -> Either String ByteString # encodePalettedPngWithMetadata :: Metadatas -> Image PixelRGB8 -> Image Pixel8 -> Either String ByteString # | |||||
PngSavable PixelRGB8 # | |||||
Defined in Codec.Picture.Png.Internal.Export Methods encodePng :: Image PixelRGB8 -> ByteString # encodePngWithMetadata :: Metadatas -> Image PixelRGB8 -> ByteString # | |||||
TgaSaveable PixelRGB8 # | |||||
Defined in Codec.Picture.Tga Methods tgaDataOfImage :: Image PixelRGB8 -> ByteString tgaPixelDepthOfImage :: Image PixelRGB8 -> Word8 tgaTypeOfImage :: Image PixelRGB8 -> TgaImageType | |||||
TiffSaveable PixelRGB8 # | |||||
Defined in Codec.Picture.Tiff Methods colorSpaceOfPixel :: PixelRGB8 -> TiffColorspace extraSampleCodeOfPixel :: PixelRGB8 -> Maybe ExtraSample subSamplingInfo :: PixelRGB8 -> Vector Word32 sampleFormat :: PixelRGB8 -> [TiffSampleFormat] | |||||
LumaPlaneExtractable PixelRGB8 # | |||||
Defined in Codec.Picture.Types Methods computeLuma :: PixelRGB8 -> PixelBaseComponent PixelRGB8 # extractLumaPlane :: Image PixelRGB8 -> Image (PixelBaseComponent PixelRGB8) # | |||||
Pixel PixelRGB8 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods mixWith :: (Int -> PixelBaseComponent PixelRGB8 -> PixelBaseComponent PixelRGB8 -> PixelBaseComponent PixelRGB8) -> PixelRGB8 -> PixelRGB8 -> PixelRGB8 # mixWithAlpha :: (Int -> PixelBaseComponent PixelRGB8 -> PixelBaseComponent PixelRGB8 -> PixelBaseComponent PixelRGB8) -> (PixelBaseComponent PixelRGB8 -> PixelBaseComponent PixelRGB8 -> PixelBaseComponent PixelRGB8) -> PixelRGB8 -> PixelRGB8 -> PixelRGB8 # pixelOpacity :: PixelRGB8 -> PixelBaseComponent PixelRGB8 # componentCount :: PixelRGB8 -> Int # colorMap :: (PixelBaseComponent PixelRGB8 -> PixelBaseComponent PixelRGB8) -> PixelRGB8 -> PixelRGB8 # pixelBaseIndex :: Image PixelRGB8 -> Int -> Int -> Int # mutablePixelBaseIndex :: MutableImage s PixelRGB8 -> Int -> Int -> Int # pixelAt :: Image PixelRGB8 -> Int -> Int -> PixelRGB8 # readPixel :: PrimMonad m => MutableImage (PrimState m) PixelRGB8 -> Int -> Int -> m PixelRGB8 # writePixel :: PrimMonad m => MutableImage (PrimState m) PixelRGB8 -> Int -> Int -> PixelRGB8 -> m () # unsafePixelAt :: Vector (PixelBaseComponent PixelRGB8) -> Int -> PixelRGB8 # unsafeReadPixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelRGB8) -> Int -> m PixelRGB8 # unsafeWritePixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelRGB8) -> Int -> PixelRGB8 -> m () # | |||||
Show PixelRGB8 # | |||||
Eq PixelRGB8 # | |||||
Ord PixelRGB8 # | |||||
ColorConvertible Pixel8 PixelRGB8 # | |||||
Defined in Codec.Picture.Types | |||||
ColorConvertible PixelRGB8 PixelRGB16 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelRGB8 -> PixelRGB16 # promoteImage :: Image PixelRGB8 -> Image PixelRGB16 # | |||||
ColorConvertible PixelRGB8 PixelRGBA16 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelRGB8 -> PixelRGBA16 # promoteImage :: Image PixelRGB8 -> Image PixelRGBA16 # | |||||
ColorConvertible PixelRGB8 PixelRGBA8 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelRGB8 -> PixelRGBA8 # promoteImage :: Image PixelRGB8 -> Image PixelRGBA8 # | |||||
ColorConvertible PixelRGB8 PixelRGBF # | |||||
Defined in Codec.Picture.Types | |||||
ColorConvertible PixelYA8 PixelRGB8 # | |||||
Defined in Codec.Picture.Types | |||||
ColorPlane PixelRGB8 PlaneBlue # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGB8 -> PlaneBlue -> Int | |||||
ColorPlane PixelRGB8 PlaneGreen # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGB8 -> PlaneGreen -> Int | |||||
ColorPlane PixelRGB8 PlaneRed # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGB8 -> PlaneRed -> Int | |||||
ColorSpaceConvertible PixelCMYK8 PixelRGB8 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelCMYK8 -> PixelRGB8 # convertImage :: Image PixelCMYK8 -> Image PixelRGB8 # | |||||
ColorSpaceConvertible PixelRGB8 PixelCMYK8 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelRGB8 -> PixelCMYK8 # convertImage :: Image PixelRGB8 -> Image PixelCMYK8 # | |||||
ColorSpaceConvertible PixelRGB8 PixelYCbCr8 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelRGB8 -> PixelYCbCr8 # convertImage :: Image PixelRGB8 -> Image PixelYCbCr8 # | |||||
ColorSpaceConvertible PixelYCbCr8 PixelRGB8 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelYCbCr8 -> PixelRGB8 # convertImage :: Image PixelYCbCr8 -> Image PixelRGB8 # | |||||
ColorSpaceConvertible PixelYCbCrK8 PixelRGB8 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelYCbCrK8 -> PixelRGB8 # convertImage :: Image PixelYCbCrK8 -> Image PixelRGB8 # | |||||
TransparentPixel PixelRGBA8 PixelRGB8 # | |||||
Defined in Codec.Picture.Types Methods dropTransparency :: PixelRGBA8 -> PixelRGB8 # getTransparency :: PixelRGBA8 -> PixelBaseComponent PixelRGBA8 # | |||||
type PixelBaseComponent PixelRGB8 # | |||||
Defined in Codec.Picture.Types |
data PixelRGB16 #
Pixel type storing 16bit red, green and blue (RGB) information. Values are stored in the following order:
- Red
- Green
- Blue
Constructors
PixelRGB16 !Pixel16 !Pixel16 !Pixel16 |
Instances
PngSavable PixelRGB16 # | |||||
Defined in Codec.Picture.Png.Internal.Export Methods encodePng :: Image PixelRGB16 -> ByteString # encodePngWithMetadata :: Metadatas -> Image PixelRGB16 -> ByteString # | |||||
TiffSaveable PixelRGB16 # | |||||
Defined in Codec.Picture.Tiff Methods colorSpaceOfPixel :: PixelRGB16 -> TiffColorspace extraSampleCodeOfPixel :: PixelRGB16 -> Maybe ExtraSample subSamplingInfo :: PixelRGB16 -> Vector Word32 sampleFormat :: PixelRGB16 -> [TiffSampleFormat] | |||||
LumaPlaneExtractable PixelRGB16 # | |||||
Defined in Codec.Picture.Types Methods computeLuma :: PixelRGB16 -> PixelBaseComponent PixelRGB16 # extractLumaPlane :: Image PixelRGB16 -> Image (PixelBaseComponent PixelRGB16) # | |||||
Pixel PixelRGB16 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods mixWith :: (Int -> PixelBaseComponent PixelRGB16 -> PixelBaseComponent PixelRGB16 -> PixelBaseComponent PixelRGB16) -> PixelRGB16 -> PixelRGB16 -> PixelRGB16 # mixWithAlpha :: (Int -> PixelBaseComponent PixelRGB16 -> PixelBaseComponent PixelRGB16 -> PixelBaseComponent PixelRGB16) -> (PixelBaseComponent PixelRGB16 -> PixelBaseComponent PixelRGB16 -> PixelBaseComponent PixelRGB16) -> PixelRGB16 -> PixelRGB16 -> PixelRGB16 # pixelOpacity :: PixelRGB16 -> PixelBaseComponent PixelRGB16 # componentCount :: PixelRGB16 -> Int # colorMap :: (PixelBaseComponent PixelRGB16 -> PixelBaseComponent PixelRGB16) -> PixelRGB16 -> PixelRGB16 # pixelBaseIndex :: Image PixelRGB16 -> Int -> Int -> Int # mutablePixelBaseIndex :: MutableImage s PixelRGB16 -> Int -> Int -> Int # pixelAt :: Image PixelRGB16 -> Int -> Int -> PixelRGB16 # readPixel :: PrimMonad m => MutableImage (PrimState m) PixelRGB16 -> Int -> Int -> m PixelRGB16 # writePixel :: PrimMonad m => MutableImage (PrimState m) PixelRGB16 -> Int -> Int -> PixelRGB16 -> m () # unsafePixelAt :: Vector (PixelBaseComponent PixelRGB16) -> Int -> PixelRGB16 # unsafeReadPixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelRGB16) -> Int -> m PixelRGB16 # unsafeWritePixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelRGB16) -> Int -> PixelRGB16 -> m () # | |||||
Show PixelRGB16 # | |||||
Defined in Codec.Picture.Types Methods showsPrec :: Int -> PixelRGB16 -> ShowS # show :: PixelRGB16 -> String # showList :: [PixelRGB16] -> ShowS # | |||||
Eq PixelRGB16 # | |||||
Defined in Codec.Picture.Types | |||||
Ord PixelRGB16 # | |||||
Defined in Codec.Picture.Types Methods compare :: PixelRGB16 -> PixelRGB16 -> Ordering # (<) :: PixelRGB16 -> PixelRGB16 -> Bool # (<=) :: PixelRGB16 -> PixelRGB16 -> Bool # (>) :: PixelRGB16 -> PixelRGB16 -> Bool # (>=) :: PixelRGB16 -> PixelRGB16 -> Bool # max :: PixelRGB16 -> PixelRGB16 -> PixelRGB16 # min :: PixelRGB16 -> PixelRGB16 -> PixelRGB16 # | |||||
ColorConvertible Pixel16 PixelRGB16 # | |||||
Defined in Codec.Picture.Types | |||||
ColorConvertible Pixel8 PixelRGB16 # | |||||
Defined in Codec.Picture.Types | |||||
ColorConvertible PixelRGB16 PixelRGBA16 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelRGB16 -> PixelRGBA16 # promoteImage :: Image PixelRGB16 -> Image PixelRGBA16 # | |||||
ColorConvertible PixelRGB8 PixelRGB16 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelRGB8 -> PixelRGB16 # promoteImage :: Image PixelRGB8 -> Image PixelRGB16 # | |||||
ColorConvertible PixelYA16 PixelRGB16 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelYA16 -> PixelRGB16 # promoteImage :: Image PixelYA16 -> Image PixelRGB16 # | |||||
ColorConvertible PixelYA8 PixelRGB16 # | |||||
Defined in Codec.Picture.Types | |||||
ColorPlane PixelRGB16 PlaneBlue # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGB16 -> PlaneBlue -> Int | |||||
ColorPlane PixelRGB16 PlaneGreen # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGB16 -> PlaneGreen -> Int | |||||
ColorPlane PixelRGB16 PlaneRed # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGB16 -> PlaneRed -> Int | |||||
ColorSpaceConvertible PixelCMYK16 PixelRGB16 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelCMYK16 -> PixelRGB16 # convertImage :: Image PixelCMYK16 -> Image PixelRGB16 # | |||||
ColorSpaceConvertible PixelRGB16 PixelCMYK16 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelRGB16 -> PixelCMYK16 # convertImage :: Image PixelRGB16 -> Image PixelCMYK16 # | |||||
TransparentPixel PixelRGBA16 PixelRGB16 # | |||||
Defined in Codec.Picture.Types Methods dropTransparency :: PixelRGBA16 -> PixelRGB16 # getTransparency :: PixelRGBA16 -> PixelBaseComponent PixelRGBA16 # | |||||
type PixelBaseComponent PixelRGB16 # | |||||
Defined in Codec.Picture.Types |
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
LumaPlaneExtractable PixelRGBF # | |||||
Defined in Codec.Picture.Types Methods computeLuma :: PixelRGBF -> PixelBaseComponent PixelRGBF # extractLumaPlane :: Image PixelRGBF -> Image (PixelBaseComponent PixelRGBF) # | |||||
Pixel PixelRGBF # | |||||
Defined in Codec.Picture.Types Associated Types
Methods mixWith :: (Int -> PixelBaseComponent PixelRGBF -> PixelBaseComponent PixelRGBF -> PixelBaseComponent PixelRGBF) -> PixelRGBF -> PixelRGBF -> PixelRGBF # mixWithAlpha :: (Int -> PixelBaseComponent PixelRGBF -> PixelBaseComponent PixelRGBF -> PixelBaseComponent PixelRGBF) -> (PixelBaseComponent PixelRGBF -> PixelBaseComponent PixelRGBF -> PixelBaseComponent PixelRGBF) -> PixelRGBF -> PixelRGBF -> PixelRGBF # pixelOpacity :: PixelRGBF -> PixelBaseComponent PixelRGBF # componentCount :: PixelRGBF -> Int # colorMap :: (PixelBaseComponent PixelRGBF -> PixelBaseComponent PixelRGBF) -> PixelRGBF -> PixelRGBF # pixelBaseIndex :: Image PixelRGBF -> Int -> Int -> Int # mutablePixelBaseIndex :: MutableImage s PixelRGBF -> Int -> Int -> Int # pixelAt :: Image PixelRGBF -> Int -> Int -> PixelRGBF # readPixel :: PrimMonad m => MutableImage (PrimState m) PixelRGBF -> Int -> Int -> m PixelRGBF # writePixel :: PrimMonad m => MutableImage (PrimState m) PixelRGBF -> Int -> Int -> PixelRGBF -> m () # unsafePixelAt :: Vector (PixelBaseComponent PixelRGBF) -> Int -> PixelRGBF # unsafeReadPixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelRGBF) -> Int -> m PixelRGBF # unsafeWritePixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelRGBF) -> Int -> PixelRGBF -> m () # | |||||
Show PixelRGBF # | |||||
Eq PixelRGBF # | |||||
Ord PixelRGBF # | |||||
ColorConvertible PixelF PixelRGBF # | |||||
Defined in Codec.Picture.Types | |||||
ColorConvertible PixelRGB8 PixelRGBF # | |||||
Defined in Codec.Picture.Types | |||||
ColorPlane PixelRGBF PlaneBlue # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGBF -> PlaneBlue -> Int | |||||
ColorPlane PixelRGBF PlaneGreen # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGBF -> PlaneGreen -> Int | |||||
ColorPlane PixelRGBF PlaneRed # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGBF -> PlaneRed -> Int | |||||
type PixelBaseComponent PixelRGBF # | |||||
Defined in Codec.Picture.Types |
data PixelRGBA8 #
Classical pixel type storing 8bit red, green, blue and alpha (RGBA) information. Values are stored in the following order:
- Red
- Green
- Blue
- Alpha
Constructors
PixelRGBA8 !Pixel8 !Pixel8 !Pixel8 !Pixel8 |
Instances
BmpEncodable PixelRGBA8 # | |||||
Defined in Codec.Picture.Bitmap Methods bitsPerPixel :: PixelRGBA8 -> Int bmpEncode :: Image PixelRGBA8 -> Put hasAlpha :: Image PixelRGBA8 -> Bool defaultPalette :: PixelRGBA8 -> BmpPalette | |||||
PngPaletteSaveable PixelRGBA8 # | |||||
Defined in Codec.Picture.Png.Internal.Export Methods encodePalettedPng :: Image PixelRGBA8 -> Image Pixel8 -> Either String ByteString # encodePalettedPngWithMetadata :: Metadatas -> Image PixelRGBA8 -> Image Pixel8 -> Either String ByteString # | |||||
PngSavable PixelRGBA8 # | |||||
Defined in Codec.Picture.Png.Internal.Export Methods encodePng :: Image PixelRGBA8 -> ByteString # encodePngWithMetadata :: Metadatas -> Image PixelRGBA8 -> ByteString # | |||||
TgaSaveable PixelRGBA8 # | |||||
Defined in Codec.Picture.Tga Methods tgaDataOfImage :: Image PixelRGBA8 -> ByteString tgaPixelDepthOfImage :: Image PixelRGBA8 -> Word8 tgaTypeOfImage :: Image PixelRGBA8 -> TgaImageType | |||||
TiffSaveable PixelRGBA8 # | |||||
Defined in Codec.Picture.Tiff Methods colorSpaceOfPixel :: PixelRGBA8 -> TiffColorspace extraSampleCodeOfPixel :: PixelRGBA8 -> Maybe ExtraSample subSamplingInfo :: PixelRGBA8 -> Vector Word32 sampleFormat :: PixelRGBA8 -> [TiffSampleFormat] | |||||
LumaPlaneExtractable PixelRGBA8 # | |||||
Defined in Codec.Picture.Types Methods computeLuma :: PixelRGBA8 -> PixelBaseComponent PixelRGBA8 # extractLumaPlane :: Image PixelRGBA8 -> Image (PixelBaseComponent PixelRGBA8) # | |||||
PackeablePixel PixelRGBA8 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods packPixel :: PixelRGBA8 -> PackedRepresentation PixelRGBA8 # unpackPixel :: PackedRepresentation PixelRGBA8 -> PixelRGBA8 # | |||||
Pixel PixelRGBA8 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods mixWith :: (Int -> PixelBaseComponent PixelRGBA8 -> PixelBaseComponent PixelRGBA8 -> PixelBaseComponent PixelRGBA8) -> PixelRGBA8 -> PixelRGBA8 -> PixelRGBA8 # mixWithAlpha :: (Int -> PixelBaseComponent PixelRGBA8 -> PixelBaseComponent PixelRGBA8 -> PixelBaseComponent PixelRGBA8) -> (PixelBaseComponent PixelRGBA8 -> PixelBaseComponent PixelRGBA8 -> PixelBaseComponent PixelRGBA8) -> PixelRGBA8 -> PixelRGBA8 -> PixelRGBA8 # pixelOpacity :: PixelRGBA8 -> PixelBaseComponent PixelRGBA8 # componentCount :: PixelRGBA8 -> Int # colorMap :: (PixelBaseComponent PixelRGBA8 -> PixelBaseComponent PixelRGBA8) -> PixelRGBA8 -> PixelRGBA8 # pixelBaseIndex :: Image PixelRGBA8 -> Int -> Int -> Int # mutablePixelBaseIndex :: MutableImage s PixelRGBA8 -> Int -> Int -> Int # pixelAt :: Image PixelRGBA8 -> Int -> Int -> PixelRGBA8 # readPixel :: PrimMonad m => MutableImage (PrimState m) PixelRGBA8 -> Int -> Int -> m PixelRGBA8 # writePixel :: PrimMonad m => MutableImage (PrimState m) PixelRGBA8 -> Int -> Int -> PixelRGBA8 -> m () # unsafePixelAt :: Vector (PixelBaseComponent PixelRGBA8) -> Int -> PixelRGBA8 # unsafeReadPixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelRGBA8) -> Int -> m PixelRGBA8 # unsafeWritePixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelRGBA8) -> Int -> PixelRGBA8 -> m () # | |||||
Show PixelRGBA8 # | |||||
Defined in Codec.Picture.Types Methods showsPrec :: Int -> PixelRGBA8 -> ShowS # show :: PixelRGBA8 -> String # showList :: [PixelRGBA8] -> ShowS # | |||||
Eq PixelRGBA8 # | |||||
Defined in Codec.Picture.Types | |||||
Ord PixelRGBA8 # | |||||
Defined in Codec.Picture.Types Methods compare :: PixelRGBA8 -> PixelRGBA8 -> Ordering # (<) :: PixelRGBA8 -> PixelRGBA8 -> Bool # (<=) :: PixelRGBA8 -> PixelRGBA8 -> Bool # (>) :: PixelRGBA8 -> PixelRGBA8 -> Bool # (>=) :: PixelRGBA8 -> PixelRGBA8 -> Bool # max :: PixelRGBA8 -> PixelRGBA8 -> PixelRGBA8 # min :: PixelRGBA8 -> PixelRGBA8 -> PixelRGBA8 # | |||||
ColorConvertible Pixel8 PixelRGBA8 # | |||||
Defined in Codec.Picture.Types | |||||
ColorConvertible PixelRGB8 PixelRGBA8 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelRGB8 -> PixelRGBA8 # promoteImage :: Image PixelRGB8 -> Image PixelRGBA8 # | |||||
ColorConvertible PixelRGBA8 PixelRGBA16 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelRGBA8 -> PixelRGBA16 # promoteImage :: Image PixelRGBA8 -> Image PixelRGBA16 # | |||||
ColorConvertible PixelYA8 PixelRGBA8 # | |||||
Defined in Codec.Picture.Types | |||||
ColorPlane PixelRGBA8 PlaneAlpha # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGBA8 -> PlaneAlpha -> Int | |||||
ColorPlane PixelRGBA8 PlaneBlue # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGBA8 -> PlaneBlue -> Int | |||||
ColorPlane PixelRGBA8 PlaneGreen # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGBA8 -> PlaneGreen -> Int | |||||
ColorPlane PixelRGBA8 PlaneRed # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGBA8 -> PlaneRed -> Int | |||||
TransparentPixel PixelRGBA8 PixelRGB8 # | |||||
Defined in Codec.Picture.Types Methods dropTransparency :: PixelRGBA8 -> PixelRGB8 # getTransparency :: PixelRGBA8 -> PixelBaseComponent PixelRGBA8 # | |||||
type PackedRepresentation PixelRGBA8 # | |||||
Defined in Codec.Picture.Types | |||||
type PixelBaseComponent PixelRGBA8 # | |||||
Defined in Codec.Picture.Types |
data PixelRGBA16 #
Pixel type storing 16bit red, green, blue and alpha (RGBA) information. Values are stored in the following order:
- Red
- Green
- Blue
- Alpha
Constructors
PixelRGBA16 !Pixel16 !Pixel16 !Pixel16 !Pixel16 |
Instances
PngSavable PixelRGBA16 # | |||||
Defined in Codec.Picture.Png.Internal.Export Methods encodePng :: Image PixelRGBA16 -> ByteString # encodePngWithMetadata :: Metadatas -> Image PixelRGBA16 -> ByteString # | |||||
TiffSaveable PixelRGBA16 # | |||||
Defined in Codec.Picture.Tiff Methods colorSpaceOfPixel :: PixelRGBA16 -> TiffColorspace extraSampleCodeOfPixel :: PixelRGBA16 -> Maybe ExtraSample subSamplingInfo :: PixelRGBA16 -> Vector Word32 sampleFormat :: PixelRGBA16 -> [TiffSampleFormat] | |||||
PackeablePixel PixelRGBA16 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods packPixel :: PixelRGBA16 -> PackedRepresentation PixelRGBA16 # unpackPixel :: PackedRepresentation PixelRGBA16 -> PixelRGBA16 # | |||||
Pixel PixelRGBA16 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods mixWith :: (Int -> PixelBaseComponent PixelRGBA16 -> PixelBaseComponent PixelRGBA16 -> PixelBaseComponent PixelRGBA16) -> PixelRGBA16 -> PixelRGBA16 -> PixelRGBA16 # mixWithAlpha :: (Int -> PixelBaseComponent PixelRGBA16 -> PixelBaseComponent PixelRGBA16 -> PixelBaseComponent PixelRGBA16) -> (PixelBaseComponent PixelRGBA16 -> PixelBaseComponent PixelRGBA16 -> PixelBaseComponent PixelRGBA16) -> PixelRGBA16 -> PixelRGBA16 -> PixelRGBA16 # pixelOpacity :: PixelRGBA16 -> PixelBaseComponent PixelRGBA16 # componentCount :: PixelRGBA16 -> Int # colorMap :: (PixelBaseComponent PixelRGBA16 -> PixelBaseComponent PixelRGBA16) -> PixelRGBA16 -> PixelRGBA16 # pixelBaseIndex :: Image PixelRGBA16 -> Int -> Int -> Int # mutablePixelBaseIndex :: MutableImage s PixelRGBA16 -> Int -> Int -> Int # pixelAt :: Image PixelRGBA16 -> Int -> Int -> PixelRGBA16 # readPixel :: PrimMonad m => MutableImage (PrimState m) PixelRGBA16 -> Int -> Int -> m PixelRGBA16 # writePixel :: PrimMonad m => MutableImage (PrimState m) PixelRGBA16 -> Int -> Int -> PixelRGBA16 -> m () # unsafePixelAt :: Vector (PixelBaseComponent PixelRGBA16) -> Int -> PixelRGBA16 # unsafeReadPixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelRGBA16) -> Int -> m PixelRGBA16 # unsafeWritePixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelRGBA16) -> Int -> PixelRGBA16 -> m () # | |||||
Show PixelRGBA16 # | |||||
Defined in Codec.Picture.Types Methods showsPrec :: Int -> PixelRGBA16 -> ShowS # show :: PixelRGBA16 -> String # showList :: [PixelRGBA16] -> ShowS # | |||||
Eq PixelRGBA16 # | |||||
Defined in Codec.Picture.Types | |||||
Ord PixelRGBA16 # | |||||
Defined in Codec.Picture.Types Methods compare :: PixelRGBA16 -> PixelRGBA16 -> Ordering # (<) :: PixelRGBA16 -> PixelRGBA16 -> Bool # (<=) :: PixelRGBA16 -> PixelRGBA16 -> Bool # (>) :: PixelRGBA16 -> PixelRGBA16 -> Bool # (>=) :: PixelRGBA16 -> PixelRGBA16 -> Bool # max :: PixelRGBA16 -> PixelRGBA16 -> PixelRGBA16 # min :: PixelRGBA16 -> PixelRGBA16 -> PixelRGBA16 # | |||||
ColorConvertible Pixel16 PixelRGBA16 # | |||||
Defined in Codec.Picture.Types | |||||
ColorConvertible PixelRGB16 PixelRGBA16 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelRGB16 -> PixelRGBA16 # promoteImage :: Image PixelRGB16 -> Image PixelRGBA16 # | |||||
ColorConvertible PixelRGB8 PixelRGBA16 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelRGB8 -> PixelRGBA16 # promoteImage :: Image PixelRGB8 -> Image PixelRGBA16 # | |||||
ColorConvertible PixelRGBA8 PixelRGBA16 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelRGBA8 -> PixelRGBA16 # promoteImage :: Image PixelRGBA8 -> Image PixelRGBA16 # | |||||
ColorConvertible PixelYA16 PixelRGBA16 # | |||||
Defined in Codec.Picture.Types Methods promotePixel :: PixelYA16 -> PixelRGBA16 # promoteImage :: Image PixelYA16 -> Image PixelRGBA16 # | |||||
ColorPlane PixelRGBA16 PlaneAlpha # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGBA16 -> PlaneAlpha -> Int | |||||
ColorPlane PixelRGBA16 PlaneBlue # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGBA16 -> PlaneBlue -> Int | |||||
ColorPlane PixelRGBA16 PlaneGreen # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGBA16 -> PlaneGreen -> Int | |||||
ColorPlane PixelRGBA16 PlaneRed # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelRGBA16 -> PlaneRed -> Int | |||||
TransparentPixel PixelRGBA16 PixelRGB16 # | |||||
Defined in Codec.Picture.Types Methods dropTransparency :: PixelRGBA16 -> PixelRGB16 # getTransparency :: PixelRGBA16 -> PixelBaseComponent PixelRGBA16 # | |||||
type PackedRepresentation PixelRGBA16 # | |||||
Defined in Codec.Picture.Types | |||||
type PixelBaseComponent PixelRGBA16 # | |||||
Defined in Codec.Picture.Types |
data PixelYCbCr8 #
Pixel type storing 8bit luminance, blue difference and red difference (YCbCr) information. Values are stored in the following order:
- Y (luminance)
- Cb
- Cr
Constructors
PixelYCbCr8 !Pixel8 !Pixel8 !Pixel8 |
Instances
JpgEncodable PixelYCbCr8 # | |||||
Defined in Codec.Picture.Jpg Methods additionalBlocks :: Image PixelYCbCr8 -> [JpgFrame] componentsOfColorSpace :: Image PixelYCbCr8 -> [JpgComponent] encodingState :: Int -> Image PixelYCbCr8 -> Vector EncoderState imageHuffmanTables :: Image PixelYCbCr8 -> [(JpgHuffmanTableSpec, HuffmanPackedTree)] scanSpecificationOfColorSpace :: Image PixelYCbCr8 -> [JpgScanSpecification] quantTableSpec :: Image PixelYCbCr8 -> Int -> [JpgQuantTableSpec] | |||||
TiffSaveable PixelYCbCr8 # | |||||
Defined in Codec.Picture.Tiff Methods colorSpaceOfPixel :: PixelYCbCr8 -> TiffColorspace extraSampleCodeOfPixel :: PixelYCbCr8 -> Maybe ExtraSample subSamplingInfo :: PixelYCbCr8 -> Vector Word32 sampleFormat :: PixelYCbCr8 -> [TiffSampleFormat] | |||||
LumaPlaneExtractable PixelYCbCr8 # | |||||
Defined in Codec.Picture.Types Methods computeLuma :: PixelYCbCr8 -> PixelBaseComponent PixelYCbCr8 # extractLumaPlane :: Image PixelYCbCr8 -> Image (PixelBaseComponent PixelYCbCr8) # | |||||
Pixel PixelYCbCr8 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods mixWith :: (Int -> PixelBaseComponent PixelYCbCr8 -> PixelBaseComponent PixelYCbCr8 -> PixelBaseComponent PixelYCbCr8) -> PixelYCbCr8 -> PixelYCbCr8 -> PixelYCbCr8 # mixWithAlpha :: (Int -> PixelBaseComponent PixelYCbCr8 -> PixelBaseComponent PixelYCbCr8 -> PixelBaseComponent PixelYCbCr8) -> (PixelBaseComponent PixelYCbCr8 -> PixelBaseComponent PixelYCbCr8 -> PixelBaseComponent PixelYCbCr8) -> PixelYCbCr8 -> PixelYCbCr8 -> PixelYCbCr8 # pixelOpacity :: PixelYCbCr8 -> PixelBaseComponent PixelYCbCr8 # componentCount :: PixelYCbCr8 -> Int # colorMap :: (PixelBaseComponent PixelYCbCr8 -> PixelBaseComponent PixelYCbCr8) -> PixelYCbCr8 -> PixelYCbCr8 # pixelBaseIndex :: Image PixelYCbCr8 -> Int -> Int -> Int # mutablePixelBaseIndex :: MutableImage s PixelYCbCr8 -> Int -> Int -> Int # pixelAt :: Image PixelYCbCr8 -> Int -> Int -> PixelYCbCr8 # readPixel :: PrimMonad m => MutableImage (PrimState m) PixelYCbCr8 -> Int -> Int -> m PixelYCbCr8 # writePixel :: PrimMonad m => MutableImage (PrimState m) PixelYCbCr8 -> Int -> Int -> PixelYCbCr8 -> m () # unsafePixelAt :: Vector (PixelBaseComponent PixelYCbCr8) -> Int -> PixelYCbCr8 # unsafeReadPixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelYCbCr8) -> Int -> m PixelYCbCr8 # unsafeWritePixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelYCbCr8) -> Int -> PixelYCbCr8 -> m () # | |||||
Show PixelYCbCr8 # | |||||
Defined in Codec.Picture.Types Methods showsPrec :: Int -> PixelYCbCr8 -> ShowS # show :: PixelYCbCr8 -> String # showList :: [PixelYCbCr8] -> ShowS # | |||||
Eq PixelYCbCr8 # | |||||
Defined in Codec.Picture.Types | |||||
Ord PixelYCbCr8 # | |||||
Defined in Codec.Picture.Types Methods compare :: PixelYCbCr8 -> PixelYCbCr8 -> Ordering # (<) :: PixelYCbCr8 -> PixelYCbCr8 -> Bool # (<=) :: PixelYCbCr8 -> PixelYCbCr8 -> Bool # (>) :: PixelYCbCr8 -> PixelYCbCr8 -> Bool # (>=) :: PixelYCbCr8 -> PixelYCbCr8 -> Bool # max :: PixelYCbCr8 -> PixelYCbCr8 -> PixelYCbCr8 # min :: PixelYCbCr8 -> PixelYCbCr8 -> PixelYCbCr8 # | |||||
ColorPlane PixelYCbCr8 PlaneCb # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelYCbCr8 -> PlaneCb -> Int | |||||
ColorPlane PixelYCbCr8 PlaneCr # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelYCbCr8 -> PlaneCr -> Int | |||||
ColorPlane PixelYCbCr8 PlaneLuma # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelYCbCr8 -> PlaneLuma -> Int | |||||
ColorSpaceConvertible PixelRGB8 PixelYCbCr8 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelRGB8 -> PixelYCbCr8 # convertImage :: Image PixelRGB8 -> Image PixelYCbCr8 # | |||||
ColorSpaceConvertible PixelYCbCr8 PixelRGB8 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelYCbCr8 -> PixelRGB8 # convertImage :: Image PixelYCbCr8 -> Image PixelRGB8 # | |||||
type PixelBaseComponent PixelYCbCr8 # | |||||
Defined in Codec.Picture.Types |
data PixelCMYK8 #
Pixel type storing 8bit cyan, magenta, yellow and black (CMYK) information. Values are stored in the following order:
- Cyan
- Magenta
- Yellow
- Black
Constructors
PixelCMYK8 !Pixel8 !Pixel8 !Pixel8 !Pixel8 |
Instances
JpgEncodable PixelCMYK8 # | |||||
Defined in Codec.Picture.Jpg Methods additionalBlocks :: Image PixelCMYK8 -> [JpgFrame] componentsOfColorSpace :: Image PixelCMYK8 -> [JpgComponent] encodingState :: Int -> Image PixelCMYK8 -> Vector EncoderState imageHuffmanTables :: Image PixelCMYK8 -> [(JpgHuffmanTableSpec, HuffmanPackedTree)] scanSpecificationOfColorSpace :: Image PixelCMYK8 -> [JpgScanSpecification] quantTableSpec :: Image PixelCMYK8 -> Int -> [JpgQuantTableSpec] | |||||
TiffSaveable PixelCMYK8 # | |||||
Defined in Codec.Picture.Tiff Methods colorSpaceOfPixel :: PixelCMYK8 -> TiffColorspace extraSampleCodeOfPixel :: PixelCMYK8 -> Maybe ExtraSample subSamplingInfo :: PixelCMYK8 -> Vector Word32 sampleFormat :: PixelCMYK8 -> [TiffSampleFormat] | |||||
PackeablePixel PixelCMYK8 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods packPixel :: PixelCMYK8 -> PackedRepresentation PixelCMYK8 # unpackPixel :: PackedRepresentation PixelCMYK8 -> PixelCMYK8 # | |||||
Pixel PixelCMYK8 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods mixWith :: (Int -> PixelBaseComponent PixelCMYK8 -> PixelBaseComponent PixelCMYK8 -> PixelBaseComponent PixelCMYK8) -> PixelCMYK8 -> PixelCMYK8 -> PixelCMYK8 # mixWithAlpha :: (Int -> PixelBaseComponent PixelCMYK8 -> PixelBaseComponent PixelCMYK8 -> PixelBaseComponent PixelCMYK8) -> (PixelBaseComponent PixelCMYK8 -> PixelBaseComponent PixelCMYK8 -> PixelBaseComponent PixelCMYK8) -> PixelCMYK8 -> PixelCMYK8 -> PixelCMYK8 # pixelOpacity :: PixelCMYK8 -> PixelBaseComponent PixelCMYK8 # componentCount :: PixelCMYK8 -> Int # colorMap :: (PixelBaseComponent PixelCMYK8 -> PixelBaseComponent PixelCMYK8) -> PixelCMYK8 -> PixelCMYK8 # pixelBaseIndex :: Image PixelCMYK8 -> Int -> Int -> Int # mutablePixelBaseIndex :: MutableImage s PixelCMYK8 -> Int -> Int -> Int # pixelAt :: Image PixelCMYK8 -> Int -> Int -> PixelCMYK8 # readPixel :: PrimMonad m => MutableImage (PrimState m) PixelCMYK8 -> Int -> Int -> m PixelCMYK8 # writePixel :: PrimMonad m => MutableImage (PrimState m) PixelCMYK8 -> Int -> Int -> PixelCMYK8 -> m () # unsafePixelAt :: Vector (PixelBaseComponent PixelCMYK8) -> Int -> PixelCMYK8 # unsafeReadPixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelCMYK8) -> Int -> m PixelCMYK8 # unsafeWritePixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelCMYK8) -> Int -> PixelCMYK8 -> m () # | |||||
Show PixelCMYK8 # | |||||
Defined in Codec.Picture.Types Methods showsPrec :: Int -> PixelCMYK8 -> ShowS # show :: PixelCMYK8 -> String # showList :: [PixelCMYK8] -> ShowS # | |||||
Eq PixelCMYK8 # | |||||
Defined in Codec.Picture.Types | |||||
Ord PixelCMYK8 # | |||||
Defined in Codec.Picture.Types Methods compare :: PixelCMYK8 -> PixelCMYK8 -> Ordering # (<) :: PixelCMYK8 -> PixelCMYK8 -> Bool # (<=) :: PixelCMYK8 -> PixelCMYK8 -> Bool # (>) :: PixelCMYK8 -> PixelCMYK8 -> Bool # (>=) :: PixelCMYK8 -> PixelCMYK8 -> Bool # max :: PixelCMYK8 -> PixelCMYK8 -> PixelCMYK8 # min :: PixelCMYK8 -> PixelCMYK8 -> PixelCMYK8 # | |||||
ColorPlane PixelCMYK8 PlaneBlack # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelCMYK8 -> PlaneBlack -> Int | |||||
ColorPlane PixelCMYK8 PlaneCyan # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelCMYK8 -> PlaneCyan -> Int | |||||
ColorPlane PixelCMYK8 PlaneMagenta # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelCMYK8 -> PlaneMagenta -> Int | |||||
ColorPlane PixelCMYK8 PlaneYellow # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelCMYK8 -> PlaneYellow -> Int | |||||
ColorSpaceConvertible PixelCMYK8 PixelRGB8 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelCMYK8 -> PixelRGB8 # convertImage :: Image PixelCMYK8 -> Image PixelRGB8 # | |||||
ColorSpaceConvertible PixelRGB8 PixelCMYK8 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelRGB8 -> PixelCMYK8 # convertImage :: Image PixelRGB8 -> Image PixelCMYK8 # | |||||
ColorSpaceConvertible PixelYCbCrK8 PixelCMYK8 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelYCbCrK8 -> PixelCMYK8 # | |||||
type PackedRepresentation PixelCMYK8 # | |||||
Defined in Codec.Picture.Types | |||||
type PixelBaseComponent PixelCMYK8 # | |||||
Defined in Codec.Picture.Types |
data PixelCMYK16 #
Pixel type storing 16bit cyan, magenta, yellow and black (CMYK) information. Values are stored in the following order:
- Cyan
- Magenta
- Yellow
- Black
Constructors
PixelCMYK16 !Pixel16 !Pixel16 !Pixel16 !Pixel16 |
Instances
TiffSaveable PixelCMYK16 # | |||||
Defined in Codec.Picture.Tiff Methods colorSpaceOfPixel :: PixelCMYK16 -> TiffColorspace extraSampleCodeOfPixel :: PixelCMYK16 -> Maybe ExtraSample subSamplingInfo :: PixelCMYK16 -> Vector Word32 sampleFormat :: PixelCMYK16 -> [TiffSampleFormat] | |||||
PackeablePixel PixelCMYK16 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods packPixel :: PixelCMYK16 -> PackedRepresentation PixelCMYK16 # unpackPixel :: PackedRepresentation PixelCMYK16 -> PixelCMYK16 # | |||||
Pixel PixelCMYK16 # | |||||
Defined in Codec.Picture.Types Associated Types
Methods mixWith :: (Int -> PixelBaseComponent PixelCMYK16 -> PixelBaseComponent PixelCMYK16 -> PixelBaseComponent PixelCMYK16) -> PixelCMYK16 -> PixelCMYK16 -> PixelCMYK16 # mixWithAlpha :: (Int -> PixelBaseComponent PixelCMYK16 -> PixelBaseComponent PixelCMYK16 -> PixelBaseComponent PixelCMYK16) -> (PixelBaseComponent PixelCMYK16 -> PixelBaseComponent PixelCMYK16 -> PixelBaseComponent PixelCMYK16) -> PixelCMYK16 -> PixelCMYK16 -> PixelCMYK16 # pixelOpacity :: PixelCMYK16 -> PixelBaseComponent PixelCMYK16 # componentCount :: PixelCMYK16 -> Int # colorMap :: (PixelBaseComponent PixelCMYK16 -> PixelBaseComponent PixelCMYK16) -> PixelCMYK16 -> PixelCMYK16 # pixelBaseIndex :: Image PixelCMYK16 -> Int -> Int -> Int # mutablePixelBaseIndex :: MutableImage s PixelCMYK16 -> Int -> Int -> Int # pixelAt :: Image PixelCMYK16 -> Int -> Int -> PixelCMYK16 # readPixel :: PrimMonad m => MutableImage (PrimState m) PixelCMYK16 -> Int -> Int -> m PixelCMYK16 # writePixel :: PrimMonad m => MutableImage (PrimState m) PixelCMYK16 -> Int -> Int -> PixelCMYK16 -> m () # unsafePixelAt :: Vector (PixelBaseComponent PixelCMYK16) -> Int -> PixelCMYK16 # unsafeReadPixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelCMYK16) -> Int -> m PixelCMYK16 # unsafeWritePixel :: PrimMonad m => STVector (PrimState m) (PixelBaseComponent PixelCMYK16) -> Int -> PixelCMYK16 -> m () # | |||||
Show PixelCMYK16 # | |||||
Defined in Codec.Picture.Types Methods showsPrec :: Int -> PixelCMYK16 -> ShowS # show :: PixelCMYK16 -> String # showList :: [PixelCMYK16] -> ShowS # | |||||
Eq PixelCMYK16 # | |||||
Defined in Codec.Picture.Types | |||||
Ord PixelCMYK16 # | |||||
Defined in Codec.Picture.Types Methods compare :: PixelCMYK16 -> PixelCMYK16 -> Ordering # (<) :: PixelCMYK16 -> PixelCMYK16 -> Bool # (<=) :: PixelCMYK16 -> PixelCMYK16 -> Bool # (>) :: PixelCMYK16 -> PixelCMYK16 -> Bool # (>=) :: PixelCMYK16 -> PixelCMYK16 -> Bool # max :: PixelCMYK16 -> PixelCMYK16 -> PixelCMYK16 # min :: PixelCMYK16 -> PixelCMYK16 -> PixelCMYK16 # | |||||
ColorPlane PixelCMYK16 PlaneBlack # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelCMYK16 -> PlaneBlack -> Int | |||||
ColorPlane PixelCMYK16 PlaneCyan # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelCMYK16 -> PlaneCyan -> Int | |||||
ColorPlane PixelCMYK16 PlaneMagenta # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelCMYK16 -> PlaneMagenta -> Int | |||||
ColorPlane PixelCMYK16 PlaneYellow # | |||||
Defined in Codec.Picture.Types Methods toComponentIndex :: PixelCMYK16 -> PlaneYellow -> Int | |||||
ColorSpaceConvertible PixelCMYK16 PixelRGB16 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelCMYK16 -> PixelRGB16 # convertImage :: Image PixelCMYK16 -> Image PixelRGB16 # | |||||
ColorSpaceConvertible PixelRGB16 PixelCMYK16 # | |||||
Defined in Codec.Picture.Types Methods convertPixel :: PixelRGB16 -> PixelCMYK16 # convertImage :: Image PixelRGB16 -> Image PixelCMYK16 # | |||||
type PackedRepresentation PixelCMYK16 # | |||||
Defined in Codec.Picture.Types | |||||
type PixelBaseComponent PixelCMYK16 # | |||||
Defined in Codec.Picture.Types |
Foreign unsafe import
Arguments
:: (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