module Vision.Image.Transform (
InterpolMethod (..), crop, resize, horizontalFlip, verticalFlip, floodFill
) where
import Control.Monad (when)
import Control.Monad.Primitive (PrimMonad (..))
import Data.RatioInt (RatioInt, (%))
import Vision.Image.Class (
MaskedImage (..), Image (..), ImageChannel, FromFunction (..), (!)
)
import Vision.Image.Interpolate (Interpolable, bilinearInterpol)
import Vision.Image.Mutable (MutableImage (..))
import Vision.Primitive (
Z (..), (:.) (..), Point, RPoint (..), Rect (..), Size, ix2, toLinearIndex
)
data InterpolMethod =
TruncateInteger
| NearestNeighbor
| Bilinear
crop :: (Image i1, FromFunction i2, ImagePixel i1 ~ FromFunctionPixel i2)
=> Rect -> i1 -> i2
crop !(Rect rx ry rw rh) !img =
fromFunction (Z :. rh :. rw) $ \(Z :. y :. x) ->
img ! ix2 (ry + y) (rx + x)
resize :: (Image i1, Interpolable (ImagePixel i1), FromFunction i2
, ImagePixel i1 ~ FromFunctionPixel i2, Integral (ImageChannel i1))
=> InterpolMethod -> Size -> i1 -> i2
resize !method !size'@(Z :. h' :. w') !img =
case method of
TruncateInteger ->
let !widthRatio = double w / double w'
!heightRatio = double h / double h'
line !y' = truncate $ (double y' + 0.5) * heightRatio 0.5
col !x' = truncate $ (double x' + 0.5) * widthRatio 0.5
f !y !(Z :. _ :. x') = let !x = col x'
in img ! ix2 y x
in fromFunctionLine size' line f
NearestNeighbor ->
let !widthRatio = double w / double w'
!heightRatio = double h / double h'
line !y' = round $ (double y' + 0.5) * heightRatio 0.5
col !x' = round $ (double x' + 0.5) * widthRatio 0.5
f !y !(Z :. _ :. x') = let !x = col x'
in img ! ix2 y x
in fromFunctionLine size' line f
Bilinear ->
let !widthRatio = w % w'
!maxWidth = ratio (w 1)
!heightRatio = (h 1) % (h' 1)
!maxHeight = ratio (h 1)
bound !limit = min limit . max 0
line !y' = bound maxHeight $ (ratio y' + 0.5) * heightRatio
0.5
col !x' = bound maxWidth $ (ratio x' + 0.5) * widthRatio
0.5
f !y !x _ = img `bilinearInterpol` RPoint x y
in fromFunctionCached size' line col f
where
!(Z :. h :. w) = shape img
horizontalFlip :: (Image i1, FromFunction i2
, ImagePixel i1 ~ FromFunctionPixel i2)
=> i1 -> i2
horizontalFlip !img =
let f !(Z :. y :. x') = let !x = maxX x'
in img ! ix2 y x
in fromFunction size f
where
!size@(Z :. _ :. w) = shape img
!maxX = w 1
verticalFlip :: (Image i1, FromFunction i2
, ImagePixel i1 ~ FromFunctionPixel i2)
=> i1 -> i2
verticalFlip !img =
let line !y' = maxY y'
f !y !(Z :. _ :. x) = img ! ix2 y x
in fromFunctionLine size line f
where
!size@(Z :. h :. _) = shape img
!maxY = h 1
floodFill :: (PrimMonad m, MutableImage i, Eq (ImagePixel (Freezed i)))
=> Point -> ImagePixel (Freezed i) -> i (PrimState m) -> m ()
floodFill !start !newVal !img = do
let !linearIX = toLinearIndex size start
val <- linearRead img linearIX
when (val /= newVal) $
go val start linearIX
where
!size@(Z :. h :. w) = mShape img
go !val !(Z :. y :. x) !linearIX = do
pix <- linearRead img linearIX
when (pix == val) $ do
let !minLineLinearIX = linearIX x
!maxLineLinearIX = minLineLinearIX + w 1
linearWrite img linearIX newVal
stopLeft <- scanLine val (< minLineLinearIX) pred (linearIX 1)
stopRight <- scanLine val (> maxLineLinearIX) succ (linearIX + 1)
let !from = stopLeft + 1
!to = stopRight 1
!xFrom = from minLineLinearIX
when (y > 0) $
visitLine val (to w) (ix2 (y 1) xFrom) (from w)
when ((y + 1) < h) $
visitLine val (to + w) (ix2 (y + 1) xFrom) (from + w)
scanLine !val !stop !next !linearIX
| stop linearIX = return linearIX
| otherwise = do
pix <- linearRead img linearIX
if pix == val then do linearWrite img linearIX newVal
scanLine val stop next (next linearIX)
else return linearIX
visitLine !val !maxLinearIX !pt@(y :. x) !linearIX
| linearIX > maxLinearIX = return ()
| otherwise = do
go val pt linearIX
visitLine val maxLinearIX (y :. (x + 1)) (linearIX + 1)
double :: Integral a => a -> Double
double = fromIntegral
ratio :: Integral a => a -> RatioInt
ratio = fromIntegral