Get average RGB
i <- ii
tri <- getRandomTriangle i
let points = getPointsInTriangle i tri
let avgRGB = getTriangleAverageRGB i tri
This commit is contained in:
parent
37d0e29861
commit
8e724a8f74
2 changed files with 24 additions and 14 deletions
|
|
@ -3,13 +3,10 @@ module Main where
|
|||
import qualified Lib
|
||||
import Graphics.Image
|
||||
|
||||
i :: IO (Image VU RGB Double)
|
||||
i = readImageRGB VU "sierra.jpg"
|
||||
ii :: IO (Image VU RGB Double)
|
||||
ii = readImageRGB VU "sierra.jpg"
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
image <- readImageRGB VU "sierra.jpg"
|
||||
Lib.getRandomPixel image >>= print
|
||||
Lib.getRandomPixel image >>= print
|
||||
Lib.getRandomPixel image >>= print
|
||||
displayImage image
|
||||
31
src/Lib.hs
31
src/Lib.hs
|
|
@ -1,16 +1,17 @@
|
|||
{-# LANGUAGE TupleSections #-}
|
||||
|
||||
module Lib
|
||||
( getRandomPixel
|
||||
( getRandomTriangle
|
||||
, getPointsInTriangle
|
||||
, getPointsInRandomTriangle
|
||||
, getTriangleAverageRGB
|
||||
) where
|
||||
|
||||
|
||||
import Graphics.Image
|
||||
import Graphics.Image hiding (map)
|
||||
import qualified System.Random
|
||||
|
||||
type Image_ = Image VU RGB Double
|
||||
type Pixel_ = Pixel RGB Double
|
||||
type Point = (Int, Int)
|
||||
type Triangle = (Point, Point, Point)
|
||||
|
||||
|
|
@ -24,17 +25,29 @@ getRandomPixel image = do
|
|||
getCoord :: Int -> IO Int
|
||||
getCoord = System.Random.getStdRandom . System.Random.randomR . (1,)
|
||||
|
||||
getRandomTriangle :: Image_ -> IO Triangle
|
||||
getRandomTriangle image = do
|
||||
a <- Lib.getRandomPixel image
|
||||
b <- Lib.getRandomPixel image
|
||||
c <- Lib.getRandomPixel image
|
||||
return (a, b, c)
|
||||
|
||||
getPointsInTriangle :: Image_ -> Triangle -> [Point]
|
||||
getPointsInTriangle image triangle
|
||||
= filter (isPointInTriangle triangle)
|
||||
$ (,) <$> [0..(rows image)] <*> [0..(cols image)]
|
||||
|
||||
getPointsInRandomTriangle :: Image_ -> IO [Point]
|
||||
getPointsInRandomTriangle image = do
|
||||
a <- getRandomPixel image
|
||||
b <- getRandomPixel image
|
||||
c <- getRandomPixel image
|
||||
return $ getPointsInTriangle image (a, b, c)
|
||||
getTriangleAverageRGB :: Image_ -> Triangle -> Pixel_
|
||||
getTriangleAverageRGB image triangle = (foldl1 (+) pixels) / nPixels
|
||||
where
|
||||
nPixels :: Pixel RGB Double
|
||||
nPixels = fromIntegral $ length pixels
|
||||
|
||||
pixels :: [Pixel_]
|
||||
pixels = map (index image) points
|
||||
|
||||
points :: [Point]
|
||||
points = getPointsInTriangle image triangle
|
||||
|
||||
isPointInTriangle :: Triangle -> Point -> Bool
|
||||
isPointInTriangle (v1, v2, v3) pt = not (has_neg && has_pos)
|
||||
|
|
|
|||
Loading…
Add table
Add a link
Reference in a new issue