Copyright | (c) Alexey Kuleshevich 2018-2020 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- module Graphics.Pixel.ColorSpace
- type Image r cs e = Array r Ix2 (Pixel cs e)
- readArray :: (Readable f arr, MonadIO m) => f -> FilePath -> m arr
- readArrayWithMetadata :: (Readable f arr, MonadIO m) => f -> FilePath -> m (arr, Metadata f)
- readImage :: (ColorModel cs e, MonadIO m) => FilePath -> m (Image S cs e)
- readImageAuto :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadIO m) => FilePath -> m (Image r cs e)
- writeArray :: (Writable f arr, MonadIO m) => f -> WriteOptions f -> FilePath -> arr -> m ()
- writeImage :: (Source r Ix2 (Pixel cs e), ColorModel cs e, MonadIO m) => FilePath -> Image r cs e -> m ()
- writeImageAuto :: (Source r Ix2 (Pixel cs e), ColorSpace cs i e, ColorSpace (BaseSpace cs) i e, MonadIO m) => FilePath -> Image r cs e -> m ()
- data ExternalViewer = ExternalViewer FilePath [String] Int
- displayImage :: (Writable (Auto TIF) (Image r cs e), MonadIO m) => Image r cs e -> m ()
- displayImageUsing :: (Writable (Auto TIF) (Image r cs e), MonadIO m) => ExternalViewer -> Bool -> Image r cs e -> m ()
- displayImageFile :: MonadIO m => ExternalViewer -> FilePath -> m ()
- defaultViewer :: ExternalViewer
- eogViewer :: ExternalViewer
- gpicviewViewer :: ExternalViewer
- fehViewer :: ExternalViewer
- gimpViewer :: ExternalViewer
- data BMP = BMP
- newtype BitmapOptions = BitmapOptions {}
- decodeBMP :: (ColorModel cs e, MonadThrow m) => BMP -> ByteString -> m (Image S cs e)
- decodeWithMetadataBMP :: (ColorModel cs e, MonadThrow m) => BMP -> ByteString -> m (Image S cs e, Metadatas)
- decodeAutoBMP :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto BMP -> ByteString -> m (Image r cs e)
- decodeAutoWithMetadataBMP :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto BMP -> ByteString -> m (Image r cs e, Metadatas)
- encodeBMP :: forall cs e m. (ColorModel cs e, MonadThrow m) => BMP -> BitmapOptions -> Image S cs e -> m ByteString
- encodeAutoBMP :: forall r cs i e. (ColorSpace (BaseSpace cs) i e, ColorSpace cs i e, Source r Ix2 (Pixel cs e)) => Auto BMP -> BitmapOptions -> Image r cs e -> ByteString
- data GIF = GIF
- newtype GifOptions = GifOptions {}
- data SequenceGifOptions = SequenceGifOptions {}
- type GifDelay = Int
- data GifLooping
- data PaletteOptions = PaletteOptions {}
- data PaletteCreationMethod
- data GifDisposalMethod
- decodeGIF :: (ColorModel cs e, MonadThrow m) => GIF -> ByteString -> m (Image S cs e)
- decodeWithMetadataGIF :: (ColorModel cs e, MonadThrow m) => GIF -> ByteString -> m (Image S cs e, Metadatas)
- decodeAutoGIF :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto GIF -> ByteString -> m (Image r cs e)
- decodeAutoWithMetadataGIF :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto GIF -> ByteString -> m (Image r cs e, Metadatas)
- encodeGIF :: forall cs e m. (ColorModel cs e, MonadThrow m) => GIF -> GifOptions -> Image S cs e -> m ByteString
- encodeAutoGIF :: forall r cs i e m. (ColorSpace cs i e, Source r Ix2 (Pixel cs e), MonadThrow m) => Auto GIF -> GifOptions -> Image r cs e -> m ByteString
- decodeSequenceGIF :: (ColorModel cs e, MonadThrow m) => Sequence GIF -> ByteString -> m [Image S cs e]
- decodeSequenceWithMetadataGIF :: (ColorModel cs e, MonadThrow m) => Sequence GIF -> ByteString -> m ([Image S cs e], [GifDelay])
- decodeAutoSequenceGIF :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto (Sequence GIF) -> ByteString -> m [Image r cs e]
- decodeAutoSequenceWithMetadataGIF :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto (Sequence GIF) -> ByteString -> m ([Image r cs e], [GifDelay])
- data HDR = HDR
- newtype HdrOptions = HdrOptions {}
- decodeHDR :: (ColorModel cs e, MonadThrow m) => HDR -> ByteString -> m (Image S cs e)
- decodeWithMetadataHDR :: (ColorModel cs e, MonadThrow m) => HDR -> ByteString -> m (Image S cs e, Metadatas)
- decodeAutoHDR :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto HDR -> ByteString -> m (Image r cs e)
- decodeAutoWithMetadataHDR :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto HDR -> ByteString -> m (Image r cs e, Metadatas)
- encodeHDR :: forall cs e m. (ColorModel cs e, MonadThrow m) => HDR -> HdrOptions -> Image S cs e -> m ByteString
- encodeAutoHDR :: forall r cs i e. (ColorSpace cs i e, Source r Ix2 (Pixel cs e)) => Auto HDR -> HdrOptions -> Image r cs e -> ByteString
- data JPG = JPG
- data JpegOptions = JpegOptions {
- jpegQuality :: !Word8
- jpegMetadata :: !Metadatas
- decodeJPG :: (ColorModel cs e, MonadThrow m) => JPG -> ByteString -> m (Image S cs e)
- decodeWithMetadataJPG :: (ColorModel cs e, MonadThrow m) => JPG -> ByteString -> m (Image S cs e, Metadatas)
- decodeAutoJPG :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto JPG -> ByteString -> m (Image r cs e)
- decodeAutoWithMetadataJPG :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto JPG -> ByteString -> m (Image r cs e, Metadatas)
- encodeJPG :: forall cs e m. (ColorModel cs e, MonadThrow m) => JPG -> JpegOptions -> Image S cs e -> m ByteString
- encodeAutoJPG :: forall r cs i e. (ColorSpace (BaseSpace cs) i e, ColorSpace cs i e, Source r Ix2 (Pixel cs e)) => Auto JPG -> JpegOptions -> Image r cs e -> ByteString
- data PNG = PNG
- decodePNG :: (ColorModel cs e, MonadThrow m) => PNG -> ByteString -> m (Image S cs e)
- decodeWithMetadataPNG :: (ColorModel cs e, MonadThrow m) => PNG -> ByteString -> m (Image S cs e, Metadatas)
- decodeAutoPNG :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto PNG -> ByteString -> m (Image r cs e)
- decodeAutoWithMetadataPNG :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto PNG -> ByteString -> m (Image r cs e, Metadatas)
- encodePNG :: forall cs e m. (ColorModel cs e, MonadThrow m) => PNG -> Image S cs e -> m ByteString
- encodeAutoPNG :: forall r cs i e. (ColorSpace (BaseSpace cs) i e, ColorSpace cs i e, Source r Ix2 (Pixel cs e)) => Auto PNG -> Image r cs e -> ByteString
- data TGA = TGA
- decodeTGA :: (ColorModel cs e, MonadThrow m) => TGA -> ByteString -> m (Image S cs e)
- decodeWithMetadataTGA :: (ColorModel cs e, MonadThrow m) => TGA -> ByteString -> m (Image S cs e, Metadatas)
- decodeAutoTGA :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto TGA -> ByteString -> m (Image r cs e)
- decodeAutoWithMetadataTGA :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto TGA -> ByteString -> m (Image r cs e, Metadatas)
- encodeTGA :: forall cs e m. (ColorModel cs e, MonadThrow m) => TGA -> Image S cs e -> m ByteString
- encodeAutoTGA :: forall r cs i e. (ColorSpace (BaseSpace cs) i e, ColorSpace cs i e, Source r Ix2 (Pixel cs e)) => Auto TGA -> Image r cs e -> ByteString
- data TIF = TIF
- decodeTIF :: (ColorModel cs e, MonadThrow m) => TIF -> ByteString -> m (Image S cs e)
- decodeWithMetadataTIF :: (ColorModel cs e, MonadThrow m) => TIF -> ByteString -> m (Image S cs e, Metadatas)
- decodeAutoTIF :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto TIF -> ByteString -> m (Image r cs e)
- decodeAutoWithMetadataTIF :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto TIF -> ByteString -> m (Image r cs e, Metadatas)
- encodeTIF :: forall cs e m. (ColorModel cs e, MonadThrow m) => TIF -> Image S cs e -> m ByteString
- encodeAutoTIF :: forall r cs i e. (ColorSpace (BaseSpace cs) i e, ColorSpace cs i e, Source r Ix2 (Pixel cs e)) => Auto TIF -> Image r cs e -> ByteString
- toJPImageY8 :: Source r Ix2 (Pixel Y Word8) => Image r Y Word8 -> Image Pixel8
- toJPImageY16 :: Source r Ix2 (Pixel Y Word16) => Image r Y Word16 -> Image Pixel16
- toJPImageY32 :: Source r Ix2 (Pixel Y Word32) => Image r Y Word32 -> Image Pixel32
- toJPImageYA8 :: Source r Ix2 (Pixel (Alpha Y) Word8) => Image r (Alpha Y) Word8 -> Image PixelYA8
- toJPImageYA16 :: Source r Ix2 (Pixel (Alpha Y) Word16) => Image r (Alpha Y) 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
- toJPImageRGB16 :: Source r Ix2 (Pixel RGB Word16) => Image r RGB Word16 -> Image PixelRGB16
- toJPImageRGBA8 :: Source r Ix2 (Pixel (Alpha RGB) Word8) => Image r (Alpha RGB) Word8 -> Image PixelRGBA8
- toJPImageRGBA16 :: Source r Ix2 (Pixel (Alpha RGB) Word16) => Image r (Alpha RGB) 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
- toJPImageCMYK16 :: Source r Ix2 (Pixel CMYK Word16) => Image r CMYK Word16 -> Image PixelCMYK16
- fromDynamicImage :: forall cs e. ColorModel cs e => DynamicImage -> Maybe (Image S cs e)
- fromDynamicImageM :: forall cs e m. (ColorModel cs e, MonadThrow m) => DynamicImage -> m (Maybe (Image S cs e))
- fromDynamicImageAuto :: forall r cs i e m. (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => DynamicImage -> m (Image r cs e)
- data PBM = PBM
- data PGM = PGM
- data PPM = PPM
- decodeNetpbmImage :: (FileFormat f, ColorModel cs e, MonadThrow m) => f -> ByteString -> m (Image S cs e, Maybe ByteString)
- decodeNetpbmImageSequence :: (FileFormat (Sequence f), ColorModel cs e, MonadThrow m) => Sequence f -> ByteString -> m ([Image S cs e], Maybe ByteString)
- decodeAutoNetpbmImage :: (FileFormat f, Mutable r Ix2 (Pixel cs e), MonadThrow m, ColorSpace cs i e) => f -> ByteString -> m (Image r cs e, Maybe ByteString)
- decodeAutoNetpbmImageSequence :: (FileFormat (Sequence f), Mutable r Ix2 (Pixel cs e), MonadThrow m, ColorSpace cs i e) => Auto (Sequence f) -> ByteString -> m ([Image r cs e], Maybe ByteString)
- data Encode out
- encodeImageM :: MonadThrow m => [Encode (Image r cs e)] -> FilePath -> Image r cs e -> m ByteString
- imageWriteFormats :: (Source r Ix2 (Pixel cs e), ColorModel cs e) => [Encode (Image r cs e)]
- imageWriteAutoFormats :: (Source r Ix2 (Pixel cs e), ColorSpace cs i e, ColorSpace (BaseSpace cs) i e) => [Encode (Image r cs e)]
- data Decode out
- decodeImageM :: MonadThrow m => [Decode (Image r cs e)] -> FilePath -> ByteString -> m (Image r cs e)
- imageReadFormats :: ColorModel cs e => [Decode (Image S cs e)]
- imageReadAutoFormats :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e) => [Decode (Image r cs e)]
- class Monad m => MonadThrow (m :: Type -> Type) where
- class FileFormat f => Writable f arr where
- encodeM :: MonadThrow m => f -> WriteOptions f -> arr -> m ByteString
- class FileFormat f => Readable f arr where
- decodeM :: MonadThrow m => f -> ByteString -> m arr
- decodeWithMetadataM :: MonadThrow m => f -> ByteString -> m (arr, Metadata f)
- class (Default (WriteOptions f), Show f) => FileFormat f where
- newtype Auto f = Auto f
- newtype Sequence f = Sequence f
- newtype EncodeError = EncodeError String
- newtype DecodeError = DecodeError String
- newtype ConvertError = ConvertError String
- defaultWriteOptions :: FileFormat f => f -> WriteOptions f
- encode' :: Writable f arr => f -> WriteOptions f -> arr -> ByteString
- decode' :: Readable f arr => f -> ByteString -> arr
- toProxy :: a -> Proxy a
- fromMaybeEncode :: forall f r cs e b m. (ColorModel cs e, FileFormat f, Typeable r, MonadThrow m) => f -> Proxy (Image r cs e) -> Maybe b -> m b
- fromMaybeDecode :: forall r cs e a f m. (ColorModel cs e, FileFormat f, Typeable r, MonadThrow m) => f -> (a -> String) -> (a -> Maybe (Image r cs e)) -> a -> m (Image r cs e)
- convertEither :: forall r cs i e a f m. (ColorSpace cs i e, FileFormat f, Typeable r, MonadThrow m) => f -> (a -> String) -> (a -> Maybe (Image r cs e)) -> a -> m (Image r cs e)
- encodeError :: MonadThrow m => Either String a -> m a
- decodeError :: MonadThrow m => Either String a -> m a
- convertImage :: (Source r' Ix2 (Pixel cs' e'), ColorSpace cs' i' e', ColorSpace cs i e) => Image r' cs' e' -> Image D cs e
- toImageBaseModel :: Array S Ix2 (Pixel cs e) -> Array S Ix2 (Pixel (BaseModel cs) e)
- fromImageBaseModel :: Array S Ix2 (Pixel (BaseModel cs) e) -> Array S Ix2 (Pixel cs e)
- demoteLumaImage :: Array S Ix2 (Pixel Y' e) -> Array S Ix2 (Pixel Y e)
- promoteLumaImage :: Array S Ix2 (Pixel Y e) -> Array S Ix2 (Pixel Y' e)
- demoteLumaAlphaImage :: Array S Ix2 (Pixel (Alpha Y') e) -> Array S Ix2 (Pixel (Alpha Y) e)
- promoteLumaAlphaImage :: Array S Ix2 (Pixel (Alpha Y) e) -> Array S Ix2 (Pixel (Alpha Y') e)
Supported Image Formats
module Graphics.Pixel.ColorSpace
Encoding and decoding of images is done using JuicyPixels and netpbm packages.
List of image formats that are currently supported, and their exact ColorModel
s with
precision for reading and writing without any conversion:
BMP
:GIF
:HDR
:JPG
:PNG
:TGA
:TIF
:- read:
(
PixelY
Word8
), (PixelY
Word16
), (PixelY
Word32
), (PixelY
Float
), (PixelYA
Word8
), (PixelYA
Word16
), (PixelRGB
Word8
), (PixelRGB
Word16
), (PixelRGBA
Word8
), (PixelRGBA
Word16
), (PixelCMYK
Word8
), (PixelCMYK
Word16
) - write:
(
PixelY
Word8
), (PixelY
Word16
), (PixelY
Word32
), (PixelY
Float
), (PixelYA
Word8
), (PixelYA
Word16
), (PixelRGB
Word8
), (PixelRGB
Word16
), (PixelRGBA
Word8
), (PixelRGBA
Word16
) (PixelCMYK
Word8
), (PixelCMYK
Word16
), (PixelYCbCr
Word8
)
- read:
(
PBM
:PGM
:PPM
:
Reading
:: (Readable f arr, MonadIO m) | |
=> f | File format that should be used while decoding the file |
-> FilePath | Path to the file |
-> m arr |
Read an array from one of the supported Readable
file formats.
For example readImage
assumes all images to be in sRGB color space, but if you know
that the image is actually encoded in some other color space, for example AdobeRGB
,
then you can read it in manually into a matching color model and then cast into a color
space you know it is encoded in:
>>>
import qualified Graphics.ColorModel as CM
>>>
frogRGB <- readArray JPG "files/_frog.jpg" :: IO (Image S CM.RGB Word8)
>>>
let frogAdobeRGB = (fromImageBaseModel frogRGB :: Image S AdobeRGB Word8)
Since: 0.1.0
readArrayWithMetadata Source #
:: (Readable f arr, MonadIO m) | |
=> f | File format that should be used while decoding the file |
-> FilePath | Path to the file |
-> m (arr, Metadata f) |
Read an array from one of the supported file formats. Some formats are capable of preducing format specific metadata.
Since: 0.2.0
:: (ColorModel cs e, MonadIO m) | |
=> FilePath | File path for an image |
-> m (Image S cs e) |
Tries to guess an image format from file's extension, then attempts to decode it as
such. It also assumes an image is encoded in sRGB color space or its alternate
representation. In order to supply the format manually or choose a different color
space, eg. AdobeRGB
, use readArray
instead. Color space and precision of the result
image must match exactly that of the actual image.
May throw ConvertError
, DecodeError
and other standard errors related to file IO.
Resulting image will be read as specified by the type signature:
>>>
frog <- readImage "files/frog.jpg" :: IO (Image S (YCbCr SRGB) Word8)
>>>
size frog
Sz (200 :. 320)
>>> 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 SRGB Word8)
*** Exception: ConvertError "Cannot decode JPG image <Image S YCbCr Word8> as <Image S SRGB 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:
>>>
frogYCbCr <- readImage "files/frog.jpg" :: IO (Image S (YCbCr SRGB) Word8)
>>>
let frogSRGB = convertImage frogYCbCr :: Image D SRGB Word8
A simpler approach to achieve the same effect would be to use readImageAuto
:
>>>
frogSRGB' <- readImageAuto "files/frog.jpg" :: IO (Image S SRGB Word8)
>>>
compute frogSRGB == frogSRGB'
True
Since: 0.1.0
:: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadIO m) | |
=> FilePath | File path for an image |
-> m (Image r cs e) |
Similar to readImage
, but will perform all necessary color space conversion
and precision adjustment in order to match the result image type. Very useful whenever
image format isn't known ahead of time.
>>>
frogCMYK <- readImageAuto "files/frog.jpg" :: IO (Image S (CMYK SRGB) Double)
>>>
size frogCMYK
Sz (200 :. 320)
Since: 0.1.0
Writing
:: (Writable f arr, MonadIO m) | |
=> f | Format to use while encoding the array |
-> WriteOptions f | Any file format related encoding options. Use |
-> FilePath | |
-> arr | |
-> m () |
Write an array to disk.
>>>
frogYCbCr <- readImage "files/frog.jpg" :: IO (Image S (YCbCr SRGB) Word8)
>>>
frogAdobeRGB = convertImage frogYCbCr :: Image D AdobeRGB Word8
>>>
writeArray JPG def "files/_frog.jpg" $ toImageBaseModel $ computeAs S frogAdobeRGB
Note - On UNIX operating systems writing will happen with guarantees of atomicity and
durability, see withBinaryFileDurableAtomic
.
Since: 0.2.0
writeImage :: (Source r Ix2 (Pixel cs e), ColorModel cs e, MonadIO m) => FilePath -> Image r cs e -> m () Source #
This function will guess an output file format from the file extension and will write
to file any image with the color model that is supported by that format. In case that
automatic precision adjustment or colors space conversion is also desired,
writeImageAuto
can be used instead.
Can throw ConvertError
, EncodeError
and other usual IO errors.
Note - On UNIX operating systems writing will happen with guarantees of atomicity and
durability, see withBinaryFileDurableAtomic
.
Since: 0.1.0
writeImageAuto :: (Source r Ix2 (Pixel cs e), ColorSpace cs i e, ColorSpace (BaseSpace cs) i e, MonadIO m) => FilePath -> Image r cs e -> m () Source #
Write an image encoded in sRGB color space into a file while performing all necessary precision and color space conversions. If a file supports color model that the image is on then it will be encoded as such. For example writing a TIF file in CMYK color model, 8bit precision and an sRGB color space:
>>>
frogYCbCr <- readImage "files/frog.jpg" :: IO (Image S (YCbCr SRGB) Word8)
>>>
writeImageAuto "files/frog.tiff" (convertImage frogYCbCr :: Image D (CMYK AdobeRGB) Word8)
Regardless that the color space supplied was AdobeRGB
auto conversion will ensure it
is stored as SRGB
, except in CMYK
color model, since TIF
file format supports it.
Since: 0.1.0
Displaying
data ExternalViewer Source #
External viewing application to use for displaying images.
ExternalViewer FilePath [String] Int | Any custom viewer, which can be specified:
|
Instances
Show ExternalViewer Source # | |
Defined in Data.Massiv.Array.IO showsPrec :: Int -> ExternalViewer -> ShowS # show :: ExternalViewer -> String # showList :: [ExternalViewer] -> ShowS # |
displayImage :: (Writable (Auto TIF) (Image r cs e), MonadIO m) => Image r cs e -> m () Source #
Writes an image to a temporary file and 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.
Note - This function should only be used in ghci, otherwise use displayImage
defaultViewer
True
Since: 0.1.0
:: (Writable (Auto TIF) (Image r cs e), MonadIO m) | |
=> ExternalViewer | Image viewer program |
-> Bool | Should this function block the current thread until viewer is
closed. Supplying |
-> Image r cs e | Image to display |
-> m () |
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.
Since: 0.1.0
displayImageFile :: MonadIO m => ExternalViewer -> FilePath -> m () Source #
Displays an image file by calling an external image viewer. It will block until the external viewer is closed.
Since: 0.1.0
Common viewers
defaultViewer :: ExternalViewer Source #
Default viewer is inferred from the operating system.
Since: 0.1.0
eogViewer :: ExternalViewer Source #
eog /tmp/massiv/img.tiff
gpicviewViewer :: ExternalViewer Source #
gpicview /tmp/massiv/img.tiff
fehViewer :: ExternalViewer Source #
feh --fullscreen --auto-zoom /tmp/massiv/img.tiff
gimpViewer :: ExternalViewer Source #
gimp /tmp/massiv/img.tiff
Supported Image Formats
JuicyPixels formats
BMP
Bitmap image with .bmp
extension.
Instances
newtype BitmapOptions Source #
Instances
Show BitmapOptions Source # | |
Defined in Data.Massiv.Array.IO.Image.JuicyPixels.BMP showsPrec :: Int -> BitmapOptions -> ShowS # show :: BitmapOptions -> String # showList :: [BitmapOptions] -> ShowS # | |
Default BitmapOptions Source # | |
Defined in Data.Massiv.Array.IO.Image.JuicyPixels.BMP def :: BitmapOptions # |
decodeBMP :: (ColorModel cs e, MonadThrow m) => BMP -> ByteString -> m (Image S cs e) Source #
Decode a Bitmap Image
decodeWithMetadataBMP :: (ColorModel cs e, MonadThrow m) => BMP -> ByteString -> m (Image S cs e, Metadatas) Source #
Decode a Bitmap Image
decodeAutoBMP :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto BMP -> ByteString -> m (Image r cs e) Source #
Decode a Bitmap Image
decodeAutoWithMetadataBMP :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto BMP -> ByteString -> m (Image r cs e, Metadatas) Source #
Decode a Bitmap Image
encodeBMP :: forall cs e m. (ColorModel cs e, MonadThrow m) => BMP -> BitmapOptions -> Image S cs e -> m ByteString Source #
encodeAutoBMP :: forall r cs i e. (ColorSpace (BaseSpace cs) i e, ColorSpace cs i e, Source r Ix2 (Pixel cs e)) => Auto BMP -> BitmapOptions -> Image r cs e -> ByteString Source #
GIF
Graphics Interchange Format image with .gif
extension.
Instances
newtype GifOptions Source #
Instances
Default GifOptions Source # | |
Defined in Data.Massiv.Array.IO.Image.JuicyPixels.GIF def :: GifOptions # |
data SequenceGifOptions Source #
SequenceGifOptions | |
|
Instances
Default SequenceGifOptions Source # | |
Defined in Data.Massiv.Array.IO.Image.JuicyPixels.GIF |
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 |
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. |
data GifDisposalMethod #
Instances
decodeGIF :: (ColorModel cs e, MonadThrow m) => GIF -> ByteString -> m (Image S cs e) Source #
Decode a Gif Image
decodeWithMetadataGIF :: (ColorModel cs e, MonadThrow m) => GIF -> ByteString -> m (Image S cs e, Metadatas) Source #
Decode a Gif Image
decodeAutoGIF :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto GIF -> ByteString -> m (Image r cs e) Source #
Decode a Gif Image
decodeAutoWithMetadataGIF :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto GIF -> ByteString -> m (Image r cs e, Metadatas) Source #
Decode a Gif Image
encodeGIF :: forall cs e m. (ColorModel cs e, MonadThrow m) => GIF -> GifOptions -> Image S cs e -> m ByteString Source #
encodeAutoGIF :: forall r cs i e m. (ColorSpace cs i e, Source r Ix2 (Pixel cs e), MonadThrow m) => Auto GIF -> GifOptions -> Image r cs e -> m ByteString Source #
decodeSequenceGIF :: (ColorModel cs e, MonadThrow m) => Sequence GIF -> ByteString -> m [Image S cs e] Source #
Decode a sequence of Gif images
decodeSequenceWithMetadataGIF :: (ColorModel cs e, MonadThrow m) => Sequence GIF -> ByteString -> m ([Image S cs e], [GifDelay]) Source #
Decode a sequence of Gif images
decodeAutoSequenceGIF :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto (Sequence GIF) -> ByteString -> m [Image r cs e] Source #
Decode a sequence of Gif images
decodeAutoSequenceWithMetadataGIF :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto (Sequence GIF) -> ByteString -> m ([Image r cs e], [GifDelay]) Source #
Decode a sequence of Gif images
HDR
High-dynamic-range image with .hdr
or .pic
extension.
Instances
newtype HdrOptions Source #
HdrOptions | |
|
Instances
Show HdrOptions Source # | |
Defined in Data.Massiv.Array.IO.Image.JuicyPixels.HDR showsPrec :: Int -> HdrOptions -> ShowS # show :: HdrOptions -> String # showList :: [HdrOptions] -> ShowS # | |
Default HdrOptions Source # | |
Defined in Data.Massiv.Array.IO.Image.JuicyPixels.HDR def :: HdrOptions # |
decodeHDR :: (ColorModel cs e, MonadThrow m) => HDR -> ByteString -> m (Image S cs e) Source #
Decode a HDR Image
decodeWithMetadataHDR :: (ColorModel cs e, MonadThrow m) => HDR -> ByteString -> m (Image S cs e, Metadatas) Source #
Decode a HDR Image
decodeAutoHDR :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto HDR -> ByteString -> m (Image r cs e) Source #
Decode a HDR Image
decodeAutoWithMetadataHDR :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto HDR -> ByteString -> m (Image r cs e, Metadatas) Source #
Decode a HDR Image
encodeHDR :: forall cs e m. (ColorModel cs e, MonadThrow m) => HDR -> HdrOptions -> Image S cs e -> m ByteString Source #
encodeAutoHDR :: forall r cs i e. (ColorSpace cs i e, Source r Ix2 (Pixel cs e)) => Auto HDR -> HdrOptions -> Image r cs e -> ByteString Source #
JPG
Joint Photographic Experts Group image with .jpg
or .jpeg
extension.
Instances
data JpegOptions Source #
JpegOptions | |
|
Instances
Show JpegOptions Source # | |
Defined in Data.Massiv.Array.IO.Image.JuicyPixels.JPG showsPrec :: Int -> JpegOptions -> ShowS # show :: JpegOptions -> String # showList :: [JpegOptions] -> ShowS # | |
Default JpegOptions Source # | |
Defined in Data.Massiv.Array.IO.Image.JuicyPixels.JPG def :: JpegOptions # |
decodeJPG :: (ColorModel cs e, MonadThrow m) => JPG -> ByteString -> m (Image S cs e) Source #
Decode a Jpeg Image
decodeWithMetadataJPG :: (ColorModel cs e, MonadThrow m) => JPG -> ByteString -> m (Image S cs e, Metadatas) Source #
Decode a Jpeg Image
decodeAutoJPG :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto JPG -> ByteString -> m (Image r cs e) Source #
Decode a Jpeg Image
decodeAutoWithMetadataJPG :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto JPG -> ByteString -> m (Image r cs e, Metadatas) Source #
Decode a Jpeg Image
encodeJPG :: forall cs e m. (ColorModel cs e, MonadThrow m) => JPG -> JpegOptions -> Image S cs e -> m ByteString Source #
encodeAutoJPG :: forall r cs i e. (ColorSpace (BaseSpace cs) i e, ColorSpace cs i e, Source r Ix2 (Pixel cs e)) => Auto JPG -> JpegOptions -> Image r cs e -> ByteString Source #
PNG
Portable Network Graphics image with .png
extension.
Instances
decodePNG :: (ColorModel cs e, MonadThrow m) => PNG -> ByteString -> m (Image S cs e) Source #
Decode a Png Image
decodeWithMetadataPNG :: (ColorModel cs e, MonadThrow m) => PNG -> ByteString -> m (Image S cs e, Metadatas) Source #
Decode a Png Image
decodeAutoPNG :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto PNG -> ByteString -> m (Image r cs e) Source #
Decode a Png Image
decodeAutoWithMetadataPNG :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto PNG -> ByteString -> m (Image r cs e, Metadatas) Source #
Decode a Png Image
encodePNG :: forall cs e m. (ColorModel cs e, MonadThrow m) => PNG -> Image S cs e -> m ByteString Source #
encodeAutoPNG :: forall r cs i e. (ColorSpace (BaseSpace cs) i e, ColorSpace cs i e, Source r Ix2 (Pixel cs e)) => Auto PNG -> Image r cs e -> ByteString Source #
TGA
Truevision Graphics Adapter image with .tga extension.
Instances
decodeTGA :: (ColorModel cs e, MonadThrow m) => TGA -> ByteString -> m (Image S cs e) Source #
Decode a Tga Image
decodeWithMetadataTGA :: (ColorModel cs e, MonadThrow m) => TGA -> ByteString -> m (Image S cs e, Metadatas) Source #
Decode a Tga Image
decodeAutoTGA :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto TGA -> ByteString -> m (Image r cs e) Source #
Decode a Tga Image
decodeAutoWithMetadataTGA :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto TGA -> ByteString -> m (Image r cs e, Metadatas) Source #
Decode a Tga Image
encodeTGA :: forall cs e m. (ColorModel cs e, MonadThrow m) => TGA -> Image S cs e -> m ByteString Source #
encodeAutoTGA :: forall r cs i e. (ColorSpace (BaseSpace cs) i e, ColorSpace cs i e, Source r Ix2 (Pixel cs e)) => Auto TGA -> Image r cs e -> ByteString Source #
TIF
Tagged Image File Format image with .tif
or .tiff
extension.
Instances
decodeTIF :: (ColorModel cs e, MonadThrow m) => TIF -> ByteString -> m (Image S cs e) Source #
Decode a Tiff Image
decodeWithMetadataTIF :: (ColorModel cs e, MonadThrow m) => TIF -> ByteString -> m (Image S cs e, Metadatas) Source #
Decode a Tiff Image
decodeAutoTIF :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto TIF -> ByteString -> m (Image r cs e) Source #
Decode a Tiff Image
decodeAutoWithMetadataTIF :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => Auto TIF -> ByteString -> m (Image r cs e, Metadatas) Source #
Decode a Tiff Image
encodeTIF :: forall cs e m. (ColorModel cs e, MonadThrow m) => TIF -> Image S cs e -> m ByteString Source #
encodeAutoTIF :: forall r cs i e. (ColorSpace (BaseSpace cs) i e, ColorSpace cs i e, Source r Ix2 (Pixel cs e)) => Auto TIF -> Image r cs e -> ByteString Source #
JuicyPixels conversion
toJPImageYA8 :: Source r Ix2 (Pixel (Alpha Y) Word8) => Image r (Alpha Y) Word8 -> Image PixelYA8 Source #
toJPImageYA16 :: Source r Ix2 (Pixel (Alpha Y) Word16) => Image r (Alpha Y) Word16 -> Image PixelYA16 Source #
toJPImageRGB16 :: Source r Ix2 (Pixel RGB Word16) => Image r RGB Word16 -> Image PixelRGB16 Source #
toJPImageRGBA8 :: Source r Ix2 (Pixel (Alpha RGB) Word8) => Image r (Alpha RGB) Word8 -> Image PixelRGBA8 Source #
toJPImageRGBA16 :: Source r Ix2 (Pixel (Alpha RGB) Word16) => Image r (Alpha RGB) 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 #
toJPImageCMYK16 :: Source r Ix2 (Pixel CMYK Word16) => Image r CMYK Word16 -> Image PixelCMYK16 Source #
fromDynamicImage :: forall cs e. ColorModel cs e => DynamicImage -> Maybe (Image S cs e) Source #
Deprecated: In favor of fromDynamicImageM
fromDynamicImageM :: forall cs e m. (ColorModel cs e, MonadThrow m) => DynamicImage -> m (Maybe (Image S cs e)) Source #
fromDynamicImageAuto :: forall r cs i e m. (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) => DynamicImage -> m (Image r cs e) Source #
Netpbm formats
PBM
Netpbm: portable bitmap image with .pbm
extension.
Instances
PGM
Netpbm: portable graymap image with .pgm
extension.
Instances
PPM
Netpbm: portable pixmap image with .ppm
extension.
Instances
decodeNetpbmImage :: (FileFormat f, ColorModel cs e, MonadThrow m) => f -> ByteString -> m (Image S cs e, Maybe ByteString) Source #
Try to decode a Netpbm image
Since: 0.2.0
decodeNetpbmImageSequence :: (FileFormat (Sequence f), ColorModel cs e, MonadThrow m) => Sequence f -> ByteString -> m ([Image S cs e], Maybe ByteString) Source #
Try to decode a Netpbm image sequence
Since: 0.2.0
decodeAutoNetpbmImage :: (FileFormat f, Mutable r Ix2 (Pixel cs e), MonadThrow m, ColorSpace cs i e) => f -> ByteString -> m (Image r cs e, Maybe ByteString) Source #
Try to decode a Netpbm image, while auto converting the colorspace.
Since: 0.2.0
decodeAutoNetpbmImageSequence :: (FileFormat (Sequence f), Mutable r Ix2 (Pixel cs e), MonadThrow m, ColorSpace cs i e) => Auto (Sequence f) -> ByteString -> m ([Image r cs e], Maybe ByteString) Source #
Try to decode a Netpbm image sequence, while auto converting the colorspace.
Since: 0.2.0
Helper image functions
Instances
Show (Encode out) Source # | |
FileFormat (Encode (Image r cs e)) Source # | |
Defined in Data.Massiv.Array.IO.Image | |
Writable (Encode (Image r cs e)) (Image r cs e) Source # | |
Defined in Data.Massiv.Array.IO.Image encodeM :: MonadThrow m => Encode (Image r cs e) -> WriteOptions (Encode (Image r cs e)) -> Image r cs e -> m ByteString Source # | |
type WriteOptions (Encode (Image r cs e)) Source # | |
Defined in Data.Massiv.Array.IO.Image | |
type Metadata (Encode (Image r cs e)) Source # | |
Defined in Data.Massiv.Array.IO.Image |
:: MonadThrow m | |
=> [Encode (Image r cs e)] | List of image formats to choose from (useful lists are
|
-> FilePath | File name with extension, so the format can be inferred |
-> Image r cs e | Image to encode |
-> m ByteString |
Encode an image into a lazy ByteString
, while selecting the appropriate format from the
file extension.
Since: 0.2.0
imageWriteFormats :: (Source r Ix2 (Pixel cs e), ColorModel cs e) => [Encode (Image r cs e)] Source #
List of image formats that can be encoded without any color space conversion.
imageWriteAutoFormats :: (Source r Ix2 (Pixel cs e), ColorSpace cs i e, ColorSpace (BaseSpace cs) i e) => [Encode (Image r cs e)] Source #
List of image formats that can be encoded with any necessary color space conversions.
Instances
Show (Decode out) Source # | |
FileFormat (Decode (Image r cs e)) Source # | |
Defined in Data.Massiv.Array.IO.Image | |
Readable (Decode (Image r cs e)) (Image r cs e) Source # | |
Defined in Data.Massiv.Array.IO.Image decodeM :: MonadThrow m => Decode (Image r cs e) -> ByteString -> m (Image r cs e) Source # decodeWithMetadataM :: MonadThrow m => Decode (Image r cs e) -> ByteString -> m (Image r cs e, Metadata (Decode (Image r cs e))) Source # | |
type WriteOptions (Decode (Image r cs e)) Source # | |
Defined in Data.Massiv.Array.IO.Image | |
type Metadata (Decode (Image r cs e)) Source # | |
Defined in Data.Massiv.Array.IO.Image |
:: MonadThrow m | |
=> [Decode (Image r cs e)] | List of available formats to choose from |
-> FilePath | File name with extension, so format can be inferred |
-> ByteString | Encoded image |
-> m (Image r cs e) |
Decode an image from the strict ByteString
while inferring format the image is encoded in
from the file extension
Since: 0.2.0
imageReadFormats :: ColorModel cs e => [Decode (Image S cs e)] Source #
List of image formats decodable with no color space conversion
imageReadAutoFormats :: (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e) => [Decode (Image r cs e)] Source #
List of image formats decodable with automatic colorspace conversion
All other common reading/writing components
class Monad m => MonadThrow (m :: Type -> Type) where #
A class for monads in which exceptions may be thrown.
Instances should obey the following law:
throwM e >> x = throwM e
In other words, throwing an exception short-circuits the rest of the monadic computation.
throwM :: Exception e => e -> m a #
Throw an exception. Note that this throws when this action is run in
the monad m
, not when it is applied. It is a generalization of
Control.Exception's throwIO
.
Should satisfy the law:
throwM e >> f = throwM e
Instances
class FileFormat f => Writable f arr where Source #
Arrays that can be written into a file.
encodeM :: MonadThrow m => f -> WriteOptions f -> arr -> m ByteString Source #
Encode an array into a ByteString
.
Since: 0.2.0
Instances
class FileFormat f => Readable f arr where Source #
File formats that can be read into arrays.
decodeM :: MonadThrow m => f -> ByteString -> m arr Source #
Decode a ByteString
into an array. Can also return whatever left over data that
was not consumed during decoding.
Since: 0.2.0
decodeWithMetadataM :: MonadThrow m => f -> ByteString -> m (arr, Metadata f) Source #
Just as decodeM
, but also return any format type specific metadata
Since: 0.2.0
decodeWithMetadataM :: (Metadata f ~ (), MonadThrow m) => f -> ByteString -> m (arr, Metadata f) Source #
Just as decodeM
, but also return any format type specific metadata
Since: 0.2.0
Instances
class (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 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
Instances
FileFormat BMP Source # | |
FileFormat GIF Source # | |
FileFormat HDR Source # | |
FileFormat JPG Source # | |
FileFormat PNG Source # | |
FileFormat TGA Source # | |
FileFormat TIF Source # | |
FileFormat PPM Source # | |
FileFormat PGM Source # | |
FileFormat PBM Source # | |
FileFormat f => FileFormat (Auto f) Source # | |
FileFormat (Sequence GIF) Source # | |
FileFormat (Sequence PPM) Source # | |
FileFormat (Sequence PGM) Source # | |
FileFormat (Sequence PBM) Source # | |
FileFormat (Decode (Image r cs e)) Source # | |
Defined in Data.Massiv.Array.IO.Image | |
FileFormat (Encode (Image r cs e)) Source # | |
Defined in Data.Massiv.Array.IO.Image |
Auto f |
Instances
Special wrapper for formats that support encoding/decoding sequence of array.
Sequence f |
Instances
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.
Instances
Show EncodeError Source # | |
Defined in Data.Massiv.Array.IO.Base showsPrec :: Int -> EncodeError -> ShowS # show :: EncodeError -> String # showList :: [EncodeError] -> ShowS # | |
Exception EncodeError Source # | |
Defined in Data.Massiv.Array.IO.Base |
newtype DecodeError Source #
This exception can be thrown while reading/decoding a file and indicates an error in the file itself.
Instances
Show DecodeError Source # | |
Defined in Data.Massiv.Array.IO.Base showsPrec :: Int -> DecodeError -> ShowS # show :: DecodeError -> String # showList :: [DecodeError] -> ShowS # | |
Exception DecodeError Source # | |
Defined in Data.Massiv.Array.IO.Base |
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.
Instances
Show ConvertError Source # | |
Defined in Data.Massiv.Array.IO.Base showsPrec :: Int -> ConvertError -> ShowS # show :: ConvertError -> String # showList :: [ConvertError] -> ShowS # | |
Exception ConvertError Source # | |
Defined in Data.Massiv.Array.IO.Base |
defaultWriteOptions :: FileFormat f => f -> WriteOptions f Source #
Generate default write options for a file format
encode' :: Writable f arr => f -> WriteOptions f -> arr -> ByteString Source #
Encode an array into a ByteString
.
decode' :: Readable f arr => f -> ByteString -> arr Source #
Decode a ByteString
into an Array.
fromMaybeEncode :: forall f r cs e b m. (ColorModel cs e, FileFormat f, Typeable r, MonadThrow m) => f -> Proxy (Image r cs e) -> Maybe b -> m b Source #
Encode an image using the supplied function or throw an error in case of failure.
fromMaybeDecode :: forall r cs e a f m. (ColorModel cs e, FileFormat f, Typeable r, MonadThrow m) => f -> (a -> String) -> (a -> Maybe (Image r cs e)) -> a -> m (Image r cs e) Source #
Decode an image using the supplied function or throw an error in case of failure.
convertEither :: forall r cs i e a f m. (ColorSpace cs i e, FileFormat f, Typeable r, MonadThrow m) => f -> (a -> String) -> (a -> Maybe (Image r cs e)) -> a -> m (Image r cs e) Source #
Convert an image using the supplied function and return ConvertError error in case of failure.
encodeError :: MonadThrow m => Either String a -> m a Source #
decodeError :: MonadThrow m => Either String a -> m a Source #
convertImage :: (Source r' Ix2 (Pixel cs' e'), ColorSpace cs' i' e', ColorSpace cs i e) => Image r' cs' e' -> Image D cs e Source #
Convert image to any supported color space
Since: 0.2.0
toImageBaseModel :: Array S Ix2 (Pixel cs e) -> Array S Ix2 (Pixel (BaseModel cs) e) Source #
Cast an array. This is theoretically unsafe operation, but for all currently
available ColorSpace
instances this function is perfectly safe.
Since: 0.2.0
fromImageBaseModel :: Array S Ix2 (Pixel (BaseModel cs) e) -> Array S Ix2 (Pixel cs e) Source #
Cast an array. This is theoretically unsafe operation, but for all currently
available ColorSpace
instances this function is perfectly safe.
Since: 0.2.0
demoteLumaImage :: Array S Ix2 (Pixel Y' e) -> Array S Ix2 (Pixel Y e) Source #
Cast an array with Luma pixels to an array with pixels in a plain single channel
Color
color model
Since: 0.2.1
promoteLumaImage :: Array S Ix2 (Pixel Y e) -> Array S Ix2 (Pixel Y' e) Source #
Cast an array with pixels in a plain single channel Color
color model to an array
with Luma pixels
Since: 0.2.1