module Graphics.Image.Processing.Interpolation (
Interpolation(..), Nearest(..), Bilinear(..)
) where
import Graphics.Image.Interface
class Interpolation method where
interpolate :: (Elevator e, Num e, ColorSpace cs) =>
method (Pixel cs e)
-> (Int, Int)
-> ((Int, Int) -> Pixel cs e)
-> (Double, Double)
-> Pixel cs e
data Nearest px = Nearest !(Border px)
data Bilinear px = Bilinear !(Border px)
instance Interpolation Nearest where
interpolate (Nearest border) !sz !getPx !(round -> i, round -> j) =
borderIndex border sz getPx (i, j)
instance Interpolation Bilinear where
interpolate (Bilinear border) !sz !getPx !(i, j) = fi0 + jPx*(fi1fi0) where
getPx' = borderIndex border sz getPx
!(i0, j0) = (floor i, floor j)
!(i1, j1) = (i0 + 1, j0 + 1)
!iPx = fromDouble $ fromChannel (i fromIntegral i0)
!jPx = fromDouble $ fromChannel (j fromIntegral j0)
!f00 = getPx' (i0, j0)
!f10 = getPx' (i1, j0)
!f01 = getPx' (i0, j1)
!f11 = getPx' (i1, j1)
!fi0 = f00 + iPx*(f10f00)
!fi1 = f01 + iPx*(f11f01)