Last active
July 18, 2016 05:32
-
-
Save huseyinyilmaz/4b212ace5cfae808428d8f98bc8575ab to your computer and use it in GitHub Desktop.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- https://leetcode.com/problems/rectangle-area/ | |
module Main where | |
import Test.HUnit | |
import Control.Monad(guard) | |
import Data.List(nub) | |
-- Data Types | |
data Point = Point Int Int | |
deriving (Eq, Show) | |
data Line = HorizontalLine {x1::Int, x2::Int, y::Int} | VerticalLine {x::Int, y1::Int, y2::Int} | |
deriving (Eq, Show) | |
data Rectangle = Rectangle Point Point | |
deriving (Eq, Show) | |
-- Takes 3 items and returns True if they are in order | |
inOrder :: Ord a => a -> a -> a -> Bool | |
inOrder x y z = (x <= y) && (y <= z) | |
-- Gets a Point and rectangle and returns if | |
-- Point is in that particular rectangle | |
isPointInRectangle :: Rectangle -> Point -> Bool | |
isPointInRectangle (Rectangle (Point x1 y1) (Point x2 y2)) (Point x y) = | |
inOrder minX x maxX && inOrder minY y maxY | |
where minX = min x1 x2 | |
maxX = max x1 x2 | |
minY = min y1 y2 | |
maxY = max y1 y2 | |
-- Gets two lines and returns the crossing point of those lines | |
getCrossingPoint :: Line -> Line -> Maybe Point | |
getCrossingPoint (HorizontalLine _ _ _) (HorizontalLine _ _ _) = Nothing | |
getCrossingPoint (VerticalLine _ _ _) (VerticalLine _ _ _) = Nothing | |
getCrossingPoint l1@(VerticalLine _ _ _) l2@(HorizontalLine _ _ _) = getCrossingPoint l2 l1 | |
getCrossingPoint (HorizontalLine x1 x2 y) (VerticalLine x y1 y2) = do | |
guard (inOrder minX x maxX && inOrder minY y maxY) | |
return (Point x y) | |
where minX = min x1 x2 | |
maxX = max x1 x2 | |
minY = min y1 y2 | |
maxY = max y1 y2 | |
-- Get for lines of given rectangle | |
rectangleToLines :: Rectangle -> [Line] | |
rectangleToLines (Rectangle (Point x1 y1) (Point x2 y2)) = | |
[HorizontalLine{x1=x1, x2=x2, y=y1}, | |
HorizontalLine{x1=x1, x2=x2, y=y2}, | |
VerticalLine{x=x1, y1=y1, y2=y2}, | |
VerticalLine{x=x2, y1=y1, y2=y2}] | |
-- Get all Points for given rectangle | |
rectangleToPoints :: Rectangle -> [Point] | |
rectangleToPoints (Rectangle p1@(Point x1 y1) p2@(Point x2 y2)) = | |
[p1, p2, Point x1 y2, Point x2 y1] | |
-- Convert Points to a rectangle | |
pointsToRectangle :: [Point] -> Rectangle | |
pointsToRectangle ps = | |
Rectangle (Point minX minY) (Point maxX maxY) | |
where (xs, ys) = unzip $ fmap (\(Point x y) -> (x, y)) ps | |
minX = minimum xs | |
maxX = maximum xs | |
minY = minimum ys | |
maxY = maximum ys | |
-- Calculates area of given rectangle | |
calculateArea :: Rectangle -> Int | |
calculateArea (Rectangle (Point x1 y1) (Point x2 y2)) = abs ((x1-x2)*(y1-y2)) | |
-- Returns intersection of 2 rectangles | |
getIntersection :: Rectangle -> Rectangle -> Maybe Rectangle | |
getIntersection r1 r2 = do | |
guard (length(allPoints) >= 4) | |
return $ pointsToRectangle allPoints | |
where | |
innerCorners1 = [p |p <- rectangleToPoints r1 , isPointInRectangle r2 p] | |
innerCorners2 = [p |p <- rectangleToPoints r2 , isPointInRectangle r1 p] | |
intersectionPoints = do l1 <- rectangleToLines r1 | |
l2 <- rectangleToLines r2 | |
let maybeCross = getCrossingPoint l1 l2 | |
case maybeCross of | |
Just point -> return point | |
Nothing -> [] | |
allPoints = nub(innerCorners1 ++ innerCorners2 ++ intersectionPoints) | |
-- Calculates area of 2 rectangles. | |
area2 :: Rectangle -> Rectangle -> Int | |
area2 r1 r2 = | |
case maybeIntersection of | |
Just intersection -> (totalArea - (calculateArea intersection)) | |
Nothing -> totalArea | |
where area1 = calculateArea r1 | |
area2 = calculateArea r2 | |
totalArea = (area1 + area2) | |
maybeIntersection = getIntersection r1 r2 | |
----------- | |
-- Tests -- | |
----------- | |
test1 = TestCase (assertEqual "Calculate Separate Rectangle" | |
totalArea | |
(area2 rectangle1 rectangle2) | |
) | |
where | |
rectangle1 = (Rectangle (Point 0 0) (Point 2 2)) | |
rectangle2 = (Rectangle (Point 2 2) (Point 4 4)) | |
totalArea = 8 | |
test2 = TestCase (assertEqual "Calculate with Inner Rectangle" | |
totalArea | |
(area2 rectangle1 rectangle2) | |
) | |
where | |
rectangle1 = (Rectangle (Point 0 0) (Point 10 10)) | |
rectangle2 = (Rectangle (Point 3 3) (Point 5 5)) | |
totalArea = 100 | |
test3 = TestCase (assertEqual "Calculate with One Corner Covered" | |
totalArea | |
(area2 rectangle1 rectangle2) | |
) | |
where | |
rectangle1 = (Rectangle (Point 0 0) (Point 3 3)) | |
rectangle2 = (Rectangle (Point 2 2) (Point 5 5)) | |
totalArea = 17 | |
test4 = TestCase (assertEqual "Calculate with Two Corners Covered" | |
totalArea | |
(area2 rectangle1 rectangle2) | |
) | |
where | |
rectangle1 = (Rectangle (Point 0 0) (Point 5 5)) | |
rectangle2 = (Rectangle (Point 4 1) (Point 6 4)) | |
totalArea = 28 | |
test5 = TestCase (assertEqual "Calculate with Cross rectangles" | |
totalArea | |
(area2 rectangle1 rectangle2) | |
) | |
where | |
rectangle1 = (Rectangle (Point 1 0) (Point 2 3)) | |
rectangle2 = (Rectangle (Point 0 1) (Point 3 2)) | |
totalArea = 5 | |
test6 = TestCase (assertEqual "Calculate with Same rectangle" | |
totalArea | |
(area2 rectangle1 rectangle2) | |
) | |
where | |
rectangle1 = (Rectangle (Point 0 0) (Point 10 10)) | |
rectangle2 = (Rectangle (Point 0 0) (Point 10 10)) | |
totalArea = 100 | |
main = runTestTT $ TestList [test1, test2, test3, test4, test5, test6] |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- https://leetcode.com/problems/rectangle-area/ | |
module Main where | |
import Test.HUnit | |
getArea2 :: (Num a, Ord a) => a -> a -> a -> a -> a -> a -> a -> a -> a | |
getArea2 x11 y11 x12 y12 x21 y21 x22 y22 = | |
(area1 + area2 - intersectionArea) | |
where | |
getArea x1 y1 x2 y2 = if x2>x1 && y2>y1 | |
then (x2-x1)*(y2-y1) | |
else 0 | |
area1 = getArea x11 y11 x12 y12 | |
area2 = getArea x21 y21 x22 y22 | |
-- Calculate intersection start and stop points | |
x31 = max x11 x21 | |
y31 = max y11 y21 | |
x32 = min x12 x22 | |
y32 = min y12 y22 | |
-- If intersection area is negative that means | |
-- there is no intersection between two rectangles. | |
-- In that case Intersection area is set to 0 | |
intersectionArea = getArea x31 y31 x32 y32 | |
----------- | |
-- Tests -- | |
----------- | |
test1 = TestCase (assertEqual "Calculate Separate Rectangle" | |
8 | |
(getArea2 0 0 2 2 2 2 4 4) | |
) | |
test2 = TestCase (assertEqual "Calculate with Inner Rectangle" | |
100 | |
(getArea2 0 0 10 10 3 3 5 5) | |
) | |
test3 = TestCase (assertEqual "Calculate with One Corner Covered" | |
17 | |
(getArea2 0 0 3 3 2 2 5 5) | |
) | |
test4 = TestCase (assertEqual "Calculate with Two Corners Covered" | |
28 | |
(getArea2 0 0 5 5 4 1 6 4) | |
) | |
test5 = TestCase (assertEqual "Calculate with Cross rectangles" | |
5 | |
(getArea2 1 0 2 3 0 1 3 2) | |
) | |
test6 = TestCase (assertEqual "Calculate with Same rectangle" | |
100 | |
(getArea2 0 0 10 10 0 0 10 10) | |
) | |
test7 = TestCase (assertEqual "Calculate with negative point" | |
17 | |
(getArea2 (-2) (-2) 2 2 3 3 4 4) | |
) | |
main = runTestTT $ TestList [test1, test2, test3, test4, test5, test6, test7] |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
def getArea(x1, y1, x2, y2): | |
if x2 > x1 and y2 > y1: | |
return (x2 - x1) * (y2 - y1) | |
else: | |
return 0 | |
class Solution(object): | |
def computeArea(self, A, B, C, D, E, F, G, H): | |
""" | |
:type A: int | |
:type B: int | |
:type C: int | |
:type D: int | |
:type E: int | |
:type F: int | |
:type G: int | |
:type H: int | |
:rtype: int | |
""" | |
area1 = getArea(A, B, C, D) | |
area2 = getArea(E, F, G, H) | |
#print('area1 = %s' % area1) | |
#print('area2 = %s' % area2) | |
x1, y1, x2, y2 = max(A, E), max(B, F), min(C, G), min(D, H) | |
#print 'x1=%s y1=%s x2=%s, y2=%s' % (x1, y1, x2, y2) | |
intersection_area = getArea(x1, y1, x2, y2) | |
#print('intersection_area=%s' % intersection_area) | |
return area1 + area2 - intersection_area |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment