Skip to content

Instantly share code, notes, and snippets.

@mrnkr
Created December 16, 2019 14:16
Show Gist options
  • Save mrnkr/63d5b10c5f8b2cb84f69e99fc59740bb to your computer and use it in GitHub Desktop.
Save mrnkr/63d5b10c5f8b2cb84f69e99fc59740bb to your computer and use it in GitHub Desktop.
Quick coding challenge - find all horizontal rectangles formed given a list of points
module RectangleFinder where
import Prelude hiding ((*))
import qualified Data.Map as Map
type Point = (Int, Int)
countRects :: [Point] -> Int
countRects pts = fst $ foldl processPoints (0, Map.empty) $ filter isAbove $ pts * pts
(*) :: [a] -> [b] -> [(a, b)]
(*) xs ys = [(x,y) | x <- xs, y <- ys]
isAbove :: (Point, Point) -> Bool
isAbove ((x1, y1), (x2, y2)) = y1 > y2 && x1 == x2
processPoints :: (Int, Map.Map (Int, Int) Int) -> (Point, Point) -> (Int, Map.Map (Int, Int) Int)
processPoints (n, m) (p1, p2) = (n + currentValue, Map.insert (snd p1, snd p2) (currentValue + 1) m)
where
currentValue :: Int
currentValue = Map.findWithDefault 0 (snd p1, snd p2) m
testPlain1 :: [Point]
testPlain1 = [
(0,2), (1,2), (2,2),
(0,1), (1,1), (2,1),
(0,0), (1,0), (2,0)]
testPlain2 :: [Point]
testPlain2 = [
(0,1), (1,1), (2,1),
(0,0), (1,0), (2,0)]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment