@@ -2,6 +2,7 @@ module Recursion where
22
33import Basics (Nat )
44import Tree (findAllPaths )
5+ import qualified Data.Vector as V
56
67{-
78 Recursion: the program call itself
@@ -336,11 +337,11 @@ complement a (x:xs)
336337 | otherwise = x: complement a xs
337338
338339-- Insert the character/string to every index of the input
339- appendPermHelper :: String -> String -> Nat -> [String ]
340- appendPermHelper str c ind
341- | ind > length str = []
342- | otherwise = (fstHalf ++ c ++ sndHalf): appendPermHelper str c (ind+ 1 )
343- where (fstHalf,sndHalf) = splitAt ind str
340+ -- appendPermHelper :: String -> String -> Nat -> [String]
341+ -- appendPermHelper str c ind
342+ -- | ind > length str = []
343+ -- | otherwise = (fstHalf ++ c ++ sndHalf): appendPermHelper str c (ind+1)
344+ -- where (fstHalf,sndHalf) = splitAt ind str
344345
345346-- Insert the character/string to every index of the input with no duplicates
346347appendPermHelper' :: String -> String -> Nat -> [String ] -> [String ]
@@ -364,6 +365,109 @@ appendPermHelper' str c ind acc
364365paren :: String
365366paren = " ()"
366367
367- -- generate all possible valid parentheses
368+ -- Generate all possible valid parentheses
368369genPerm' :: [String ] -> [String ]
369370genPerm' = genPermHelper [[] ]
371+
372+ {-
373+ 8.10
374+ Implement the "paint fill" function that one might see on many image
375+ editing programs. That is, given a screen (represented by a
376+ two-dimensional array of colors), a point, and a new color, fill in
377+ the surrounding area until the color changes from the original color.
378+ -}
379+
380+ data Color = Red | Yellow | Blue deriving Show
381+
382+ instance Eq Color where
383+ Red == Red = True
384+ Red == Yellow = False
385+ Red == Blue = False
386+ Yellow == Yellow = True
387+ Yellow == Blue = True
388+ Yellow == Red = False
389+ Blue == Blue = True
390+ Blue == Yellow = True
391+ Blue == Red = True
392+
393+ data Direction = Up | Down | PLeft | PRight
394+
395+ type Image = V. Vector (V. Vector Color )
396+
397+ image :: Image
398+ image = V. fromList
399+ [
400+ V. fromList [Red , Red , Red ],
401+ V. fromList [Red , Yellow , Red ],
402+ V. fromList [Yellow , Yellow , Blue ]
403+ ]
404+
405+ -- Paint a color in one location
406+ paint :: Image -> (Int , Int ) -> Color -> Image
407+ paint vs (i, j) c =
408+ fstHVects V. ++ V. fromList[newPaintRow] V. ++ V. drop 1 secHVects
409+ where
410+ (fstHVects, secHVects) = V. splitAt i vs
411+ (fstHPaintRow, secHPaintRow) = V. splitAt j (vs V. ! i)
412+ newPaintRow =
413+ fstHPaintRow V. ++ V. fromList[c] V. ++ V. drop 1 secHPaintRow
414+
415+ -- Find all locations which need to paint
416+ findArea :: Image -> (Int , Int ) -> [(Int , Int )]
417+ findArea img (i,j) = uniq (
418+ findAreaOnDir img (i,j) boundC Up ++
419+ findAreaOnDir img (i,j) boundC Down ++
420+ findAreaOnDir img (i,j) boundC PLeft ++
421+ findAreaOnDir img (i,j) boundC PRight ) []
422+ where boundC = img V. ! i V. ! j
423+
424+ uniq :: [(Int , Int )] -> [(Int , Int )]-> [(Int , Int )]
425+ uniq [] buf = buf
426+ uniq (x: xs) buf
427+ | x `elem` buf = uniq xs buf
428+ | otherwise = uniq xs (x: buf)
429+
430+ findAreaOnDir :: Image -> (Int , Int ) -> Color -> Direction -> [(Int , Int )]
431+ findAreaOnDir img (i,j) c Up
432+ | isInBound img (i,j- 1 ) && selectC == c =
433+ (i,j- 1 ): findAreaOnDir img (i,j- 1 ) c PLeft
434+ | isInBound img (i- 1 ,j) && selectC == c =
435+ (i- 1 ,j): findAreaOnDir img (i- 1 ,j) c Up
436+ | isInBound img (i,j+ 1 ) && selectC == c =
437+ (i,j+ 1 ): findAreaOnDir img (i,j+ 1 ) c PRight
438+ | otherwise = []
439+ where selectC = img V. ! i V. ! j
440+ findAreaOnDir img (i,j) c Down
441+ | isInBound img (i,j- 1 ) && selectC == c =
442+ (i,j- 1 ): findAreaOnDir img (i,j- 1 ) c PLeft
443+ | isInBound img (i+ 1 , j) && selectC == c =
444+ (i+ 1 ,j): findAreaOnDir img (i+ 1 ,j) c Down
445+ | isInBound img (i,j+ 1 ) && selectC == c =
446+ (i,j+ 1 ): findAreaOnDir img (i,j+ 1 ) c PRight
447+ | otherwise = []
448+ where selectC = img V. ! i V. ! j
449+ findAreaOnDir img (i,j) c PLeft
450+ | isInBound img (i- 1 , j) && selectC == c =
451+ (i- 1 ,j): findAreaOnDir img (i- 1 ,j) c Up
452+ | isInBound img (i,j- 1 ) && selectC == c =
453+ (i,j- 1 ): findAreaOnDir img (i,j- 1 ) c PLeft
454+ | isInBound img (i+ 1 ,j) && selectC == c =
455+ (i+ 1 ,j): findAreaOnDir img (i+ 1 ,j) c Down
456+ | otherwise = []
457+ where selectC = img V. ! i V. ! j
458+ findAreaOnDir img (i,j) c PRight
459+ | isInBound img (i- 1 ,j) && selectC == c =
460+ (i- 1 ,j): findAreaOnDir img (i- 1 ,j) c Up
461+ | isInBound img (i,j+ 1 ) && selectC == c =
462+ (i,j+ 1 ): findAreaOnDir img (i,j+ 1 ) c PRight
463+ | isInBound img (i+ 1 ,j) && selectC == c =
464+ (i+ 1 ,j): findAreaOnDir img (i+ 1 ,j) c Down
465+ | otherwise = []
466+ where selectC = img V. ! i V. ! j
467+
468+ isInBound :: Image -> (Int , Int ) -> Bool
469+ isInBound img (i,j)
470+ | (0 <= i && i < xBound) && (0 <= j && j < yBound) = True
471+ | otherwise = False
472+ where xBound = length img
473+ yBound = length $ img V. ! 0
0 commit comments