Copyright | (c) Alexey Kuleshevich 2016 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Haskell Image Processing (HIP) library is a wrapper around any array like data structure and is fully agnostic to the underlying representation. All of the functionality in this library relies on few type classes that corresponding representation types are instances of:
- this is a base class for everyArray
arr cs eImage
arr
cs
e
, wherearr
stands for an underlying array representation,cs
is theColorSpace
of an image ande
is the type denoting precision of an image.
- is a kind of array that is represented by an actual data in memory.ManifestArray
arr cs e
- contains functionality that can only be computed sequentially.SequentialArray
arr cs e
- allows mutation onMutableArray
arr cs eMImage
st
arr
cs
e
, which isImage
's mutable cousin.
Array representation type and the above classes it is installed in determine operations that can be done on the image with that representation.
Representations using Vector and Repa packages:
VU
- Unboxed Vector representation. (Default)RD
- Delayed Repa array representation.RS
- Unboxed Repa array representation (computation is done sequentially).RP
- Unboxed Repa array representation (computation is done in parallel).
Images with RD
type hold functions rather then actual data, so this
representation should be used for fusing computation together, and later
changed to RS
or RP
using exchange
, which in turn performs the fused
computation.
Just as it is mentioned above, Vector representation is a default one, so in order to create images with Repa representation Graphics.Image.Interface.Repa module can be used. It should be imported as qualified, since it contains image generating functions with same names as here.
Many of the function names exported by this module will clash with the ones from Prelude, hence it can be more convenient to import it qualified and all relevenat types import using Graphics.Image.Types module:
import qualified Graphics.Image as I import Graphics.Image.Types
- makeImage :: Array VU cs Double => (Int, Int) -> ((Int, Int) -> Pixel cs Double) -> Image VU cs Double
- fromLists :: Array VU cs e => [[Pixel cs e]] -> Image VU cs e
- readImageY :: FilePath -> IO (Image VU Y Double)
- readImageYA :: FilePath -> IO (Image VU YA Double)
- readImageRGB :: FilePath -> IO (Image VU RGB Double)
- readImageRGBA :: FilePath -> IO (Image VU RGBA Double)
- readImageExact :: Readable img format => format -> FilePath -> IO (Either String img)
- writeImage :: (ManifestArray arr cs Double, Writable (Image arr cs Double) OutputFormat) => FilePath -> Image arr cs Double -> IO ()
- writeImageExact :: Writable img format => format -> [SaveOption format] -> FilePath -> img -> IO ()
- displayImage :: (ManifestArray arr cs e, Writable (Image arr cs e) TIF) => Image arr cs e -> IO (Maybe ThreadId)
- rows :: Array arr cs e => Image arr cs e -> Int
- cols :: Array arr cs e => Image arr cs e -> Int
- dims :: Array arr cs e => Image arr cs e -> (Int, Int)
- index :: ManifestArray arr cs e => Image arr cs e -> (Int, Int) -> Pixel cs e
- defaultIndex :: ManifestArray arr cs e => Pixel cs e -> Image arr cs e -> (Int, Int) -> Pixel cs e
- maybeIndex :: ManifestArray arr cs e => Image arr cs e -> (Int, Int) -> Maybe (Pixel cs e)
- map :: (Array arr cs e, Array arr cs' e') => (Pixel cs' e' -> Pixel cs e) -> Image arr cs' e' -> Image arr cs e
- imap :: (Array arr cs e, Array arr cs' e') => ((Int, Int) -> Pixel cs' e' -> Pixel cs e) -> Image arr cs' e' -> Image arr cs e
- zipWith :: (Array arr cs e, Array arr cs1 e1, Array arr cs2 e2) => (Pixel cs1 e1 -> Pixel cs2 e2 -> Pixel cs e) -> Image arr cs1 e1 -> Image arr cs2 e2 -> Image arr cs e
- izipWith :: (Array arr cs e, Array arr cs1 e1, Array arr cs2 e2) => ((Int, Int) -> Pixel cs1 e1 -> Pixel cs2 e2 -> Pixel cs e) -> Image arr cs1 e1 -> Image arr cs2 e2 -> Image arr cs e
- traverse :: (Array arr cs e, Array arr cs' e') => Image arr cs' e' -> ((Int, Int) -> (Int, Int)) -> (((Int, Int) -> Pixel cs' e') -> (Int, Int) -> Pixel cs e) -> Image arr cs e
- traverse2 :: (Array arr cs e, Array arr cs1 e1, Array arr cs2 e2) => Image arr cs1 e1 -> Image arr cs2 e2 -> ((Int, Int) -> (Int, Int) -> (Int, Int)) -> (((Int, Int) -> Pixel cs1 e1) -> ((Int, Int) -> Pixel cs2 e2) -> (Int, Int) -> Pixel cs e) -> Image arr cs e
- transpose :: Array arr cs e => Image arr cs e -> Image arr cs e
- backpermute :: Array arr cs e => (Int, Int) -> ((Int, Int) -> (Int, Int)) -> Image arr cs e -> Image arr cs e
- (|*|) :: ManifestArray arr cs e => Image arr cs e -> Image arr cs e -> Image arr cs e
- fold :: ManifestArray arr cs e => (Pixel cs e -> Pixel cs e -> Pixel cs e) -> Pixel cs e -> Image arr cs e -> Pixel cs e
- sum :: ManifestArray arr cs e => Image arr cs e -> Pixel cs e
- product :: ManifestArray arr cs e => Image arr cs e -> Pixel cs e
- maximum :: (ManifestArray arr cs e, Ord (Pixel cs e)) => Image arr cs e -> Pixel cs e
- minimum :: (ManifestArray arr cs e, Ord (Pixel cs e)) => Image arr cs e -> Pixel cs e
- normalize :: (ManifestArray arr cs e, ManifestArray arr Gray e, Fractional e, Ord e) => Image arr cs e -> Image arr cs e
- exchange :: (Exchangable arr' arr, Array arr' cs e, Array arr cs e) => arr -> Image arr' cs e -> Image arr cs e
- data VU = VU
- data RD = RD
- data RS = RS
- data RP = RP
Color Space
Here is a list of default Pixels with their respective constructors:
*Pixel
Y
e = PixelY e - Luma, also commonly denoted as Y'. *Pixel
YA
e = PixelYA e - Luma with alpha. *Pixel
RGB
e = PixelRGB e - Red, Green and Blue. *Pixel
RGBA
e = PixelRGBA e - RGB with alpha *Pixel
HSI
e = PixelHSI e - Hue, Saturation and Intensity. *Pixel
HSIA
e = PixelHSIA e - HSI with alpha *Pixel
CMYK
e = PixelCMYK e - Cyan, Magenta, Yellow and Key (Black). *Pixel
CMYKA
e = PixelCMYKA e - CMYK with alpha. *Pixel
YCbCr
e = PixelYCbCr e - Luma, blue-difference and red-difference chromas. *Pixel
YCbCrA
e = PixelYCbCrA e - YCbCr with alpha. ------------------------------------------------------------------------------------------ *Pixel
Binary
Bit
=on
|off
- Bi-tonal. *Pixel
cs (Complex
e) = (Pixel
cs e)+:
(Pixel
cs e) - Complex pixels with any color space. *Pixel
Gray
e = PixelGray e - Used for separating channels from other color spaces.
Every Pixel
is an instance of Functor
, Applicative
, Foldable
and
Num
, as well as Floating
and Fractional
if e is also an instance.
All of the functionality related to every ColorSpace
is re-exported by
Graphics.Image.Types module.
Creation
:: Array VU cs Double | |
=> (Int, Int) | ( |
-> ((Int, Int) -> Pixel cs Double) | A function that takes ( |
-> Image VU cs Double |
Create an image with VU
(Vector Unboxed) representation and pixels of Double
precision. Note, that for Double
precision pixels it is essential to keep values
normalized in the [0, 1]
range in order for an image to be written to file
properly.
>>>
let grad_gray = makeImage (200, 200) (\(i, j) -> PixelY (fromIntegral i)/200 * (fromIntegral j)/200)
Because all Pixel
s and Image
s are installed into Num
, above is equivalent to:
>>>
let grad_gray = makeImage (200, 200) (\(i, j) -> PixelY $ fromIntegral (i*j)) / (200*200)
>>>
writeImage "images/grad_gray.png" grad_gray
Creating color images is just as easy.
>>>
let grad_color = makeImage (200, 200) (\(i, j) -> PixelRGB (fromIntegral i) (fromIntegral j) (fromIntegral (i + j))) / 400
>>>
writeImage "images/grad_color.png" grad_color
fromLists :: Array VU cs e => [[Pixel cs e]] -> Image VU cs e Source
Construct an image from a nested rectangular shaped list of pixels.
Length of an outer list will constitute m
rows, while the length of inner lists -
n
columns. All of the inner lists must be the same length and greater than 0
.
>>>
fromLists [[PixelY (fromIntegral (i*j) / 60000) | j <- [1..300]] | i <- [1..200]]
<Image VectorUnboxed Y (Double): 200x300>
IO
Reading
Read any supported image file into an Image
with VU
(Vector Unboxed)
representation and pixels with Double
precision. In order to read an
image with different representation, color space and precision readImage
or readImageExact
from Graphics.Image.IO can be
used.
readImageRGBA :: FilePath -> IO (Image VU RGBA Double) Source
Read image in RGB colorspace with Alpha
channel.
:: Readable img format | |
=> format | A file format that an image should be read as. See Supported Image Formats |
-> FilePath | Location of an image. |
-> IO (Either String img) |
This function allows for reading any supported image in the exact colorspace
and precision it is currently encoded in. For instance, frog image can be
read into it's YCbCr
colorspace with
Word8
precision and into any supported array
representation.
>>>
readImageExact JPG "images/frog.jpg" :: IO (Either String (Image RP YCbCr Word8))
Right <Image RepaParallel YCbCr (Word8): 200x320>
The drawback here is that colorspace and precision has to match exactly, otherwise it will return an error:
>>>
readImageExact JPG "images/frog.jpg" :: IO (Either String (Image RD RGB Word8))
Left "JuicyPixel decoding error: Input image is in YCbCr8 (Pixel YCbCr Word8), cannot convert it to RGB8 (Pixel RGB Word8) colorspace."
Attempt to read an image in a particular color space that is not supported by
the format, will result in a compile error. Refer to Readable
class for all
images that can be decoded.
Writing
:: (ManifestArray arr cs Double, Writable (Image arr cs Double) OutputFormat) | |
=> FilePath | Location where an image should be written. |
-> Image arr cs Double | An image to write. |
-> IO () |
Just like readImage
, this function will guess an output file format from the
extension and write to file any image that is in one of Y
, YA
, RGB
or
RGBA
ColorSpace
s with Double
precision. While doing necessary
conversions the choice will be given to the most suited color space supported
by the format, for instance, in case of a PNG
format, an (Image
arr
RGBA
Double
) would be written as RGBA
16, hence preserving transparency
and using highest supported precision Word16
. At the same time, writing
that image in GIF
format would save it in RGB8
, since Word8
is the
highest precision GIF
supports and it currently cannot be saved with
transparency.
:: Writable img format | |
=> format | A file format that an image should be saved in. See Supported Image Formats |
-> [SaveOption format] | A list of format specific options. |
-> FilePath | Location where an image should be written. |
-> img | An image to write. Can be a list of images in case of formats supporting animation. |
-> IO () |
Write an image in a specific format, while supplying any format specific options. Precision and color space that an image will be written is decided from image's type. Attempt to write image file in a format that does not support color space and precision combination will result in a compile error.
:: (ManifestArray arr cs e, Writable (Image arr cs e) TIF) | |
=> Image arr cs e | Image to be displayed |
-> IO (Maybe ThreadId) |
Makes a call to the current display program, which can be changed using
setDisplayProgram
. An image is written as a .tiff
file into an operating
system's temporary directory and passed as an argument to the display
program. If a blocking flag was set to False
using setDisplayProgram
, then
function will return immediately with (Just
ThreadId
), otherwise it will
block current thread until external program is terminated, in which case
Nothing
is returned. Temporary file is deleted, after a program displaying an
image is closed.
>>>
frog <- readImageRGB "images/frog.jpg"
>>>
displayImage frog
Just ThreadId 505>>>
setDisplayProgram ("gimp", True)
>>>
displayImage frog -- will only return after gimp is closed.
Nothing
Accessors
Dimensions
rows :: Array arr cs e => Image arr cs e -> Int Source
Get the number of rows in an image.
>>>
frog <- readImageRGB "images/frog.jpg"
>>>
frog
<Image VectorUnboxed RGB (Double): 200x320>>>>
rows frog
200
cols :: Array arr cs e => Image arr cs e -> Int Source
Get the number of columns in an image.
>>>
frog <- readImageRGB "images/frog.jpg"
>>>
frog
<Image VectorUnboxed RGB (Double): 200x320>>>>
cols frog
320
dims :: Array arr cs e => Image arr cs e -> (Int, Int) Source
Get dimensions of an image.
>>>
frog <- readImageRGB "images/frog.jpg"
>>>
frog
<Image VectorUnboxed RGB (Double): 200x320>>>>
dims frog
(200,320)
Indexing
index :: ManifestArray arr cs e => Image arr cs e -> (Int, Int) -> Pixel cs e Source
Get a pixel at i
-th and j
-th location.
>>>
let grad_gray = makeImage (200, 200) (\(i, j) -> PixelY $ fromIntegral (i*j)) / (200*200)
>>>
index grad_gray (20, 30) == PixelY ((20*30) / (200*200))
True
defaultIndex :: ManifestArray arr cs e => Pixel cs e -> Image arr cs e -> (Int, Int) -> Pixel cs e Source
Image indexing function that returns a default pixel if index is out of bounds.
maybeIndex :: ManifestArray arr cs e => Image arr cs e -> (Int, Int) -> Maybe (Pixel cs e) Source
Transformation
Pointwise
:: (Array arr cs e, Array arr cs' e') | |
=> (Pixel cs' e' -> Pixel cs e) | A function that takes a pixel of a source image and returns a pixel for the result image a the same location. |
-> Image arr cs' e' | Source image. |
-> Image arr cs e | Result image. |
Map a function over a an image.
:: (Array arr cs e, Array arr cs' e') | |
=> ((Int, Int) -> Pixel cs' e' -> Pixel cs e) | A function that takes an index |
-> Image arr cs' e' | Source image. |
-> Image arr cs e | Result image. |
Map an index aware function over each pixel in an image.
zipWith :: (Array arr cs e, Array arr cs1 e1, Array arr cs2 e2) => (Pixel cs1 e1 -> Pixel cs2 e2 -> Pixel cs e) -> Image arr cs1 e1 -> Image arr cs2 e2 -> Image arr cs e Source
Zip two images with a function
izipWith :: (Array arr cs e, Array arr cs1 e1, Array arr cs2 e2) => ((Int, Int) -> Pixel cs1 e1 -> Pixel cs2 e2 -> Pixel cs e) -> Image arr cs1 e1 -> Image arr cs2 e2 -> Image arr cs e Source
Zip two images with an index aware function
Geometric
:: (Array arr cs e, Array arr cs' e') | |
=> Image arr cs' e' | Source image. |
-> ((Int, Int) -> (Int, Int)) | Function that takes dimensions of a source image and returns dimensions of a new image. |
-> (((Int, Int) -> Pixel cs' e') -> (Int, Int) -> Pixel cs e) | Function that receives a pixel getter (a source image index
function), a location |
-> Image arr cs e |
Traverse an image
:: (Array arr cs e, Array arr cs1 e1, Array arr cs2 e2) | |
=> Image arr cs1 e1 | First source image. |
-> Image arr cs2 e2 | Second source image. |
-> ((Int, Int) -> (Int, Int) -> (Int, Int)) | Function that produces dimensions for the new image. |
-> (((Int, Int) -> Pixel cs1 e1) -> ((Int, Int) -> Pixel cs2 e2) -> (Int, Int) -> Pixel cs e) | Function that produces pixels for the new image. |
-> Image arr cs e |
Traverse two images.
:: Array arr cs e | |
=> (Int, Int) | Dimensions of a result image. |
-> ((Int, Int) -> (Int, Int)) | Function that maps an index of a source image to an index of a result image. |
-> Image arr cs e | Source image. |
-> Image arr cs e | Result image. |
Backwards permutation of an image.
(|*|) :: ManifestArray arr cs e => Image arr cs e -> Image arr cs e -> Image arr cs e Source
Perform matrix multiplication on two images. Inner dimensions must agree.
Reduction
:: ManifestArray arr cs e | |
=> (Pixel cs e -> Pixel cs e -> Pixel cs e) | An associative folding function. |
-> Pixel cs e | Initial element, that is neutral with respect to the folding function. |
-> Image arr cs e | Source image. |
-> Pixel cs e |
Undirected reduction of an image.
sum :: ManifestArray arr cs e => Image arr cs e -> Pixel cs e Source
Sum all pixels in the image.
product :: ManifestArray arr cs e => Image arr cs e -> Pixel cs e Source
Multiply all pixels in the image.
maximum :: (ManifestArray arr cs e, Ord (Pixel cs e)) => Image arr cs e -> Pixel cs e Source
Retrieve the biggest pixel from an image
minimum :: (ManifestArray arr cs e, Ord (Pixel cs e)) => Image arr cs e -> Pixel cs e Source
Retrieve the smallest pixel from an image
normalize :: (ManifestArray arr cs e, ManifestArray arr Gray e, Fractional e, Ord e) => Image arr cs e -> Image arr cs e Source
Scales all of the pixels to be in the range [0, 1]
.
Representations
:: (Exchangable arr' arr, Array arr' cs e, Array arr cs e) | |
=> arr | New representation of an image. |
-> Image arr' cs e | Source image. |
-> Image arr cs e |
Exchange the underlying array representation of an image.
Unboxed Vector
representation.
Show VU Source | |
Exchangable VU RS Source | O(1) - Changes to Repa representation. |
Exchangable VU RP Source | O(1) - Changes to Repa representation. |
Exchangable RS VU Source | O(1) - Changes to Vector representation. |
Exchangable RP VU Source | O(1) - Changes to Vector representation. |
ManifestArray VU cs e => MutableArray VU cs e Source | |
ManifestArray VU cs e => SequentialArray VU cs e Source | |
Array VU cs e => ManifestArray VU cs e Source | |
Elt VU cs e => Array VU cs e Source | |
data Image VU Source | |
type Elt VU cs e = (ColorSpace cs, Num e, Unbox e, Typeable * e, Unbox (PixelElt cs e), Unbox (Pixel cs e)) Source | |
data MImage st VU cs e Source |
Repa D
elayed Array representation, which allows for fusion of computation.
Show RD Source | |
Exchangable RS RD Source | O(1) - Delays manifest array. |
Exchangable RP RD Source | O(1) - Delays manifest array. |
Exchangable RD RS Source | Computes delayed array sequentially. |
Exchangable RD RP Source | Computes delayed array in parallel. |
Elt RD cs e => Array RD cs e Source | |
data Image RD Source | |
type Elt RD cs e = (ColorSpace cs, Num e, Typeable * e, Elt e, Unbox e, Elt (PixelElt cs e), Unbox (PixelElt cs e), Elt (Pixel cs e), Unbox (Pixel cs e)) Source |
Repa U
nboxed Array representation, which is computed sequentially.
Show RS Source | |
Exchangable VU RS Source | O(1) - Changes to Repa representation. |
Exchangable RS VU Source | O(1) - Changes to Vector representation. |
Exchangable RS RP Source | O(1) - Changes computation strategy. |
Exchangable RS RD Source | O(1) - Delays manifest array. |
Exchangable RP RS Source | O(1) - Changes computation strategy. |
Exchangable RD RS Source | Computes delayed array sequentially. |
ManifestArray RS cs e => MutableArray RS cs e Source | |
ManifestArray RS cs e => SequentialArray RS cs e Source | |
Array RS cs e => ManifestArray RS cs e Source | |
Elt RS cs e => Array RS cs e Source | |
data Image RS = RSImage !(Image RD cs e) Source | |
type Elt RS cs e = (ColorSpace cs, Elt e, Unbox e, Num e, Typeable * e, Elt (PixelElt cs e), Unbox (PixelElt cs e), Elt (Pixel cs e), Unbox (Pixel cs e)) Source | |
data MImage st RS cs e = MRSImage !(MImage st VU cs e) Source |
Repa U
nboxed Array representation, which is computed in parallel.
Show RP Source | |
Exchangable VU RP Source | O(1) - Changes to Repa representation. |
Exchangable RS RP Source | O(1) - Changes computation strategy. |
Exchangable RP VU Source | O(1) - Changes to Vector representation. |
Exchangable RP RS Source | O(1) - Changes computation strategy. |
Exchangable RP RD Source | O(1) - Delays manifest array. |
Exchangable RD RP Source | Computes delayed array in parallel. |
Array RP cs e => ManifestArray RP cs e Source | |
Elt RP cs e => Array RP cs e Source | |
data Image RP = RPImage !(Image RD cs e) Source | |
type Elt RP cs e = (ColorSpace cs, Elt e, Unbox e, Num e, Typeable * e, Elt (PixelElt cs e), Unbox (PixelElt cs e), Elt (Pixel cs e), Unbox (Pixel cs e)) Source |