module Vision.Image.Threshold (
ThresholdType (..), thresholdType
, threshold
, AdaptiveThresholdKernel (..), AdaptiveThreshold
, adaptiveThreshold, adaptiveThresholdFilter
, otsu, scw
) where
import Data.Int
import Foreign.Storable (Storable)
import qualified Data.Vector.Storable as V
import qualified Data.Vector as VU
import Vision.Image.Class (
Image, ImagePixel, FromFunction (..), FunctorImage, (!), shape
)
import Vision.Image.Filter.Internal (
Filter (..), BoxFilter, Kernel (..), SeparableFilter, SeparatelyFiltrable
, KernelAnchor (KernelAnchorCenter), FilterFold (..)
, BorderInterpolate (BorderReplicate)
, apply, blur, gaussianBlur, Mean, mean
)
import Vision.Image.Type (Manifest, delayed, manifest)
import Vision.Histogram (
HistogramShape, PixelValueSpace, ToHistogram, histogram
)
import Vision.Primitive (Z (..), (:.) (..), Size, shapeLength)
import qualified Vision.Histogram as H
import qualified Vision.Image.Class as I
data ThresholdType src res where
BinaryThreshold :: res -> res -> ThresholdType src res
Truncate :: src -> ThresholdType src src
TruncateInv :: src -> ThresholdType src src
thresholdType :: ThresholdType src res -> Bool -> src -> res
thresholdType (BinaryThreshold ifTrue ifFalse) match _ | match = ifTrue
| otherwise = ifFalse
thresholdType (Truncate ifTrue) match pix | match = ifTrue
| otherwise = pix
thresholdType (TruncateInv ifFalse) match pix | match = pix
| otherwise = ifFalse
threshold :: FunctorImage src res
=> (ImagePixel src -> Bool)
-> ThresholdType (ImagePixel src) (ImagePixel res) -> src -> res
threshold !cond !thresType =
I.map (\pix -> thresholdType thresType (cond pix) pix)
data AdaptiveThresholdKernel acc where
MeanKernel :: Integral acc => AdaptiveThresholdKernel acc
GaussianKernel :: (Floating acc, RealFrac acc)
=> Maybe acc -> AdaptiveThresholdKernel acc
adaptiveThreshold :: ( Image src, Integral (ImagePixel src)
, Ord (ImagePixel src)
, FromFunction res, Integral (FromFunctionPixel res)
, Storable acc
, SeparatelyFiltrable src res acc)
=> AdaptiveThresholdKernel acc
-> Int
-> ImagePixel src
-> ThresholdType (ImagePixel src) (FromFunctionPixel res)
-> src
-> res
adaptiveThreshold kernelType radius thres thresType img =
adaptiveThresholdFilter kernelType radius thres thresType `apply` img
type AdaptiveThreshold src acc res = SeparableFilter src () acc res
adaptiveThresholdFilter :: (Integral src, Ord src, Storable acc)
=> AdaptiveThresholdKernel acc
-> Int
-> src
-> ThresholdType src res
-> AdaptiveThreshold src acc res
adaptiveThresholdFilter !kernelType !radius !thres !thresType =
kernelFilter { fPost = post }
where
!kernelFilter =
case kernelType of MeanKernel -> blur radius
GaussianKernel sig -> gaussianBlur radius sig
post ix pix ini acc =
let !acc' = (fPost kernelFilter) ix pix ini acc
!cond = (pix acc') > thres
in thresholdType thresType cond pix
otsu :: ( HistogramShape (PixelValueSpace (ImagePixel src))
, ToHistogram (ImagePixel src), FunctorImage src res
, Ord (ImagePixel src), Num (ImagePixel src), Enum (ImagePixel src))
=> ThresholdType (ImagePixel src) (ImagePixel res) -> src -> res
otsu !thresType !img =
threshold (<= thresh) thresType img
where
!thresh =
let hist = histogram Nothing img
histV = H.vector hist
tot = shapeLength (I.shape img)
runningMul = V.zipWith (\v i -> v * i) histV (V.fromList [0..255])
sm = double (V.sum $ V.drop 1 runningMul)
wB = V.scanl1 (+) histV
wF = V.map (\x -> tot x) wB
sumB = V.scanl1 (+) runningMul
mB = V.zipWith (\n d -> if d == 0 then 1
else double n / double d)
sumB wB
mF = V.zipWith (\b f -> if f == 0 then 1
else (sm double b)
/ double f)
sumB wF
between = V.zipWith4 (\x y b f -> double x * double y
* (b f)^two)
wB wF mB mF
in snd $ VU.maximum (VU.zip (VU.fromList $ V.toList between)
(VU.fromList [0..255]))
!two = 2 :: Int
scw :: ( Image src, Integral (ImagePixel src), FromFunction dst
, Floating stdev, Fractional stdev, Ord stdev, Storable stdev)
=> Size -> Size -> stdev
-> ThresholdType (ImagePixel src) (FromFunctionPixel dst) -> src -> dst
scw !sizeA !sizeB !beta !thresType !img =
betaThreshold (stdDev sizeA) (stdDev sizeB)
where
betaThreshold a b =
fromFunction (shape img) $ \pt ->
let !cond = (b ! pt) / (a ! pt) < beta
in thresholdType thresType cond (img ! pt)
stdDev size =
let filt :: (Integral src, Fractional res) => Mean src Int16 res
filt = mean size
!meanImg = manifest $ apply filt img
!varImg = manifest $ apply (variance size meanImg) img
in delayed $ I.map sqrt varImg
variance :: (Integral src, Fractional res, Storable res)
=> Size -> Manifest res -> BoxFilter src res res res
variance !size@(Z :. h :. w) !meanImg =
Filter size KernelAnchorCenter (Kernel kernel) (\pt _ -> meanImg ! pt)
(FilterFold (const 0)) post BorderReplicate
where
kernel !kernelMean _ !val !acc =
acc + square (fromIntegral val kernelMean)
!nPixsFactor = 1 / (fromIntegral $! h * w)
post _ _ _ !acc = acc * nPixsFactor
square :: Num a => a -> a
square a = a * a
double :: Integral a => a -> Double
double = fromIntegral