{-# LANGUAGE PatternGuards #-}
module Brillo.Data.Extent (
Extent,
Coord,
makeExtent,
takeExtent,
squareExtent,
sizeOfExtent,
isUnitExtent,
coordInExtent,
pointInExtent,
centerCoordOfExtent,
cutQuadOfExtent,
quadOfCoord,
pathToCoord,
intersectSegExtent,
touchesSegExtent,
)
where
import Brillo.Data.Point
import Brillo.Data.Quad
import Brillo.Geometry.Line
import Data.Maybe
data Extent
= Extent Int Int Int Int
deriving (Extent -> Extent -> Bool
(Extent -> Extent -> Bool)
-> (Extent -> Extent -> Bool) -> Eq Extent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Extent -> Extent -> Bool
== :: Extent -> Extent -> Bool
$c/= :: Extent -> Extent -> Bool
/= :: Extent -> Extent -> Bool
Eq, Int -> Extent -> ShowS
[Extent] -> ShowS
Extent -> String
(Int -> Extent -> ShowS)
-> (Extent -> String) -> ([Extent] -> ShowS) -> Show Extent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Extent -> ShowS
showsPrec :: Int -> Extent -> ShowS
$cshow :: Extent -> String
show :: Extent -> String
$cshowList :: [Extent] -> ShowS
showList :: [Extent] -> ShowS
Show)
type Coord =
(Int, Int)
makeExtent
:: Int
-> Int
-> Int
-> Int
-> Extent
makeExtent :: Int -> Int -> Int -> Int -> Extent
makeExtent Int
n Int
s Int
e Int
w
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
s
, Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
w =
Int -> Int -> Int -> Int -> Extent
Extent Int
n Int
s Int
e Int
w
| Bool
otherwise =
String -> Extent
forall a. HasCallStack => String -> a
error String
"Brillo.Geometry.Extent.makeExtent: invalid extent"
takeExtent :: Extent -> (Int, Int, Int, Int)
takeExtent :: Extent -> (Int, Int, Int, Int)
takeExtent (Extent Int
n Int
s Int
e Int
w) =
(Int
n, Int
s, Int
e, Int
w)
squareExtent :: Int -> Extent
squareExtent :: Int -> Extent
squareExtent Int
i =
Int -> Int -> Int -> Int -> Extent
Extent Int
i Int
0 Int
i Int
0
sizeOfExtent :: Extent -> (Int, Int)
sizeOfExtent :: Extent -> (Int, Int)
sizeOfExtent (Extent Int
n Int
s Int
e Int
w) =
(Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
w, Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
s)
isUnitExtent :: Extent -> Bool
isUnitExtent :: Extent -> Bool
isUnitExtent Extent
extent =
Extent -> (Int, Int)
sizeOfExtent Extent
extent (Int, Int) -> (Int, Int) -> Bool
forall a. Eq a => a -> a -> Bool
== (Int
1, Int
1)
coordInExtent :: Extent -> Coord -> Bool
coordInExtent :: Extent -> (Int, Int) -> Bool
coordInExtent (Extent Int
n Int
s Int
e Int
w) (Int
x, Int
y) =
Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
w
Bool -> Bool -> Bool
&& Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
e
Bool -> Bool -> Bool
&& Int
y Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
s
Bool -> Bool -> Bool
&& Int
y Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
n
pointInExtent :: Extent -> Point -> Bool
pointInExtent :: Extent -> Point -> Bool
pointInExtent (Extent Int
n Int
s Int
e Int
w) (Float
x, Float
y) =
let n' :: Float
n' = Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n
s' :: Float
s' = Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s
e' :: Float
e' = Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
e
w' :: Float
w' = Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
w
in Float
x Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= Float
w'
Bool -> Bool -> Bool
&& Float
x Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
<= Float
e'
Bool -> Bool -> Bool
&& Float
y Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= Float
s'
Bool -> Bool -> Bool
&& Float
y Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
<= Float
n'
centerCoordOfExtent :: Extent -> (Int, Int)
centerCoordOfExtent :: Extent -> (Int, Int)
centerCoordOfExtent (Extent Int
n Int
s Int
e Int
w) =
( Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
w) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2
, Int
s Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
s) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2
)
cutQuadOfExtent :: Quad -> Extent -> Extent
cutQuadOfExtent :: Quad -> Extent -> Extent
cutQuadOfExtent Quad
quad (Extent Int
n Int
s Int
e Int
w) =
let hheight :: Int
hheight = (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
s) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2
hwidth :: Int
hwidth = (Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
w) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2
in case Quad
quad of
Quad
NW -> Int -> Int -> Int -> Int -> Extent
Extent Int
n (Int
s Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
hheight) (Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
hwidth) Int
w
Quad
NE -> Int -> Int -> Int -> Int -> Extent
Extent Int
n (Int
s Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
hheight) Int
e (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
hwidth)
Quad
SW -> Int -> Int -> Int -> Int -> Extent
Extent (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
hheight) Int
s (Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
hwidth) Int
w
Quad
SE -> Int -> Int -> Int -> Int -> Extent
Extent (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
hheight) Int
s Int
e (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
hwidth)
quadOfCoord :: Extent -> Coord -> Maybe Quad
quadOfCoord :: Extent -> (Int, Int) -> Maybe Quad
quadOfCoord Extent
extent (Int, Int)
coord =
[Quad] -> Maybe Quad
forall a. [a] -> Maybe a
listToMaybe ([Quad] -> Maybe Quad) -> [Quad] -> Maybe Quad
forall a b. (a -> b) -> a -> b
$
(Quad -> Bool) -> [Quad] -> [Quad]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Quad
q -> Extent -> (Int, Int) -> Bool
coordInExtent (Quad -> Extent -> Extent
cutQuadOfExtent Quad
q Extent
extent) (Int, Int)
coord) ([Quad] -> [Quad]) -> [Quad] -> [Quad]
forall a b. (a -> b) -> a -> b
$
[Quad]
allQuads
pathToCoord :: Extent -> Coord -> Maybe [Quad]
pathToCoord :: Extent -> (Int, Int) -> Maybe [Quad]
pathToCoord Extent
extent (Int, Int)
coord
| Extent -> Bool
isUnitExtent Extent
extent =
[Quad] -> Maybe [Quad]
forall a. a -> Maybe a
Just []
| Bool
otherwise =
do
Quad
quad <- Extent -> (Int, Int) -> Maybe Quad
quadOfCoord Extent
extent (Int, Int)
coord
[Quad]
rest <- Extent -> (Int, Int) -> Maybe [Quad]
pathToCoord (Quad -> Extent -> Extent
cutQuadOfExtent Quad
quad Extent
extent) (Int, Int)
coord
[Quad] -> Maybe [Quad]
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Quad] -> Maybe [Quad]) -> [Quad] -> Maybe [Quad]
forall a b. (a -> b) -> a -> b
$ Quad
quad Quad -> [Quad] -> [Quad]
forall a. a -> [a] -> [a]
: [Quad]
rest
intersectSegExtent :: Point -> Point -> Extent -> Maybe Point
intersectSegExtent :: Point -> Point -> Extent -> Maybe Point
intersectSegExtent p1 :: Point
p1@(Float
x1, Float
y1) Point
p2 (Extent Int
n' Int
s' Int
e' Int
w')
| Float
y1 Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
s
, Just Point
pos <- Point -> Point -> Float -> Float -> Float -> Maybe Point
intersectSegHorzSeg Point
p1 Point
p2 Float
s Float
w Float
e =
Point -> Maybe Point
forall a. a -> Maybe a
Just Point
pos
| Float
y1 Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
n
, Just Point
pos <- Point -> Point -> Float -> Float -> Float -> Maybe Point
intersectSegHorzSeg Point
p1 Point
p2 Float
n Float
w Float
e =
Point -> Maybe Point
forall a. a -> Maybe a
Just Point
pos
| Float
x1 Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
w
, Just Point
pos <- Point -> Point -> Float -> Float -> Float -> Maybe Point
intersectSegVertSeg Point
p1 Point
p2 Float
w Float
s Float
n =
Point -> Maybe Point
forall a. a -> Maybe a
Just Point
pos
| Float
x1 Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
e
, Just Point
pos <- Point -> Point -> Float -> Float -> Float -> Maybe Point
intersectSegVertSeg Point
p1 Point
p2 Float
e Float
s Float
n =
Point -> Maybe Point
forall a. a -> Maybe a
Just Point
pos
| Bool
otherwise =
Maybe Point
forall a. Maybe a
Nothing
where
n :: Float
n = Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n'
s :: Float
s = Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s'
e :: Float
e = Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
e'
w :: Float
w = Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
w'
touchesSegExtent :: Point -> Point -> Extent -> Bool
touchesSegExtent :: Point -> Point -> Extent -> Bool
touchesSegExtent Point
p1 Point
p2 Extent
extent =
Extent -> Point -> Bool
pointInExtent Extent
extent Point
p1
Bool -> Bool -> Bool
|| Extent -> Point -> Bool
pointInExtent Extent
extent Point
p2
Bool -> Bool -> Bool
|| Maybe Point -> Bool
forall a. Maybe a -> Bool
isJust (Point -> Point -> Extent -> Maybe Point
intersectSegExtent Point
p1 Point
p2 Extent
extent)