never executed always true always false
    1 {-# language CPP #-}
    2 {-# language QuasiQuotes #-}
    3 {-# language TemplateHaskell #-}
    4 
    5 #if __GLASGOW_HASKELL__ >= 800
    6 {-# options_ghc -Wno-redundant-constraints #-}
    7 #endif
    8 
    9 module OpenCV.ImgProc.MiscImgTransform
   10     ( -- * Color conversion
   11       cvtColor
   12     , module OpenCV.ImgProc.MiscImgTransform.ColorCodes
   13 
   14       -- * Flood filling
   15     , floodFill
   16     , FloodFillOperationFlags(..)
   17     , defaultFloodFillOperationFlags
   18 
   19       -- * Thresholding
   20     , ThreshType(..)
   21     , ThreshValue(..)
   22     , threshold
   23 
   24       -- * Watershed
   25     , watershed
   26 
   27       -- * GrabCut
   28     , GrabCutOperationMode(..)
   29     , grabCut
   30 
   31       -- * In range
   32     , inRange
   33     ) where
   34 
   35 import "base" Data.Bits
   36 import "base" Data.Int
   37 import "base" Data.Proxy ( Proxy(..) )
   38 import "base" Data.Word
   39 import "base" Foreign.Marshal.Alloc ( alloca )
   40 import "base" Foreign.Storable ( peek )
   41 import "base" GHC.TypeLits
   42 import "primitive" Control.Monad.Primitive ( PrimMonad, PrimState, unsafePrimToPrim )
   43 import qualified "inline-c" Language.C.Inline as C
   44 import qualified "inline-c-cpp" Language.C.Inline.Cpp as C
   45 import "linear" Linear.V4 ( V4 )
   46 import "this" OpenCV.Core.Types
   47 import "this" OpenCV.ImgProc.MiscImgTransform.ColorCodes
   48 import "this" OpenCV.Internal.C.Inline ( openCvCtx )
   49 import "this" OpenCV.Internal.C.Types
   50 import "this" OpenCV.Internal.Exception
   51 import "this" OpenCV.Internal.Core.Types.Mat
   52 import "this" OpenCV.Internal.ImgProc.MiscImgTransform
   53 import "this" OpenCV.Internal.ImgProc.MiscImgTransform.TypeLevel
   54 import "this" OpenCV.Internal.ImgProc.MiscImgTransform.ColorCodes ( colorConversionCode )
   55 import "this" OpenCV.TypeLevel
   56 
   57 --------------------------------------------------------------------------------
   58 
   59 C.context openCvCtx
   60 
   61 C.include "opencv2/core.hpp"
   62 C.include "opencv2/imgproc.hpp"
   63 C.using "namespace cv"
   64 
   65 --------------------------------------------------------------------------------
   66 
   67 -- ignore next Haddock code block, because of the hash sign in the link at the end of the comment.
   68 {- | Converts an image from one color space to another
   69 
   70 The function converts an input image from one color space to
   71 another. In case of a transformation to-from RGB color space, the
   72 order of the channels should be specified explicitly (RGB or
   73 BGR). Note that the default color format in OpenCV is often
   74 referred to as RGB but it is actually BGR (the bytes are
   75 reversed). So the first byte in a standard (24-bit) color image
   76 will be an 8-bit Blue component, the second byte will be Green, and
   77 the third byte will be Red. The fourth, fifth, and sixth bytes
   78 would then be the second pixel (Blue, then Green, then Red), and so
   79 on.
   80 
   81 The conventional ranges for R, G, and B channel values are:
   82 
   83   * 0 to 255 for 'Word8' images
   84 
   85   * 0 to 65535 for 'Word16' images
   86 
   87   * 0 to 1 for 'Float' images
   88 
   89 In case of linear transformations, the range does not matter. But
   90 in case of a non-linear transformation, an input RGB image should
   91 be normalized to the proper value range to get the correct results,
   92 for example, for RGB to L*u*v* transformation. For example, if you
   93 have a 32-bit floating-point image directly converted from an 8-bit
   94 image without any scaling, then it will have the 0..255 value range
   95 instead of 0..1 assumed by the function. So, before calling
   96 'cvtColor', you need first to scale the image down:
   97 
   98 >  cvtColor (img * 1/255) 'ColorConvBGR2Luv'
   99 
  100 If you use 'cvtColor' with 8-bit images, the conversion will have
  101 some information lost. For many applications, this will not be
  102 noticeable but it is recommended to use 32-bit images in
  103 applications that need the full range of colors or that convert an
  104 image before an operation and then convert back.
  105 
  106 If conversion adds the alpha channel, its value will set to the
  107 maximum of corresponding channel range: 255 for 'Word8', 65535 for
  108 'Word16', 1 for 'Float'.
  109 
  110 Example:
  111 
  112 @
  113 cvtColorImg
  114     :: forall (width    :: Nat)
  115               (width2   :: Nat)
  116               (height   :: Nat)
  117               (channels :: Nat)
  118               (depth    :: *)
  119      . ( Mat (ShapeT [height, width]) ('S channels) ('S depth) ~ Kodak_512x341
  120        , width2 ~ (width + width)
  121        )
  122     => Mat (ShapeT [height, width2]) ('S channels) ('S depth)
  123 cvtColorImg = exceptError $
  124     withMatM ((Proxy :: Proxy height) ::: (Proxy :: Proxy width2) ::: Z)
  125              (Proxy :: Proxy channels)
  126              (Proxy :: Proxy depth)
  127              white $ \\imgM -> do
  128       birds_gray <- pureExcept $   cvtColor gray bgr
  129                                =<< cvtColor bgr gray birds_512x341
  130       matCopyToM imgM (V2 0 0) birds_512x341 Nothing
  131       matCopyToM imgM (V2 w 0) birds_gray    Nothing
  132       lift $ arrowedLine imgM (V2 startX midY) (V2 pointX midY) red 4 LineType_8 0 0.15
  133   where
  134     h, w :: Int32
  135     h = fromInteger $ natVal (Proxy :: Proxy height)
  136     w = fromInteger $ natVal (Proxy :: Proxy width)
  137 
  138     startX, pointX :: Int32
  139     startX = round $ fromIntegral w * (0.95 :: Double)
  140     pointX = round $ fromIntegral w * (1.05 :: Double)
  141     midY = h \`div\` 2
  142 @
  143 
  144 <<doc/generated/examples/cvtColorImg.png cvtColorImg>>
  145 
  146 <http://goo.gl/3rfrhu OpenCV Sphinx Doc>
  147 -}
  148 
  149 -- the link avove is minified because it includes a hash, which the CPP tries to parse and fails
  150 
  151 -- TODO (RvD): Allow value level color codes
  152 -- Allow statically unknown color codes: fromColor :: DS ColorCode
  153 cvtColor :: forall (fromColor   :: ColorCode)
  154                    (toColor     :: ColorCode)
  155                    (shape       :: DS [DS Nat])
  156                    (srcChannels :: DS Nat)
  157                    (dstChannels :: DS Nat)
  158                    (srcDepth    :: DS *)
  159                    (dstDepth    :: DS *)
  160           . ( ColorConversion fromColor toColor
  161             , ColorCodeMatchesChannels fromColor srcChannels
  162             , dstChannels ~ 'S (ColorCodeChannels toColor)
  163             , srcDepth `In` ['D, 'S Word8, 'S Word16, 'S Float]
  164             , dstDepth ~ ColorCodeDepth fromColor toColor srcDepth
  165             )
  166          => Proxy fromColor -- ^ Convert from 'ColorCode'. Make sure the source image has this 'ColorCode'
  167          -> Proxy toColor   -- ^ Convert to 'ColorCode'.
  168          -> Mat shape srcChannels srcDepth -- ^ Source image
  169          -> CvExcept (Mat shape dstChannels dstDepth)
  170 cvtColor fromColor toColor src = unsafeWrapException $ do
  171     dst <- newEmptyMat
  172     handleCvException (pure $ unsafeCoerceMat dst) $
  173       withPtr src $ \srcPtr ->
  174       withPtr dst $ \dstPtr ->
  175         [cvExcept|
  176           cv::cvtColor( *$(Mat * srcPtr)
  177                       , *$(Mat * dstPtr)
  178                       , $(int32_t c'code)
  179                       , 0
  180                       );
  181         |]
  182   where
  183     c'code = colorConversionCode fromColor toColor
  184 
  185 {- | The function 'floodFill' fills a connected component starting from the seed point with the specified color.
  186 
  187 The connectivity is determined by the color/brightness closeness of the neighbor pixels. See the OpenCV
  188 documentation for details on the algorithm.
  189 
  190 Example:
  191 
  192 @
  193 floodFillImg
  194     :: forall (width    :: Nat)
  195               (width2   :: Nat)
  196               (height   :: Nat)
  197               (channels :: Nat)
  198               (depth    :: *)
  199      . ( Mat (ShapeT [height, width]) ('S channels) ('S depth) ~ Kodak_768x512
  200        , width2 ~ (width + width)
  201        )
  202     => Mat (ShapeT [height, width2]) ('S channels) ('S depth)
  203 floodFillImg = exceptError $
  204     withMatM ((Proxy :: Proxy height) ::: (Proxy :: Proxy width2) ::: Z)
  205              (Proxy :: Proxy channels)
  206              (Proxy :: Proxy depth)
  207              white $ \\imgM -> do
  208       sailboatEvening_768x512 <- thaw sailboat_768x512
  209       mask <- mkMatM (Proxy :: Proxy [height + 2, width + 2])
  210                      (Proxy :: Proxy 1)
  211                      (Proxy :: Proxy Word8)
  212                      black
  213       circle mask (V2 450 120 :: V2 Int32) 45 white (-1) LineType_AA 0
  214       rect <- floodFill sailboatEvening_768x512 (Just mask) seedPoint eveningRed (Just tolerance) (Just tolerance) defaultFloodFillOperationFlags
  215       rectangle sailboatEvening_768x512 rect blue 2 LineType_8 0
  216       frozenSailboatEvening_768x512 <- freeze sailboatEvening_768x512
  217       matCopyToM imgM (V2 0 0) sailboat_768x512 Nothing
  218       matCopyToM imgM (V2 w 0) frozenSailboatEvening_768x512 Nothing
  219       lift $ arrowedLine imgM (V2 startX midY) (V2 pointX midY) red 4 LineType_8 0 0.15
  220   where
  221     h, w :: Int32
  222     h = fromInteger $ natVal (Proxy :: Proxy height)
  223     w = fromInteger $ natVal (Proxy :: Proxy width)
  224 
  225     startX, pointX :: Int32
  226     startX = round $ fromIntegral w * (0.95 :: Double)
  227     pointX = round $ fromIntegral w * (1.05 :: Double)
  228 
  229     midY = h \`div\` 2
  230 
  231     seedPoint :: V2 Int32
  232     seedPoint = V2 100 50
  233 
  234     eveningRed :: V4 Double
  235     eveningRed = V4 0 100 200 255
  236 
  237     tolerance :: V4 Double
  238     tolerance = pure 7
  239 @
  240 
  241 <<doc/generated/examples/floodFillImg.png floodFillImg>>
  242 
  243 <http://goo.gl/9XIIne OpenCV Sphinx Doc>
  244 -}
  245 floodFill
  246     :: ( PrimMonad m
  247        , channels `In` '[ 'S 1, 'S 3 ]
  248        , depth `In` '[ 'D, 'S Word8, 'S Float, 'S Double ]
  249        , IsPoint2 point2 Int32
  250        , ToScalar color
  251        )
  252     => Mut (Mat shape channels depth) (PrimState m)
  253         -- ^ Input/output 1- or 3-channel, 8-bit, or floating-point image. It is modified by the function unless the FLOODFILL_MASK_ONLY flag is set.
  254     -> Maybe (Mut (Mat (WidthAndHeightPlusTwo shape) ('S 1) ('S Word8)) (PrimState m))
  255         -- ^ Operation mask that should be a single-channel 8-bit image, 2 pixels wider and 2 pixels taller than image. Since this is both an input and output parameter, you must take responsibility of initializing it. Flood-filling cannot go across non-zero pixels in the input mask. For example, an edge detector output can be used as a mask to stop filling at edges. On output, pixels in the mask corresponding to filled pixels in the image are set to 1 or to the a value specified in flags as described below. It is therefore possible to use the same mask in multiple calls to the function to make sure the filled areas do not overlap.
  256         -- Note: Since the mask is larger than the filled image, a pixel  (x, y) in image corresponds to the pixel  (x+1, y+1) in the mask.
  257     -> point2 Int32
  258         -- ^ Starting point.
  259     -> color
  260         -- ^ New value of the repainted domain pixels.
  261     -> Maybe color
  262         -- ^ Maximal lower brightness/color difference between the currently observed pixel and one of its neighbors belonging to the component, or a seed pixel being added to the component. Zero by default.
  263     -> Maybe color
  264         -- ^ Maximal upper brightness/color difference between the currently observed pixel and one of its neighbors belonging to the component, or a seed pixel being added to the component. Zero by default.
  265     -> FloodFillOperationFlags
  266     -> m Rect2i
  267 floodFill img mbMask seedPoint color mLoDiff mUpDiff opFlags =
  268     unsafePrimToPrim $
  269     withPtr img $ \matPtr ->
  270     withPtr mbMask $ \maskPtr ->
  271     withPtr (toPoint seedPoint) $ \seedPointPtr ->
  272     withPtr (toScalar color) $ \colorPtr ->
  273     withPtr loDiff $ \loDiffPtr ->
  274     withPtr upDiff $ \upDiffPtr ->
  275     withPtr rect $ \rectPtr -> do
  276       [C.block|void {
  277         cv::Mat * maskPtr = $(Mat * maskPtr);
  278         cv::floodFill( *$(Mat * matPtr)
  279                      , maskPtr ? cv::_InputOutputArray(*maskPtr) : cv::_InputOutputArray(noArray())
  280                      , *$(Point2i * seedPointPtr)
  281                      , *$(Scalar * colorPtr)
  282                      , $(Rect2i * rectPtr)
  283                      , *$(Scalar * loDiffPtr)
  284                      , *$(Scalar * upDiffPtr)
  285                      , $(int32_t c'opFlags)
  286                      );
  287       }|]
  288       pure rect
  289   where
  290     rect :: Rect2i
  291     rect = toRect HRect{ hRectTopLeft = pure 0
  292                        , hRectSize    = pure 0
  293                        }
  294     c'opFlags = marshalFloodFillOperationFlags opFlags
  295     zeroScalar = toScalar (pure 0 :: V4 Double)
  296     loDiff = maybe zeroScalar toScalar mLoDiff
  297     upDiff = maybe zeroScalar toScalar mUpDiff
  298 
  299 data FloodFillOperationFlags
  300    = FloodFillOperationFlags
  301    { floodFillConnectivity :: Word8
  302       -- ^ Connectivity value. The default value of 4 means that only the four nearest neighbor pixels (those that share
  303       -- an edge) are considered. A connectivity value of 8 means that the eight nearest neighbor pixels (those that share
  304       -- a corner) will be considered.
  305    , floodFillMaskFillColor :: Word8
  306       -- ^ Value between 1 and 255 with which to fill the mask (the default value is 1).
  307    , floodFillFixedRange :: Bool
  308       -- ^ If set, the difference between the current pixel and seed pixel is considered. Otherwise, the difference
  309       -- between neighbor pixels is considered (that is, the range is floating).
  310    , floodFillMaskOnly :: Bool
  311       -- ^ If set, the function does not change the image ( newVal is ignored), and only fills the mask with the
  312       -- value specified in bits 8-16 of flags as described above. This option only make sense in function variants
  313       -- that have the mask parameter.
  314    }
  315 
  316 defaultFloodFillOperationFlags :: FloodFillOperationFlags
  317 defaultFloodFillOperationFlags =
  318     FloodFillOperationFlags
  319     { floodFillConnectivity = 4
  320     , floodFillMaskFillColor = 1
  321     , floodFillFixedRange = False
  322     , floodFillMaskOnly = False
  323     }
  324 
  325 marshalFloodFillOperationFlags :: FloodFillOperationFlags -> Int32
  326 marshalFloodFillOperationFlags opFlags =
  327     let connectivityBits = fromIntegral (floodFillConnectivity opFlags)
  328         maskFillColorBits = fromIntegral (floodFillMaskFillColor opFlags) `shiftL` 8
  329         fixedRangeBits = if floodFillFixedRange opFlags then c'FLOODFILL_FIXED_RANGE else 0
  330         fillMaskOnlyBits = if floodFillMaskOnly opFlags then c'FLOODFILL_MASK_ONLY else 0
  331     in connectivityBits .|. maskFillColorBits .|. fixedRangeBits .|. fillMaskOnlyBits
  332 
  333 -- TODO (RvD): Otsu and triangle are only implemented for 8 bit images.
  334 
  335 {- | Applies a fixed-level threshold to each array element
  336 
  337 The function applies fixed-level thresholding to a single-channel array. The
  338 function is typically used to get a bi-level (binary) image out of a
  339 grayscale image or for removing a noise, that is, filtering out pixels with
  340 too small or too large values. There are several types of thresholding
  341 supported by the function.
  342 
  343 Example:
  344 
  345 @
  346 grayBirds :: Mat (ShapeT [341, 512]) ('S 1) ('S Word8)
  347 grayBirds = exceptError $ cvtColor bgr gray birds_512x341
  348 
  349 threshBinaryBirds :: Mat (ShapeT [341, 512]) ('S 3) ('S Word8)
  350 threshBinaryBirds =
  351     exceptError $ cvtColor gray bgr $ fst $ exceptError $
  352     threshold (ThreshVal_Abs 100) (Thresh_Binary 150) grayBirds
  353 
  354 threshBinaryInvBirds :: Mat (ShapeT [341, 512]) ('S 3) ('S Word8)
  355 threshBinaryInvBirds =
  356     exceptError $ cvtColor gray bgr $ fst $ exceptError $
  357     threshold (ThreshVal_Abs 100) (Thresh_BinaryInv 150) grayBirds
  358 
  359 threshTruncateBirds :: Mat (ShapeT [341, 512]) ('S 3) ('S Word8)
  360 threshTruncateBirds =
  361     exceptError $ cvtColor gray bgr $ fst $ exceptError $
  362     threshold (ThreshVal_Abs 100) Thresh_Truncate grayBirds
  363 
  364 threshToZeroBirds :: Mat (ShapeT [341, 512]) ('S 3) ('S Word8)
  365 threshToZeroBirds =
  366     exceptError $ cvtColor gray bgr $ fst $ exceptError $
  367     threshold (ThreshVal_Abs 100) Thresh_ToZero grayBirds
  368 
  369 threshToZeroInvBirds :: Mat (ShapeT [341, 512]) ('S 3) ('S Word8)
  370 threshToZeroInvBirds =
  371     exceptError $ cvtColor gray bgr $ fst $ exceptError $
  372     threshold (ThreshVal_Abs 100) Thresh_ToZeroInv grayBirds
  373 @
  374 
  375 <<doc/generated/examples/threshBinaryBirds.png threshBinaryBirds>>
  376 <<doc/generated/examples/threshBinaryInvBirds.png threshBinaryInvBirds>>
  377 <<doc/generated/examples/threshTruncateBirds.png threshTruncateBirds>>
  378 <<doc/generated/examples/threshToZeroBirds.png threshToZeroBirds>>
  379 <<doc/generated/examples/threshToZeroInvBirds.png threshToZeroInvBirds>>
  380 
  381 <http://docs.opencv.org/3.0-last-rst/modules/imgproc/doc/miscellaneous_transformations.html#threshold OpenCV Sphinx doc>
  382 -}
  383 threshold
  384     :: (depth `In` [Word8, Float])
  385     => ThreshValue -- ^
  386     -> ThreshType
  387     -> (Mat shape ('S 1) ('S depth))
  388     -> CvExcept (Mat shape ('S 1) ('S depth), Double)
  389 threshold threshVal threshType src = unsafeWrapException $ do
  390     dst <- newEmptyMat
  391     alloca $ \calcThreshPtr ->
  392       handleCvException ((unsafeCoerceMat dst, ) . realToFrac <$> peek calcThreshPtr) $
  393       withPtr src $ \srcPtr ->
  394       withPtr dst $ \dstPtr ->
  395         [cvExcept|
  396           *$(double * calcThreshPtr) =
  397             cv::threshold( *$(Mat * srcPtr)
  398                          , *$(Mat * dstPtr)
  399                          , $(double c'threshVal)
  400                          , $(double c'maxVal)
  401                          , $(int32_t c'type)
  402                          );
  403         |]
  404   where
  405     c'type = c'threshType .|. c'threshValMode
  406     (c'threshType, c'maxVal) = marshalThreshType threshType
  407     (c'threshValMode, c'threshVal) = marshalThreshValue threshVal
  408 
  409 
  410 {- | Performs a marker-based image segmentation using the watershed algorithm.
  411 
  412 The function implements one of the variants of watershed, non-parametric marker-based segmentation algorithm, described in [Meyer, F. Color Image Segmentation, ICIP92, 1992].
  413 
  414 Before passing the image to the function, you have to roughly outline the desired regions in the image markers with positive (>0) indices. So, every region is represented as one or more connected components with the pixel values 1, 2, 3, and so on. Such markers can be retrieved from a binary mask using 'findContours' and 'drawContours'. The markers are “seeds” of the future image regions. All the other pixels in markers , whose relation to the outlined regions is not known and should be defined by the algorithm, should be set to 0’s. In the function output, each pixel in markers is set to a value of the “seed” components or to -1 at boundaries between the regions.
  415 
  416 <http://docs.opencv.org/3.0-last-rst/modules/imgproc/doc/miscellaneous_transformations.html#watershed OpenCV Sphinx doc>
  417 -}
  418 watershed
  419   :: (PrimMonad m)
  420   => Mat ('S [h, w]) ('S 3) ('S Word8) -- ^ Input 8-bit 3-channel image
  421   -> Mut (Mat ('S [h, w]) ('S 1) ('S Int32)) (PrimState m) -- ^ Input/output 32-bit single-channel image (map) of markers
  422   -> CvExceptT m ()
  423 watershed img markers =
  424     unsafePrimToPrim $
  425     withPtr img $ \imgPtr ->
  426     withPtr markers $ \markersPtr ->
  427       [C.exp|void {
  428         cv::watershed( *$(Mat * imgPtr)
  429                      , *$(Mat * markersPtr)
  430                      )
  431       }|]
  432 
  433 {- | Runs the <http://docs.opencv.org/3.0-last-rst/modules/imgproc/doc/miscellaneous_transformations.html#grabcut GrabCut> algorithm.
  434 
  435 Example:
  436 
  437 @
  438 grabCutBird :: Kodak_512x341
  439 grabCutBird = exceptError $ do
  440     mask <- withMatM (Proxy :: Proxy [341, 512])
  441                      (Proxy :: Proxy 1)
  442                      (Proxy :: Proxy Word8)
  443                      black $ \\mask -> do
  444       fgTmp <- mkMatM (Proxy :: Proxy [1, 65]) (Proxy :: Proxy 1) (Proxy :: Proxy Double) black
  445       bgTmp <- mkMatM (Proxy :: Proxy [1, 65]) (Proxy :: Proxy 1) (Proxy :: Proxy Double) black
  446       grabCut birds_512x341 mask fgTmp bgTmp 5 (GrabCut_InitWithRect rect)
  447     mask' <- matScalarCompare mask 3 Cmp_Ge
  448     withMatM (Proxy :: Proxy [341, 512])
  449              (Proxy :: Proxy 3)
  450              (Proxy :: Proxy Word8)
  451              transparent $ \\imgM -> do
  452       matCopyToM imgM (V2 0 0) birds_512x341 (Just mask')
  453   where
  454     rect :: Rect Int32
  455     rect = toRect $ HRect { hRectTopLeft = V2 264 60, hRectSize = V2 248 281 }
  456 @
  457 
  458 <<doc/generated/examples/grabCutBird.png grabCutBird>>
  459 
  460 -}
  461 grabCut
  462     :: ( PrimMonad m
  463        , depth `In` '[ 'D, 'S Word8 ]
  464        )
  465     => Mat shape ('S 3) depth
  466         -- ^ Input 8-bit 3-channel image.
  467     -> Mut (Mat shape ('S 1) ('S Word8)) (PrimState m)
  468         -- ^ Input/output 8-bit single-channel mask. The mask is initialized by the function when mode is set to GC_INIT_WITH_RECT. Its elements may have one of following values:
  469         --
  470         --     * GC_BGD defines an obvious background pixels.
  471         --
  472         --     * GC_FGD defines an obvious foreground (object) pixel.
  473         --
  474         --     * GC_PR_BGD defines a possible background pixel.
  475         --
  476         --     * GC_PR_FGD defines a possible foreground pixel.
  477     -> Mut (Mat ('S ['S 1, 'S 65]) ('S 1) ('S Double)) (PrimState m)
  478         -- ^ Temporary array for the background model. Do not modify it while you are processing the same image.
  479     -> Mut (Mat ('S ['S 1, 'S 65]) ('S 1) ('S Double)) (PrimState m)
  480         -- ^ Temporary arrays for the foreground model. Do not modify it while you are processing the same image.
  481     -> Int32
  482         -- ^ Number of iterations the algorithm should make before returning the result. Note that the result can be refined with further calls with mode==GC_INIT_WITH_MASK or mode==GC_EVAL.
  483     -> GrabCutOperationMode
  484         -- ^ Operation mode
  485     -> CvExceptT m ()
  486 grabCut img mask bgdModel fgdModel iterCount mode =
  487     unsafePrimToPrim $
  488     withPtr img $ \imgPtr ->
  489     withPtr mask $ \maskPtr ->
  490     withPtr rect $ \rectPtr ->
  491     withPtr bgdModel $ \bgdModelPtr ->
  492     withPtr fgdModel $ \fgdModelPtr ->
  493       [C.block|void {
  494         cv::grabCut( *$(Mat * imgPtr)
  495                    , *$(Mat * maskPtr)
  496                    , *$(Rect2i * rectPtr)
  497                    , *$(Mat * bgdModelPtr)
  498                    , *$(Mat * fgdModelPtr)
  499                    , $(int32_t iterCount)
  500                    , $(int32_t c'modeFlags)
  501                    );
  502       }|]
  503   where
  504     rect = marshalGrabCutOperationModeRect mode
  505     c'modeFlags = marshalGrabCutOperationMode mode
  506 
  507 {- | Returns 0 if the pixels are not in the range, 255 otherwise. -}
  508 inRange ::
  509      (ToScalar scalar)
  510   => Mat ('S [w, h]) channels depth
  511   -> scalar -- ^ Lower bound
  512   -> scalar -- ^ Upper bound
  513   -> CvExcept (Mat ('S [w, h]) ('S 1) ('S Word8))
  514 inRange src lo hi = unsafeWrapException $ do
  515   dst <- newEmptyMat
  516   withPtr src $ \srcPtr ->
  517     handleCvException (return (unsafeCoerceMat dst)) $
  518     withPtr (toScalar lo) $ \loPtr ->
  519     withPtr (toScalar hi) $ \hiPtr ->
  520     withPtr dst $ \dstPtr ->
  521       [cvExcept|
  522         cv::inRange(*$(Mat * srcPtr), *$(Scalar * loPtr), *$(Scalar * hiPtr), *$(Mat * dstPtr));
  523       |]