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

Safe HaskellNone
LanguageHaskell2010

OpenCV.Features2d

Contents

Synopsis

ORB

data Orb Source #

Instances

FromPtr Orb Source # 

Methods

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

WithPtr Orb Source # 

Methods

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

data WTA_K Source #

Constructors

WTA_K_2 
WTA_K_3 
WTA_K_4 

data OrbParams Source #

Constructors

OrbParams 

Fields

  • orb_nfeatures :: !Int32

    The maximum number of features to retain.

  • orb_scaleFactor :: !Float

    Pyramid decimation ratio, greater than 1. orb_scaleFactor == 2 means the classical pyramid, where each next level has 4x less pixels than the previous, but such a big scale factor will degrade feature matching scores dramatically. On the other hand, too close to 1 scale factor will mean that to cover certain scale range you will need more pyramid levels and so the speed will suffer.

  • orb_nlevels :: !Int32

    The number of pyramid levels. The smallest level will have linear size equal to input_image_linear_size / orb_scaleFactor ** orb_nlevels.

  • orb_edgeThreshold :: !Int32

    This is size of the border where the features are not detected. It should roughly match the patchSize parameter.

  • orb_firstLevel :: !Int32

    It should be 0 in the current implementation.

  • orb_WTA_K :: !WTA_K

    The number of points that produce each element of the oriented BRIEF descriptor. The default value WTA_K_2 means the BRIEF where we take a random point pair and compare their brightnesses, so we get 0/1 response. Other possible values are WTA_K_3 and WTA_K_4. For example, WTA_K_3 means that we take 3 random points (of course, those point coordinates are random, but they are generated from the pre-defined seed, so each element of BRIEF descriptor is computed deterministically from the pixel rectangle), find point of maximum brightness and output index of the winner (0, 1 or 2). Such output will occupy 2 bits, and therefore it will need a special variant of Hamming distance, denoted as Norm_Hamming2 (2 bits per bin). When WTA_K_4, we take 4 random points to compute each bin (that will also occupy 2 bits with possible values 0, 1, 2 or 3).

  • orb_scoreType :: !OrbScoreType

    The default HarrisScore means that Harris algorithm is used to rank features (the score is written to KeyPoint::score and is used to retain best nfeatures features); FastScore is alternative value of the parameter that produces slightly less stable keypoints, but it is a little faster to compute.

  • orb_patchSize :: !Int32

    Size of the patch used by the oriented BRIEF descriptor. Of course, on smaller pyramid layers the perceived image area covered by a feature will be larger.

  • orb_fastThreshold :: !Int32
     

orbDetectAndCompute Source #

Arguments

:: Orb 
-> Mat (S '[height, width]) channels depth

Image.

-> Maybe (Mat (S '[height, width]) (S 1) (S Word8))

Mask.

-> CvExcept (Vector KeyPoint, Mat D D D) 

Detect keypoints and compute descriptors

Example:

orbDetectAndComputeImg
    :: forall (width    :: Nat)
              (height   :: Nat)
              (channels :: Nat)
              (depth    :: *)
     . (Mat (ShapeT [height, width]) ('S channels) ('S depth) ~ Frog)
    => Mat (ShapeT [height, width]) ('S channels) ('S depth)
orbDetectAndComputeImg = exceptError $ do
    (kpts, _descs) <- orbDetectAndCompute orb frog Nothing
    withMatM (Proxy :: Proxy [height, width])
             (Proxy :: Proxy channels)
             (Proxy :: Proxy depth)
             white $ \imgM -> do
      void $ matCopyToM imgM (V2 0 0) frog Nothing
      forM_ kpts $ \kpt -> do
        let kptRec = keyPointAsRec kpt
        circle imgM (round <$> kptPoint kptRec :: V2 Int32) 5 blue 1 LineType_AA 0
  where
    orb = mkOrb defaultOrbParams

BLOB

data SimpleBlobDetectorParams Source #

Constructors

SimpleBlobDetectorParams 

Fields

blobDetect Source #

Arguments

:: SimpleBlobDetector 
-> Mat (S '[height, width]) channels depth

Image.

-> Maybe (Mat (S '[height, width]) (S 1) (S Word8))

Mask.

-> CvExcept (Vector KeyPoint) 

Detect keypoints and compute descriptors

DescriptorMatcher

class DescriptorMatcher a where Source #

Minimal complete definition

upcast

Methods

upcast :: a -> BaseMatcher Source #

add :: a -> Vector (Mat D D D) -> IO () Source #

train :: a -> IO () Source #

match :: a -> Mat D D D -> Mat D D D -> Maybe (Mat (S '[height, width]) (S 1) (S Word8)) -> IO (Vector DMatch) Source #

match' :: a -> Mat D D D -> Maybe (Mat (S '[height, width]) (S 1) (S Word8)) -> IO (Vector DMatch) Source #

Match in pre-trained matcher

Instances

DescriptorMatcher FlannBasedMatcher Source # 

Methods

upcast :: FlannBasedMatcher -> BaseMatcher Source #

add :: FlannBasedMatcher -> Vector (Mat (D [DS Nat]) (D Nat) (D *)) -> IO () Source #

train :: FlannBasedMatcher -> IO () Source #

match :: FlannBasedMatcher -> Mat (D [DS Nat]) (D Nat) (D *) -> Mat (D [DS Nat]) (D Nat) (D *) -> Maybe (Mat (S [DS Nat] ((DS Nat ': height) ((DS Nat ': width) [DS Nat]))) (S Nat 1) (S * Word8)) -> IO (Vector DMatch) Source #

match' :: FlannBasedMatcher -> Mat (D [DS Nat]) (D Nat) (D *) -> Maybe (Mat (S [DS Nat] ((DS Nat ': height) ((DS Nat ': width) [DS Nat]))) (S Nat 1) (S * Word8)) -> IO (Vector DMatch) Source #

DescriptorMatcher BFMatcher Source # 

Methods

upcast :: BFMatcher -> BaseMatcher Source #

add :: BFMatcher -> Vector (Mat (D [DS Nat]) (D Nat) (D *)) -> IO () Source #

train :: BFMatcher -> IO () Source #

match :: BFMatcher -> Mat (D [DS Nat]) (D Nat) (D *) -> Mat (D [DS Nat]) (D Nat) (D *) -> Maybe (Mat (S [DS Nat] ((DS Nat ': height) ((DS Nat ': width) [DS Nat]))) (S Nat 1) (S * Word8)) -> IO (Vector DMatch) Source #

match' :: BFMatcher -> Mat (D [DS Nat]) (D Nat) (D *) -> Maybe (Mat (S [DS Nat] ((DS Nat ': height) ((DS Nat ': width) [DS Nat]))) (S Nat 1) (S * Word8)) -> IO (Vector DMatch) Source #

drawMatches :: Mat (S '[height, width]) channels depth -> Vector KeyPoint -> Mat (S '[height, width]) channels depth -> Vector KeyPoint -> Vector DMatch -> DrawMatchesParams -> CvExcept (Mat (S '[D, D]) channels depth) Source #

BFMatcher

data BFMatcher Source #

Brute-force descriptor matcher

For each descriptor in the first set, this matcher finds the closest descriptor in the second set by trying each one. This descriptor matcher supports masking permissible matches of descriptor sets.

Example:

bfMatcherImg
    :: forall (width    :: Nat)
              (width2   :: Nat)
              (height   :: Nat)
              (channels :: Nat)
              (depth    :: *)
     . ( Mat (ShapeT [height, width]) ('S channels) ('S depth) ~ Frog
       , width2 ~ (*) width 2
       )
    => IO (Mat (ShapeT [height, width2]) ('S channels) ('S depth))
bfMatcherImg = do
    let (kpts1, descs1) = exceptError $ orbDetectAndCompute orb frog        Nothing
        (kpts2, descs2) = exceptError $ orbDetectAndCompute orb rotatedFrog Nothing

    bfmatcher <- newBFMatcher Norm_Hamming True
    matches <- match bfmatcher
                     descs1 -- Query descriptors
                     descs2 -- Train descriptors
                     Nothing
    exceptErrorIO $ pureExcept $
      withMatM (Proxy :: Proxy [height, width2])
               (Proxy :: Proxy channels)
               (Proxy :: Proxy depth)
               white $ \imgM -> do
        matCopyToM imgM (V2 0     0) frog        Nothing
        matCopyToM imgM (V2 width 0) rotatedFrog Nothing

        -- Draw the matches as lines from the query image to the train image.
        forM_ matches $ \dmatch -> do
          let matchRec = dmatchAsRec dmatch
              queryPt = kpts1 V.! fromIntegral (dmatchQueryIdx matchRec)
              trainPt = kpts2 V.! fromIntegral (dmatchTrainIdx matchRec)
              queryPtRec = keyPointAsRec queryPt
              trainPtRec = keyPointAsRec trainPt

          -- We translate the train point one width to the right in order to
          -- match the position of rotatedFrog in imgM.
          line imgM
               (round <$> kptPoint queryPtRec :: V2 Int32)
               ((round <$> kptPoint trainPtRec :: V2 Int32) ^+^ V2 width 0)
               blue 1 LineType_AA 0
  where
    orb = mkOrb defaultOrbParams {orb_nfeatures = 50}

    width = fromInteger $ natVal (Proxy :: Proxy width)

    rotatedFrog = exceptError $
                  warpAffine frog rotMat InterArea False False (BorderConstant black)
    rotMat = getRotationMatrix2D (V2 250 195 :: V2 CFloat) 45 0.8

OpenCV Sphinx doc

Instances

FromPtr BFMatcher Source # 

Methods

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

WithPtr BFMatcher Source # 

Methods

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

DescriptorMatcher BFMatcher Source # 

Methods

upcast :: BFMatcher -> BaseMatcher Source #

add :: BFMatcher -> Vector (Mat (D [DS Nat]) (D Nat) (D *)) -> IO () Source #

train :: BFMatcher -> IO () Source #

match :: BFMatcher -> Mat (D [DS Nat]) (D Nat) (D *) -> Mat (D [DS Nat]) (D Nat) (D *) -> Maybe (Mat (S [DS Nat] ((DS Nat ': height) ((DS Nat ': width) [DS Nat]))) (S Nat 1) (S * Word8)) -> IO (Vector DMatch) Source #

match' :: BFMatcher -> Mat (D [DS Nat]) (D Nat) (D *) -> Maybe (Mat (S [DS Nat] ((DS Nat ': height) ((DS Nat ': width) [DS Nat]))) (S Nat 1) (S * Word8)) -> IO (Vector DMatch) Source #

newBFMatcher Source #

Arguments

:: NormType

Norm_L1 and Norm_L2 norms are preferable choices for SIFT and SURF descriptors, Norm_Hamming should be used with Orb, BRISK and BRIEF, Norm_Hamming2 should be used with Orb when WTA_K_3 or WTA_K_4 (see orb_WTA_K).

-> Bool

If it is false, this is will be default BFMatcher behaviour when it finds the k nearest neighbors for each query descriptor. If crossCheck == True, then the knnMatch() method with k=1 will only return pairs (i,j) such that for i-th query descriptor the j-th descriptor in the matcher's collection is the nearest and vice versa, i.e. the BFMatcher will only return consistent pairs. Such technique usually produces best results with minimal number of outliers when there are enough matches. This is alternative to the ratio test, used by D. Lowe in SIFT paper.

-> IO BFMatcher 

FlannBasedMatcher

data FlannBasedMatcher Source #

Flann-based descriptor matcher.

This matcher trains flann::Index_ on a train descriptor collection and calls it nearest search methods to find the best matches. So, this matcher may be faster when matching a large train collection than the brute force matcher. FlannBasedMatcher does not support masking permissible matches of descriptor sets because flann::Index does not support this.

Example:

fbMatcherImg
    :: forall (width    :: Nat)
              (width2   :: Nat)
              (height   :: Nat)
              (channels :: Nat)
              (depth    :: *)
     . ( Mat (ShapeT [height, width]) ('S channels) ('S depth) ~ Frog
       , width2 ~ (*) width 2
       )
    => IO (Mat (ShapeT [height, width2]) ('S channels) ('S depth))
fbMatcherImg = do
    let (kpts1, descs1) = exceptError $ orbDetectAndCompute orb frog        Nothing
        (kpts2, descs2) = exceptError $ orbDetectAndCompute orb rotatedFrog Nothing

    fbmatcher <- newFlannBasedMatcher (def { indexParams = FlannLshIndexParams 20 10 2 })
    matches <- match fbmatcher
                     descs1 -- Query descriptors
                     descs2 -- Train descriptors
                     Nothing
    exceptErrorIO $ pureExcept $
      withMatM (Proxy :: Proxy [height, width2])
               (Proxy :: Proxy channels)
               (Proxy :: Proxy depth)
               white $ \imgM -> do
        matCopyToM imgM (V2 0     0) frog        Nothing
        matCopyToM imgM (V2 width 0) rotatedFrog Nothing

        -- Draw the matches as lines from the query image to the train image.
        forM_ matches $ \dmatch -> do
          let matchRec = dmatchAsRec dmatch
              queryPt = kpts1 V.! fromIntegral (dmatchQueryIdx matchRec)
              trainPt = kpts2 V.! fromIntegral (dmatchTrainIdx matchRec)
              queryPtRec = keyPointAsRec queryPt
              trainPtRec = keyPointAsRec trainPt

          -- We translate the train point one width to the right in order to
          -- match the position of rotatedFrog in imgM.
          line imgM
               (round <$> kptPoint queryPtRec :: V2 Int32)
               ((round <$> kptPoint trainPtRec :: V2 Int32) ^+^ V2 width 0)
               blue 1 LineType_AA 0
  where
    orb = mkOrb defaultOrbParams {orb_nfeatures = 50}

    width = fromInteger $ natVal (Proxy :: Proxy width)

    rotatedFrog = exceptError $
                  warpAffine frog rotMat InterArea False False (BorderConstant black)
    rotMat = getRotationMatrix2D (V2 250 195 :: V2 CFloat) 45 0.8

OpenCV Sphinx doc

Instances

FromPtr FlannBasedMatcher Source # 
WithPtr FlannBasedMatcher Source # 

Methods

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

DescriptorMatcher FlannBasedMatcher Source # 

Methods

upcast :: FlannBasedMatcher -> BaseMatcher Source #

add :: FlannBasedMatcher -> Vector (Mat (D [DS Nat]) (D Nat) (D *)) -> IO () Source #

train :: FlannBasedMatcher -> IO () Source #

match :: FlannBasedMatcher -> Mat (D [DS Nat]) (D Nat) (D *) -> Mat (D [DS Nat]) (D Nat) (D *) -> Maybe (Mat (S [DS Nat] ((DS Nat ': height) ((DS Nat ': width) [DS Nat]))) (S Nat 1) (S * Word8)) -> IO (Vector DMatch) Source #

match' :: FlannBasedMatcher -> Mat (D [DS Nat]) (D Nat) (D *) -> Maybe (Mat (S [DS Nat] ((DS Nat ': height) ((DS Nat ': width) [DS Nat]))) (S Nat 1) (S * Word8)) -> IO (Vector DMatch) Source #

data FlannSearchParams Source #

Constructors

FlannSearchParams 

Fields

Instances