{-#LANGUAGE ScopedTypeVariables#-} module Main where import CV.ColourUtils import CV.DFT import CV.Drawing import CV.Edges import CV.Filters import CV.Image import CV.ImageOp import CV.Pixelwise import Control.Applicative hiding ((<**>),empty) import qualified CV.ImageMath as IM import qualified CV.Transforms as T import Data.Complex import CV.ImageMathOp import CV.Thresholding fi = fromIntegral main = do Just x <- loadImage "d2.png" let d = dft x c (x,y) = circleOp (0:+0) (x,y) 23 Filled d2 = d <# c (155,215) <# c (400,205) <# c (180,365) <# c (425,370) <# c (40,370) <# c (540,215) <# c (200,150) <# c (375,432) <# c (260,130) <# c (315,450) <# c (262,520) <# c (315,66) <# c (375,44) <# c (202,540) mag = fst $ dftSplit $ d pat = gaussian (3,3) $ unsafeImageTo32F $ nibbly 0.01 0.001 $ gaussian (31,31) mag #- gaussian (9,9) mag saveImage "target.png" $ logarithmicCompression $ fst $ dftSplit $ d2 saveImage "dftmanip.png" $ montage (3,1) 0 [ x ,logarithmicCompression $ fst $ dftSplit $ (d #* dftMerge (pat,empty (getSize pat))) ,idft (d #* dftMerge (pat,empty (getSize pat))) ]