{-# language CPP #-} {-# language QuasiQuotes #-} {-# language TemplateHaskell #-} #if __GLASGOW_HASKELL__ >= 800 {-# options_ghc -Wno-redundant-constraints #-} #endif module OpenCV.ImgProc.ObjectDetection ( MatchTemplateMethod(..) , MatchTemplateNormalisation(..) , matchTemplate ) where import "base" Data.Int import "base" Data.Word import "base" GHC.TypeLits import qualified "inline-c" Language.C.Inline as C import qualified "inline-c-cpp" Language.C.Inline.Cpp as C import "this" OpenCV.Core.Types import "this" OpenCV.Internal.C.Inline ( openCvCtx ) import "this" OpenCV.Internal.C.Types import "this" OpenCV.Internal.Core.Types.Mat import "this" OpenCV.Internal.Exception import "this" OpenCV.TypeLevel -------------------------------------------------------------------------------- C.context openCvCtx C.include "opencv2/core.hpp" C.include "opencv2/imgproc.hpp" C.include "opencv2/objdetect.hpp" C.using "namespace cv" #include #include "opencv2/core.hpp" #include "opencv2/imgproc.hpp" #include "namespace.hpp" #include "hsc_macros.hpp" -------------------------------------------------------------------------------- -- | data MatchTemplateMethod = MatchTemplateSqDiff -- ^ * not normed: <> -- * normed: <> | MatchTemplateCCorr -- ^ * not normed: <> -- * normed: <> | MatchTemplateCCoeff -- ^ * not normed: <> -- * where <> -- * normed: <> deriving Show -- | Whether to use normalisation. See 'MatchTemplateMethod'. data MatchTemplateNormalisation = MatchTemplateNotNormed | MatchTemplateNormed deriving (Show, Eq) #num CV_TM_SQDIFF #num CV_TM_SQDIFF_NORMED #num CV_TM_CCORR #num CV_TM_CCORR_NORMED #num CV_TM_CCOEFF #num CV_TM_CCOEFF_NORMED marshalMatchTemplateMethod :: MatchTemplateMethod -> Bool -> Int32 marshalMatchTemplateMethod m n = case (m, n) of (MatchTemplateSqDiff, False) -> c'CV_TM_SQDIFF (MatchTemplateSqDiff, True ) -> c'CV_TM_SQDIFF_NORMED (MatchTemplateCCorr , False) -> c'CV_TM_CCORR (MatchTemplateCCorr , True ) -> c'CV_TM_CCORR_NORMED (MatchTemplateCCoeff, False) -> c'CV_TM_CCOEFF (MatchTemplateCCoeff, True ) -> c'CV_TM_CCOEFF_NORMED -- | -- -- Compares a template against overlapped image regions. -- -- The function slides through image, compares the overlapped patches -- of size -- <> -- against templ using the specified method and stores the comparison -- results in result . Here are the formulae for the available -- comparison methods -- (<> denotes image, -- <> template, -- <> result). -- The summation is done over template and/or the image patch: -- <> matchTemplate :: ( depth `In` [Word8, Float] , Length searchShape <= 2 ) => Mat ('S searchShape) ('S 1) ('S depth) -- ^ Image where the search is running. It must be 8-bit or 32-bit floating-point. -> Mat ('S [th, tw]) ('S 1) ('S depth) -- ^ Searched template. It must be not greater than the source image and have the same data type. -> MatchTemplateMethod -- ^ Parameter specifying the comparison method. -> MatchTemplateNormalisation -- ^ Normalise -> CvExcept (Mat ('S [rh, rw]) ('S 1) ('S Float)) -- ^ Map of comparison results. It must be single-channel 32-bit floating-point. -- If image is -- <> -- and templ is -- <> -- , then result is -- <>. matchTemplate image templ method normalisation = unsafeWrapException $ do result <- newEmptyMat handleCvException (pure $ unsafeCoerceMat result) $ withPtr result $ \resultPtr -> withPtr image $ \imagePtr -> withPtr templ $ \templPtr -> [cvExcept| cv::matchTemplate( *$(Mat * imagePtr) , *$(Mat * templPtr) , *$(Mat * resultPtr) , $(int32_t c'method) ); |] where normed = case normalisation of MatchTemplateNotNormed -> False MatchTemplateNormed -> True c'method = marshalMatchTemplateMethod method normed