Copyright | (c) Alexey Kuleshevich 2016 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <[email protected]> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Graphics.Image.Interface
Description
- class (Eq cs, Enum cs, Show cs, Typeable cs) => ColorSpace cs where
- class (ColorSpace (Opaque cs), ColorSpace cs) => Alpha cs where
- type Opaque cs
- class Elevator e where
- class (Show arr, ColorSpace cs, Num (Pixel cs e), Functor (Pixel cs), Applicative (Pixel cs), Foldable (Pixel cs), Num e, Typeable e, Elt arr cs e) => Array arr cs e where
- type Elt arr cs e :: Constraint
- data Image arr cs e
- class Array arr cs e => ManifestArray arr cs e where
- class ManifestArray arr cs e => SequentialArray arr cs e where
- class ManifestArray arr cs e => MutableArray arr cs e where
- data MImage st arr cs e
- class Exchangable arr' arr where
- defaultIndex :: ManifestArray arr cs e => Pixel cs e -> Image arr cs e -> (Int, Int) -> Pixel cs e
- borderIndex :: ManifestArray arr cs e => Border (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)
- data Border px
- handleBorderIndex :: Border (Pixel cs e) -> (Int, Int) -> ((Int, Int) -> Pixel cs e) -> (Int, Int) -> Pixel cs e
Documentation
class (Eq cs, Enum cs, Show cs, Typeable cs) => ColorSpace cs where Source #
This class has all included color spaces installed into it and is also
intended for implementing any other possible custom color spaces. Every
instance of this class automatically installs an associated Pixel
into
Num
, Fractional
, Floating
, Functor
, Applicative
and Foldable
,
which in turn make it possible to be used by the rest of the library.
Minimal complete definition
fromChannel, toElt, fromElt, getPxCh, chOp, pxOp, chApp, pxFoldMap, csColour
Associated Types
Representation of a pixel, such that it can be an element of any Array. Which is usally a tuple of channels or a channel itself for single channel color spaces.
A concrete Pixel representation for a particular color space.
Methods
fromChannel :: e -> Pixel cs e Source #
Construt a pixel by replicating a same value among all of the channels.
toElt :: Pixel cs e -> PixelElt cs e Source #
Convert a Pixel to a representation suitable for storage as an unboxed element, usually a tuple of channels.
fromElt :: PixelElt cs e -> Pixel cs e Source #
Convert from an elemnt representation back to a Pixel.
getPxCh :: Pixel cs e -> cs -> e Source #
Retrieve Pixel's channel value
chOp :: (cs -> e' -> e) -> Pixel cs e' -> Pixel cs e Source #
Map a channel aware function over all Pixel's channels.
pxOp :: (e' -> e) -> Pixel cs e' -> Pixel cs e Source #
Map a function over all Pixel's channels.
chApp :: Pixel cs (e' -> e) -> Pixel cs e' -> Pixel cs e Source #
Function application to a Pixel.
pxFoldMap :: Monoid m => (e -> m) -> Pixel cs e -> m Source #
A pixel eqiuvalent of foldMap
.
csColour :: cs -> AlphaColour Double Source #
Get a pure colour representation of a channel.
Instances
class (ColorSpace (Opaque cs), ColorSpace cs) => Alpha cs where Source #
A color space that supports transparency.
Methods
getAlpha :: Pixel cs e -> e Source #
Get an alpha channel of a transparant pixel.
addAlpha :: e -> Pixel (Opaque cs) e -> Pixel cs e Source #
Add an alpha channel of an opaque pixel.
addAlpha 0 (PixelHSI 1 2 3) == PixelHSIA 1 2 3 0
dropAlpha :: Pixel cs e -> Pixel (Opaque cs) e Source #
Convert a transparent pixel to an opaque one by dropping the alpha channel.
dropAlpha (PixelRGBA 1 2 3 4) == PixelRGB 1 2 3
opaque :: cs -> Opaque cs Source #
Get a corresponding opaque channel type.
class Elevator e where Source #
A class with a set of convenient functions that allow for changing precision of channels within pixels, while scaling the values to keep them in an appropriate range.
>>>
let rgb = PixelRGB 0.0 0.5 1.0 :: Pixel RGB Double
>>>
toWord8 rgb
<RGB:(0|128|255)>
Methods
toWord8 :: ColorSpace cs => Pixel cs e -> Pixel cs Word8 Source #
toWord16 :: ColorSpace cs => Pixel cs e -> Pixel cs Word16 Source #
toWord32 :: ColorSpace cs => Pixel cs e -> Pixel cs Word32 Source #
toWord64 :: ColorSpace cs => Pixel cs e -> Pixel cs Word64 Source #
toFloat :: ColorSpace cs => Pixel cs e -> Pixel cs Float Source #
toDouble :: ColorSpace cs => Pixel cs e -> Pixel cs Double Source #
fromDouble :: ColorSpace cs => Pixel cs Double -> Pixel cs e Source #
class (Show arr, ColorSpace cs, Num (Pixel cs e), Functor (Pixel cs), Applicative (Pixel cs), Foldable (Pixel cs), Num e, Typeable e, Elt arr cs e) => Array arr cs e where Source #
Base array like representation for an image.
Minimal complete definition
makeImage, singleton, dims, map, imap, zipWith, izipWith, traverse, traverse2, transpose, backpermute, fromLists
Associated Types
type Elt arr cs e :: Constraint Source #
Required array specific constraints for an array element.
Underlying image representation.
Methods
makeImage :: (Int, Int) -> ((Int, Int) -> Pixel cs e) -> Image arr cs e Source #
Create an Image by supplying it's dimensions and a pixel generating function.
singleton :: Pixel cs e -> Image arr cs e Source #
Create a singleton image, required for various operations on images with a scalar.
dims :: 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)
map :: Array arr cs' e' => (Pixel cs' e' -> Pixel cs e) -> Image arr cs' e' -> Image arr cs e Source #
Map a function over a an image.
imap :: Array arr cs' e' => ((Int, Int) -> Pixel cs' e' -> Pixel cs e) -> Image arr cs' e' -> Image arr cs e Source #
Map an index aware function over each pixel in an image.
zipWith :: (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 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
traverse :: 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 Source #
Traverse an image
traverse2 :: (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 Source #
Traverse two images.
transpose :: Image arr cs e -> Image arr cs e Source #
Transpose an image
backpermute :: (Int, Int) -> ((Int, Int) -> (Int, Int)) -> Image arr cs e -> Image arr cs e Source #
Backwards permutation of an image.
fromLists :: [[Pixel cs e]] -> Image arr 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
.
class Array arr cs e => ManifestArray arr cs e where Source #
Array representation that is actually has real data stored in memory, hence allowing for image indexing, forcing pixels into computed state etc.
Minimal complete definition
index, deepSeqImage, (|*|), fold, eq
Methods
index :: 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
deepSeqImage :: Image arr cs e -> a -> a Source #
Make sure that an image is fully evaluated.
(|*|) :: Image arr cs e -> Image arr cs e -> Image arr cs e Source #
Perform matrix multiplication on two images. Inner dimensions must agree.
fold :: (Pixel cs e -> Pixel cs e -> Pixel cs e) -> Pixel cs e -> Image arr cs e -> Pixel cs e Source #
Undirected reduction of an image.
eq :: Eq (Pixel cs e) => Image arr cs e -> Image arr cs e -> Bool Source #
Pixelwise equality function of two images. Images are
considered distinct if either images' dimensions or at least one pair of
corresponding pixels are not the same. Used in defining an in instance for
the Eq
typeclass.
class ManifestArray arr cs e => SequentialArray arr cs e where Source #
Array representation that allows computation, which depends on some specific order, consequently making it possible to be computed only sequentially.
Methods
foldl :: (a -> Pixel cs e -> a) -> a -> Image arr cs e -> a Source #
Fold an image from the left in a row major order.
foldr :: (Pixel cs e -> a -> a) -> a -> Image arr cs e -> a Source #
Fold an image from the right in a row major order.
mapM :: (SequentialArray arr cs' e', Functor m, Monad m) => (Pixel cs' e' -> m (Pixel cs e)) -> Image arr cs' e' -> m (Image arr cs e) Source #
Monading mapping over an image.
mapM_ :: (Functor m, Monad m) => (Pixel cs e -> m b) -> Image arr cs e -> m () Source #
Monading mapping over an image. Result is discarded.
foldM :: (Functor m, Monad m) => (a -> Pixel cs e -> m a) -> a -> Image arr cs e -> m a Source #
foldM_ :: (Functor m, Monad m) => (a -> Pixel cs e -> m a) -> a -> Image arr cs e -> m () Source #
Instances
ManifestArray VU cs e => SequentialArray VU cs e Source # | |
ManifestArray RS cs e => SequentialArray RS cs e Source # | |
class ManifestArray arr cs e => MutableArray arr cs e where Source #
Array representation that supports mutation.
Methods
mdims :: MImage st arr cs e -> (Int, Int) Source #
Get dimensions of a mutable image.
thaw :: (Functor m, PrimMonad m) => Image arr cs e -> m (MImage (PrimState m) arr cs e) Source #
Yield a mutable copy of an image.
freeze :: (Functor m, PrimMonad m) => MImage (PrimState m) arr cs e -> m (Image arr cs e) Source #
Yield an immutable copy of an image.
new :: (Functor m, PrimMonad m) => (Int, Int) -> m (MImage (PrimState m) arr cs e) Source #
Create a mutable image with given dimensions. Pixels are likely uninitialized.
read :: (Functor m, PrimMonad m) => MImage (PrimState m) arr cs e -> (Int, Int) -> m (Pixel cs e) Source #
Yield the pixel at a given location.
write :: (Functor m, PrimMonad m) => MImage (PrimState m) arr cs e -> (Int, Int) -> Pixel cs e -> m () Source #
Set a pixel at a given location.
swap :: (Functor m, PrimMonad m) => MImage (PrimState m) arr cs e -> (Int, Int) -> (Int, Int) -> m () Source #
Swap pixels at given locations.
Instances
ManifestArray VU cs e => MutableArray VU cs e Source # | |
ManifestArray RS cs e => MutableArray RS cs e Source # | |
class Exchangable arr' arr where Source #
Allows for changing an underlying image representation.
Minimal complete definition
Methods
exchange :: (Array arr' cs e, Array arr cs e) => arr -> Image arr' cs e -> Image arr cs e Source #
Exchange the underlying array representation of an image.
Instances
Exchangable arr arr Source # | Changing to the same array representation as before is disabled and |
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 RS RP Source # | O(1) - Changes computation strategy. |
Exchangable RS RD Source # | O(1) - Delays manifest array. |
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 RS Source # | Computes delayed array sequentially. |
Exchangable RD RP Source # | Computes delayed array in parallel. |
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.
borderIndex :: ManifestArray arr cs e => Border (Pixel cs e) -> Image arr cs e -> (Int, Int) -> Pixel cs e Source #
Image indexing function that uses a special border resolutions strategy for out of bounds pixels.
maybeIndex :: ManifestArray arr cs e => Image arr cs e -> (Int, Int) -> Maybe (Pixel cs e) Source #
Approach to be used near the borders during various transformations. Whenever a function needs information not only about a pixel of interest, but also about it's neighbours, it will go out of bounds around the image edges, hence is this set of approaches that can be used in such situtation.
Constructors
Fill !px | Fill in a constant pixel. outside | Image | outside
( |
Wrap | Wrap around from the opposite border of the image. outside | Image | outside
|
Edge | Replicate the pixel at the edge. outside | Image | outside
|
Reflect | Mirror like reflection. outside | Image | outside
|
Continue | Also mirror like reflection, but without repeating the edge pixel. outside | Image | outside
|
Arguments
:: Border (Pixel cs e) | Border handling strategy. |
-> (Int, Int) | Image dimensions |
-> ((Int, Int) -> Pixel cs e) | Image's indexing function. |
-> (Int, Int) |
|
-> Pixel cs e |
Border handling function. If (i, j)
location is within bounds, then supplied
lookup function will be used, otherwise it will be handled according to a
supplied border strategy.