Copyright | (c) Alexey Kuleshevich 2016 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
- class (Eq cs, Enum cs, Show cs, Typeable cs) => ColorSpace cs where
- type PixelElt cs e
- data Pixel cs e
- fromChannel :: e -> Pixel cs e
- toElt :: Pixel cs e -> PixelElt cs e
- fromElt :: PixelElt cs e -> Pixel cs e
- getPxCh :: Pixel cs e -> cs -> e
- chOp :: (cs -> e' -> e) -> Pixel cs e' -> Pixel cs e
- pxOp :: (e' -> e) -> Pixel cs e' -> Pixel cs e
- chApp :: Pixel cs (e' -> e) -> Pixel cs e' -> Pixel cs e
- pxFoldMap :: Monoid m => (e -> m) -> Pixel cs e -> m
- csColour :: cs -> AlphaColour Double
- class (ColorSpace (Opaque cs), ColorSpace cs) => Alpha cs where
- class Elevator e where
- toWord8 :: ColorSpace cs => Pixel cs e -> Pixel cs Word8
- toWord16 :: ColorSpace cs => Pixel cs e -> Pixel cs Word16
- toWord32 :: ColorSpace cs => Pixel cs e -> Pixel cs Word32
- toWord64 :: ColorSpace cs => Pixel cs e -> Pixel cs Word64
- toFloat :: ColorSpace cs => Pixel cs e -> Pixel cs Float
- toDouble :: ColorSpace cs => Pixel cs e -> Pixel cs Double
- fromDouble :: ColorSpace cs => Pixel cs Double -> Pixel cs e
- 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
- makeImage :: (Int, Int) -> ((Int, Int) -> Pixel cs e) -> Image arr cs e
- singleton :: Pixel cs e -> Image arr cs e
- dims :: Image arr cs e -> (Int, Int)
- map :: Array arr cs' e' => (Pixel cs' e' -> Pixel cs e) -> Image arr cs' e' -> Image arr cs e
- imap :: Array arr cs' e' => ((Int, Int) -> Pixel cs' e' -> Pixel cs e) -> Image arr cs' e' -> Image arr cs e
- 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
- 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
- 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
- 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
- transpose :: Image arr cs e -> Image arr cs e
- backpermute :: (Int, Int) -> ((Int, Int) -> (Int, Int)) -> Image arr cs e -> Image arr cs e
- fromLists :: [[Pixel cs e]] -> Image arr cs e
- class Array arr cs e => ManifestArray arr cs e where
- index :: Image arr cs e -> (Int, Int) -> Pixel cs e
- deepSeqImage :: Image arr cs e -> a -> a
- (|*|) :: Image arr cs e -> Image arr cs e -> Image arr cs e
- fold :: (Pixel cs e -> Pixel cs e -> Pixel cs e) -> Pixel cs e -> Image arr cs e -> Pixel cs e
- eq :: Eq (Pixel cs e) => Image arr cs e -> Image arr cs e -> Bool
- class ManifestArray arr cs e => SequentialArray arr cs e where
- foldl :: (a -> Pixel cs e -> a) -> a -> Image arr cs e -> a
- foldr :: (Pixel cs e -> a -> a) -> a -> Image arr cs e -> a
- 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)
- mapM_ :: (Functor m, Monad m) => (Pixel cs e -> m b) -> Image arr cs e -> m ()
- foldM :: (Functor m, Monad m) => (a -> Pixel cs e -> m a) -> a -> Image arr cs e -> m a
- foldM_ :: (Functor m, Monad m) => (a -> Pixel cs e -> m a) -> a -> Image arr cs e -> m ()
- class ManifestArray arr cs e => MutableArray arr cs e where
- data MImage st arr cs e
- mdims :: MImage st arr cs e -> (Int, Int)
- thaw :: (Functor m, PrimMonad m) => Image arr cs e -> m (MImage (PrimState m) arr cs e)
- freeze :: (Functor m, PrimMonad m) => MImage (PrimState m) arr cs e -> m (Image arr cs e)
- new :: (Functor m, PrimMonad m) => (Int, Int) -> m (MImage (PrimState m) arr cs e)
- read :: (Functor m, PrimMonad m) => MImage (PrimState m) arr cs e -> (Int, Int) -> m (Pixel cs e)
- write :: (Functor m, PrimMonad m) => MImage (PrimState m) arr cs e -> (Int, Int) -> Pixel cs e -> m ()
- swap :: (Functor m, PrimMonad m) => MImage (PrimState m) arr cs e -> (Int, Int) -> (Int, Int) -> m ()
- class Exchangable arr' arr where
- 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)
- data Border px
- borderIndex :: Border (Pixel cs e) -> (Int, Int) -> ((Int, Int) -> Pixel cs e) -> (Int, Int) -> Pixel cs e
- class Functor f => Applicative f where
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<$) :: Functor f => forall a b. a -> f b -> f a
- (<**>) :: Applicative f => f a -> f (a -> b) -> f b
- liftA :: Applicative f => (a -> b) -> f a -> f b
- liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
- liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
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.
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.
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.
class (ColorSpace (Opaque cs), ColorSpace cs) => Alpha cs where Source
A color space that supports transparency.
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.
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)>
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.
type Elt arr cs e :: Constraint Source
Required array specific constraints for an array element.
Underlying image representation.
:: (Int, Int) | ( |
-> ((Int, Int) -> Pixel cs e) | A function that takes ( |
-> Image arr cs e |
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)
:: 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' | |
=> ((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 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
:: 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 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.
transpose :: Image arr cs e -> Image arr cs e Source
Transpose an image
:: (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.
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.
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.
:: (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.
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.
Array VU cs e => ManifestArray VU cs e Source | |
Array RS cs e => ManifestArray RS cs e Source | |
Array RP cs e => ManifestArray RP cs e Source |
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.
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
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.
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 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.
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.
:: (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.
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.
maybeIndex :: ManifestArray arr cs e => Image arr cs e -> (Int, Int) -> Maybe (Pixel cs e) Source
Approach to be used near the border during transformations, which, besides a pixel of interest, also use it's neighbors, consequently going out of bounds at the edges of an image.
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
|
:: 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.
class Functor f => Applicative f where
A functor with application, providing operations to
A minimal complete definition must include implementations of these functions satisfying the following laws:
- identity
pure
id
<*>
v = v- composition
pure
(.)<*>
u<*>
v<*>
w = u<*>
(v<*>
w)- homomorphism
pure
f<*>
pure
x =pure
(f x)- interchange
u
<*>
pure
y =pure
($
y)<*>
u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor
instance for f
will satisfy
If f
is also a Monad
, it should satisfy
(which implies that pure
and <*>
satisfy the applicative functor laws).
pure :: a -> f a
Lift a value.
(<*>) :: f (a -> b) -> f a -> f b infixl 4
Sequential application.
(*>) :: f a -> f b -> f b infixl 4
Sequence actions, discarding the value of the first argument.
(<*) :: f a -> f b -> f a infixl 4
Sequence actions, discarding the value of the second argument.
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4
An infix synonym for fmap
.
Examples
Convert from a
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing>>>
show <$> Just 3
Just "3"
Convert from an
to an Either
Int
Int
Either
Int
String
using show
:
>>>
show <$> Left 17
Left 17>>>
show <$> Right 17
Right "17"
Double each element of a list:
>>>
(*2) <$> [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
even <$> (2,2)
(2,True)
(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4
A variant of <*>
with the arguments reversed.
liftA :: Applicative f => (a -> b) -> f a -> f b
liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
Lift a binary function to actions.
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
Lift a ternary function to actions.