{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE BangPatterns #-}
module Graphics.Image.Processing.Ahe where
import Control.Monad (forM_, when)
import Control.Monad.ST
import Data.STRef
import Prelude as P hiding (subtract)
import Graphics.Image.Processing.Filter
import Graphics.Image.Interface as I
import Graphics.Image
import Graphics.Image.Types as IP
simpleFilter :: (Array arr cs e, Array arr X e) => Direction -> Border (Pixel cs e) -> Filter arr cs e
simpleFilter dir !border =
Filter (correlate border kernel)
where
!kernel =
case dir of
Vertical -> fromLists [ [ 0, -1, 0 ], [ -1, 4, -1 ], [ 0, -1, 0 ] ]
Horizontal -> fromLists [ [ 0, -1, 0 ], [ -1, 4, -1 ], [ 0, -1, 0 ] ]
ahe ::
forall arr.
( MArray arr Y Double
, IP.Array arr Y Double
, IP.Array arr Y Word16
, MArray arr Y Word16
, Array arr X Double
)
=> Image arr Y Double
-> Int
-> Int
-> Int
-> Image arr Y Word16
ahe image thetaSz distSz neighborhoodFactor = I.map (fmap toWord16) accBin
where
ip = applyFilter (simpleFilter Horizontal Edge) image
_widthMax, var1, _heightMax, var2 :: Int
var1 = ((rows ip) - 1)
_widthMax = ((rows ip) - 1)
var2 = ((cols ip) - 1)
_heightMax = ((cols ip) - 1)
accBin :: Image arr Y Word16
accBin = runST $
do arr <- I.new (thetaSz, distSz)
forM_ [0 .. var1] $ \x -> do
forM_ [0 .. var2] $ \y -> do
rankRef <- newSTRef (0 :: Int)
let neighborhood a maxValue = filter (\a -> a >= 0 && a < maxValue) [a-5 .. a+5]
forM_ (neighborhood x var1) $ \i -> do
forM_ (neighborhood y var2) $ \j -> do
when (I.index ip (x, y) > I.index ip (i, j)) $ modifySTRef' rankRef (+1)
rank <- readSTRef rankRef
let px = ((rank * 255))
I.write arr (x, y) (PixelY (fromIntegral px))
freeze arr