This commit is contained in:
Jack Wines 2023-02-03 19:34:57 -08:00
parent 3ceb4e9961
commit d2ccaf0e8a
2 changed files with 1 additions and 55 deletions

View file

@ -40,44 +40,18 @@ defaultOpts = Options {
gen = Nothing
}
genList :: StdGen -> [StdGen]
genList = map snd . iterate (split . fst) . split
-- CL.rgb might be the wrong fn...
tosRGB' :: (Ord b, Floating b) => Pixel G.RGB b -> CL.Colour b
tosRGB' (G.PixelRGB r g b) = CL.rgb r g b
convImage = Vec.map tosRGB' . Int.toVector
-- -- progress goes from 0 to 1 the farther we get along the process
-- -- note, 0 represents the topmost triangle
-- renderTri :: Vec.Vector (Colour Double) -> (Int, Int) -> StdGen -> Double -> QDiagram SVG V2 Double Any
-- renderTri image dimensions gen progress = Ren.makeTriangle (Ren.toPointList dimensions triangle) color opacity'
-- where
-- triangle = Tri.getRandomTriangle image dimensions (Just area) gen
-- color = Tri.getTriangleAverageRGB image triangle dimensions
-- -- the following should be considered triangle shaders
-- -- modify them to your liking, their outputs are expected to be in [0, 1]
-- -- TODO: move these into a separate module
-- -- opacity' = 0.4
-- opacity' = 0.3 + ((1 - progress) * 0.5)
-- area = max ((progress ** 2) * 0.2) 0.02
corners :: [(Double, Double)]
corners = (,) <$> [0, 1] <*> [0, 1]
scalePointToImage :: (Int, Int) -> Point V2 Double -> Point V2 Int
scalePointToImage (ymax, xmax) p = round <$> (p2 (fromIntegral xmax, fromIntegral ymax) * p)
-- derive Generic (RGB Double)
-- genImage :: String -> IO (Diagram B)
-- genImage :: FilePath -> IO (QDiagram SVG V2 Double Any)
genImage image gen cornerCount =
scaleY ((fromIntegral $ fst dimensions) / ((fromIntegral $ snd dimensions) :: Double))
. reflectY . mconcat
@ -86,26 +60,19 @@ genImage image gen cornerCount =
$ My.mapMaybe (\tri -> (tri,) . CL.toRGB <$> triColor tri) triangles
where
img' = convImage image
dimensions = (rows image, cols image)
dimensions = Img.dims image
triangles = S.toList . Tri.findTriangles . withStrategy (parListChunk 1000 rdeepseq) . Tri.toPlanarGraph . take cornerCount . map p2 $ corners ++ Tri.randomPoints gen
triColor tri = getTriangleAverageRGB img' dimensions <$> (if S.size scaled == 3 then Just scaled else Nothing)
where
scaled = S.map (scalePointToImage dimensions) tri
-- let progressList = withStrategy (parListChunk 500 rdeepseq) . map (/ (fromIntegral numTriangles)) $ [0.0 .. (fromIntegral numTriangles)]
-- return $ center . reflectY . mconcat $ zipWith (renderTri img' dimensions) (genList gen'') progressList
deriving instance Generic (CL.RGB a)
deriving instance NFData a => NFData (CL.RGB a)
toDimensionVector :: (Int.BaseArray arr cs e, Fractional n) => Image arr cs e -> SizeSpec V2 n
toDimensionVector image = Diagrams.Prelude.dims $ p2 (fromIntegral $ cols image, fromIntegral $ rows image) .-. p2 (0.0, 0.0)
name = "examples/sierra.jpg"
data CLIOptions = CLIOptions {
input :: FilePath,
output :: FilePath,

View file

@ -96,10 +96,6 @@ findTriangles edges = S.unions . S.map threeCyclesOf . M.keysSet $ adjacencyMap
adjacencyMap = M.fromListWith S.union . map (second S.singleton) $ (edges ++ edgesReversed)
edgesReversed = map (\(a, b) -> (b, a)) edges
pointsInTriangle tri = []
where
[fst, snd, thrd] = S.toList tri
getPointsInTriangle :: p -> S.Set (P2 Int) -> [(Int, Int)]
getPointsInTriangle image pts = S.toList . S.unions . map S.fromList $ [
@ -123,7 +119,6 @@ getTriangleAverageRGB image (y', x') triangle = blendEqually pixels
points :: [(Int, Int)]
points = getPointsInTriangle image triangle
-- I got so upset that I put this function in here instead of in general scope that I went to bed for the night.
index' :: (Int, Int) -> Maybe Pixel_
index' (y, x)
| y >= y' = Nothing
@ -150,9 +145,6 @@ range' a b = [(min a b) .. (max a b)]
yAt :: LineMXB -> Int -> Int
yAt (LineMXB {m = m, b = b}) x = round $ (m * (fromIntegral x)) + b
-- -- y = mx + b
-- -- y - mx = b
makeLine :: (Int, Int) -> (Int, Int) -> LineMXB
makeLine (y1, x1) (y2, x2) = LineMXB {
m = slope,
@ -172,16 +164,3 @@ data LineMXB = LineMXB
startX :: Int,
endX :: Int
} deriving (Show, Ord, Eq)
-- isPointInTriangle :: Triangle -> Point -> Bool
-- isPointInTriangle (v1, v2, v3) pt = not (has_neg && has_pos)
-- where
-- d1 = sign pt v1 v2
-- d2 = sign pt v2 v3
-- d3 = sign pt v3 v1
-- has_neg = (d1 < 0) || (d2 < 0) || (d3 < 0)
-- has_pos = (d1 > 0) || (d2 > 0) || (d3 > 0)
-- sign :: Point -> Point -> Point -> Int
-- sign p1 p2 p3 = (fst p1 - fst p3) * (snd p2 - snd p3) - (fst p2 - fst p3) * (snd p1 - snd p3)