Chuck Aguilar
Chuck Aguilar

Reputation: 2048

GaussianBlurImage in haskell-opencv (Haskell binding to OpenCV-3.1)

H!

I'm using haskell-opencv library. I don't know if another one is using it, or know something about it.

I was trying to use gaussianBlurImage, but there's an error that I can't recognize.

I have this:

cropped image = do 
     resized <- resizeImage image
     gaussianBlurred <- gaussianBlurImage ((M.unsafeCoerceMat . getImageFromEither) resized)

Where resized is an Either CV.Exception (M.Mat shape channels depth) And I get from here ((M.unsafeCoerceMat . getImageFromEither) resized) a Mat shape (S channels) (S depth) as gaussianBlurImage function needs.

The I defined gaussianBlurImage so:

gaussianBlurImage image = runExceptT $ CV.pureExcept $ CV.gaussianBlur (V2 13 13 :: V2 Int32) 0 0 image

And for me, it looks fine. Similar as here: blur. But I get this error:

Couldn't match expected type ‘'True’ with actual type ‘Elem depth0 '[Word8, Word16, Float, Double]’

I noticed, that my gaussianBlurImage has this type:

gaussianBlurImage :: (M.Mat shape0 ('S channels0) ('S depth0)) -> Either CV.CvException (Either CV.CvException (M.Mat shape0 ('S channels0) ('S depth0)))

And I liked this one:

gaussianBlurImage :: (M.Mat shape0 ('S channels0) ('S depth0)) -> Either CV.CvException (M.Mat shape0 ('S channels0) ('S depth0))

Maybe it has something to do.

I tried it with medianBlur, blur and with gaussianBlur. I used a not resized image, and an image with three channels and another with 2 (color and gray), and I always get the same error. I'm wondering if the error is in M.unsafeCoerceMat image. And why 'True as expected type? I don't have idea

Upvotes: 1

Views: 195

Answers (1)

Chuck Aguilar
Chuck Aguilar

Reputation: 2048

haskell-opencv is an excellent library, but sometimes it's difficult to use because there are a lot of documentation, but difficult to understand, and there are no many examples.

There, every Blur function need a (M.Mat shape ('S channels) ('S depth)) matrix, but the matrix are usually so: (M.Mat shape channels depth), where 'S tells it's static.

I use this function:

M.coerceMat to have such a Matrix.

coerceMAt :: (ToShapeDS (Proxy shapeOut), ToChannelsDS (Proxy 
    channelsOut), ToDepthDS (Proxy depthOut))    
    => Mat shapeIn channelsIn depthIn    
    -> CvExcept (Mat shapeOut channelsOut depthOut)

As it returns CVExcept, I use exceptError :: CvExcept a -> a to get just the image.

But the most important is the definition of the function. There was the problem in my code. depth cannot be ambiguous, that's why I wrote:

forall height0 width0 channels depth . ( depth `In` '[Word8, Word16, Float, Double] , channels `In` '[1, 3, 4]) => M.Mat ('S '[height0, width0]) ('S channels) ('S depth) -> IO (M.Mat ('S '[height0, width0]) ('S channels) ('S depth))

Here's a complete example. I get an image, resize it, blur it and show it.

Main:

module Main where

import Lib
import qualified OpenCV.Internal.Core.Types.Mat as M
import Control.Monad ( void )
import qualified OpenCV as CV
import qualified Data.ByteString as B

main :: IO ()
main = do
    test <- controller
    CV.withWindow "test" $ \window -> do
        CV.imshow window test  
        void $ CV.waitKey 10000

Lib:

{-# LANGUAGE TypeFamilies #-}

module Lib
    ( controller
    ) where

import BlurImage
import ResizeImage
import Utils
import Control.Monad ( void )
import Data.Word
import qualified OpenCV.Internal.Core.Types.Mat as M
import qualified OpenCV as CV
import qualified Data.ByteString as B

controller :: IO (CV.Mat (CV.S '[CV.D, CV.D]) (CV.S 1) (CV.S Word8))
controller = do
    file <- B.readFile "path/to/image.jpg"
    img <- return $ CV.imdecode CV.ImreadGrayscale file
    resized_little_img <- resizeImage img --little image for making a blur in and find the receipt
    blurImage ((CV.exceptError $ M.coerceMat resized_little_img) :: M.Mat (CV.S '[ CV.D, CV.D]) (CV.S 1) (CV.S Word8))

ResizeImage:

{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE AllowAmbiguousTypes #-}

module ResizeImage
    ( 
    resizeImage
    ) where

import Utils
import Control.Monad ( void )
import Control.Monad.Except
import Data.Functor.Identity
import Data.Word
import Data.Proxy
import qualified OpenCV as CV
import Linear.V2
import OpenCV.TypeLevel
import qualified OpenCV.Internal.Core.Types.Mat as M
import qualified OpenCV.Core.Types.Size as S
import qualified OpenCV.ImgProc.GeometricImgTransform as GIT
import GHC.Int (Int32)

resizingImage :: (M.Mat (CV.S [CV.D, CV.D]) CV.D CV.D) -> CV.CvExcept (M.Mat (CV.S [CV.D, CV.D]) CV.D CV.D)
resizingImage image = GIT.resize (GIT.ResizeAbs $ S.toSize $ (getSize w h Nothing (Just 500))) CV.InterCubic image
    where
        [h, w] = getHandW image

resizeImage :: (M.Mat (S '[CV.D, CV.D]) CV.D CV.D) -> IO(M.Mat (CV.S [CV.D, CV.D]) CV.D CV.D)
resizeImage image = do        
    resized <- return $ resizingImage image
    return $ CV.exceptError $ resized

BlurImage:

{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE AllowAmbiguousTypes #-}

module BlurImage
    ( 
    blurImage
    ) where

import Utils
import Control.Monad ( void )
import Control.Monad.Except
import qualified Data.ByteString as B
import Data.Word
import Data.Proxy
import qualified OpenCV as CV
import Linear.V2
import OpenCV.TypeLevel
import qualified OpenCV.Internal.Core.Types.Mat as M
import qualified OpenCV.Core.Types.Size as S
import qualified OpenCV.ImgProc.GeometricImgTransform as GIT
import GHC.Int (Int32)


medianBlurImage :: (depth `In` '[Word8, Word16, Float], channels `In` '[1, 3, 4]) => (M.Mat shape ('S channels) ('S depth)) -> CV.CvExcept (M.Mat shape ('S channels) ('S depth)) 
medianBlurImage image = CV.medianBlur image 13 

gaussianBlurImage :: (depth `In` '[Word8, Word16, Float, Double], channels `In` '[1, 3, 4]) => (M.Mat shape ('S channels) ('S depth)) -> CV.CvExcept (M.Mat shape ('S channels) ('S depth)) 
gaussianBlurImage image = CV.gaussianBlur (V2 13 13 :: V2 Int32) 0 0 image

blurImage :: forall height0 width0 channels depth . ( depth `In` '[Word8, Word16, Float, Double] , channels `In` '[1, 3, 4]) => M.Mat ('S '[height0, width0]) ('S channels) ('S depth) -> IO (M.Mat ('S '[height0, width0]) ('S channels) ('S depth))
blurImage image = do
    gaussianBlurred   <- return $ gaussianBlurImage image     
    return $ CV.exceptError $ gaussianBlurred

And that's it. :) I hope it can help someone.

Upvotes: 1

Related Questions