| Safe Haskell | None | 
|---|
CV.Image
Contents
- newtype Image channels depth = S BareImage
- empty :: CreateImage (Image a b) => (Int, Int) -> Image a b
- emptyCopy :: CreateImage (Image a b) => Image a b -> Image a b
- emptyCopy' :: CreateImage (Image a b) => Image a b -> IO (Image a b)
- cloneImage :: Image a b -> IO (Image a b)
- withClone :: Image channels depth -> (Image channels depth -> IO ()) -> IO (Image channels depth)
- withCloneValue :: Image channels depth -> (Image channels depth -> IO a) -> IO a
- class CreateImage a where
- type family ChannelOf a :: *
- data GrayScale
- data Complex
- data RGB
- data RGBA
- data RGB_Channel
- data LAB
- data LAB_Channel
- type D32 = Float
- type D64 = Double
- type D8 = Word8
- data Tag tp
- lab :: Tag LAB
- rgba :: Tag RGBA
- rgb :: Tag RGB
- compose :: Composes a => Source a -> a
- composeMultichannelImage :: CreateImage (Image tp a) => Maybe (Image GrayScale a) -> Maybe (Image GrayScale a) -> Maybe (Image GrayScale a) -> Maybe (Image GrayScale a) -> Tag tp -> Image tp a
- class  Loadable a  where- readFromFile :: FilePath -> IO a
 
- saveImage :: Save (Image c d) => FilePath -> Image c d -> IO ()
- loadColorImage :: FilePath -> IO (Maybe (Image BGR D32))
- loadImage :: FilePath -> IO (Maybe (Image GrayScale D32))
- class GetPixel a where
- class SetPixel a where
- getAllPixels :: (Sized a, GetPixel a, ~ * (Size a) (Int, Int)) => a -> [P a]
- getAllPixelsRowMajor :: (Sized a, GetPixel a, ~ * (Size a) (Int, Int)) => a -> [P a]
- mapImageInplace :: (P (Image GrayScale D32) -> P (Image GrayScale D32)) -> Image GrayScale D32 -> IO ()
- data ImageDepth
- class Sized a where
- biggerThan :: (Sized a, Sized b, Size a ~ (Int, Int), Size b ~ Size a) => a -> b -> Bool
- getArea :: (Sized a, Num b, Size a ~ (b, b)) => a -> b
- getChannel :: Enum a => a -> Image (ChannelOf a) d -> Image GrayScale d
- getImageChannels :: Image c d -> IO CInt
- getImageDepth :: Image c d -> IO ImageDepth
- getImageInfo :: Image c d -> IO ((Int, Int), ImageDepth, CInt)
- setCOI :: Integral a => a -> Image c d -> IO ()
- setROI :: (Integral t, Integral t1, Integral t2, Integral t3) => (t, t1) -> (t2, t3) -> Image c d -> IO ()
- resetROI :: Image c d -> IO ()
- getRegion :: (Int, Int) -> (Int, Int) -> Image c d -> Image c d
- withIOROI :: (Integral t, Integral t1, Integral t2, Integral t3) => (t, t1) -> (t2, t3) -> Image c d -> IO b -> IO b
- withROI :: (Int, Int) -> (Int, Int) -> Image c d -> (Image c d -> a) -> a
- blendBlit :: Image c d -> Image c1 d1 -> Image c3 d3 -> Image c2 d2 -> (CInt, CInt) -> IO ()
- blit :: Image GrayScale D32 -> Image GrayScale D32 -> (Int, Int) -> IO ()
- blitM :: (Integral a, Integral a1, Integral a2, Integral a3) => (a, a1) -> [((a2, a3), Image GrayScale D32)] -> Image GrayScale D32
- subPixelBlit :: Image c d -> Image c d -> (CDouble, CDouble) -> IO ()
- safeBlit :: Image GrayScale D32 -> Image GrayScale D32 -> (Int, Int) -> Image GrayScale D32
- montage :: CreateImage (Image GrayScale D32) => (Int, Int) -> Int -> [Image GrayScale D32] -> Image GrayScale D32
- tileImages :: Image c d -> Image c1 d1 -> (CInt, CInt) -> Image channels depth
- rgbToGray :: Image RGB D32 -> Image GrayScale D32
- grayToRGB :: Image GrayScale D32 -> Image RGB D32
- rgbToLab :: Image RGB D32 -> Image LAB D32
- bgrToRgb :: Image BGR D8 -> Image RGB D8
- rgbToBgr :: Image RGB D8 -> Image BGR D8
- cloneTo64F :: Image c d -> IO (Image c D64)
- unsafeImageTo32F :: Image c d -> Image c D32
- unsafeImageTo64F :: Image c d -> Image c D64
- unsafeImageTo8Bit :: Image cspace a -> Image cspace D8
- newtype BareImage = BareImage (ForeignPtr BareImage)
- creatingImage :: IO (Ptr BareImage) -> IO (Image channels depth)
- unImage :: Image t t1 -> ForeignPtr BareImage
- unS :: Image t t1 -> BareImage
- withGenBareImage :: BareImage -> (Ptr b -> IO b1) -> IO b1
- withBareImage :: BareImage -> (Ptr BareImage -> IO b) -> IO b
- creatingBareImage :: IO (Ptr BareImage) -> IO BareImage
- withGenImage :: Image c d -> (Ptr b -> IO a) -> IO a
- withImage :: Image c d -> (Ptr BareImage -> IO a) -> IO a
- imageFPTR :: Image c d -> ForeignPtr BareImage
- ensure32F :: Ptr BareImage -> IO (Ptr BareImage)
- setCatch :: IO CInt
- data CvException
- data CvSizeError = CvSizeError String
- data CvIOError = CvIOError String
Basic types
newtype Image channels depth Source
The type for Images
Instances
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.
emptyCopy' :: CreateImage (Image a b) => Image a b -> IO (Image a b)Source
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
class CreateImage a whereSource
Class for images that exist.
Instances
| CreateImage (Image RGBA D64) | |
| CreateImage (Image RGBA D32) | |
| CreateImage (Image RGBA D8) | |
| CreateImage (Image LAB D64) | |
| CreateImage (Image LAB D32) | |
| CreateImage (Image LAB D8) | |
| CreateImage (Image RGB D64) | |
| CreateImage (Image RGB D32) | |
| CreateImage (Image RGB D8) | |
| CreateImage (Image Complex D32) | |
| CreateImage (Image GrayScale D64) | |
| CreateImage (Image GrayScale D32) | |
| CreateImage (Image GrayScale D8) | 
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.
Single channel grayscale image
Instances
Instances
| Drawable RGB D32 | |
| SetPixel (Image RGB D32) | |
| Save (Image RGB D32) | |
| Save (Image RGB D8) | |
| CreateImage (Image RGB D64) | |
| CreateImage (Image RGB D32) | |
| CreateImage (Image RGB D8) | |
| GetPixel (Image RGB D32) | |
| GetPixel (Image RGB D8) | |
| Loadable (Image RGB D32) | |
| Loadable (Image RGB D8) | |
| CreateImage (Image RGB a) => Composes (Image RGB a) | |
| HasMedianFiltering (Image RGB D8) | 
Instances
| CreateImage (Image RGBA D64) | |
| CreateImage (Image RGBA D32) | |
| CreateImage (Image RGBA D8) | |
| CreateImage (Image RGBA a) => Composes (Image RGBA a) | 
data RGB_Channel Source
Instances
data LAB_Channel Source
Instances
composeMultichannelImage :: CreateImage (Image tp a) => Maybe (Image GrayScale a) -> Maybe (Image GrayScale a) -> Maybe (Image GrayScale a) -> Maybe (Image GrayScale a) -> Tag tp -> Image tp aSource
Deprecated: This is unsafe. Use compose instead
IO operations
Typeclass for CV items that can be read from file. Mainly images at this point.
Methods
readFromFile :: FilePath -> IO aSource
Pixel level access
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
data ImageDepth Source
Instances
Typeclass for elements with a size, such as images and matrices.
getImageChannels :: Image c d -> IO CIntSource
getImageDepth :: Image c d -> IO ImageDepthSource
getImageInfo :: Image c d -> IO ((Int, Int), ImageDepth, CInt)Source
ROI's, COI's and subregions
setROI :: (Integral t, Integral t1, Integral t2, Integral t3) => (t, t1) -> (t2, t3) -> Image c d -> IO ()Source
withIOROI :: (Integral t, Integral t1, Integral t2, Integral t3) => (t, t1) -> (t2, t3) -> Image c d -> IO b -> IO bSource
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 a, Integral a1, Integral a2, Integral a3) => (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
unsafeImageTo32F :: Image c d -> Image c D32Source
unsafeImageTo64F :: Image c d -> Image c D64Source
unsafeImageTo8Bit :: Image cspace a -> Image cspace D8Source
Low level access operations
unImage :: Image t t1 -> ForeignPtr BareImageSource
imageFPTR :: Image c d -> ForeignPtr BareImageSource
Extended error handling
data CvException Source
Instances