hip-1.0.0.0: Haskell Image Processing (HIP) Library.

Safe HaskellNone
LanguageHaskell2010

Graphics.Image.Interface.Vector

Contents

Synopsis

Construction

makeImage Source

Arguments

:: Array VU cs Double 
=> (Int, Int)

(m rows, n columns) - dimensions of a new image.

-> ((Int, Int) -> Pixel cs Double)

A function that takes (i-th row, and j-th column) as an argument and returns a pixel for that location.

-> 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 Pixels and Images 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

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

readImageY :: FilePath -> IO (Image VU Y Double) Source

Read image as luma (brightness).

readImageYA :: FilePath -> IO (Image VU YA Double) Source

Read image as luma with Alpha channel.

readImageRGB :: FilePath -> IO (Image VU RGB Double) Source

Read image in RGB colorspace.

readImageRGBA :: FilePath -> IO (Image VU RGBA Double) Source

Read image in RGB colorspace with Alpha channel.

Representation

data VU Source

Unboxed Vector representation.

Constructors

VU 

Instances

Show VU 
Exchangable VU RS

O(1) - Changes to Repa representation.

Exchangable VU RP

O(1) - Changes to Repa representation.

Exchangable RS VU

O(1) - Changes to Vector representation.

Exchangable RP VU

O(1) - Changes to Vector representation.

ManifestArray VU cs e => MutableArray VU cs e 
ManifestArray VU cs e => SequentialArray VU cs e 
Array VU cs e => ManifestArray VU cs e 
Elt VU cs e => Array VU cs e 
data Image VU  
type Elt VU cs e = (ColorSpace cs, Num e, Unbox e, Typeable * e, Unbox (PixelElt cs e), Unbox (Pixel cs e)) 
data MImage st VU cs e