[go: nahoru, domu]

Skip to content

Commit

Permalink
Merge branch 'master' of https://github.com/MajronMan/Himage
Browse files Browse the repository at this point in the history
  • Loading branch information
ciastkoMalinowe committed Jan 26, 2017
2 parents 21f6cc4 + 0a9f61f commit 95db43f
Show file tree
Hide file tree
Showing 8 changed files with 196 additions and 112 deletions.
5 changes: 3 additions & 2 deletions Himage.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -17,9 +17,10 @@ library
hs-source-dirs: src
exposed-modules: Lib,
Filters.Figures,
IO.Arrays
IO.Arrays,
IO.Files
other-modules: Filters.Effects, Filters.General, Filters.Stencils,
Filters.Types, IO.Files
Filters.Types
build-depends: base >= 4.7 && < 5.0, repa, repa-io,
transformers, JuicyPixels
default-language: Haskell2010
Expand Down
14 changes: 2 additions & 12 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,17 +2,7 @@ module Main where

import Lib

-- |
-- Main function: asks for input, calls functions and sings quietly
main :: IO ()
main = greeter
-- path <- greeter
-- img <- reader path
-- let matrix = fromImageToRepa img
-- --matrixP <- gaussianBlurOutsideFigureWithFrameP (Circle (Point 256 256) 150 ) matrix
-- --matrixP <- extractColor Blue matrix
-- --matrixP <- add matrix matrix
-- -- putStrLn "How many times bigger image?"
-- -- line <- getLine
-- -- let i = read line :: Int
-- -- matrixP <- sizeUp i matrix
-- matrixP <- detectEdgeP matrix
-- writer path (fromRepaToImage matrixP)
25 changes: 24 additions & 1 deletion src/Filters/Effects.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,40 +25,61 @@ import Filters.General
import Filters.Types
import Filters.Figures

-- |
-- Apply gauss and edge filters in parallel to create a detect edge effect
-- on image represented as REPA array
detectEdgeP :: Array D DIM2 RGBA8 -> IO(Array D DIM2 RGBA8)
detectEdgeP matrix = (applyForP 3 gauss2 >=> applyFilterP edge) matrix

-- |
-- Apply gaussian blur in parallel
-- to image represented as REPA array
gaussianBlurP :: Array D DIM2 RGBA8 -> IO(Array D DIM2 RGBA8)
gaussianBlurP = applyFilterP gauss2

-- |
-- Apply inversion filter which
inversionP :: Array D DIM2 RGBA8 -> IO(Array D DIM2 RGBA8)
inversionP = applyFilterP invert

-- |
-- Apply gauss and edge filters to create a detect edge effect
-- to image represented as REPA array
detectEdge :: Array D DIM2 RGBA8 -> Array D DIM2 RGBA8
detectEdge matrix = applyFor 3 gauss2 .
applyFilter edge $
matrix

-- |
-- Apply gaussian blur
-- to image represented as REPA array
gaussianBlur :: Array D DIM2 RGBA8 -> Array D DIM2 RGBA8
gaussianBlur = applyFilter gauss1

-- |
-- Change transparency of image represented as REPA array
setTransparency :: Array D DIM2 RGBA8 -> IO (Array D DIM2 RGBA8)
setTransparency matrix = do
putStrLn "Please specify transparency by typing number from 0 to 255."
putStrLn "(It may not be visible unless you had chosen .png extension.)"
alpha <- getLine
return (setAlpha (read alpha) matrix)

-- |
-- Desaturate image represented as REPA array
grayscale :: Array D DIM2 RGBA8 -> IO (Array D DIM2 RGBA8)
grayscale matrix = do
matrix <- desaturationP matrix
return (delay matrix)


-- |
-- Something like return
noFilter :: Array D DIM2 RGBA8 -> IO(Array D DIM2 RGBA8)
noFilter matrix = do
return matrix

-- |
-- Create focus effect by using gaussian blur outside of figure
gaussianBlurOutsideFigureWithFrameP :: Figure -> Array D DIM2 RGBA8 -> IO(Array D DIM2 RGBA8)
gaussianBlurOutsideFigureWithFrameP figure matrix =
do
Expand All @@ -69,5 +90,7 @@ gaussianBlurOutsideFigureWithFrameP figure matrix =
matrix
return (addFrame figure 5 (0,0,0,255) filtered)

-- |
-- Apply detect edge filter inside given figure
edgeInsideFigureP :: Figure -> Array D DIM2 RGBA8 -> IO(Array D DIM2 RGBA8)
edgeInsideFigureP figure = applyPartiallyInFigureP figure detectEdgeP noFilter
78 changes: 46 additions & 32 deletions src/Filters/Figures.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,8 @@
module Filters.Figures
(
Point(Point),
Figure(Circle,Square,Diamond),
center,
Figure(Circle,Square,Diamond),
center,
radius,
inside,
insideFrame,
Expand All @@ -19,56 +19,67 @@ module Filters.Figures
) where

import Control.Monad
import Data.Array.Repa as Repa hiding ((++))
import Data.Array.Repa as Repa hiding ((++))

import Filters.Types

data Point = Point {x::Int, y::Int}

instance Show Point where
show (Point x y) = "x = " ++ (show x) ++ " y = " ++ (show y)


instance Eq Point where
(==) (Point x1 y1) (Point x2 y2) = and [x1==x2, y1==y2]
-- |
-- Point in two dimensional space
data Point = Point {x::Int, y::Int}

instance Show Point where
show (Point x y) = "x = " ++ (show x) ++ " y = " ++ (show y)

instance Eq Point where
(==) (Point x1 y1) (Point x2 y2) = and [x1==x2, y1==y2]

-- |
-- Circles in metric spaces
data Figure =
Circle {center::Point, radius::Double}
| Square {center::Point, radius::Double} --promień to połowa długości przekątnej
| Diamond {center::Point, radius::Double} --promień to połowa długości przekątnej

instance Show Figure where
show (Circle p r) = "Circle, center = " ++ show p ++ ", radius = " ++ show r
show (Square p r) = "Circle, center = " ++ show p ++ ", radius = " ++ show r
show (Diamond p r) = "Circle, center = " ++ show p ++ ", radius = " ++ show r

--odległość od środka figury do punktu w odpowiedniej normie

instance Show Figure where
show (Circle p r) = "Circle, center = " ++ show p ++ ", radius = " ++ show r
show (Square p r) = "Circle, center = " ++ show p ++ ", radius = " ++ show r
show (Diamond p r) = "Circle, center = " ++ show p ++ ", radius = " ++ show r

-- |
-- distance from the middle of the figure in right norm (euclid, city or maximal)
norm:: Figure -> Point -> Double
norm (Circle c r) p = sqrt (fromIntegral (((x p) - (x c))^2 + ((y p) - (y c))^2))
norm (Square c r) p = fromIntegral (max (abs ((x p) - (x c))) (abs ((y p) - (y c))))
norm (Diamond c r) p = fromIntegral (abs ((x p) - (x c)) + abs ((y p) - (y c)))

-- |
-- Checks if point is inside the figure
inside:: Figure -> Point -> Bool
inside figure point = (norm figure point <= ( radius figure))


-- |
-- Checks if point is outside the figure
outside:: Figure -> Point -> Bool
outside figure point = not $ inside figure point


-- |
-- Check if point is inside figures frame of given width
insideFrame:: Figure -> Double -> Point -> Bool
insideFrame figure frameWidth point =
(outside figure point) && (inside (enlarge figure ( frameWidth)) point)


-- |
-- Extends figure radius adding given n
enlarge:: Figure -> Double -> Figure
enlarge (Circle c r) d = (Circle c (r+d))
enlarge (Diamond c r) d = (Diamond c (r+d))
enlarge (Diamond c r) d = (Diamond c (r+d))
enlarge (Square c r) d = (Square c (r+d))

doubleAbs :: Double -> Double
doubleAbs a
| a < 0 = -a
| otherwise = a

--Przyjmuje funkcje inside lub outside i zwraca odpowiednio wnętrze figury lub zewnętrze, reszta czarna i przezroczysta

-- |
-- Takes a figure and function (inside or outside) and returns array that's black and transparent on
-- inside or outside fiven figure and unchanged on the other side
cutFigure :: Figure -> (Figure->Point->Bool)-> Array D DIM2 RGBA8 -> Array D DIM2 RGBA8
cutFigure figure fun matrix =
fromFunction
Expand All @@ -79,10 +90,11 @@ cutFigure figure fun matrix =
then matrix!(Z :. w :. h)
else (0,0,0,0))

--wyodrębnia podaną figurę i aplikuje jeden filtr wewnątrz, a drugi na zewnątrz
-- |
-- Cuts figure and applies one filter on the inside, other on the outside
applyPartiallyInFigureP :: Figure
-> (Array D DIM2 RGBA8->IO(Array D DIM2 RGBA8)) --filtr wewnętrzny
-> (Array D DIM2 RGBA8->IO(Array D DIM2 RGBA8)) --filtr zewnętrzny
-> (Array D DIM2 RGBA8->IO(Array D DIM2 RGBA8)) -- ^ inside filter
-> (Array D DIM2 RGBA8->IO(Array D DIM2 RGBA8)) -- ^ outside filter
-> Array D DIM2 RGBA8
-> IO(Array D DIM2 RGBA8)
applyPartiallyInFigureP figure innerFun outterFun matrix =
Expand All @@ -91,8 +103,10 @@ applyPartiallyInFigureP figure innerFun outterFun matrix =
outsideFigure <- outterFun matrix
let insideFigure' = cutFigure figure inside insideFigure
let outsideFigure' = cutFigure figure outside outsideFigure
return (Repa.zipWith addRGBA8 insideFigure' outsideFigure')

return (Repa.zipWith addRGBA8 insideFigure' outsideFigure')

-- |
-- Draws given figure (with position, frame width and colour ) on a given image
addFrame :: Figure -> Double -> RGBA8 -> Array D DIM2 RGBA8 -> Array D DIM2 RGBA8
addFrame figure frameWidth frameColour matrix =
fromFunction
Expand Down
39 changes: 36 additions & 3 deletions src/Filters/General.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,8 @@ import Filters.Types
import IO.Arrays
import Filters.Stencils

-- |
-- Alias for Repa.append
add :: Array D DIM2 RGBA8 -> Array D DIM2 RGBA8 -> IO(Array D DIM2 RGBA8)
add m1 m2 = return $ Repa.append m1 m2

Expand All @@ -46,12 +48,15 @@ getNeighbours' x y width matrix (Z :. w :. h) =
(mw, mh) = (\(Z :. a :. b) -> (a, b)) $ extent matrix
cw = min (w+x) (mw-1)
ch = min (h+y) (mh-1)

-- |
-- Returns neighbours of given pixel
getNeighbours :: Int -> Array D DIM2 RGBA8 -> DIM2 -> [RGBA8]
getNeighbours 0 _ _ = []
getNeighbours n matrix shape = getNeighbours' n1 n1 n1 matrix shape where
n1 = n-1

-- |
-- Returns quadruple containing summed components of pixels
sumPixels :: [RGBA8] -> (Int, Int, Int, Int)
sumPixels [] = (0, 0, 0, 0)
sumPixels ((r, g, b, a):xs) = (ir+r', ig+g', ib+b', ia+a') where
Expand All @@ -61,6 +66,8 @@ sumPixels ((r, g, b, a):xs) = (ir+r', ig+g', ib+b', ia+a') where
ib = fromIntegral b
ia = fromIntegral a

-- |
-- Count an average of a group of pixels
meanPixels :: Int -> [RGBA8] -> RGBA8
meanPixels n l = (
fromIntegral $ r `div` n2,
Expand All @@ -70,39 +77,55 @@ meanPixels n l = (
(r, g, b, a) = sumPixels l
n2 = n*n

-- |
-- Calculate average values from neighbours of the given pixel
meanNeighbours :: Int -> Array D DIM2 RGBA8 -> DIM2 -> RGBA8
meanNeighbours i matrix shape = (r , g , b , a ) where
(r, g, b, a) = meanPixels i (getNeighbours i matrix (getNth i matrix shape))

-- |
-- Return nth pixel from given array
getNth :: Int -> Array D DIM2 RGBA8 -> DIM2 -> DIM2
getNth i matrix (Z :. w :. h) = (Z :. cw :. ch) where
(mw, mh) = (\(Z :. a :. b) -> (a, b)) $ extent matrix
cw = max 0 (min (i*w) (mw-1))
ch = max 0 (min (i*h) (mh-1))

part :: Int -- jaką część macierzy wyciąć
-- |
-- Takes an array and returns just a part of it
part :: Int -- ^ how much to cut
-> Array D DIM2 RGBA8 -> DIM2
part i matrix = f $ extent matrix where
f = \(Z :. w :. h)-> (Z :. (w `div` i) :. (h `div` i))

sizeDown :: Int -- ilokrotnie zmniejszyć macierz
-- |
-- Resize array n times
sizeDown :: Int -- ^ how many times smaller
-> Array D DIM2 RGBA8 -> IO(Array D DIM2 RGBA8)
sizeDown n matrix = return $ fromFunction (part n matrix) (meanNeighbours n matrix)

-- |
-- Return shape describing n times bigger array
extendMatrix :: Int -> Array D DIM2 RGBA8 -> DIM2
extendMatrix i matrix = f $ extent matrix where
f = \(Z :. w :. h) -> (Z :. (w * i) :. (h*i))

-- |
-- Increase size of array by simply copying pixels
brutalSizeUp :: Int -- ilokrotnie zwiększyć macierz
-> Array D DIM2 RGBA8 -> Array D DIM2 RGBA8
brutalSizeUp n matrix = fromFunction (extendMatrix n matrix) f where
f = \(Z :. w :. h) -> index matrix (Z :. (w `div` n) :. (h `div` n))

-- |
-- Increase size of array using bilinear interpolation
sizeUp :: Int -- ilokrotnie zwiększyć macierz
-> Array D DIM2 RGBA8 -> IO(Array D DIM2 RGBA8)
sizeUp n matrix = return (fromFunction (extendMatrix n matrix) f) where
f = \shape -> meanPixels n (getNeighbours n (brutalSizeUp n matrix) shape)

-- |
-- Change transparency of all pixels
setAlpha :: Pixel8 -> Array D DIM2 RGBA8 -> Array D DIM2 RGBA8
setAlpha newAlpha matrix = Repa.map
(\(r, g, b, _) -> (r,g,b,newAlpha) )
Expand All @@ -120,9 +143,13 @@ luminosity f (Z :. i :. j) = (x,x,x,alpha)
x = ceiling $ a1 *(fromIntegral r) + a2 * (fromIntegral g) + a3 * (fromIntegral b)
(r,g,b,alpha) = f (Z :. i :. j)

-- |
-- Create a black image of given shape
toBlack :: DIM2 -> Array D DIM2 Pixel8
toBlack shape = fromFunction shape (\(Z :. _ :. _) -> 0)

-- |
-- Set components of each pixel to 0 except for given colour
extractColor :: Color -> Array D DIM2 RGBA8 -> IO(Array D DIM2 RGBA8)
extractColor color matrix
| color == Red = return $ zip4 r n n a
Expand Down Expand Up @@ -193,9 +220,13 @@ applyFor :: Int -> Filter -> Array D DIM2 RGBA8 -> Array D DIM2 RGBA8
applyFor 0 _ matrix = matrix
applyFor n f matrix = applyFor (n-1) f . applyFilter f $ matrix

-- |
-- Like zipWith, but for pixels
zipWithRGBA8 :: RGBA8 -> RGBA8 -> (Pixel8 -> Pixel8 -> Pixel8) -> RGBA8
zipWithRGBA8 (r1, g1, b1, a1) (r2, g2, b2, a2) f = (f r1 r2, f g1 g2, f b1 b2, f a1 a2)

-- |
-- Calculate sum of two pixels using "overlay" method
overlayPixel :: Pixel8 -> Pixel8 -> Pixel8
overlayPixel p1 p2
| a < 0.5 = round (2*a*b*255) :: Pixel8
Expand All @@ -204,6 +235,8 @@ overlayPixel p1 p2
a = fromIntegral p1 / 255 :: Double
b = fromIntegral p2 / 255 :: Double

-- |
-- Use overlay function to add two images
overlay :: Array D DIM2 RGBA8 -> Array D DIM2 RGBA8 -> IO(Array D DIM2 RGBA8)
overlay base top = return $ fromFunction (extent base) f where
(Z:. tw :. th) = extent top
Expand Down
Loading

0 comments on commit 95db43f

Please sign in to comment.