never executed always true always false
    1 {-# language CPP #-}
    2 
    3 #ifndef ENABLE_INTERNAL_DOCUMENTATION
    4 {-# OPTIONS_HADDOCK hide #-}
    5 #endif
    6 
    7 module OpenCV.Internal.C.Types where
    8 
    9 import "base" Foreign.C.Types
   10 import "base" Foreign.Ptr ( Ptr, nullPtr )
   11 import "base" Data.Int ( Int32 )
   12 import "base" GHC.TypeLits
   13 import "this" OpenCV.Internal.Core.Types.Constants
   14 import "this" OpenCV.Internal.Mutable
   15 
   16 --------------------------------------------------------------------------------
   17 
   18 data C'Matx  (dimR :: Nat) (dimC :: Nat) (depth :: *)
   19 data C'Vec   (dim :: Nat) (depth :: *)
   20 data C'Point (dim :: Nat) (depth :: *)
   21 data C'Size  (depth :: *)
   22 data C'Rect  (depth :: *)
   23 
   24 type C'Matx12f = C'Matx 1 2 CFloat
   25 type C'Matx12d = C'Matx 1 2 CDouble
   26 type C'Matx13f = C'Matx 1 3 CFloat
   27 type C'Matx13d = C'Matx 1 3 CDouble
   28 type C'Matx14f = C'Matx 1 4 CFloat
   29 type C'Matx14d = C'Matx 1 4 CDouble
   30 type C'Matx16f = C'Matx 1 6 CFloat
   31 type C'Matx16d = C'Matx 1 6 CDouble
   32 type C'Matx21f = C'Matx 2 1 CFloat
   33 type C'Matx21d = C'Matx 2 1 CDouble
   34 type C'Matx22f = C'Matx 2 2 CFloat
   35 type C'Matx22d = C'Matx 2 2 CDouble
   36 type C'Matx23f = C'Matx 2 3 CFloat
   37 type C'Matx23d = C'Matx 2 3 CDouble
   38 type C'Matx31f = C'Matx 3 1 CFloat
   39 type C'Matx31d = C'Matx 3 1 CDouble
   40 type C'Matx32f = C'Matx 3 2 CFloat
   41 type C'Matx32d = C'Matx 3 2 CDouble
   42 type C'Matx33f = C'Matx 3 3 CFloat
   43 type C'Matx33d = C'Matx 3 3 CDouble
   44 type C'Matx34f = C'Matx 3 4 CFloat
   45 type C'Matx34d = C'Matx 3 4 CDouble
   46 type C'Matx41f = C'Matx 4 1 CFloat
   47 type C'Matx41d = C'Matx 4 1 CDouble
   48 type C'Matx43f = C'Matx 4 3 CFloat
   49 type C'Matx43d = C'Matx 4 3 CDouble
   50 type C'Matx44f = C'Matx 4 4 CFloat
   51 type C'Matx44d = C'Matx 4 4 CDouble
   52 type C'Matx51f = C'Matx 5 1 CFloat
   53 type C'Matx51d = C'Matx 5 1 CDouble
   54 type C'Matx61f = C'Matx 6 1 CFloat
   55 type C'Matx61d = C'Matx 6 1 CDouble
   56 type C'Matx66f = C'Matx 6 6 CFloat
   57 type C'Matx66d = C'Matx 6 6 CDouble
   58 
   59 type C'Vec2i = C'Vec 2 Int32
   60 type C'Vec2f = C'Vec 2 CFloat
   61 type C'Vec2d = C'Vec 2 CDouble
   62 
   63 type C'Vec3i = C'Vec 3 Int32
   64 type C'Vec3f = C'Vec 3 CFloat
   65 type C'Vec3d = C'Vec 3 CDouble
   66 
   67 type C'Vec4i = C'Vec 4 Int32
   68 type C'Vec4f = C'Vec 4 CFloat
   69 type C'Vec4d = C'Vec 4 CDouble
   70 
   71 type C'Point2i = C'Point 2 Int32
   72 type C'Point2f = C'Point 2 CFloat
   73 type C'Point2d = C'Point 2 CDouble
   74 
   75 type C'Point3i = C'Point 3 Int32
   76 type C'Point3f = C'Point 3 CFloat
   77 type C'Point3d = C'Point 3 CDouble
   78 
   79 type C'Size2i = C'Size Int32
   80 type C'Size2f = C'Size CFloat
   81 type C'Size2d = C'Size CDouble
   82 
   83 type C'Rect2i = C'Rect Int32
   84 type C'Rect2f = C'Rect CFloat
   85 type C'Rect2d = C'Rect CDouble
   86 
   87 -- | Haskell representation of an OpenCV exception
   88 data C'CvCppException
   89 -- | Haskell representation of an OpenCV @cv::RotatedRect@ object
   90 data C'RotatedRect
   91 -- | Haskell representation of an OpenCV @cv::TermCriteria@ object
   92 data C'TermCriteria
   93 -- | Haskell representation of an OpenCV @cv::Range@ object
   94 data C'Range
   95 -- | Haskell representation of an OpenCV @cv::Scalar_\<double>@ object
   96 data C'Scalar
   97 -- | Haskell representation of an OpenCV @cv::Mat@ object
   98 data C'Mat
   99 
  100 -- | Haskell representation of an OpenCV @cv::Keypoint@ object
  101 data C'KeyPoint
  102 -- | Haskell representation of an OpenCV @cv::DMatch@ object
  103 data C'DMatch
  104 
  105 -- -- | Haskell representation of an OpenCV @cv::MSER@ object
  106 -- data C'MSER
  107 -- | Haskell representation of an OpenCV @cv::Ptr<cv::ORB>@ object
  108 data C'Ptr_ORB
  109 -- -- | Haskell representation of an OpenCV @cv::BRISK@ object
  110 -- data C'BRISK
  111 -- -- | Haskell representation of an OpenCV @cv::KAZE@ object
  112 -- data C'KAZE
  113 -- -- | Haskell representation of an OpenCV @cv::AKAZE@ object
  114 -- data C'AKAZE
  115 -- | Haskell representation of an OpenCV @cv::Ptr<cv::SimpleBlobDetector>@ object
  116 data C'Ptr_SimpleBlobDetector
  117 
  118 -- | Haskell representation of an OpenCV @cv::DescriptorMatcher@ object
  119 data C'DescriptorMatcher
  120 -- | Haskell representation of an OpenCV @cv::BFMatcher@ object
  121 data C'BFMatcher
  122 -- | Haskell representation of an OpenCV @cv::FlannBasedMatcher@ object
  123 data C'FlannBasedMatcher
  124 
  125 -- | Haskell representation of an OpenCV @cv::Ptr<cv::BackgroundSubtractorMOG2>@ object
  126 data C'Ptr_BackgroundSubtractorKNN
  127 -- | Haskell representation of an OpenCV @cv::Ptr<cv::BackgroundSubtractorKNN>@ object
  128 data C'Ptr_BackgroundSubtractorMOG2
  129 
  130 
  131 -- | Haskell representation of an OpenCV @cv::VideoCapture@ object
  132 data C'VideoCapture
  133 
  134 -- | Haskell representation of an OpenCV @cv::VideoWriter@ object
  135 data C'VideoWriter
  136 
  137 -- | Haskell representation of an OpenCV @cv::CascadeClassifier@ object
  138 data C'CascadeClassifier
  139 
  140 -- | Callback function for mouse events
  141 type C'MouseCallback
  142    =  Int32 -- ^ One of the @cv::MouseEvenTypes@ constants.
  143    -> Int32 -- ^ The x-coordinate of the mouse event.
  144    -> Int32 -- ^ The y-coordinate of the mouse event.
  145    -> Int32 -- ^ One of the @cv::MouseEventFlags@ constants.
  146    -> Ptr () -- ^ Optional pointer to user data.
  147    -> IO ()
  148 
  149 -- | Callback function for trackbars
  150 type C'TrackbarCallback
  151    =  Int32 -- ^ Current position of the specified trackbar.
  152    -> Ptr () -- ^ Optional pointer to user data.
  153    -> IO ()
  154 
  155 
  156 --------------------------------------------------------------------------------
  157 
  158 -- | Information about the storage requirements of values in C
  159 --
  160 -- This class assumes that the type @a@ is merely a symbol that corresponds with
  161 -- a type in C.
  162 class CSizeOf a where
  163     -- | Computes the storage requirements (in bytes) of values of
  164     -- type @a@ in C.
  165     cSizeOf :: proxy a -> Int
  166 
  167 instance CSizeOf C'Point2i where cSizeOf _proxy = c'sizeof_Point2i
  168 instance CSizeOf C'Point2f where cSizeOf _proxy = c'sizeof_Point2f
  169 instance CSizeOf C'Point2d where cSizeOf _proxy = c'sizeof_Point2d
  170 instance CSizeOf C'Point3i where cSizeOf _proxy = c'sizeof_Point3i
  171 instance CSizeOf C'Point3f where cSizeOf _proxy = c'sizeof_Point3f
  172 instance CSizeOf C'Point3d where cSizeOf _proxy = c'sizeof_Point3d
  173 instance CSizeOf C'Size2i  where cSizeOf _proxy = c'sizeof_Size2i
  174 instance CSizeOf C'Size2f  where cSizeOf _proxy = c'sizeof_Size2f
  175 instance CSizeOf C'Scalar  where cSizeOf _proxy = c'sizeof_Scalar
  176 instance CSizeOf C'Range   where cSizeOf _proxy = c'sizeof_Range
  177 instance CSizeOf C'Mat     where cSizeOf _proxy = c'sizeof_Mat
  178 
  179 -- | Equivalent type in C
  180 --
  181 -- Actually a proxy type in Haskell that stands for the equivalent type in C.
  182 type family C (a :: *) :: *
  183 
  184 type instance C (Maybe a) = C a
  185 
  186 -- | Mutable types have the same C equivalent as their unmutable variants.
  187 type instance C (Mut a s) = C a
  188 
  189 --------------------------------------------------------------------------------
  190 
  191 -- | Perform an IO action with a pointer to the C equivalent of a value
  192 class WithPtr a where
  193     -- | Perform an action with a temporary pointer to the underlying
  194     -- representation of @a@
  195     --
  196     -- The pointer is not guaranteed to be usuable outside the scope of this
  197     -- function. The same warnings apply as for 'withForeignPtr'.
  198     withPtr :: a -> (Ptr (C a) -> IO b) -> IO b
  199 
  200 -- | 'Nothing' is represented as a 'nullPtr'.
  201 instance (WithPtr a) => WithPtr (Maybe a) where
  202     withPtr Nothing    f = f nullPtr
  203     withPtr (Just obj) f = withPtr obj f
  204 
  205 -- | Mutable types use the same underlying representation as unmutable types.
  206 instance (WithPtr a) => WithPtr (Mut a s) where
  207     withPtr = withPtr . unMut
  208 
  209 --------------------------------------------------------------------------------
  210 
  211 -- | Types of which a value can be constructed from a pointer to the C
  212 -- equivalent of that value
  213 --
  214 -- Used to wrap values created in C.
  215 class FromPtr a where
  216     fromPtr :: IO (Ptr (C a)) -> IO a
  217 
  218 --------------------------------------------------------------------------------
  219 
  220 toCFloat :: Float -> CFloat
  221 toCFloat = realToFrac
  222 
  223 fromCFloat :: CFloat -> Float
  224 fromCFloat = realToFrac
  225 
  226 toCDouble :: Double -> CDouble
  227 toCDouble = realToFrac
  228 
  229 fromCDouble :: CDouble -> Double
  230 fromCDouble = realToFrac