Copyright | (c) Alexey Kuleshevich 2016 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
- 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
- fromUnboxedVector :: Array VU cs e => (Int, Int) -> Vector (Pixel cs e) -> Image VU cs e
- toUnboxedVector :: Array VU cs e => Image VU cs e -> Vector (Pixel 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)
- data VU = VU
Construction
:: 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>
fromUnboxedVector :: Array VU cs e => (Int, Int) -> Vector (Pixel cs e) -> Image VU cs e Source
Construct a two dimensional image with m
rows and n
columns from a flat
Unboxed Vector
of length k
. It is a O(1) opeartion. Make sure that m * n = k
.
>>>
fromUnboxedVector (200, 300) $ generate 60000 (\i -> PixelY $ fromIntegral i / 60000)
<Image VectorUnboxed Luma: 200x300>
toUnboxedVector :: Array VU cs e => Image VU cs e -> Vector (Pixel cs e) Source
Convert an image to a flattened Unboxed Vector
. It is a O(1) opeartion.
>>>
toUnboxedVector $ makeImage (3, 2) (\(i, j) -> PixelY $ fromIntegral (i+j))
fromList [<Luma:(0.0)>,<Luma:(1.0)>,<Luma:(1.0)>,<Luma:(2.0)>,<Luma:(2.0)>,<Luma:(3.0)>]
IO
readImageRGBA :: FilePath -> IO (Image VU RGBA Double) Source
Read image in RGB colorspace with Alpha
channel.
Representation
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 |