Skip to content

Commit

Permalink
Fix Bicubic interpolation. Ensure tests are passing. Bump up the vers…
Browse files Browse the repository at this point in the history
…ion and update changelog
  • Loading branch information
lehins committed May 3, 2020
1 parent 9debfc3 commit 3f8a39a
Show file tree
Hide file tree
Showing 4 changed files with 103 additions and 98 deletions.
5 changes: 5 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,8 @@
1.5.6.0
=======

* Addition of Bicubic interpolation (Thanks to @kirisaki)

1.5.5.0
=======

Expand Down
2 changes: 1 addition & 1 deletion hip.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
Name: hip
Version: 1.5.5.0
Version: 1.5.6.0
License: BSD3
License-File: LICENSE
Author: Alexey Kuleshevich
Expand Down
160 changes: 80 additions & 80 deletions src/Graphics/Image/Processing/Interpolation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,19 +40,19 @@ data Bilinear = Bilinear deriving Show

-- | Bicubic interpolation method.
-- The parameter is usually set from -0.5 to -1.0.
data Bicubic = Bicubic Double deriving Show
newtype Bicubic = Bicubic Double deriving Show


instance Interpolation Nearest where

interpolate Nearest border !sz getPx !(i, j) =
interpolate Nearest border !sz getPx (i, j) =
handleBorderIndex border sz getPx (round i, round j)
{-# INLINE interpolate #-}


instance Interpolation Bilinear where

interpolate Bilinear border !sz getPx !(i, j) = fi0 + jPx*(fi1-fi0) where
interpolate Bilinear border !sz getPx (i, j) = fi0 + jPx*(fi1-fi0) where
getPx' = handleBorderIndex border sz getPx
{-# INLINE getPx' #-}
!(i0, j0) = (floor i, floor j)
Expand All @@ -70,81 +70,81 @@ instance Interpolation Bilinear where

instance Interpolation Bicubic where

interpolate (Bicubic a) border !sz getPx !(i, j) = ( f00 + f10 + f20 + f30
+ f01 + f11 + f21 + f31
+ f02 + f12 + f22 + f32
+ f03 + f13 + f23 + f33
) * w where
getPx' = handleBorderIndex border sz getPx
{-# INLINE getPx' #-}
distX x = fromIntegral x - i
{-# INLINE distX #-}
distY y = fromIntegral y - j
{-# INLINE distY #-}
weight x
| x' <= 1 = (a + 2) * x' ** 3 - (a + 3) * x' ** 2 + 1
| x' < 2 = a * x' ** 3 - 5 * a * x' ** 2 + 8 * a * x' - 4 * a
| otherwise = 0
where x' = abs x
{-# INLINE weight #-}
!(i1, j1) = (floor i, floor j)
!(i0, j0) = (i1 - 1, j1 - 1)
!(i2, j2) = (i1 + 1, j1 + 1)
!(i3, j3) = (i1 + 2, j1 + 2)

!weightX0 = weight (distX i0)
!weightY0 = weight (distY i0)
!weightX1 = weight (distX i1)
!weightY1 = weight (distY i1)
!weightX2 = weight (distX i2)
!weightY2 = weight (distY i2)
!weightX3 = weight (distX i3)
!weightY3 = weight (distY i3)

!weightX0Y0 = weightX0 * weightY0
!weightX1Y0 = weightX1 * weightY0
!weightX2Y0 = weightX2 * weightY0
!weightX3Y0 = weightX3 * weightY0

!weightX0Y1 = weightX0 * weightY1
!weightX1Y1 = weightX1 * weightY1
!weightX2Y1 = weightX2 * weightY1
!weightX3Y1 = weightX3 * weightY1

!weightX0Y2 = weightX0 * weightY2
!weightX1Y2 = weightX1 * weightY2
!weightX2Y2 = weightX2 * weightY2
!weightX3Y2 = weightX3 * weightY2

!weightX0Y3 = weightX0 * weightY3
!weightX1Y3 = weightX1 * weightY3
!weightX2Y3 = weightX2 * weightY3
!weightX3Y3 = weightX3 * weightY3

!f00 = getPx' (i0, j0) * promote (fromDouble weightX0Y0)
!f10 = getPx' (i1, j0) * promote (fromDouble weightX1Y0)
!f20 = getPx' (i2, j0) * promote (fromDouble weightX2Y0)
!f30 = getPx' (i3, j0) * promote (fromDouble weightX3Y0)

!f01 = getPx' (i0, j1) * promote (fromDouble weightX0Y1)
!f11 = getPx' (i1, j1) * promote (fromDouble weightX1Y1)
!f21 = getPx' (i2, j1) * promote (fromDouble weightX2Y1)
!f31 = getPx' (i3, j1) * promote (fromDouble weightX3Y1)

!f02 = getPx' (i0, j2) * promote (fromDouble weightX0Y2)
!f12 = getPx' (i1, j2) * promote (fromDouble weightX1Y2)
!f22 = getPx' (i2, j2) * promote (fromDouble weightX2Y2)
!f32 = getPx' (i3, j2) * promote (fromDouble weightX3Y2)

!f03 = getPx' (i0, j3) * promote (fromDouble weightX0Y3)
!f13 = getPx' (i1, j3) * promote (fromDouble weightX1Y3)
!f23 = getPx' (i2, j3) * promote (fromDouble weightX2Y3)
!f33 = getPx' (i3, j3) * promote (fromDouble weightX3Y3)

!w = promote . fromDouble . (1 /) $
weightX0Y0 + weightX1Y0 + weightX2Y0 + weightX3Y0
+ weightX0Y1 + weightX1Y1 + weightX2Y1 + weightX3Y1
+ weightX0Y2 + weightX1Y2 + weightX2Y2 + weightX3Y2
+ weightX0Y3 + weightX1Y3 + weightX2Y3 + weightX3Y3
interpolate (Bicubic a) border !sz getPx (i, j) =
( f00 + f10 + f20 + f30
+ f01 + f11 + f21 + f31
+ f02 + f12 + f22 + f32
+ f03 + f13 + f23 + f33 ) * promote (fromDouble (1 / w))
where
getPx' = handleBorderIndex border sz getPx
{-# INLINE getPx' #-}
distX x = fromIntegral x - i
{-# INLINE distX #-}
distY y = fromIntegral y - j
{-# INLINE distY #-}
weight x
| x' <= 1 = ((a + 2) * x' - (a + 3)) * x2' + 1
| x' < 2 = a * ((x2' - 5 * x' + 8) * x' - 4)
| otherwise = 0
where x' = abs x
x2' = x' * x'
{-# INLINE weight #-}
!(i0, j0) = (i1 - 1, j1 - 1)
!(i1, j1) = (floor i, floor j)
!(i2, j2) = (i1 + 1, j1 + 1)
!(i3, j3) = (i1 + 2, j1 + 2)

!weightX0 = weight (distX i0)
!weightX1 = weight (distX i1)
!weightX2 = weight (distX i2)
!weightX3 = weight (distX i3)
!weightY0 = weight (distY j0)
!weightY1 = weight (distY j1)
!weightY2 = weight (distY j2)
!weightY3 = weight (distY j3)

!weightX0Y0 = weightX0 * weightY0
!weightX1Y0 = weightX1 * weightY0
!weightX2Y0 = weightX2 * weightY0
!weightX3Y0 = weightX3 * weightY0

!weightX0Y1 = weightX0 * weightY1
!weightX1Y1 = weightX1 * weightY1
!weightX2Y1 = weightX2 * weightY1
!weightX3Y1 = weightX3 * weightY1

!weightX0Y2 = weightX0 * weightY2
!weightX1Y2 = weightX1 * weightY2
!weightX2Y2 = weightX2 * weightY2
!weightX3Y2 = weightX3 * weightY2

!weightX0Y3 = weightX0 * weightY3
!weightX1Y3 = weightX1 * weightY3
!weightX2Y3 = weightX2 * weightY3
!weightX3Y3 = weightX3 * weightY3

!f00 = getPx' (i0, j0) * promote (fromDouble weightX0Y0)
!f10 = getPx' (i1, j0) * promote (fromDouble weightX1Y0)
!f20 = getPx' (i2, j0) * promote (fromDouble weightX2Y0)
!f30 = getPx' (i3, j0) * promote (fromDouble weightX3Y0)

!f01 = getPx' (i0, j1) * promote (fromDouble weightX0Y1)
!f11 = getPx' (i1, j1) * promote (fromDouble weightX1Y1)
!f21 = getPx' (i2, j1) * promote (fromDouble weightX2Y1)
!f31 = getPx' (i3, j1) * promote (fromDouble weightX3Y1)

!f02 = getPx' (i0, j2) * promote (fromDouble weightX0Y2)
!f12 = getPx' (i1, j2) * promote (fromDouble weightX1Y2)
!f22 = getPx' (i2, j2) * promote (fromDouble weightX2Y2)
!f32 = getPx' (i3, j2) * promote (fromDouble weightX3Y2)

!f03 = getPx' (i0, j3) * promote (fromDouble weightX0Y3)
!f13 = getPx' (i1, j3) * promote (fromDouble weightX1Y3)
!f23 = getPx' (i2, j3) * promote (fromDouble weightX2Y3)
!f33 = getPx' (i3, j3) * promote (fromDouble weightX3Y3)

!w = weightX0Y0 + weightX1Y0 + weightX2Y0 + weightX3Y0
+ weightX0Y1 + weightX1Y1 + weightX2Y1 + weightX3Y1
+ weightX0Y2 + weightX1Y2 + weightX2Y2 + weightX3Y2
+ weightX0Y3 + weightX1Y3 + weightX2Y3 + weightX3Y3
{-# INLINE interpolate #-}

34 changes: 17 additions & 17 deletions tests/Graphics/Image/ProcessingSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ instance Arbitrary Interpol where
case ix `mod` (3 :: Int) of
0 -> return $ I1 Nearest
1 -> return $ I2 Bilinear
2 -> I3 . Bicubic <$> choose (-1, -0.5)
2 -> I3 . Bicubic <$> pure (-1) -- choose (-1, -0.5)
_ -> error $ "Unknown interpolation: " ++ show ix


Expand Down Expand Up @@ -74,25 +74,25 @@ prop_concatRotate img =
rotate90 (leftToRight img $ rotate180 img)


prop_rotate90 :: Interpol -> Border (Pixel RGB Double) -> Image VU RGB Double -> Bool
prop_rotate90 (I1 i) border img = rotate90 img == rotate i border (pi/2) img
prop_rotate90 (I2 i) border img = rotate90 img == rotate i border (pi/2) img
prop_rotate90 (I3 i) border img = rotate90 img == rotate i border (pi/2) img
prop_rotate90 :: Interpol -> Border (Pixel RGB Double) -> Image VU RGB Double -> Property
prop_rotate90 (I1 i) border img = rotate90 img === rotate i border (pi/2) img
prop_rotate90 (I2 i) border img = rotate90 img === rotate i border (pi/2) img
prop_rotate90 (I3 i) border img = rotate90 img === rotate i border (pi/2) img

prop_rotate180 :: Interpol -> Border (Pixel RGB Double) -> Image VU RGB Double -> Bool
prop_rotate180 (I1 i) border img = rotate180 img == rotate i border pi img
prop_rotate180 (I2 i) border img = rotate180 img == rotate i border pi img
prop_rotate180 (I3 i) border img = rotate180 img == rotate i border pi img
prop_rotate180 :: Interpol -> Border (Pixel RGB Double) -> Image VU RGB Double -> Property
prop_rotate180 (I1 i) border img = rotate180 img === rotate i border pi img
prop_rotate180 (I2 i) border img = rotate180 img === rotate i border pi img
prop_rotate180 (I3 i) border img = rotate180 img === rotate i border pi img

prop_rotate270 :: Interpol -> Border (Pixel RGB Double) -> Image VU RGB Double -> Bool
prop_rotate270 (I1 i) border img = rotate270 img == rotate i border (3*pi/2) img
prop_rotate270 (I2 i) border img = rotate270 img == rotate i border (3*pi/2) img
prop_rotate270 (I3 i) border img = rotate270 img == rotate i border (3*pi/2) img
prop_rotate270 :: Interpol -> Border (Pixel RGB Double) -> Image VU RGB Double -> Property
prop_rotate270 (I1 i) border img = rotate270 img === rotate i border (3*pi/2) img
prop_rotate270 (I2 i) border img = rotate270 img === rotate i border (3*pi/2) img
prop_rotate270 (I3 i) border img = rotate270 img === rotate i border (3*pi/2) img

prop_rotate360 :: Interpol -> Border (Pixel RGB Double) -> Image VU RGB Double -> Bool
prop_rotate360 (I1 i) border img = (rotate270 . rotate90) img == rotate i border (2*pi) img
prop_rotate360 (I2 i) border img = (rotate270 . rotate90) img == rotate i border (2*pi) img
prop_rotate360 (I3 i) border img = (rotate270 . rotate90) img == rotate i border (2*pi) img
prop_rotate360 :: Interpol -> Border (Pixel RGB Double) -> Image VU RGB Double -> Property
prop_rotate360 (I1 i) border img = (rotate270 . rotate90) img === rotate i border (2*pi) img
prop_rotate360 (I2 i) border img = (rotate270 . rotate90) img === rotate i border (2*pi) img
prop_rotate360 (I3 i) border img = (rotate270 . rotate90) img === rotate i border (2*pi) img


struct :: Image VS X Bit
Expand Down

0 comments on commit 3f8a39a

Please sign in to comment.