CV-0.3.5.4: OpenCV based machine vision library

Safe HaskellSafe-Infered

CV.Image

Contents

Synopsis

Basic types

empty :: CreateImage (Image a b) => (Int, Int) -> Image a bSource

Allocate a new empty image

emptyCopy :: CreateImage (Image a b) => Image a b -> Image a bSource

 Allocate a new image that of the same size and type as the exemplar image given.

cloneImage :: Image a b -> IO (Image a b)Source

Create a copy of an image

withClone :: Image channels depth -> (Image channels depth -> IO ()) -> IO (Image channels depth)Source

withCloneValue :: Image channels depth -> (Image channels depth -> IO a) -> IO aSource

Colour spaces

type family ChannelOf a :: *Source

Type family for expressing which channels a colorspace contains. This needs to be fixed wrt. the BGR color space.

data Tag tp Source

compose :: Composes a => Source a -> aSource

IO operations

class Loadable a whereSource

Typeclass for CV items that can be read from file. Mainly images at this point.

saveImage :: Save (Image c d) => FilePath -> Image c d -> IO ()Source

Pixel level access

class SetPixel a whereSource

Associated Types

type SP a :: *Source

Methods

setPixel :: (Int, Int) -> SP a -> a -> IO ()Source

getAllPixels :: (GetPixel a, Sized a, ~ * (Size a) (Int, Int)) => a -> [P a]Source

getAllPixelsRowMajor :: (GetPixel a, Sized a, ~ * (Size a) (Int, Int)) => a -> [P a]Source

mapImageInplace :: (P (Image GrayScale D32) -> P (Image GrayScale D32)) -> Image GrayScale D32 -> IO ()Source

Perform (a destructive) inplace map of the image. This should be wrapped inside withClone or an image operation

Image information

class Sized a whereSource

Typeclass for elements with a size, such as images and matrices.

Associated Types

type Size a :: *Source

Methods

getSize :: a -> Size aSource

getArea :: (Sized a, Num b, Size a ~ (b, b)) => a -> bSource

ROI's, COI's and subregions

setCOI :: Integral a => a -> Image c d -> IO ()Source

setROI :: (Integral t3, Integral t2, Integral t1, Integral t) => (t, t1) -> (t2, t3) -> Image c d -> IO ()Source

resetROI :: Image c d -> IO ()Source

getRegion :: (Int, Int) -> (Int, Int) -> Image c d -> Image c dSource

withIOROI :: (Integral t, Integral t1, Integral t2, Integral t3) => (t, t1) -> (t2, t3) -> Image c d -> IO b -> IO bSource

withROI :: (Int, Int) -> (Int, Int) -> Image c d -> (Image c d -> a) -> aSource

Blitting

blendBlit :: Image c d -> Image c1 d1 -> Image c3 d3 -> Image c2 d2 -> (CInt, CInt) -> IO ()Source

Blit image2 onto image1. This uses an alpha channel bitmap for determining the regions where the image should be blended with the base image.

blitM :: (Integral a3, Integral a2, Integral a1, Integral a) => (a, a1) -> [((a2, a3), Image GrayScale D32)] -> Image GrayScale D32Source

montage :: CreateImage (Image GrayScale D32) => (Int, Int) -> Int -> [Image GrayScale D32] -> Image GrayScale D32Source

Create a montage form given images (u,v) determines the layout and space the spacing between images. Images are assumed to be the same size (determined by the first image)

tileImages :: Image c d -> Image c1 d1 -> (CInt, CInt) -> Image channels depthSource

Tile images by overlapping them on a black canvas.

Conversions

unsafeImageTo8Bit :: Image cspace a -> Image cspace D8Source

Low level access operations

newtype BareImage Source

Instances

creatingImage :: IO (Ptr BareImage) -> IO (Image channels depth)Source

unS :: Image t t1 -> BareImageSource

 Remove typing info from an image

withGenBareImage :: BareImage -> (Ptr b -> IO b1) -> IO b1Source

withGenImage :: Image c d -> (Ptr b -> IO a) -> IO aSource

withImage :: Image c d -> (Ptr BareImage -> IO a) -> IO aSource

Extended error handling