opencv-0.0.2.1: Haskell binding to OpenCV-3.x

Safe HaskellNone
LanguageHaskell2010

OpenCV.Core.Types

Contents

Synopsis

Mutable values

data Mut a s Source #

Wrapper for mutable values

Instances

WithPtr a => WithPtr (Mut k a s) Source #

Mutable types use the same underlying representation as unmutable types.

Methods

withPtr :: Mut k a s -> (Ptr (C (Mut k a s)) -> IO b) -> IO b

type family Mutable (a :: *) :: * -> * Source #

Instances

type Mutable (Mat shape channels depth) Source # 
type Mutable (Mat shape channels depth) = Mut * (Mat shape channels depth)

class FreezeThaw a where Source #

Minimal complete definition

freeze, thaw, unsafeFreeze, unsafeThaw

Methods

freeze :: PrimMonad m => Mutable a (PrimState m) -> m a Source #

thaw :: PrimMonad m => a -> m (Mutable a (PrimState m)) Source #

unsafeFreeze :: PrimMonad m => Mutable a (PrimState m) -> m a Source #

unsafeThaw :: PrimMonad m => a -> m (Mutable a (PrimState m)) Source #

Instances

FreezeThaw (Mat shape channels depth) Source # 

Methods

freeze :: PrimMonad m => Mutable (Mat shape channels depth) (PrimState m) -> m (Mat shape channels depth) Source #

thaw :: PrimMonad m => Mat shape channels depth -> m (Mutable (Mat shape channels depth) (PrimState m)) Source #

unsafeFreeze :: PrimMonad m => Mutable (Mat shape channels depth) (PrimState m) -> m (Mat shape channels depth) Source #

unsafeThaw :: PrimMonad m => Mat shape channels depth -> m (Mutable (Mat shape channels depth) (PrimState m)) Source #

Point

Size

Scalar

data Scalar Source #

A 4-element vector with 64 bit floating point elements

The type Scalar is widely used in OpenCV to pass pixel values.

OpenCV Sphinx doc

class ToScalar a where Source #

Minimal complete definition

toScalar

Methods

toScalar :: a -> Scalar Source #

class FromScalar a where Source #

Minimal complete definition

fromScalar

Methods

fromScalar :: Scalar -> a Source #

Rect

RotatedRect

data RotatedRect Source #

Rotated (i.e. not up-right) rectangles on a plane

Each rectangle is specified by the center point (mass center), length of each side (represented by Size2f) and the rotation angle in degrees.

OpenCV Sphinx doc

mkRotatedRect Source #

Arguments

:: (IsPoint2 point2 CFloat, IsSize size CFloat) 
=> point2 CFloat

Rectangle mass center

-> size CFloat

Width and height of the rectangle

-> Float

The rotation angle (in degrees). When the angle is 0, 90, 180, 270 etc., the rectangle becomes an up-right rectangle.

-> RotatedRect 

rotatedRectCenter :: RotatedRect -> Point2f Source #

Rectangle mass center

rotatedRectSize :: RotatedRect -> Size2f Source #

Width and height of the rectangle

rotatedRectAngle :: RotatedRect -> Float Source #

The rotation angle (in degrees)

When the angle is 0, 90, 180, 270 etc., the rectangle becomes an up-right rectangle.

rotatedRectBoundingRect :: RotatedRect -> Rect2i Source #

The minimal up-right rectangle containing the rotated rectangle

TermCriteria

data TermCriteria Source #

Termination criteria for iterative algorithms

OpenCV Sphinx doc

mkTermCriteria Source #

Arguments

:: Maybe Int

Optionally the maximum number of iterations/elements.

-> Maybe Double

Optionally the desired accuracy.

-> TermCriteria 

Range

data Range Source #

A continuous subsequence (slice) of a sequence

The type is used to specify a row or a column span in a matrix (Mat) and for many other purposes. mkRange a b is basically the same as a:b in Matlab or a..b in Python. As in Python, start is an inclusive left boundary of the range and end is an exclusive right boundary of the range. Such a half-opened interval is usually denoted as [start, end).

OpenCV Sphinx doc

Instances

FromPtr Range Source # 

Methods

fromPtr :: IO (Ptr (C Range)) -> IO Range

WithPtr Range Source # 

Methods

withPtr :: Range -> (Ptr (C Range) -> IO b) -> IO b

KeyPoint

data KeyPoint Source #

Data structure for salient point detectors

OpenCV Sphinx doc

Instances

FromPtr KeyPoint Source # 

Methods

fromPtr :: IO (Ptr (C KeyPoint)) -> IO KeyPoint

WithPtr KeyPoint Source # 

Methods

withPtr :: KeyPoint -> (Ptr (C KeyPoint) -> IO b) -> IO b

data KeyPointRec Source #

Constructors

KeyPointRec 

Fields

  • kptPoint :: !(V2 Float)

    Coordinates of the keypoints.

  • kptSize :: !Float

    Diameter of the meaningful keypoint neighborhood.

  • kptAngle :: !Float

    Computed orientation of the keypoint (-1 if not applicable); it's in [0,360) degrees and measured relative to image coordinate system, ie in clockwise.

  • kptResponse :: !Float

    The response by which the most strong keypoints have been selected. Can be used for the further sorting or subsampling.

  • kptOctave :: !Int32

    Octave (pyramid layer) from which the keypoint has been extracted.

  • kptClassId :: !Int32

    Object class (if the keypoints need to be clustered by an object they belong to).

DMatch

data DMatch Source #

Class for matching keypoint descriptors: query descriptor index, train descriptor index, train image index, and distance between descriptors

OpenCV Sphinx Doc

Instances

FromPtr DMatch Source # 

Methods

fromPtr :: IO (Ptr (C DMatch)) -> IO DMatch

WithPtr DMatch Source # 

Methods

withPtr :: DMatch -> (Ptr (C DMatch) -> IO b) -> IO b

data DMatchRec Source #

Constructors

DMatchRec 

Fields

Matrix

Vec

Exception

Algorithm

Polymorphic stuff

class WithPtr a Source #

Perform an IO action with a pointer to the C equivalent of a value

Minimal complete definition

withPtr

Instances

WithPtr Range Source # 

Methods

withPtr :: Range -> (Ptr (C Range) -> IO b) -> IO b

WithPtr TermCriteria Source # 

Methods

withPtr :: TermCriteria -> (Ptr (C TermCriteria) -> IO b) -> IO b

WithPtr RotatedRect Source # 

Methods

withPtr :: RotatedRect -> (Ptr (C RotatedRect) -> IO b) -> IO b

WithPtr Scalar Source # 

Methods

withPtr :: Scalar -> (Ptr (C Scalar) -> IO b) -> IO b

WithPtr CvCppException Source # 

Methods

withPtr :: CvCppException -> (Ptr (C CvCppException) -> IO b) -> IO b

WithPtr KeyPoint Source # 

Methods

withPtr :: KeyPoint -> (Ptr (C KeyPoint) -> IO b) -> IO b

WithPtr DMatch Source # 

Methods

withPtr :: DMatch -> (Ptr (C DMatch) -> IO b) -> IO b

WithPtr CascadeClassifier Source # 

Methods

withPtr :: CascadeClassifier -> (Ptr (C CascadeClassifier) -> IO b) -> IO b

WithPtr FlannBasedMatcher Source # 

Methods

withPtr :: FlannBasedMatcher -> (Ptr (C FlannBasedMatcher) -> IO b) -> IO b

WithPtr BFMatcher Source # 

Methods

withPtr :: BFMatcher -> (Ptr (C BFMatcher) -> IO b) -> IO b

WithPtr SimpleBlobDetector Source # 

Methods

withPtr :: SimpleBlobDetector -> (Ptr (C SimpleBlobDetector) -> IO b) -> IO b

WithPtr Orb Source # 

Methods

withPtr :: Orb -> (Ptr (C Orb) -> IO b) -> IO b

WithPtr VideoCapture Source # 

Methods

withPtr :: VideoCapture -> (Ptr (C VideoCapture) -> IO b) -> IO b

WithPtr VideoWriter Source # 

Methods

withPtr :: VideoWriter -> (Ptr (C VideoWriter) -> IO b) -> IO b

WithPtr a => WithPtr (Maybe a) Source #

Nothing is represented as a nullPtr.

Methods

withPtr :: Maybe a -> (Ptr (C (Maybe a)) -> IO b) -> IO b

WithPtr (Size depth) Source # 

Methods

withPtr :: Size depth -> (Ptr (C (Size depth)) -> IO b) -> IO b

WithPtr (Rect depth) Source # 

Methods

withPtr :: Rect depth -> (Ptr (C (Rect depth)) -> IO b) -> IO b

WithPtr (Vec dim depth) Source # 

Methods

withPtr :: Vec dim depth -> (Ptr (C (Vec dim depth)) -> IO b) -> IO b

WithPtr (Point dim depth) Source # 

Methods

withPtr :: Point dim depth -> (Ptr (C (Point dim depth)) -> IO b) -> IO b

WithPtr (BackgroundSubtractorMOG2 k s) Source # 

Methods

withPtr :: BackgroundSubtractorMOG2 k s -> (Ptr (C (BackgroundSubtractorMOG2 k s)) -> IO b) -> IO b

WithPtr (BackgroundSubtractorKNN k s) Source # 

Methods

withPtr :: BackgroundSubtractorKNN k s -> (Ptr (C (BackgroundSubtractorKNN k s)) -> IO b) -> IO b

WithPtr a => WithPtr (Mut k a s) Source #

Mutable types use the same underlying representation as unmutable types.

Methods

withPtr :: Mut k a s -> (Ptr (C (Mut k a s)) -> IO b) -> IO b

WithPtr (Matx dimR dimC depth) Source # 

Methods

withPtr :: Matx dimR dimC depth -> (Ptr (C (Matx dimR dimC depth)) -> IO b) -> IO b

WithPtr (Mat shape channels depth) Source # 

Methods

withPtr :: Mat shape channels depth -> (Ptr (C (Mat shape channels depth)) -> IO b) -> IO b

class FromPtr a Source #

Types of which a value can be constructed from a pointer to the C equivalent of that value

Used to wrap values created in C.

Minimal complete definition

fromPtr

Instances

FromPtr Range Source # 

Methods

fromPtr :: IO (Ptr (C Range)) -> IO Range

FromPtr TermCriteria Source # 
FromPtr RotatedRect Source # 

Methods

fromPtr :: IO (Ptr (C RotatedRect)) -> IO RotatedRect

FromPtr Scalar Source # 

Methods

fromPtr :: IO (Ptr (C Scalar)) -> IO Scalar

FromPtr CvCppException Source # 
FromPtr KeyPoint Source # 

Methods

fromPtr :: IO (Ptr (C KeyPoint)) -> IO KeyPoint

FromPtr DMatch Source # 

Methods

fromPtr :: IO (Ptr (C DMatch)) -> IO DMatch

FromPtr CascadeClassifier Source # 
FromPtr FlannBasedMatcher Source # 
FromPtr BFMatcher Source # 

Methods

fromPtr :: IO (Ptr (C BFMatcher)) -> IO BFMatcher

FromPtr SimpleBlobDetector Source # 
FromPtr Orb Source # 

Methods

fromPtr :: IO (Ptr (C Orb)) -> IO Orb

FromPtr VideoCapture Source # 
FromPtr VideoWriter Source # 

Methods

fromPtr :: IO (Ptr (C VideoWriter)) -> IO VideoWriter

FromPtr (BackgroundSubtractorMOG2 k s) Source # 
FromPtr (BackgroundSubtractorKNN k s) Source # 
FromPtr (Mat shape channels depth) Source # 

Methods

fromPtr :: IO (Ptr (C (Mat shape channels depth))) -> IO (Mat shape channels depth)

class CSizeOf a Source #

Information about the storage requirements of values in C

This class assumes that the type a is merely a symbol that corresponds with a type in C.

Minimal complete definition

cSizeOf

class PlacementNew a Source #

Copy source to destination using C++'s placement new feature

Minimal complete definition

placementNew, placementDelete