#ifndef ENABLE_INTERNAL_DOCUMENTATION
#endif
module OpenCV.Internal.C.Types where
import "base" Foreign.C.Types
import "base" Foreign.Ptr ( Ptr, nullPtr )
import "base" Data.Int ( Int32 )
import "base" GHC.TypeLits
import "this" OpenCV.Internal.Core.Types.Constants
import "this" OpenCV.Internal.Mutable
data C'Matx (dimR :: Nat) (dimC :: Nat) (depth :: *)
data C'Vec (dim :: Nat) (depth :: *)
data C'Point (dim :: Nat) (depth :: *)
data C'Size (depth :: *)
data C'Rect (depth :: *)
type C'Matx12f = C'Matx 1 2 CFloat
type C'Matx12d = C'Matx 1 2 CDouble
type C'Matx13f = C'Matx 1 3 CFloat
type C'Matx13d = C'Matx 1 3 CDouble
type C'Matx14f = C'Matx 1 4 CFloat
type C'Matx14d = C'Matx 1 4 CDouble
type C'Matx16f = C'Matx 1 6 CFloat
type C'Matx16d = C'Matx 1 6 CDouble
type C'Matx21f = C'Matx 2 1 CFloat
type C'Matx21d = C'Matx 2 1 CDouble
type C'Matx22f = C'Matx 2 2 CFloat
type C'Matx22d = C'Matx 2 2 CDouble
type C'Matx23f = C'Matx 2 3 CFloat
type C'Matx23d = C'Matx 2 3 CDouble
type C'Matx31f = C'Matx 3 1 CFloat
type C'Matx31d = C'Matx 3 1 CDouble
type C'Matx32f = C'Matx 3 2 CFloat
type C'Matx32d = C'Matx 3 2 CDouble
type C'Matx33f = C'Matx 3 3 CFloat
type C'Matx33d = C'Matx 3 3 CDouble
type C'Matx34f = C'Matx 3 4 CFloat
type C'Matx34d = C'Matx 3 4 CDouble
type C'Matx41f = C'Matx 4 1 CFloat
type C'Matx41d = C'Matx 4 1 CDouble
type C'Matx43f = C'Matx 4 3 CFloat
type C'Matx43d = C'Matx 4 3 CDouble
type C'Matx44f = C'Matx 4 4 CFloat
type C'Matx44d = C'Matx 4 4 CDouble
type C'Matx51f = C'Matx 5 1 CFloat
type C'Matx51d = C'Matx 5 1 CDouble
type C'Matx61f = C'Matx 6 1 CFloat
type C'Matx61d = C'Matx 6 1 CDouble
type C'Matx66f = C'Matx 6 6 CFloat
type C'Matx66d = C'Matx 6 6 CDouble
type C'Vec2i = C'Vec 2 Int32
type C'Vec2f = C'Vec 2 CFloat
type C'Vec2d = C'Vec 2 CDouble
type C'Vec3i = C'Vec 3 Int32
type C'Vec3f = C'Vec 3 CFloat
type C'Vec3d = C'Vec 3 CDouble
type C'Vec4i = C'Vec 4 Int32
type C'Vec4f = C'Vec 4 CFloat
type C'Vec4d = C'Vec 4 CDouble
type C'Point2i = C'Point 2 Int32
type C'Point2f = C'Point 2 CFloat
type C'Point2d = C'Point 2 CDouble
type C'Point3i = C'Point 3 Int32
type C'Point3f = C'Point 3 CFloat
type C'Point3d = C'Point 3 CDouble
type C'Size2i = C'Size Int32
type C'Size2f = C'Size CFloat
type C'Size2d = C'Size CDouble
type C'Rect2i = C'Rect Int32
type C'Rect2f = C'Rect CFloat
type C'Rect2d = C'Rect CDouble
data C'CvCppException
data C'RotatedRect
data C'TermCriteria
data C'Range
data C'Scalar
data C'Mat
data C'KeyPoint
data C'DMatch
data C'Ptr_ORB
data C'Ptr_SimpleBlobDetector
data C'DescriptorMatcher
data C'BFMatcher
data C'FlannBasedMatcher
data C'Ptr_BackgroundSubtractorKNN
data C'Ptr_BackgroundSubtractorMOG2
data C'VideoCapture
data C'VideoWriter
data C'CascadeClassifier
type C'MouseCallback
= Int32
-> Int32
-> Int32
-> Int32
-> Ptr ()
-> IO ()
type C'TrackbarCallback
= Int32
-> Ptr ()
-> IO ()
class CSizeOf a where
cSizeOf :: proxy a -> Int
instance CSizeOf C'Point2i where cSizeOf _proxy = c'sizeof_Point2i
instance CSizeOf C'Point2f where cSizeOf _proxy = c'sizeof_Point2f
instance CSizeOf C'Point2d where cSizeOf _proxy = c'sizeof_Point2d
instance CSizeOf C'Point3i where cSizeOf _proxy = c'sizeof_Point3i
instance CSizeOf C'Point3f where cSizeOf _proxy = c'sizeof_Point3f
instance CSizeOf C'Point3d where cSizeOf _proxy = c'sizeof_Point3d
instance CSizeOf C'Size2i where cSizeOf _proxy = c'sizeof_Size2i
instance CSizeOf C'Size2f where cSizeOf _proxy = c'sizeof_Size2f
instance CSizeOf C'Scalar where cSizeOf _proxy = c'sizeof_Scalar
instance CSizeOf C'Range where cSizeOf _proxy = c'sizeof_Range
instance CSizeOf C'Mat where cSizeOf _proxy = c'sizeof_Mat
type family C (a :: *) :: *
type instance C (Maybe a) = C a
type instance C (Mut a s) = C a
class WithPtr a where
withPtr :: a -> (Ptr (C a) -> IO b) -> IO b
instance (WithPtr a) => WithPtr (Maybe a) where
withPtr Nothing f = f nullPtr
withPtr (Just obj) f = withPtr obj f
instance (WithPtr a) => WithPtr (Mut a s) where
withPtr = withPtr . unMut
class FromPtr a where
fromPtr :: IO (Ptr (C a)) -> IO a
toCFloat :: Float -> CFloat
toCFloat = realToFrac
fromCFloat :: CFloat -> Float
fromCFloat = realToFrac
toCDouble :: Double -> CDouble
toCDouble = realToFrac
fromCDouble :: CDouble -> Double
fromCDouble = realToFrac