Skip to content

Instantly share code, notes, and snippets.

@karoyakani
Created January 21, 2019 05:45
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save karoyakani/d526bc778e0296ad75feb6751b061502 to your computer and use it in GitHub Desktop.
Save karoyakani/d526bc778e0296ad75feb6751b061502 to your computer and use it in GitHub Desktop.
RotateImage.hs
{-# LANGUAGE FlexibleContexts, BangPatterns #-}
import Data.Array.Repa
-- import Data.Array.Repa.IO.DevIL (repa.devil installation fails)
import Data.Array.Repa.IO.BMP (readImageFromBMP, writeImageToBMP)
{-
readImageFromBMP :: FilePath ->
IO (Either Error (Array Unboxed.U DIM2 (Word8, Word8, Word8)))
writeImageToBMP :: FilePath -> Array U DIM2 (Word8, Word8, Word8) -> IO ()
-}
import Data.Array.Repa.Repr.Unboxed as RU (zip3, unzip3)
import System.Environment
import Data.Word
import Data.Array.Repa (Array (..), Z (..), (:.) (..), DIM2, DIM3, extent)
-- <<main
main :: IO ()
main = do
[n,f1,f2] <- getArgs
let deg = read n
Right v <- readImageFromBMP f1
let (r,g,b) = RU.unzip3 v
r' <- computeP $ rotate deg r :: IO (Array U DIM2 Word8)
g' <- computeP $ rotate deg g :: IO (Array U DIM2 Word8)
b' <- computeP $ rotate deg b :: IO (Array U DIM2 Word8)
writeImageToBMP f2 $ RU.zip3 r' g' b' -- <3>
-- >>
-- <<rotate
rotate :: Double -> Array U DIM2 Word8 -> Array D DIM2 Word8
rotate deg g = fromFunction (Z :. y :. x) f -- <1>
where
sh@(Z :. y :. x) = extent g
!theta = pi/180 * deg -- <2>
!st = sin theta -- <3>
!ct = cos theta
!cy = fromIntegral y / 2 :: Double -- <4>
!cx = fromIntegral x / 2 :: Double
f (Z :. i :. j) -- <5>
| inShape sh old = g ! old -- <6>
| otherwise = 0 -- <7>
where
fi = fromIntegral i - cy -- <8>
fj = fromIntegral j - cx
i' = round (st * fj + ct * fi + cy) -- <9>
j' = round (ct * fj - st * fi + cx)
old = Z :. i' :. j' -- <10>
-- >>
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment