| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
OpenCV.Extra.XFeatures2d
Contents
- data Surf
- data SurfParams = SurfParams {}
- defaultSurfParams :: SurfParams
- mkSurf :: SurfParams -> Surf
- surfDetectAndCompute :: Surf -> Mat (S [height, width]) channels depth -> Maybe (Mat (S [height, width]) (S 1) (S Word8)) -> CvExcept (Vector KeyPoint, Mat D D D)
SURF
data SurfParams Source #
Constructors
| SurfParams | |
Fields
| |
mkSurf :: SurfParams -> Surf Source #
Arguments
| :: Surf | |
| -> 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:
surfDetectAndComputeImg
:: 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)
surfDetectAndComputeImg = exceptError $ do
(kpts, _descs) <- surfDetectAndCompute surf 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
surf = mkSurf defaultSurfParams
