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

Safe HaskellNone
LanguageHaskell2010

OpenCV.ImgProc.FeatureDetection

Synopsis

Documentation

canny Source #

Arguments

:: Double

First threshold for the hysteresis procedure.

-> Double

Second threshold for the hysteresis procedure.

-> Maybe Int32

Aperture size for the Sobel() operator. If not specified defaults to 3. Must be 3, 5 or 7.

-> CannyNorm

A flag, indicating whether to use the more accurate L2 norm or the default L1 norm.

-> Mat (S [h, w]) channels (S Word8)

8-bit input image.

-> CvExcept (Mat (S [h, w]) (S 1) (S Word8)) 

Finds edges in an image using the Canny86 algorithm.

Example:

cannyImg
    :: forall shape channels depth
     . (Mat shape channels depth ~ Lambda)
    => Mat shape ('S 1) depth
cannyImg = exceptError $
  canny 30 200 Nothing CannyNormL1 lambda

goodFeaturesToTrack Source #

Arguments

:: depth `In` [S Word8, S Float, D] 
=> Mat (S [h, w]) (S 1) depth

Input 8-bit or floating-point 32-bit, single-channel image.

-> Int32

Maximum number of corners to return. If there are more corners than are found, the strongest of them is returned.

-> Double

Parameter characterizing the minimal accepted quality of image corners. The parameter value is multiplied by the best corner quality measure, which is the minimal eigenvalue (see cornerMinEigenVal ) or the Harris function response (see cornerHarris ). The corners with the quality measure less than the product are rejected. For example, if the best corner has the quality measure = 1500, and the qualityLevel=0.01 , then all the corners with the quality measure less than 15 are rejected.

-> Double

Minimum possible Euclidean distance between the returned corners.

-> Maybe (Mat (S [h, w]) (S 1) (S Word8))

Optional region of interest. If the image is not empty (it needs to have the type CV_8UC1 and the same size as image ), it specifies the region in which the corners are detected.

-> Maybe Int32

Size of an average block for computing a derivative covariation matrix over each pixel neighborhood. See cornerEigenValsAndVecs.

-> GoodFeaturesToTrackDetectionMethod

Parameter indicating whether to use a Harris detector (see cornerHarris) or cornerMinEigenVal.

-> Vector (V2 Float) 

Determines strong corners on an image.

The function finds the most prominent corners in the image or in the specified image region.

  • Function calculates the corner quality measure at every source image pixel using the cornerMinEigenVal or cornerHarris.
  • Function performs a non-maximum suppression (the local maximums in 3 x 3 neighborhood are retained).
  • The corners with the minimal eigenvalue less than 𝚚𝚞𝚊𝚕𝚒𝚝𝚢𝙻𝚎𝚟𝚎𝚕 * max(x,y) qualityMeasureMap(x,y) are rejected.
  • The remaining corners are sorted by the quality measure in the descending order.
  • Function throws away each corner for which there is a stronger corner at a distance less than maxDistance.

Example:

goodFeaturesToTrackTraces
    :: 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)
goodFeaturesToTrackTraces = exceptError $ do
  imgG <- cvtColor bgr gray frog
  let features = goodFeaturesToTrack imgG 20 0.01 0.5 Nothing Nothing CornerMinEigenVal
  withMatM (Proxy :: Proxy [height, width])
           (Proxy :: Proxy channels)
           (Proxy :: Proxy depth)
           white $ \imgM -> do
    void $ matCopyToM imgM (V2 0 0) frog Nothing
    forM_ features $ \f -> do
      circle imgM (round <$> f :: V2 Int32) 2 blue 5 LineType_AA 0

houghCircles Source #

Arguments

:: Double

Inverse ratio of the accumulator resolution to the image resolution. For example, if dp=1, the accumulator has the same resolution as the input image. If dp=2, the accumulator has half as big width and height.

-> Double

Minimum distance between the centers of the detected circles. If the parameter is too small, multiple neighbor circles may be falsely detected in addition to a true one. If it is too large, some circles may be missed.

-> Maybe Double

The higher threshold of the two passed to the canny edge detector (the lower one is twice smaller). Default is 100.

-> Maybe Double

The accumulator threshold for the circle centers at the detection stage. The smaller it is, the more false circles may be detected. Circles, corresponding to the larger accumulator values, will be returned first. Default is 100.

-> Maybe Int32

Minimum circle radius.

-> Maybe Int32

Maximum circle radius.

-> Mat (S [h, w]) (S 1) (S Word8) 
-> Vector Circle 

Finds circles in a grayscale image using a modification of the Hough transformation.

Example:

houghCircleTraces
    :: forall (width    :: Nat)
              (height   :: Nat)
              (channels :: Nat)
              (depth    :: *)
     . (Mat (ShapeT [height, width]) ('S channels) ('S depth) ~ Circles_1000x625)
    => Mat (ShapeT [height, width]) ('S channels) ('S depth)
houghCircleTraces = exceptError $ do
  imgG <- cvtColor bgr gray circles_1000x625
  let circles = houghCircles 1 10 Nothing Nothing Nothing Nothing imgG
  withMatM (Proxy :: Proxy [height, width])
           (Proxy :: Proxy channels)
           (Proxy :: Proxy depth)
           white $ \imgM -> do
    void $ matCopyToM imgM (V2 0 0) circles_1000x625 Nothing
    forM_ circles $ \c -> do
      circle imgM (round <$> circleCenter c :: V2 Int32) (round (circleRadius c)) blue 1 LineType_AA 0

houghLinesP Source #

Arguments

:: PrimMonad m 
=> Double

Distance resolution of the accumulator in pixels.

-> Double

Angle resolution of the accumulator in radians.

-> Int32

Accumulator threshold parameter. Only those lines are returned that get enough votes (> threshold).

-> Maybe Double

Minimum line length. Line segments shorter than that are rejected.

-> Maybe Double

Maximum allowed gap between points on the same line to link them.

-> Mut (Mat (S [h, w]) (S 1) (S Word8)) (PrimState m)

Source image. May be modified by the function.

-> m (Vector (LineSegment Int32)) 

Example:

houghLinesPTraces
  :: forall (width    :: Nat)
            (height   :: Nat)
            (channels :: Nat)
            (depth    :: *  )
   . (Mat (ShapeT [height, width]) ('S channels) ('S depth) ~ Building_868x600)
  => Mat (ShapeT [height, width]) ('S channels) ('S depth)
houghLinesPTraces = exceptError $ do
    edgeImg <- canny 50 200 Nothing CannyNormL1 building_868x600
    edgeImgBgr <- cvtColor gray bgr edgeImg
    withMatM (Proxy :: Proxy [height, width])
             (Proxy :: Proxy channels)
             (Proxy :: Proxy depth)
             white $ \imgM -> do
      edgeImgM <- thaw edgeImg
      lineSegments <- houghLinesP 1 (pi / 180) 80 (Just 30) (Just 10) edgeImgM
      void $ matCopyToM imgM (V2 0 0) edgeImgBgr Nothing
      forM_ lineSegments $ \lineSegment -> do
        line imgM
             (lineSegmentStart lineSegment)
             (lineSegmentStop  lineSegment)
             red 2 LineType_8 0

data CannyNorm Source #

A flag, indicating whether to use the more accurate L2 norm or the default L1 norm.

Constructors

CannyNormL1 
CannyNormL2 

data Circle Source #

Constructors

Circle 

Instances

data LineSegment depth Source #

Constructors

LineSegment 

Fields

Instances

Functor LineSegment Source # 

Methods

fmap :: (a -> b) -> LineSegment a -> LineSegment b #

(<$) :: a -> LineSegment b -> LineSegment a #

Foldable LineSegment Source # 

Methods

fold :: Monoid m => LineSegment m -> m #

foldMap :: Monoid m => (a -> m) -> LineSegment a -> m #

foldr :: (a -> b -> b) -> b -> LineSegment a -> b #

foldr' :: (a -> b -> b) -> b -> LineSegment a -> b #

foldl :: (b -> a -> b) -> b -> LineSegment a -> b #

foldl' :: (b -> a -> b) -> b -> LineSegment a -> b #

foldr1 :: (a -> a -> a) -> LineSegment a -> a #

foldl1 :: (a -> a -> a) -> LineSegment a -> a #

toList :: LineSegment a -> [a] #

null :: LineSegment a -> Bool #

length :: LineSegment a -> Int #

elem :: Eq a => a -> LineSegment a -> Bool #

maximum :: Ord a => LineSegment a -> a #

minimum :: Ord a => LineSegment a -> a #

sum :: Num a => LineSegment a -> a #

product :: Num a => LineSegment a -> a #

Traversable LineSegment Source # 

Methods

traverse :: Applicative f => (a -> f b) -> LineSegment a -> f (LineSegment b) #

sequenceA :: Applicative f => LineSegment (f a) -> f (LineSegment a) #

mapM :: Monad m => (a -> m b) -> LineSegment a -> m (LineSegment b) #

sequence :: Monad m => LineSegment (m a) -> m (LineSegment a) #

IsVec V4 depth => IsVec LineSegment depth Source # 
Show depth => Show (LineSegment depth) Source # 

Methods

showsPrec :: Int -> LineSegment depth -> ShowS #

show :: LineSegment depth -> String #

showList :: [LineSegment depth] -> ShowS #

type VecDim LineSegment Source #