module OpenCV.Features2d
    ( 
      Orb
    , OrbScoreType(..)
    , WTA_K(..)
    , OrbParams(..)
    , defaultOrbParams
    , mkOrb
    , orbDetectAndCompute
      
    , SimpleBlobDetector
    , SimpleBlobDetectorParams(..)
    , BlobFilterByArea(..)
    , BlobFilterByCircularity(..)
    , BlobFilterByColor(..)
    , BlobFilterByConvexity(..)
    , BlobFilterByInertia(..)
    , defaultSimpleBlobDetectorParams
    , mkSimpleBlobDetector
    , blobDetect
      
    , DescriptorMatcher(..)
    , drawMatches
      
    , BFMatcher
    , newBFMatcher
      
    , FlannBasedMatcher
    , FlannIndexParams(..)
    , FlannSearchParams(..)
    , FlannBasedMatcherParams(..)
    , newFlannBasedMatcher
    ) where
import "base" Control.Exception ( mask_ )
import "base" Data.Int
import "base" Data.Word
import "base" Data.Maybe
import "base" Foreign.ForeignPtr ( ForeignPtr, withForeignPtr, castForeignPtr )
import "base" Foreign.Marshal.Alloc ( alloca )
import "base" Foreign.Marshal.Array ( peekArray )
import "base" Foreign.Marshal.Utils ( fromBool )
import "base" Foreign.Ptr ( Ptr, nullPtr )
import "base" Foreign.Storable ( peek )
import "base" System.IO.Unsafe ( unsafePerformIO )
import "data-default" Data.Default
import "linear" Linear.V4
import qualified "inline-c" Language.C.Inline as C
import qualified "inline-c" Language.C.Inline.Unsafe as CU
import qualified "inline-c-cpp" Language.C.Inline.Cpp as C
import "this" OpenCV.Core.Types
import "this" OpenCV.Internal
import "this" OpenCV.Internal.C.Inline ( openCvCtx )
import "this" OpenCV.Internal.C.Types
import "this" OpenCV.Internal.Core.ArrayOps
import "this" OpenCV.Internal.Core.Types ( withArrayPtr, Scalar )
import "this" OpenCV.Internal.Core.Types.Mat
import "this" OpenCV.Internal.Exception ( cvExcept, unsafeWrapException, handleCvException )
import "this" OpenCV.TypeLevel
import qualified "vector" Data.Vector as V
C.context openCvCtx
C.include "opencv2/core.hpp"
C.include "opencv2/features2d.hpp"
C.include "orb.hpp"
C.include "simple_blob_detector.hpp"
C.using "namespace cv"
C.using "namespace cv::flann"
infinity :: Float
infinity = 1 / 0
newtype Orb = Orb {unOrb :: ForeignPtr C'Ptr_ORB}
type instance C Orb = C'Ptr_ORB
instance WithPtr Orb where
    withPtr = withForeignPtr . unOrb
instance FromPtr Orb where
    fromPtr = objFromPtr Orb $ \ptr ->
                [CU.block| void {
                  cv::Ptr<cv::ORB> * orb_ptr_ptr = $(Ptr_ORB * ptr);
                  orb_ptr_ptr->release();
                  delete orb_ptr_ptr;
                }|]
data WTA_K
   = WTA_K_2
   | WTA_K_3
   | WTA_K_4
marshalWTA_K :: WTA_K -> Int32
marshalWTA_K = \case
    WTA_K_2 -> 2
    WTA_K_3 -> 3
    WTA_K_4 -> 4
data OrbScoreType
   = HarrisScore
   | FastScore
c'HARRIS_SCORE = 0
c'HARRIS_SCORE :: (Num a) => a
c'FAST_SCORE = 1
c'FAST_SCORE :: (Num a) => a
marshalOrbScoreType :: OrbScoreType -> Int32
marshalOrbScoreType = \case
    HarrisScore -> c'HARRIS_SCORE
    FastScore   -> c'FAST_SCORE
data OrbParams
   = OrbParams
     { orb_nfeatures :: !Int32
       
     , orb_scaleFactor :: !Float
       
       
       
       
       
       
     , orb_nlevels :: !Int32
       
       
       
     , orb_edgeThreshold :: !Int32
       
       
     , orb_firstLevel :: !Int32
       
     , orb_WTA_K :: !WTA_K
       
       
       
       
       
       
       
       
       
       
       
       
       
     , orb_scoreType :: !OrbScoreType
       
       
       
       
       
     , orb_patchSize :: !Int32
       
       
       
     , orb_fastThreshold :: !Int32
     }
defaultOrbParams :: OrbParams
defaultOrbParams =
    OrbParams
     { orb_nfeatures     = 500
     , orb_scaleFactor   = 1.2
     , orb_nlevels       = 8
     , orb_edgeThreshold = 31
     , orb_firstLevel    = 0
     , orb_WTA_K         = WTA_K_2
     , orb_scoreType     = HarrisScore
     , orb_patchSize     = 31
     , orb_fastThreshold = 20
     }
newOrb :: OrbParams -> IO Orb
newOrb OrbParams{..} = fromPtr
    [CU.block|Ptr_ORB * {
      cv::Ptr<cv::ORB> orbPtr =
        cv::ORB::create
        ( $(int32_t orb_nfeatures)
        , $(float   c'scaleFactor)
        , $(int32_t orb_nlevels)
        , $(int32_t orb_edgeThreshold)
        , $(int32_t orb_firstLevel)
        , $(int32_t c'WTA_K)
        , $(int32_t c'scoreType)
        , $(int32_t orb_patchSize)
        , $(int32_t orb_fastThreshold)
        );
      return new cv::Ptr<cv::ORB>(orbPtr);
    }|]
  where
    c'scaleFactor = realToFrac orb_scaleFactor
    c'WTA_K       = marshalWTA_K        orb_WTA_K
    c'scoreType   = marshalOrbScoreType orb_scoreType
mkOrb :: OrbParams -> Orb
mkOrb = unsafePerformIO . newOrb
orbDetectAndCompute
    :: Orb
    -> Mat ('S [height, width]) channels depth 
    -> Maybe (Mat ('S [height, width]) ('S 1) ('S Word8)) 
    -> CvExcept ( V.Vector KeyPoint
                , Mat 'D 'D 'D
                )
orbDetectAndCompute orb img mbMask = unsafeWrapException $ do
    descriptors <- newEmptyMat
    withPtr orb $ \orbPtr ->
      withPtr img $ \imgPtr ->
      withPtr mbMask $ \maskPtr ->
      withPtr descriptors $ \descPtr ->
      alloca $ \(numPtsPtr :: Ptr Int32) ->
      alloca $ \(arrayPtrPtr :: Ptr (Ptr (Ptr C'KeyPoint))) -> mask_ $ do
        ptrException <- [cvExcept|
          cv::ORB * orb = *$(Ptr_ORB * orbPtr);
          cv::Mat * maskPtr = $(Mat * maskPtr);
          std::vector<cv::KeyPoint> keypoints = std::vector<cv::KeyPoint>();
          orb->
            detectAndCompute
            ( *$(Mat * imgPtr)
            , maskPtr ? cv::_InputArray(*maskPtr) : cv::_InputArray(noArray())
            , keypoints
            , *$(Mat * descPtr)
            , false
            );
          *$(int32_t * numPtsPtr) = keypoints.size();
          cv::KeyPoint * * * arrayPtrPtr = $(KeyPoint * * * arrayPtrPtr);
          cv::KeyPoint * * arrayPtr = new cv::KeyPoint * [keypoints.size()];
          *arrayPtrPtr = arrayPtr;
          for (std::vector<cv::KeyPoint>::size_type ix = 0; ix != keypoints.size(); ix++)
          {
            cv::KeyPoint & org = keypoints[ix];
            cv::KeyPoint * newPt =
              new cv::KeyPoint( org.pt
                              , org.size
                              , org.angle
                              , org.response
                              , org.octave
                              , org.class_id
                              );
            arrayPtr[ix] = newPt;
          }
        |]
        if ptrException /= nullPtr
        then Left . BindingException <$> fromPtr (pure ptrException)
        else do
          numPts <- fromIntegral <$> peek numPtsPtr
          arrayPtr <- peek arrayPtrPtr
          keypoints <- mapM (fromPtr . pure) =<< peekArray numPts arrayPtr
          [CU.block| void {
            delete [] *$(KeyPoint * * * arrayPtrPtr);
          }|]
          pure $ Right (V.fromList keypoints, relaxMat descriptors)
newtype SimpleBlobDetector = SimpleBlobDetector {unSimpleBlobDetector :: ForeignPtr C'Ptr_SimpleBlobDetector}
type instance C SimpleBlobDetector = C'Ptr_SimpleBlobDetector
instance WithPtr SimpleBlobDetector where
    withPtr = withForeignPtr . unSimpleBlobDetector
instance FromPtr SimpleBlobDetector where
    fromPtr = objFromPtr SimpleBlobDetector $ \ptr ->
                [CU.block| void {
                  cv::Ptr<cv::SimpleBlobDetector> * simpleBlobDetector_ptr_ptr = $(Ptr_SimpleBlobDetector * ptr);
                  simpleBlobDetector_ptr_ptr->release();
                  delete simpleBlobDetector_ptr_ptr;
                }|]
data BlobFilterByArea
     = BlobFilterByArea
     { blob_minArea :: !Float
     , blob_maxArea :: !Float
     } deriving Eq
data BlobFilterByCircularity
     = BlobFilterByCircularity
     { blob_minCircularity :: !Float
     , blob_maxCircularity :: !Float
     } deriving Eq
data BlobFilterByColor
     = BlobFilterByColor
     { blob_blobColor :: !Word8
     } deriving Eq
data BlobFilterByConvexity
     = BlobFilterByConvexity
     { blob_minConvexity :: !Float
     , blob_maxConvexity :: !Float
     } deriving Eq
data BlobFilterByInertia
     = BlobFilterByInertia
     { blob_minInertiaRatio :: !Float
     , blob_maxInertiaRatio :: !Float
     } deriving Eq
data SimpleBlobDetectorParams
   = SimpleBlobDetectorParams
     { blob_minThreshold :: !Float
     , blob_maxThreshold :: !Float
     , blob_thresholdStep :: !Float
     , blob_minRepeatability :: !Int32
     , blob_minDistBetweenBlobs :: !Float
     , blob_filterByArea :: !(Maybe BlobFilterByArea)
       
       
     , blob_filterByCircularity :: !(Maybe BlobFilterByCircularity)
       
       
       
     , blob_filterByColor :: !(Maybe BlobFilterByColor)
       
       
       
       
     , blob_filterByConvexity :: !(Maybe BlobFilterByConvexity)
       
       
     , blob_filterByInertia :: !(Maybe BlobFilterByInertia)
       
       
     }
defaultSimpleBlobDetectorParams :: SimpleBlobDetectorParams
defaultSimpleBlobDetectorParams =
    SimpleBlobDetectorParams
    { blob_minThreshold = 50
    , blob_maxThreshold = 220
    , blob_thresholdStep = 10
    , blob_minRepeatability = 2
    , blob_minDistBetweenBlobs = 10
    , blob_filterByArea = Just (BlobFilterByArea 25 5000)
    , blob_filterByCircularity = Nothing
    , blob_filterByColor = Just (BlobFilterByColor 0)
    , blob_filterByConvexity = Just (BlobFilterByConvexity 0.95 infinity)
    , blob_filterByInertia = Just (BlobFilterByInertia 0.1 infinity)
    }
newSimpleBlobDetector :: SimpleBlobDetectorParams -> IO SimpleBlobDetector
newSimpleBlobDetector SimpleBlobDetectorParams{..} = fromPtr
    [CU.block|Ptr_SimpleBlobDetector * {
      cv::SimpleBlobDetector::Params params;
      params.blobColor           = $(unsigned char c'blobColor);
      params.filterByArea        = $(bool c'filterByArea);
      params.filterByCircularity = $(bool c'filterByCircularity);
      params.filterByColor       = $(bool c'filterByColor);
      params.filterByConvexity   = $(bool c'filterByConvexity);
      params.filterByInertia     = $(bool c'filterByInertia);
      params.maxArea             = $(float c'maxArea);
      params.maxCircularity      = $(float c'maxCircularity);
      params.maxConvexity        = $(float c'maxConvexity);
      params.maxInertiaRatio     = $(float c'maxInertiaRatio);
      params.maxThreshold        = $(float c'maxThreshold);
      params.minArea             = $(float c'minArea);
      params.minCircularity      = $(float c'minCircularity);
      params.minConvexity        = $(float c'minConvexity);
      params.minDistBetweenBlobs = $(float c'minDistBetweenBlobs);
      params.minInertiaRatio     = $(float c'minInertiaRatio);
      params.minRepeatability    = $(float c'minRepeatability);
      params.minThreshold        = $(float c'minThreshold);
      params.thresholdStep       = $(float c'thresholdStep);
      cv::Ptr<cv::SimpleBlobDetector> detectorPtr =
        cv::SimpleBlobDetector::create(params);
      return new cv::Ptr<cv::SimpleBlobDetector>(detectorPtr);
    }|]
  where
    c'minThreshold        = realToFrac blob_minThreshold
    c'maxThreshold        = realToFrac blob_maxThreshold
    c'thresholdStep       = realToFrac blob_thresholdStep
    c'minRepeatability    = realToFrac blob_minRepeatability
    c'minDistBetweenBlobs = realToFrac blob_minDistBetweenBlobs
    c'filterByArea        = fromBool (isJust blob_filterByArea)
    c'filterByCircularity = fromBool (isJust blob_filterByCircularity)
    c'filterByColor       = fromBool (isJust blob_filterByColor)
    c'filterByConvexity   = fromBool (isJust blob_filterByConvexity)
    c'filterByInertia     = fromBool (isJust blob_filterByInertia)
    c'minArea             = realToFrac (fromMaybe 25 (fmap blob_minArea blob_filterByArea))
    c'maxArea             = realToFrac (fromMaybe 5000 (fmap blob_maxArea blob_filterByArea))
    c'minCircularity      = realToFrac (fromMaybe 0.8 (fmap blob_minCircularity blob_filterByCircularity))
    c'maxCircularity      = realToFrac (fromMaybe infinity (fmap blob_maxCircularity blob_filterByCircularity))
    c'blobColor           = fromIntegral (fromMaybe 0 (fmap blob_blobColor blob_filterByColor))
    c'minConvexity        = realToFrac (fromMaybe 0.95 (fmap blob_minConvexity blob_filterByConvexity))
    c'maxConvexity        = realToFrac (fromMaybe infinity (fmap blob_maxConvexity blob_filterByConvexity))
    c'minInertiaRatio     = realToFrac (fromMaybe 0.1 (fmap blob_minInertiaRatio blob_filterByInertia))
    c'maxInertiaRatio     = realToFrac (fromMaybe infinity (fmap blob_maxInertiaRatio blob_filterByInertia))
mkSimpleBlobDetector :: SimpleBlobDetectorParams -> SimpleBlobDetector
mkSimpleBlobDetector = unsafePerformIO . newSimpleBlobDetector
blobDetect
    :: SimpleBlobDetector
    -> Mat ('S [height, width]) channels depth 
    -> Maybe (Mat ('S [height, width]) ('S 1) ('S Word8)) 
    -> CvExcept (V.Vector KeyPoint)
blobDetect detector img mbMask = unsafeWrapException $ do
    withPtr detector $ \detectorPtr ->
      withPtr img $ \imgPtr ->
      withPtr mbMask $ \maskPtr ->
      alloca $ \(numPtsPtr :: Ptr Int32) ->
      alloca $ \(arrayPtrPtr :: Ptr (Ptr (Ptr C'KeyPoint))) -> mask_ $ do
        ptrException <- [cvExcept|
          cv::SimpleBlobDetector * detector = *$(Ptr_SimpleBlobDetector * detectorPtr);
          cv::Mat * maskPtr = $(Mat * maskPtr);
          std::vector<cv::KeyPoint> keypoints = std::vector<cv::KeyPoint>();
          detector->
            detect
            ( *$(Mat * imgPtr)
            , keypoints
            , maskPtr ? cv::_InputArray(*maskPtr) : cv::_InputArray(noArray())
            );
          *$(int32_t * numPtsPtr) = keypoints.size();
          cv::KeyPoint * * * arrayPtrPtr = $(KeyPoint * * * arrayPtrPtr);
          cv::KeyPoint * * arrayPtr = new cv::KeyPoint * [keypoints.size()];
          *arrayPtrPtr = arrayPtr;
          for (std::vector<cv::KeyPoint>::size_type ix = 0; ix != keypoints.size(); ix++)
          {
            arrayPtr[ix] = new cv::KeyPoint(keypoints[ix]);
          }
        |]
        if ptrException /= nullPtr
        then Left . BindingException <$> fromPtr (pure ptrException)
        else do
          numPts <- fromIntegral <$> peek numPtsPtr
          arrayPtr <- peek arrayPtrPtr
          keypoints <- mapM (fromPtr . pure) =<< peekArray numPts arrayPtr
          [CU.block| void {
            delete [] *$(KeyPoint * * * arrayPtrPtr);
          }|]
          pure $ Right (V.fromList keypoints)
class DescriptorMatcher a where
    upcast :: a -> BaseMatcher
    add :: a
        -> V.Vector (Mat 'D 'D 'D) 
        -> IO ()
    add dm trainDescriptors =
        withPtr (upcast dm)           $ \dmPtr       ->
        withArrayPtr trainDescriptors $ \trainVecPtr ->
            [C.block| void {
                std::vector<Mat> buffer( $(Mat * trainVecPtr)
                                       , $(Mat * trainVecPtr) + $(int32_t c'trainVecLength) );
                $(DescriptorMatcher * dmPtr)->add(buffer);
            }|]
      where
        c'trainVecLength = fromIntegral $ V.length trainDescriptors
    train :: a
          -> IO ()
    train dm =
        withPtr (upcast dm) $ \dmPtr ->
            [C.block| void { $(DescriptorMatcher * dmPtr)->train(); } |]
    match
        :: a
        -> Mat 'D 'D 'D 
        -> Mat 'D 'D 'D 
        -> Maybe (Mat ('S [height, width]) ('S 1) ('S Word8))
           
           
        -> IO (V.Vector DMatch)
    match dm queryDescriptors trainDescriptors mbMask =
        withPtr (upcast dm)      $ \dmPtr    ->
        withPtr queryDescriptors $ \queryPtr ->
        withPtr trainDescriptors $ \trainPtr ->
        withPtr mbMask           $ \maskPtr  ->
        alloca $ \(numMatchesPtr :: Ptr Int32) ->
        alloca $ \(arrayPtrPtr :: Ptr (Ptr (Ptr C'DMatch))) -> mask_ $ do
            [C.block| void {
                cv::Mat * maskPtr = $(Mat * maskPtr);
                std::vector<cv::DMatch> matches = std::vector<cv::DMatch>();
                $(DescriptorMatcher * dmPtr)->match
                    ( *$(Mat * queryPtr)
                    , *$(Mat * trainPtr)
                    , matches
                    , maskPtr ? cv::_InputArray(*maskPtr) : cv::_InputArray(noArray())
                    );
                *$(int32_t * numMatchesPtr) = matches.size();
                cv::DMatch * * * arrayPtrPtr = $(DMatch * * * arrayPtrPtr);
                cv::DMatch * * arrayPtr = new cv::DMatch * [matches.size()];
                *arrayPtrPtr = arrayPtr;
                for (std::vector<cv::DMatch>::size_type ix = 0; ix != matches.size(); ix++)
                {
                    cv::DMatch & org = matches[ix];
                    cv::DMatch * newMatch =
                        new cv::DMatch( org.queryIdx
                                      , org.trainIdx
                                      , org.imgIdx
                                      , org.distance
                                      );
                    arrayPtr[ix] = newMatch;
                }
            }|]
            (numMatches :: Int) <- fromIntegral <$> peek numMatchesPtr
            arrayPtr <- peek arrayPtrPtr
            matches <- mapM (fromPtr . pure) =<< peekArray numMatches arrayPtr
            [CU.block| void {
                delete [] *$(DMatch * * * arrayPtrPtr);
            }|]
            pure $ V.fromList matches
    
    
    match'
        :: a
        -> Mat 'D 'D 'D 
        -> Maybe (Mat ('S [height, width]) ('S 1) ('S Word8))
           
           
        -> IO (V.Vector DMatch)
    match' dm queryDescriptors mbMask =
        withPtr (upcast dm)      $ \dmPtr    ->
        withPtr queryDescriptors $ \queryPtr ->
        withPtr mbMask           $ \maskPtr  ->
        alloca $ \(numMatchesPtr :: Ptr Int32) ->
        alloca $ \(arrayPtrPtr :: Ptr (Ptr (Ptr C'DMatch))) -> mask_ $ do
            [C.block| void {
                cv::Mat * maskPtr = $(Mat * maskPtr);
                std::vector<cv::DMatch> matches = std::vector<cv::DMatch>();
                $(DescriptorMatcher * dmPtr)->match
                    ( *$(Mat * queryPtr)
                    , matches
                    , maskPtr ? cv::_InputArray(*maskPtr) : cv::_InputArray(noArray())
                    );
                *$(int32_t * numMatchesPtr) = matches.size();
                cv::DMatch * * * arrayPtrPtr = $(DMatch * * * arrayPtrPtr);
                cv::DMatch * * arrayPtr = new cv::DMatch * [matches.size()];
                *arrayPtrPtr = arrayPtr;
                for (std::vector<cv::DMatch>::size_type ix = 0; ix != matches.size(); ix++)
                {
                    cv::DMatch & org = matches[ix];
                    cv::DMatch * newMatch =
                        new cv::DMatch( org.queryIdx
                                      , org.trainIdx
                                      , org.imgIdx
                                      , org.distance
                                      );
                    arrayPtr[ix] = newMatch;
                }
            }|]
            (numMatches :: Int) <- fromIntegral <$> peek numMatchesPtr
            arrayPtr <- peek arrayPtrPtr
            matches <- mapM (fromPtr . pure) =<< peekArray numMatches arrayPtr
            [CU.block| void {
                delete [] *$(DMatch * * * arrayPtrPtr);
            }|]
            pure $ V.fromList matches
newtype BaseMatcher = BaseMatcher {unBaseMatcher :: ForeignPtr C'DescriptorMatcher}
type instance C BaseMatcher = C'DescriptorMatcher
instance WithPtr BaseMatcher where
    withPtr = withForeignPtr . unBaseMatcher
newtype BFMatcher = BFMatcher {unBFMatcher :: ForeignPtr C'BFMatcher}
type instance C BFMatcher = C'BFMatcher
instance WithPtr BFMatcher where
    withPtr = withForeignPtr . unBFMatcher
instance FromPtr BFMatcher where
    fromPtr = objFromPtr BFMatcher $ \ptr ->
                [CU.exp| void { delete $(BFMatcher * ptr) }|]
newBFMatcher
    :: NormType
       
       
       
       
    -> Bool
       
       
       
       
       
       
       
       
       
    -> IO BFMatcher
newBFMatcher normType crossCheck = fromPtr
    [CU.exp|BFMatcher * {
      new cv::BFMatcher
          ( $(int32_t c'normType)
          , $(bool c'crossCheck)
          )
    }|]
  where
    c'normType = marshalNormType NormAbsolute normType
    c'crossCheck = fromBool crossCheck
instance DescriptorMatcher BFMatcher where
    upcast (BFMatcher ptr) = BaseMatcher $ castForeignPtr ptr
newtype FlannBasedMatcher = FlannBasedMatcher {unFlannBasedMatcher :: ForeignPtr C'FlannBasedMatcher}
type instance C FlannBasedMatcher = C'FlannBasedMatcher
instance WithPtr FlannBasedMatcher where
    withPtr = withForeignPtr . unFlannBasedMatcher
instance FromPtr FlannBasedMatcher where
    fromPtr = objFromPtr FlannBasedMatcher $ \ptr ->
                [CU.exp| void { delete $(FlannBasedMatcher * ptr) }|]
data FlannIndexParams = FlannKDTreeIndexParams { trees :: Int }
                      | FlannLshIndexParams { tableNumber :: Int, keySize :: Int, multiProbeLevel :: Int }
data FlannSearchParams = FlannSearchParams { checks :: Int, eps :: Float, sorted :: Bool }
data FlannBasedMatcherParams = FlannBasedMatcherParams
    { indexParams :: FlannIndexParams
    , searchParams :: FlannSearchParams
    }
instance Default FlannIndexParams where
    def = FlannKDTreeIndexParams { trees = 4 }
instance Default FlannSearchParams where
    def = FlannSearchParams { checks = 32, eps = 0, sorted = True }
instance Default FlannBasedMatcherParams where
    def = FlannBasedMatcherParams def def
marshalIndexParams :: FlannIndexParams -> Ptr ()
marshalIndexParams (FlannKDTreeIndexParams tree) = unsafePerformIO $
    [CU.exp| void* { new flann::KDTreeIndexParams($(int32_t c'tree)) } |]
    where c'tree = fromIntegral tree
marshalIndexParams (FlannLshIndexParams tableNumber keySize multiProbeLevel) = unsafePerformIO $
    [CU.exp| void* { new cv::flann::LshIndexParams($(int32_t c'tableNumber), $(int32_t c'keySize), $(int32_t c'multiProbeLevel)) } |]
    where c'tableNumber     = fromIntegral tableNumber
          c'keySize         = fromIntegral keySize
          c'multiProbeLevel = fromIntegral multiProbeLevel
marshallSearchParams :: FlannSearchParams -> Ptr ()
marshallSearchParams (FlannSearchParams checks eps sorted) = unsafePerformIO $
    [CU.exp| void* { new cv::flann::SearchParams($(int32_t c'checks), $(float c'eps), $(bool c'sorted)) } |]
    where c'checks = fromIntegral checks
          c'eps    = realToFrac eps
          c'sorted = fromBool sorted
newFlannBasedMatcher :: FlannBasedMatcherParams -> IO FlannBasedMatcher
newFlannBasedMatcher FlannBasedMatcherParams{..} = fromPtr
    [CU.exp|FlannBasedMatcher * {
      new cv::FlannBasedMatcher((flann::IndexParams*)($(void* c'indexParams)), (flann::SearchParams*)($(void* c'searchParams)))
    }|]
  where
    c'indexParams  = marshalIndexParams indexParams
    c'searchParams = marshallSearchParams searchParams
instance DescriptorMatcher FlannBasedMatcher where
    upcast (FlannBasedMatcher ptr) = BaseMatcher $ castForeignPtr ptr
data DrawMatchesParams = DrawMatchesParams
    { matchColor :: Scalar
    , singlePointColor :: Scalar
    
    , flags :: Int32
    }
instance Default DrawMatchesParams where
    def = DrawMatchesParams
        { matchColor = toScalar $ V4 (255::Double) 255 255 125
        , singlePointColor = toScalar $ V4 (255::Double) 255 255 125
        , flags = 0
        }
drawMatches :: Mat ('S [height, width]) channels depth
            -> V.Vector KeyPoint
            -> Mat ('S [height, width]) channels depth
            -> V.Vector KeyPoint
            -> V.Vector DMatch
            -> DrawMatchesParams
            -> CvExcept (Mat ('S ['D, 'D]) channels depth)
drawMatches img1 keypoints1 img2 keypoints2 matches1to2 (DrawMatchesParams{..}) = unsafeWrapException $ do
    outImg <- newEmptyMat
    handleCvException (pure $ unsafeCoerceMat outImg) $
        withPtr img1             $ \img1Ptr ->
        withArrayPtr keypoints1  $ \kps1Ptr ->
        withPtr img2             $ \img2Ptr ->
        withArrayPtr keypoints2  $ \kps2Ptr ->
        withArrayPtr matches1to2 $ \mt12Ptr ->
        withPtr outImg           $ \outImgPtr ->
            [cvExcept|
                std::vector<KeyPoint> kps1($(KeyPoint * kps1Ptr), $(KeyPoint * kps1Ptr) + $(int32_t c'kps1Length));
                std::vector<KeyPoint> kps2($(KeyPoint * kps2Ptr), $(KeyPoint * kps2Ptr) + $(int32_t c'kps2Length));
                std::vector<DMatch>   mt12($(DMatch * mt12Ptr),   $(DMatch * mt12Ptr) + $(int32_t c'matches1to2Length));
                drawMatches(
                    *$(Mat* img1Ptr),
                    kps1,
                    *$(Mat* img2Ptr),
                    kps2,
                    mt12,
                    *$(Mat* outImgPtr));
            |]
  where
    c'kps1Length = fromIntegral $ V.length keypoints1
    c'kps2Length = fromIntegral $ V.length keypoints2
    c'matches1to2Length = fromIntegral $ V.length matches1to2