Copyright | (c) Alexey Kuleshevich 2018 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
- readArray :: Readable f arr => f -> ReadOptions f -> FilePath -> IO arr
- readImage :: (Source S Ix2 (Pixel cs e), ColorSpace cs e) => FilePath -> IO (Image S cs e)
- readImageAuto :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => FilePath -> IO (Image r cs e)
- writeArray :: Writable f arr => f -> WriteOptions f -> FilePath -> arr -> IO ()
- writeImage :: (Source r Ix2 (Pixel cs e), ColorSpace cs e) => FilePath -> Image r cs e -> IO ()
- writeImageAuto :: (Source r Ix2 (Pixel cs e), ColorSpace cs e, ToYA cs e, ToRGBA cs e, ToYCbCr cs e, ToCMYK cs e) => FilePath -> Image r cs e -> IO ()
- data ExternalViewer = ExternalViewer FilePath [String] Int
- displayImage :: Writable (Auto TIF) (Image r cs e) => Image r cs e -> IO ()
- displayImageUsing :: Writable (Auto TIF) (Image r cs e) => ExternalViewer -> Bool -> Image r cs e -> IO ()
- displayImageFile :: ExternalViewer -> FilePath -> IO ()
- defaultViewer :: ExternalViewer
- eogViewer :: ExternalViewer
- gpicviewViewer :: ExternalViewer
- fehViewer :: ExternalViewer
- gimpViewer :: ExternalViewer
- class (Default (ReadOptions f), Default (WriteOptions f), Show f) => FileFormat f where
- type ReadOptions f
- type WriteOptions f
- class Readable f arr where
- class Writable f arr where
- newtype ConvertError = ConvertError String
- newtype EncodeError = EncodeError String
- newtype DecodeError = DecodeError String
- newtype Sequence f = Sequence f
- newtype Auto f = Auto f
- type Image r cs e = Array r Ix2 (Pixel cs e)
- defaultReadOptions :: FileFormat f => f -> ReadOptions f
- defaultWriteOptions :: FileFormat f => f -> WriteOptions f
- toProxy :: a -> Proxy a
- fromMaybeEncode :: forall f r cs e b. (ColorSpace cs e, FileFormat f, Typeable r) => f -> Proxy (Image r cs e) -> Maybe b -> b
- fromEitherDecode :: forall r cs e a f. (ColorSpace cs e, FileFormat f, Typeable r) => f -> (a -> String) -> (a -> Maybe (Image r cs e)) -> Either String a -> Image r cs e
- convertEither :: forall r cs e a f. (ColorSpace cs e, FileFormat f, Typeable r) => f -> (a -> String) -> (a -> Maybe (Image r cs e)) -> a -> Either ConvertError (Image r cs e)
- data Encode out
- encodeImage :: (Source r Ix2 (Pixel cs e), ColorSpace cs e) => [Encode (Image r cs e)] -> FilePath -> Image r cs e -> ByteString
- imageWriteFormats :: (Source r Ix2 (Pixel cs e), ColorSpace cs e) => [Encode (Image r cs e)]
- imageWriteAutoFormats :: (Source r Ix2 (Pixel cs e), ColorSpace cs e, ToYA cs e, ToRGBA cs e, ToYCbCr cs e, ToCMYK cs e) => [Encode (Image r cs e)]
- data Decode out
- decodeImage :: (Source r Ix2 (Pixel cs e), ColorSpace cs e) => [Decode (Image r cs e)] -> FilePath -> ByteString -> Image r cs e
- imageReadFormats :: (Source S Ix2 (Pixel cs e), ColorSpace cs e) => [Decode (Image S cs e)]
- imageReadAutoFormats :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => [Decode (Image r cs e)]
- data BMP = BMP
- data GIF = GIF
- data WriteOptionsGIF
- woGetPaletteOptionsGIF :: WriteOptionsGIF -> PaletteOptions
- woSetPaletteOptionsGIF :: PaletteOptions -> WriteOptionsGIF -> WriteOptionsGIF
- data PaletteOptions :: * = PaletteOptions {}
- data PaletteCreationMethod :: *
- data WriteOptionsSequenceGIF
- woGetGifLoopingGIFs :: WriteOptionsSequenceGIF -> GifLooping
- woGetPaletteOptionsGIFs :: WriteOptionsSequenceGIF -> PaletteOptions
- woSetGifLoopingGIFs :: GifLooping -> WriteOptionsSequenceGIF -> WriteOptionsSequenceGIF
- woSetPaletteOptionsGIFs :: PaletteOptions -> WriteOptionsSequenceGIF -> WriteOptionsSequenceGIF
- type GifDelay = Int
- data GifLooping :: *
- data HDR = HDR
- data JPG = JPG
- data WriteOptionsJPG
- woGetQualityJPG :: WriteOptionsJPG -> Word8
- woSetQualityJPG :: Word8 -> WriteOptionsJPG -> WriteOptionsJPG
- data PNG = PNG
- data TGA = TGA
- data TIF = TIF
- toAnyCS :: forall r' cs' e' r cs e. (Source r' Ix2 (Pixel cs' e'), Mutable r Ix2 (Pixel cs e), Storable (Pixel cs e), ColorSpace cs e, ToYA cs' e', ToRGBA cs' e', ToHSIA cs' e', ToCMYKA cs' e', ToYCbCrA cs' e') => Image r' cs' e' -> Maybe (Image r cs e)
- toJPImageY8 :: Source r Ix2 (Pixel Y Word8) => Image r Y Word8 -> Image Pixel8
- toJPImageYA8 :: Source r Ix2 (Pixel YA Word8) => Image r YA Word8 -> Image PixelYA8
- toJPImageY16 :: Source r Ix2 (Pixel Y Word16) => Image r Y Word16 -> Image Pixel16
- toJPImageYA16 :: Source r Ix2 (Pixel YA Word16) => Image r YA Word16 -> Image PixelYA16
- toJPImageYF :: Source r Ix2 (Pixel Y Float) => Image r Y Float -> Image PixelF
- toJPImageRGB8 :: Source r Ix2 (Pixel RGB Word8) => Image r RGB Word8 -> Image PixelRGB8
- toJPImageRGBA8 :: Source r Ix2 (Pixel RGBA Word8) => Image r RGBA Word8 -> Image PixelRGBA8
- toJPImageRGB16 :: Source r Ix2 (Pixel RGB Word16) => Image r RGB Word16 -> Image PixelRGB16
- toJPImageRGBA16 :: Source r Ix2 (Pixel RGBA Word16) => Image r RGBA Word16 -> Image PixelRGBA16
- toJPImageRGBF :: Source r Ix2 (Pixel RGB Float) => Image r RGB Float -> Image PixelRGBF
- toJPImageYCbCr8 :: Source r Ix2 (Pixel YCbCr Word8) => Image r YCbCr Word8 -> Image PixelYCbCr8
- toJPImageCMYK8 :: Source r Ix2 (Pixel CMYK Word8) => Image r CMYK Word8 -> Image PixelCMYK8
- data PBM = PBM
- data PGM = PGM
- data PPM = PPM
Reading
:: Readable f arr | |
=> f | File format that should be used while decoding the file |
-> ReadOptions f | Any file format related decoding options. Use |
-> FilePath | Path to the file |
-> IO arr |
Read an array from one of the supported file formats.
:: (Source S Ix2 (Pixel cs e), ColorSpace cs e) | |
=> FilePath | File path for an image |
-> IO (Image S cs e) |
Try to guess an image format from file's extension, then attempt to decode it as such. In order
to supply the format manually and thus avoid this guessing technique, use readArray
instead. Color space and precision of the result array must match exactly that of the actual
image, in order to apply auto conversion use readImageAuto
instead.
Might throw ConvertError
, DecodeError
and other standard errors related to file IO.
Result image will be read as specified by the type signature:
>>>
frog <- readImage "files/frog.jpg" :: IO (Image S YCbCr Word8)
>>>
displayImage frog
In case when the result image type does not match the color space or precision of the actual
image file, ConvertError
will be thrown.
>>>
frog <- readImage "files/frog.jpg" :: IO (Image S CMYK Word8)
>>>
displayImage frog
*** Exception: ConvertError "Cannot decode JPG image <Image S YCbCr Word8> as <Image S CMYK Word8>"
Whenever image is not in the color space or precision that we need, either use readImageAuto
or
manually convert to the desired one by using the appropriate conversion functions:
>>>
frogCMYK <- readImageAuto "files/frog.jpg" :: IO (Image S CMYK Double)
>>>
displayImage frogCMYK
:: (Mutable r Ix2 (Pixel cs e), ColorSpace cs e) | |
=> FilePath | File path for an image |
-> IO (Image r cs e) |
Same as readImage
, but will perform any possible color space and
precision conversions in order to match the result image type. Very useful
whenever image format isn't known at compile time.
Writing
:: Writable f arr | |
=> f | Format to use while encoding the array |
-> WriteOptions f | Any file format related encoding options. Use |
-> FilePath | |
-> arr | |
-> IO () |
writeImage :: (Source r Ix2 (Pixel cs e), ColorSpace cs e) => FilePath -> Image r cs e -> IO () Source #
Inverse of the readImage
, but similarly to it, will guess an output file format from the file
extension and will write to file any image with the colorspace that is supported by that
format. Precision of the image might be adjusted using Elevator
if precision of the source
array is not supported by the image file format. For instance, @r@ 'RGBA' 'Double'
being saved as PNG
file would be written as @r@ 'RGBA' 'Word16', thus using highest
supported precision Word16
for that format. If automatic colors space is also desired,
writeImageAuto
can be used instead.
Can throw ConvertError
, EncodeError
and other usual IO errors.
writeImageAuto :: (Source r Ix2 (Pixel cs e), ColorSpace cs e, ToYA cs e, ToRGBA cs e, ToYCbCr cs e, ToCMYK cs e) => FilePath -> Image r cs e -> IO () Source #
Displaying
data ExternalViewer Source #
External viewing application to use for displaying images.
ExternalViewer FilePath [String] Int | Any custom viewer, which can be specified:
|
displayImage :: Writable (Auto TIF) (Image r cs e) => Image r cs e -> IO () Source #
Makes a call to an external viewer that is set as a default image viewer by the OS. This is a non-blocking function call, so it might take some time before an image will appear.
:: Writable (Auto TIF) (Image r cs e) | |
=> ExternalViewer | Image viewer program |
-> Bool | Should a call block the cuurrent thread untul viewer is closed. |
-> Image r cs e | |
-> IO () |
An image is written as a .tiff
file into an operating system's temporary
directory and passed as an argument to the external viewer program.
displayImageUsing :: Writable (Auto TIF) (Image r cs e) =>
ExternalViewer -- ^ Image viewer program
-> Bool -- ^ Should a call block the cuurrent thread untul viewer is closed.
-> Image r cs e -> IO ()
displayImageFile :: ExternalViewer -> FilePath -> IO () Source #
Displays an image file by calling an external image viewer.
Common viewers
defaultViewer :: ExternalViewer Source #
Default viewer is inferred from the operating system.
eogViewer :: ExternalViewer Source #
eog /tmp/hip/img.tiff
gpicviewViewer :: ExternalViewer Source #
gpicview /tmp/hip/img.tiff
fehViewer :: ExternalViewer Source #
feh --fullscreen --auto-zoom /tmp/hip/img.tiff
gimpViewer :: ExternalViewer Source #
gimp /tmp/hip/img.tiff
Supported Image Formats
class (Default (ReadOptions f), Default (WriteOptions f), Show f) => FileFormat f where Source #
File format. Helps in guessing file format from a file extension, as well as supplying format specific options during saving the file.
type ReadOptions f Source #
Options that can be used during reading a file in this format.
type WriteOptions f Source #
Options that can be used during writing a file in this format.
Default file extension for this file format.
exts :: f -> [String] Source #
Other known file extensions for this file format, eg. ".jpeg", ".jpg".
isFormat :: String -> f -> Bool Source #
Checks if a file extension corresponds to the format, eg.
isFormat ".png" PNG == True
FileFormat TIF Source # | |
FileFormat TGA Source # | |
FileFormat JPG Source # | |
FileFormat HDR Source # | |
FileFormat GIF Source # | |
FileFormat PNG Source # | |
FileFormat BMP Source # | |
FileFormat PPM Source # | |
FileFormat PGM Source # | |
FileFormat PBM Source # | |
FileFormat f => FileFormat (Auto f) Source # | |
FileFormat (Sequence (Auto GIF)) Source # | |
FileFormat (Sequence (Auto PPM)) Source # | |
FileFormat (Sequence (Auto PGM)) Source # | |
FileFormat (Sequence (Auto PBM)) Source # | |
FileFormat (Sequence GIF) Source # | |
FileFormat (Sequence PPM) Source # | |
FileFormat (Sequence PGM) Source # | |
FileFormat (Sequence PBM) Source # | |
FileFormat (Decode (Image r cs e)) Source # | |
FileFormat (Encode (Image r cs e)) Source # | |
class Readable f arr where Source #
File formats that can be read into an Array.
decode :: f -> ReadOptions f -> ByteString -> arr Source #
Decode a ByteString
into an Array.
class Writable f arr where Source #
Arrays that can be written into a file.
encode :: f -> WriteOptions f -> arr -> ByteString Source #
Encode an array into a ByteString
.
newtype ConvertError Source #
Conversion error, which is thrown when there is a mismatch between the expected array type and the one supported by the file format. It is also thrown upon a failure of automatic conversion between those types, in case such conversion is utilized.
newtype EncodeError Source #
This exception can be thrown while writing/encoding into a file and indicates an error in an array that is being encoded.
newtype DecodeError Source #
This exception can be thrown while reading/decoding a file and indicates an error in the file itself.
Special wrapper for formats that support encoding/decoding sequence of array.
Sequence f |
Auto f |
defaultReadOptions :: FileFormat f => f -> ReadOptions f Source #
Generate default read options for a file format
defaultWriteOptions :: FileFormat f => f -> WriteOptions f Source #
Generate default write options for a file format
fromMaybeEncode :: forall f r cs e b. (ColorSpace cs e, FileFormat f, Typeable r) => f -> Proxy (Image r cs e) -> Maybe b -> b Source #
Encode an image using the supplied function or throw an error in case of failure.
fromEitherDecode :: forall r cs e a f. (ColorSpace cs e, FileFormat f, Typeable r) => f -> (a -> String) -> (a -> Maybe (Image r cs e)) -> Either String a -> Image r cs e Source #
Decode an image using the supplied function or throw an error in case of failure.
convertEither :: forall r cs e a f. (ColorSpace cs e, FileFormat f, Typeable r) => f -> (a -> String) -> (a -> Maybe (Image r cs e)) -> a -> Either ConvertError (Image r cs e) Source #
Convert an image using the supplied function and return ConvertError error in case of failure.
encodeImage :: (Source r Ix2 (Pixel cs e), ColorSpace cs e) => [Encode (Image r cs e)] -> FilePath -> Image r cs e -> ByteString Source #
imageWriteFormats :: (Source r Ix2 (Pixel cs e), ColorSpace cs e) => [Encode (Image r cs e)] Source #
imageWriteAutoFormats :: (Source r Ix2 (Pixel cs e), ColorSpace cs e, ToYA cs e, ToRGBA cs e, ToYCbCr cs e, ToCMYK cs e) => [Encode (Image r cs e)] Source #
decodeImage :: (Source r Ix2 (Pixel cs e), ColorSpace cs e) => [Decode (Image r cs e)] -> FilePath -> ByteString -> Image r cs e Source #
imageReadFormats :: (Source S Ix2 (Pixel cs e), ColorSpace cs e) => [Decode (Image S cs e)] Source #
imageReadAutoFormats :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => [Decode (Image r cs e)] Source #
JuicyPixels formats
BMP
Bitmap image with .bmp
extension.
Show BMP Source # | |
FileFormat BMP Source # | |
(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable BMP (Image r cs e) Source # | |
ColorSpace cs e => Readable BMP (Image S cs e) Source # | |
(ColorSpace cs e, ToRGBA cs e, Source r Ix2 (Pixel cs e)) => Writable (Auto BMP) (Image r cs e) Source # | |
(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto BMP) (Image r cs e) Source # | |
type ReadOptions BMP Source # | |
type WriteOptions BMP Source # | |
GIF
Graphics Interchange Format image with .gif
extension.
data PaletteOptions :: * #
To specify how the palette will be created.
PaletteOptions | |
|
data PaletteCreationMethod :: * #
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. |
Animated
woSetPaletteOptionsGIFs :: PaletteOptions -> WriteOptionsSequenceGIF -> WriteOptionsSequenceGIF Source #
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.
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 |
HDR
High-dynamic-range image with .hdr
or .pic
extension.
Show HDR Source # | |
FileFormat HDR Source # | |
(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable HDR (Image r cs e) Source # | |
ColorSpace cs e => Readable HDR (Image S cs e) Source # | |
(ColorSpace cs e, ToRGB cs e, Source r Ix2 (Pixel cs e)) => Writable (Auto HDR) (Image r cs e) Source # | |
(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto HDR) (Image r cs e) Source # | |
type ReadOptions HDR Source # | |
type WriteOptions HDR Source # | |
JPG
Joint Photographic Experts Group image with .jpg
or .jpeg
extension.
Show JPG Source # | |
FileFormat JPG Source # | |
(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable JPG (Image r cs e) Source # | |
ColorSpace cs e => Readable JPG (Image S cs e) Source # | |
(ColorSpace cs e, ToYCbCr cs e, Source r Ix2 (Pixel cs e)) => Writable (Auto JPG) (Image r cs e) Source # | |
(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto JPG) (Image r cs e) Source # | |
type ReadOptions JPG Source # | |
type WriteOptions JPG Source # | |
woSetQualityJPG :: Word8 -> WriteOptionsJPG -> WriteOptionsJPG Source #
Set the image quality, supplied value will be clamped to [0, 100]
range. This setting directly affects the Jpeg compression level.
PNG
Portable Network Graphics image with .png
extension.
Show PNG Source # | |
FileFormat PNG Source # | |
(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable PNG (Image r cs e) Source # | |
ColorSpace cs e => Readable PNG (Image S cs e) Source # | |
(ColorSpace cs e, ToYA cs e, ToRGBA cs e, Source r Ix2 (Pixel cs e)) => Writable (Auto PNG) (Image r cs e) Source # | |
(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto PNG) (Image r cs e) Source # | |
type ReadOptions PNG Source # | |
type WriteOptions PNG Source # | |
TGA
Truevision Graphics Adapter image with .tga extension.
Show TGA Source # | |
FileFormat TGA Source # | |
(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable TGA (Image r cs e) Source # | |
ColorSpace cs e => Readable TGA (Image S cs e) Source # | |
(ColorSpace cs e, ToRGBA cs e, Source r Ix2 (Pixel cs e)) => Writable (Auto TGA) (Image r cs e) Source # | |
(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto TGA) (Image r cs e) Source # | |
type ReadOptions TGA Source # | |
type WriteOptions TGA Source # | |
TIF
Tagged Image File Format image with .tif
or .tiff
extension.
Show TIF Source # | |
FileFormat TIF Source # | |
(ColorSpace cs e, Source r Ix2 (Pixel cs e)) => Writable TIF (Image r cs e) Source # | |
ColorSpace cs e => Readable TIF (Image S cs e) Source # | |
(ColorSpace cs e, ToRGBA cs e, Source r Ix2 (Pixel cs e)) => Writable (Auto TIF) (Image r cs e) Source # | |
(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto TIF) (Image r cs e) Source # | |
type ReadOptions TIF Source # | |
type WriteOptions TIF Source # | |
JuciyPixels conversion
To JuicyPixels
toAnyCS :: forall r' cs' e' r cs e. (Source r' Ix2 (Pixel cs' e'), Mutable r Ix2 (Pixel cs e), Storable (Pixel cs e), ColorSpace cs e, ToYA cs' e', ToRGBA cs' e', ToHSIA cs' e', ToCMYKA cs' e', ToYCbCrA cs' e') => Image r' cs' e' -> Maybe (Image r cs e) Source #
toJPImageRGBA8 :: Source r Ix2 (Pixel RGBA Word8) => Image r RGBA Word8 -> Image PixelRGBA8 Source #
toJPImageRGB16 :: Source r Ix2 (Pixel RGB Word16) => Image r RGB Word16 -> Image PixelRGB16 Source #
toJPImageRGBA16 :: Source r Ix2 (Pixel RGBA Word16) => Image r RGBA Word16 -> Image PixelRGBA16 Source #
toJPImageYCbCr8 :: Source r Ix2 (Pixel YCbCr Word8) => Image r YCbCr Word8 -> Image PixelYCbCr8 Source #
toJPImageCMYK8 :: Source r Ix2 (Pixel CMYK Word8) => Image r CMYK Word8 -> Image PixelCMYK8 Source #
From JuicyPixels
Netpbm formats
PBM
Netpbm: portable bitmap image with .pbm
extension.
Show PBM Source # | |
FileFormat PBM Source # | |
ColorSpace cs e => Readable PBM (Image S cs e) Source # | |
FileFormat (Sequence (Auto PBM)) Source # | |
FileFormat (Sequence PBM) Source # | |
(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto PBM) (Image r cs e) Source # | |
(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Sequence (Auto PBM)) (Array B Ix1 (Image r cs e)) Source # | |
ColorSpace cs e => Readable (Sequence PBM) (Array B Ix1 (Image S cs e)) Source # | |
type ReadOptions PBM Source # | |
type WriteOptions PBM Source # | |
type ReadOptions (Sequence (Auto PBM)) Source # | |
type ReadOptions (Sequence PBM) Source # | |
type WriteOptions (Sequence (Auto PBM)) Source # | |
type WriteOptions (Sequence PBM) Source # | |
PGM
Netpbm: portable graymap image with .pgm
extension.
Show PGM Source # | |
FileFormat PGM Source # | |
ColorSpace cs e => Readable PGM (Image S cs e) Source # | |
FileFormat (Sequence (Auto PGM)) Source # | |
FileFormat (Sequence PGM) Source # | |
(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto PGM) (Image r cs e) Source # | |
(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Sequence (Auto PGM)) (Array B Ix1 (Image r cs e)) Source # | |
ColorSpace cs e => Readable (Sequence PGM) (Array B Ix1 (Image S cs e)) Source # | |
type ReadOptions PGM Source # | |
type WriteOptions PGM Source # | |
type ReadOptions (Sequence (Auto PGM)) Source # | |
type ReadOptions (Sequence PGM) Source # | |
type WriteOptions (Sequence (Auto PGM)) Source # | |
type WriteOptions (Sequence PGM) Source # | |
PPM
Netpbm: portable pixmap image with .ppm
extension.
Show PPM Source # | |
FileFormat PPM Source # | |
ColorSpace cs e => Readable PPM (Image S cs e) Source # | |
FileFormat (Sequence (Auto PPM)) Source # | |
FileFormat (Sequence PPM) Source # | |
(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Auto PPM) (Image r cs e) Source # | |
(Mutable r Ix2 (Pixel cs e), ColorSpace cs e) => Readable (Sequence (Auto PPM)) (Array B Ix1 (Image r cs e)) Source # | |
ColorSpace cs e => Readable (Sequence PPM) (Array B Ix1 (Image S cs e)) Source # | |
type ReadOptions PPM Source # | |
type WriteOptions PPM Source # | |
type ReadOptions (Sequence (Auto PPM)) Source # | |
type ReadOptions (Sequence PPM) Source # | |
type WriteOptions (Sequence (Auto PPM)) Source # | |
type WriteOptions (Sequence PPM) Source # | |