Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Mut a s
- type family Mutable (a :: *) :: * -> *
- class FreezeThaw a where
- module OpenCV.Core.Types.Point
- module OpenCV.Core.Types.Size
- data Scalar
- class ToScalar a where
- class FromScalar a where
- module OpenCV.Core.Types.Rect
- data RotatedRect
- mkRotatedRect :: (IsPoint2 point2 CFloat, IsSize size CFloat) => point2 CFloat -> size CFloat -> Float -> RotatedRect
- rotatedRectCenter :: RotatedRect -> Point2f
- rotatedRectSize :: RotatedRect -> Size2f
- rotatedRectAngle :: RotatedRect -> Float
- rotatedRectBoundingRect :: RotatedRect -> Rect2i
- rotatedRectPoints :: RotatedRect -> (Point2f, Point2f, Point2f, Point2f)
- data TermCriteria
- mkTermCriteria :: Maybe Int -> Maybe Double -> TermCriteria
- data Range
- mkRange :: Int32 -> Int32 -> Range
- wholeRange :: Range
- data KeyPoint
- data KeyPointRec = KeyPointRec {}
- mkKeyPoint :: KeyPointRec -> KeyPoint
- keyPointAsRec :: KeyPoint -> KeyPointRec
- data DMatch
- data DMatchRec = DMatchRec {
- dmatchQueryIdx :: !Int32
- dmatchTrainIdx :: !Int32
- dmatchImgIdx :: !Int32
- dmatchDistance :: !Float
- mkDMatch :: DMatchRec -> DMatch
- dmatchAsRec :: DMatch -> DMatchRec
- module OpenCV.Core.Types.Mat
- module OpenCV.Core.Types.Matx
- module OpenCV.Core.Types.Vec
- module OpenCV.Exception
- class Algorithm a where
- class WithPtr a
- class FromPtr a
- class CSizeOf a
- class PlacementNew a
Mutable values
Wrapper for mutable values
class FreezeThaw a where Source #
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 #
FreezeThaw (Mat shape channels depth) Source # | |
Point
module OpenCV.Core.Types.Point
Size
module OpenCV.Core.Types.Size
Scalar
A 4-element vector with 64 bit floating point elements
The type Scalar
is widely used in OpenCV to pass pixel values.
class FromScalar a where Source #
fromScalar :: Scalar -> a Source #
Rect
module OpenCV.Core.Types.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.
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
rotatedRectPoints :: RotatedRect -> (Point2f, Point2f, Point2f, Point2f) Source #
TermCriteria
data TermCriteria Source #
Termination criteria for iterative algorithms
:: Maybe Int | Optionally the maximum number of iterations/elements. |
-> Maybe Double | Optionally the desired accuracy. |
-> TermCriteria |
Range
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.
is basically the same as mkRange
a ba: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)
.
wholeRange :: Range Source #
KeyPoint
Data structure for salient point detectors
data KeyPointRec Source #
KeyPointRec | |
|
mkKeyPoint :: KeyPointRec -> KeyPoint Source #
keyPointAsRec :: KeyPoint -> KeyPointRec Source #
DMatch
Class for matching keypoint descriptors: query descriptor index, train descriptor index, train image index, and distance between descriptors
DMatchRec | |
|
dmatchAsRec :: DMatch -> DMatchRec Source #
Matrix
module OpenCV.Core.Types.Mat
module OpenCV.Core.Types.Matx
Vec
module OpenCV.Core.Types.Vec
Exception
module OpenCV.Exception
Algorithm
Polymorphic stuff
Perform an IO action with a pointer to the C equivalent of a value
withPtr
WithPtr Range Source # | |
WithPtr TermCriteria Source # | |
WithPtr RotatedRect Source # | |
WithPtr Scalar Source # | |
WithPtr CvCppException Source # | |
WithPtr KeyPoint Source # | |
WithPtr DMatch Source # | |
WithPtr CascadeClassifier Source # | |
WithPtr FlannBasedMatcher Source # | |
WithPtr BFMatcher Source # | |
WithPtr SimpleBlobDetector Source # | |
WithPtr Orb Source # | |
WithPtr VideoCapture Source # | |
WithPtr VideoWriter Source # | |
WithPtr a => WithPtr (Maybe a) Source # | |
WithPtr (Size depth) Source # | |
WithPtr (Rect depth) Source # | |
WithPtr (Vec dim depth) Source # | |
WithPtr (Point dim depth) Source # | |
WithPtr (BackgroundSubtractorMOG2 k s) Source # | |
WithPtr (BackgroundSubtractorKNN k s) Source # | |
WithPtr a => WithPtr (Mut k a s) Source # | Mutable types use the same underlying representation as unmutable types. |
WithPtr (Matx dimR dimC depth) Source # | |
WithPtr (Mat shape channels depth) 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.
fromPtr
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.
cSizeOf
class PlacementNew a Source #
Copy source to destination using C++'s placement new feature
placementNew, placementDelete