{-# LANGUAGE TypeFamilies, FlexibleContexts, DeriveGeneric #-}
module Math.Geometry.Grid.HexagonalInternal where
import Prelude hiding (null)
import Data.Function (on)
import Data.List (groupBy, sortBy)
import Data.Ord (comparing)
import GHC.Generics (Generic)
import Math.Geometry.GridInternal
data HexDirection = West | Northwest | Northeast | East | Southeast | 
                      Southwest deriving (Int -> HexDirection -> ShowS
[HexDirection] -> ShowS
HexDirection -> String
(Int -> HexDirection -> ShowS)
-> (HexDirection -> String)
-> ([HexDirection] -> ShowS)
-> Show HexDirection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HexDirection] -> ShowS
$cshowList :: [HexDirection] -> ShowS
show :: HexDirection -> String
$cshow :: HexDirection -> String
showsPrec :: Int -> HexDirection -> ShowS
$cshowsPrec :: Int -> HexDirection -> ShowS
Show, HexDirection -> HexDirection -> Bool
(HexDirection -> HexDirection -> Bool)
-> (HexDirection -> HexDirection -> Bool) -> Eq HexDirection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HexDirection -> HexDirection -> Bool
$c/= :: HexDirection -> HexDirection -> Bool
== :: HexDirection -> HexDirection -> Bool
$c== :: HexDirection -> HexDirection -> Bool
Eq, (forall x. HexDirection -> Rep HexDirection x)
-> (forall x. Rep HexDirection x -> HexDirection)
-> Generic HexDirection
forall x. Rep HexDirection x -> HexDirection
forall x. HexDirection -> Rep HexDirection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HexDirection x -> HexDirection
$cfrom :: forall x. HexDirection -> Rep HexDirection x
Generic)
data UnboundedHexGrid = UnboundedHexGrid deriving (Int -> UnboundedHexGrid -> ShowS
[UnboundedHexGrid] -> ShowS
UnboundedHexGrid -> String
(Int -> UnboundedHexGrid -> ShowS)
-> (UnboundedHexGrid -> String)
-> ([UnboundedHexGrid] -> ShowS)
-> Show UnboundedHexGrid
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnboundedHexGrid] -> ShowS
$cshowList :: [UnboundedHexGrid] -> ShowS
show :: UnboundedHexGrid -> String
$cshow :: UnboundedHexGrid -> String
showsPrec :: Int -> UnboundedHexGrid -> ShowS
$cshowsPrec :: Int -> UnboundedHexGrid -> ShowS
Show, UnboundedHexGrid -> UnboundedHexGrid -> Bool
(UnboundedHexGrid -> UnboundedHexGrid -> Bool)
-> (UnboundedHexGrid -> UnboundedHexGrid -> Bool)
-> Eq UnboundedHexGrid
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnboundedHexGrid -> UnboundedHexGrid -> Bool
$c/= :: UnboundedHexGrid -> UnboundedHexGrid -> Bool
== :: UnboundedHexGrid -> UnboundedHexGrid -> Bool
$c== :: UnboundedHexGrid -> UnboundedHexGrid -> Bool
Eq, (forall x. UnboundedHexGrid -> Rep UnboundedHexGrid x)
-> (forall x. Rep UnboundedHexGrid x -> UnboundedHexGrid)
-> Generic UnboundedHexGrid
forall x. Rep UnboundedHexGrid x -> UnboundedHexGrid
forall x. UnboundedHexGrid -> Rep UnboundedHexGrid x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UnboundedHexGrid x -> UnboundedHexGrid
$cfrom :: forall x. UnboundedHexGrid -> Rep UnboundedHexGrid x
Generic)
instance Grid UnboundedHexGrid where
  type Index UnboundedHexGrid = (Int, Int)
  type Direction UnboundedHexGrid = HexDirection
  indices :: UnboundedHexGrid -> [Index UnboundedHexGrid]
indices UnboundedHexGrid
_ = [Index UnboundedHexGrid]
forall a. HasCallStack => a
undefined
  neighbours :: UnboundedHexGrid
-> Index UnboundedHexGrid -> [Index UnboundedHexGrid]
neighbours UnboundedHexGrid
_ (x,y) = 
    [(Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1,Int
y), (Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1,Int
yInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1), (Int
x,Int
yInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1), (Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1,Int
y), (Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1,Int
yInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1), (Int
x,Int
yInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)]
  distance :: UnboundedHexGrid
-> Index UnboundedHexGrid -> Index UnboundedHexGrid -> Int
distance UnboundedHexGrid
_ (x1, y1) (x2, y2) = 
    [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [Int -> Int
forall a. Num a => a -> a
abs (Int
x2Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
x1), Int -> Int
forall a. Num a => a -> a
abs (Int
y2Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
y1), Int -> Int
forall a. Num a => a -> a
abs(Int
z2Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
z1)]
    where z1 :: Int
z1 = -Int
x1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
y1
          z2 :: Int
z2 = -Int
x2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
y2
  directionTo :: UnboundedHexGrid
-> Index UnboundedHexGrid
-> Index UnboundedHexGrid
-> [Direction UnboundedHexGrid]
directionTo UnboundedHexGrid
_ (x1, y1) (x2, y2) = [HexDirection] -> [HexDirection]
f1 ([HexDirection] -> [HexDirection])
-> ([HexDirection] -> [HexDirection])
-> [HexDirection]
-> [HexDirection]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [HexDirection] -> [HexDirection]
f2 ([HexDirection] -> [HexDirection])
-> ([HexDirection] -> [HexDirection])
-> [HexDirection]
-> [HexDirection]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [HexDirection] -> [HexDirection]
f3 ([HexDirection] -> [HexDirection])
-> ([HexDirection] -> [HexDirection])
-> [HexDirection]
-> [HexDirection]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [HexDirection] -> [HexDirection]
f4 ([HexDirection] -> [HexDirection])
-> ([HexDirection] -> [HexDirection])
-> [HexDirection]
-> [HexDirection]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [HexDirection] -> [HexDirection]
f5 ([HexDirection] -> [HexDirection])
-> ([HexDirection] -> [HexDirection])
-> [HexDirection]
-> [HexDirection]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [HexDirection] -> [HexDirection]
f6 ([HexDirection] -> [HexDirection])
-> [HexDirection] -> [HexDirection]
forall a b. (a -> b) -> a -> b
$ []
    where f1 :: [HexDirection] -> [HexDirection]
f1 [HexDirection]
ds =  if Int
dx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
&& Int
dz Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then HexDirection
WestHexDirection -> [HexDirection] -> [HexDirection]
forall a. a -> [a] -> [a]
:[HexDirection]
ds else [HexDirection]
ds
          f2 :: [HexDirection] -> [HexDirection]
f2 [HexDirection]
ds =  if Int
dx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
&& Int
dy Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then HexDirection
NorthwestHexDirection -> [HexDirection] -> [HexDirection]
forall a. a -> [a] -> [a]
:[HexDirection]
ds else [HexDirection]
ds
          f3 :: [HexDirection] -> [HexDirection]
f3 [HexDirection]
ds =  if Int
dy Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
&& Int
dz Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 then HexDirection
NortheastHexDirection -> [HexDirection] -> [HexDirection]
forall a. a -> [a] -> [a]
:[HexDirection]
ds else [HexDirection]
ds
          f4 :: [HexDirection] -> [HexDirection]
f4 [HexDirection]
ds =  if Int
dx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
&& Int
dz Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 then HexDirection
EastHexDirection -> [HexDirection] -> [HexDirection]
forall a. a -> [a] -> [a]
:[HexDirection]
ds else [HexDirection]
ds
          f5 :: [HexDirection] -> [HexDirection]
f5 [HexDirection]
ds =  if Int
dx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
&& Int
dy Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 then HexDirection
SoutheastHexDirection -> [HexDirection] -> [HexDirection]
forall a. a -> [a] -> [a]
:[HexDirection]
ds else [HexDirection]
ds
          f6 :: [HexDirection] -> [HexDirection]
f6 [HexDirection]
ds =  if Int
dy Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
&& Int
dz Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then HexDirection
SouthwestHexDirection -> [HexDirection] -> [HexDirection]
forall a. a -> [a] -> [a]
:[HexDirection]
ds else [HexDirection]
ds
          dx :: Int
dx = Int
x2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
x1
          dy :: Int
dy = Int
y2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
y1
          z1 :: Int
z1 = -Int
x1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
y1
          z2 :: Int
z2 = -Int
x2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
y2
          dz :: Int
dz = Int
z2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
z1
  contains :: UnboundedHexGrid -> Index UnboundedHexGrid -> Bool
contains UnboundedHexGrid
_ Index UnboundedHexGrid
_ = Bool
True
  null :: UnboundedHexGrid -> Bool
null UnboundedHexGrid
_ = Bool
False
  nonNull :: UnboundedHexGrid -> Bool
nonNull UnboundedHexGrid
_ = Bool
True
data HexHexGrid = HexHexGrid Int [(Int, Int)] deriving (HexHexGrid -> HexHexGrid -> Bool
(HexHexGrid -> HexHexGrid -> Bool)
-> (HexHexGrid -> HexHexGrid -> Bool) -> Eq HexHexGrid
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HexHexGrid -> HexHexGrid -> Bool
$c/= :: HexHexGrid -> HexHexGrid -> Bool
== :: HexHexGrid -> HexHexGrid -> Bool
$c== :: HexHexGrid -> HexHexGrid -> Bool
Eq, (forall x. HexHexGrid -> Rep HexHexGrid x)
-> (forall x. Rep HexHexGrid x -> HexHexGrid) -> Generic HexHexGrid
forall x. Rep HexHexGrid x -> HexHexGrid
forall x. HexHexGrid -> Rep HexHexGrid x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HexHexGrid x -> HexHexGrid
$cfrom :: forall x. HexHexGrid -> Rep HexHexGrid x
Generic)
instance Show HexHexGrid where show :: HexHexGrid -> String
show (HexHexGrid Int
s [(Int, Int)]
_) = String
"hexHexGrid " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
s
instance Grid HexHexGrid where
  type Index HexHexGrid = (Int, Int)
  type Direction HexHexGrid = HexDirection
  indices :: HexHexGrid -> [Index HexHexGrid]
indices (HexHexGrid Int
_ [(Int, Int)]
xs) = [(Int, Int)]
[Index HexHexGrid]
xs
  neighbours :: HexHexGrid -> Index HexHexGrid -> [Index HexHexGrid]
neighbours = UnboundedHexGrid
-> HexHexGrid -> Index HexHexGrid -> [Index HexHexGrid]
forall u g.
(Eq (Index u), Grid g, Grid u, Index g ~ Index u) =>
u -> g -> Index g -> [Index g]
neighboursBasedOn UnboundedHexGrid
UnboundedHexGrid
  distance :: HexHexGrid -> Index HexHexGrid -> Index HexHexGrid -> Int
distance = UnboundedHexGrid
-> HexHexGrid -> Index HexHexGrid -> Index HexHexGrid -> Int
forall g u.
(Eq (Index g), Grid g, Grid u, Index g ~ Index u) =>
u -> g -> Index g -> Index g -> Int
distanceBasedOn UnboundedHexGrid
UnboundedHexGrid
  directionTo :: HexHexGrid
-> Index HexHexGrid -> Index HexHexGrid -> [Direction HexHexGrid]
directionTo = UnboundedHexGrid
-> HexHexGrid
-> Index HexHexGrid
-> Index HexHexGrid
-> [Direction HexHexGrid]
forall g u.
(Eq (Index g), Eq (Direction g), Grid g, Grid u, Index g ~ Index u,
 Direction g ~ Direction u) =>
u -> g -> Index g -> Index g -> [Direction g]
directionToBasedOn UnboundedHexGrid
UnboundedHexGrid
  contains :: HexHexGrid -> Index HexHexGrid -> Bool
contains HexHexGrid
g (x,y) = -Int
Size HexHexGrid
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
x Bool -> Bool -> Bool
&& Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
Size HexHexGrid
s Bool -> Bool -> Bool
&& Bool
check
    where s :: Size HexHexGrid
s = HexHexGrid -> Size HexHexGrid
forall g. FiniteGrid g => g -> Size g
size HexHexGrid
g
          check :: Bool
check = if Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0
                    then -Int
Size HexHexGrid
sInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
y Bool -> Bool -> Bool
&& Int
y Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
Size HexHexGrid
s
                    else -Int
Size HexHexGrid
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
y Bool -> Bool -> Bool
&& Int
y Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
Size HexHexGrid
sInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
x
instance FiniteGrid HexHexGrid where
  type Size HexHexGrid = Int
  size :: HexHexGrid -> Size HexHexGrid
size (HexHexGrid Int
s [(Int, Int)]
_) = Int
Size HexHexGrid
s
  maxPossibleDistance :: HexHexGrid -> Int
maxPossibleDistance g :: HexHexGrid
g@(HexHexGrid Int
s [(Int, Int)]
_) = HexHexGrid -> Index HexHexGrid -> Index HexHexGrid -> Int
forall g. Grid g => g -> Index g -> Index g -> Int
distance HexHexGrid
g (-Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1,Int
0) (Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1,Int
0)
instance BoundedGrid HexHexGrid where
  tileSideCount :: HexHexGrid -> Int
tileSideCount HexHexGrid
_ = Int
6
  boundary :: HexHexGrid -> [Index HexHexGrid]
boundary HexHexGrid
g = 
    [(Int, Int)]
north [(Int, Int)] -> [(Int, Int)] -> [(Int, Int)]
forall a. [a] -> [a] -> [a]
++ [(Int, Int)]
northeast [(Int, Int)] -> [(Int, Int)] -> [(Int, Int)]
forall a. [a] -> [a] -> [a]
++ [(Int, Int)]
southeast [(Int, Int)] -> [(Int, Int)] -> [(Int, Int)]
forall a. [a] -> [a] -> [a]
++ [(Int, Int)]
south [(Int, Int)] -> [(Int, Int)] -> [(Int, Int)]
forall a. [a] -> [a] -> [a]
++ [(Int, Int)]
southwest [(Int, Int)] -> [(Int, Int)] -> [(Int, Int)]
forall a. [a] -> [a] -> [a]
++ [(Int, Int)]
northwest
    where s :: Size HexHexGrid
s = HexHexGrid -> Size HexHexGrid
forall g. FiniteGrid g => g -> Size g
size HexHexGrid
g
          north :: [(Int, Int)]
north = [(Int
k,Int
Size HexHexGrid
sInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) | Int
k <- [-Int
Size HexHexGrid
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1,-Int
Size HexHexGrid
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
2..Int
0]]
          northeast :: [(Int, Int)]
northeast = [(Int
k,Int
Size HexHexGrid
sInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
k) | Int
k <- [Int
1,Int
2..Int
Size HexHexGrid
sInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1]]
          southeast :: [(Int, Int)]
southeast = [(Int
Size HexHexGrid
sInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1,Int
k) | Int
k <- [-Int
1,-Int
2..(-Int
Size HexHexGrid
s)Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1]]
          south :: [(Int, Int)]
south = [(Int
k,(-Int
Size HexHexGrid
s)Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) | Int
k <- [Int
Size HexHexGrid
sInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
2,Int
Size HexHexGrid
sInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
3..Int
0]]
          southwest :: [(Int, Int)]
southwest = [(Int
k,(-Int
Size HexHexGrid
s)Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
k) | Int
k <- [-Int
1,-Int
2..(-Int
Size HexHexGrid
s)Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1]]
          northwest :: [(Int, Int)]
northwest = [(-Int
Size HexHexGrid
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1,Int
k) | Int
k <- [Int
1,Int
2..Int
Size HexHexGrid
sInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
2]]
  centre :: HexHexGrid -> [Index HexHexGrid]
centre HexHexGrid
_ = [(Int
0,Int
0)]
hexHexGrid :: Int -> HexHexGrid
hexHexGrid :: Int -> HexHexGrid
hexHexGrid Int
r = Int -> [(Int, Int)] -> HexHexGrid
HexHexGrid Int
r [(Int
x, Int
y) | Int
x <- [-Int
rInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1..Int
rInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1], Int
y <- Int -> [Int]
f Int
x]
  where f :: Int -> [Int]
f Int
x = if Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 then [Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
rInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
x .. Int
rInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1] else [Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
r .. Int
rInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
x]
data ParaHexGrid = ParaHexGrid (Int, Int) [(Int, Int)]
  deriving (ParaHexGrid -> ParaHexGrid -> Bool
(ParaHexGrid -> ParaHexGrid -> Bool)
-> (ParaHexGrid -> ParaHexGrid -> Bool) -> Eq ParaHexGrid
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParaHexGrid -> ParaHexGrid -> Bool
$c/= :: ParaHexGrid -> ParaHexGrid -> Bool
== :: ParaHexGrid -> ParaHexGrid -> Bool
$c== :: ParaHexGrid -> ParaHexGrid -> Bool
Eq, (forall x. ParaHexGrid -> Rep ParaHexGrid x)
-> (forall x. Rep ParaHexGrid x -> ParaHexGrid)
-> Generic ParaHexGrid
forall x. Rep ParaHexGrid x -> ParaHexGrid
forall x. ParaHexGrid -> Rep ParaHexGrid x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ParaHexGrid x -> ParaHexGrid
$cfrom :: forall x. ParaHexGrid -> Rep ParaHexGrid x
Generic)
instance Show ParaHexGrid where 
  show :: ParaHexGrid -> String
show (ParaHexGrid (Int
r,Int
c) [(Int, Int)]
_) = String
"paraHexGrid " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
r String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
c
instance Grid ParaHexGrid where
  type Index ParaHexGrid = (Int, Int)
  type Direction ParaHexGrid = HexDirection
  indices :: ParaHexGrid -> [Index ParaHexGrid]
indices (ParaHexGrid (Int, Int)
_ [(Int, Int)]
xs) = [(Int, Int)]
[Index ParaHexGrid]
xs
  neighbours :: ParaHexGrid -> Index ParaHexGrid -> [Index ParaHexGrid]
neighbours = UnboundedHexGrid
-> ParaHexGrid -> Index ParaHexGrid -> [Index ParaHexGrid]
forall u g.
(Eq (Index u), Grid g, Grid u, Index g ~ Index u) =>
u -> g -> Index g -> [Index g]
neighboursBasedOn UnboundedHexGrid
UnboundedHexGrid
  distance :: ParaHexGrid -> Index ParaHexGrid -> Index ParaHexGrid -> Int
distance = UnboundedHexGrid
-> ParaHexGrid -> Index ParaHexGrid -> Index ParaHexGrid -> Int
forall g u.
(Eq (Index g), Grid g, Grid u, Index g ~ Index u) =>
u -> g -> Index g -> Index g -> Int
distanceBasedOn UnboundedHexGrid
UnboundedHexGrid
  directionTo :: ParaHexGrid
-> Index ParaHexGrid
-> Index ParaHexGrid
-> [Direction ParaHexGrid]
directionTo = UnboundedHexGrid
-> ParaHexGrid
-> Index ParaHexGrid
-> Index ParaHexGrid
-> [Direction ParaHexGrid]
forall g u.
(Eq (Index g), Eq (Direction g), Grid g, Grid u, Index g ~ Index u,
 Direction g ~ Direction u) =>
u -> g -> Index g -> Index g -> [Direction g]
directionToBasedOn UnboundedHexGrid
UnboundedHexGrid
  contains :: ParaHexGrid -> Index ParaHexGrid -> Bool
contains ParaHexGrid
g (x,y) = Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
x Bool -> Bool -> Bool
&& Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
c Bool -> Bool -> Bool
&& Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
y Bool -> Bool -> Bool
&& Int
y Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
r
    where (Int
r,Int
c) = ParaHexGrid -> Size ParaHexGrid
forall g. FiniteGrid g => g -> Size g
size ParaHexGrid
g
instance FiniteGrid ParaHexGrid where
  type Size ParaHexGrid = (Int, Int)
  size :: ParaHexGrid -> Size ParaHexGrid
size (ParaHexGrid (Int, Int)
s [(Int, Int)]
_) = (Int, Int)
Size ParaHexGrid
s
  maxPossibleDistance :: ParaHexGrid -> Int
maxPossibleDistance g :: ParaHexGrid
g@(ParaHexGrid (Int
r,Int
c) [(Int, Int)]
_) = 
    ParaHexGrid -> Index ParaHexGrid -> Index ParaHexGrid -> Int
forall g. Grid g => g -> Index g -> Index g -> Int
distance ParaHexGrid
g (Int
0,Int
0) (Int
cInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1,Int
rInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
instance BoundedGrid ParaHexGrid where
  tileSideCount :: ParaHexGrid -> Int
tileSideCount ParaHexGrid
_ = Int
6
  boundary :: ParaHexGrid -> [Index ParaHexGrid]
boundary ParaHexGrid
g = (Int, Int) -> [(Int, Int)]
forall r c.
(Enum r, Enum c, Num r, Num c, Ord r, Ord c) =>
(r, c) -> [(c, r)]
cartesianIndices ((Int, Int) -> [(Int, Int)])
-> (ParaHexGrid -> (Int, Int)) -> ParaHexGrid -> [(Int, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParaHexGrid -> (Int, Int)
forall g. FiniteGrid g => g -> Size g
size (ParaHexGrid -> [(Int, Int)]) -> ParaHexGrid -> [(Int, Int)]
forall a b. (a -> b) -> a -> b
$ ParaHexGrid
g
  centre :: ParaHexGrid -> [Index ParaHexGrid]
centre ParaHexGrid
g | [[((Int, Int), Int)]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[((Int, Int), Int)]]
xs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1  = (((Int, Int), Int) -> (Int, Int))
-> [((Int, Int), Int)] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map ((Int, Int), Int) -> (Int, Int)
forall a b. (a, b) -> a
fst ([((Int, Int), Int)] -> [(Int, Int)])
-> ([[((Int, Int), Int)]] -> [((Int, Int), Int)])
-> [[((Int, Int), Int)]]
-> [(Int, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[((Int, Int), Int)]] -> [((Int, Int), Int)]
forall a. [a] -> a
head ([[((Int, Int), Int)]] -> [(Int, Int)])
-> [[((Int, Int), Int)]] -> [(Int, Int)]
forall a b. (a -> b) -> a -> b
$ [[((Int, Int), Int)]]
xs
           | [[((Int, Int), Int)]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[((Int, Int), Int)]]
xs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2  = (((Int, Int), Int) -> (Int, Int))
-> [((Int, Int), Int)] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map ((Int, Int), Int) -> (Int, Int)
forall a b. (a, b) -> a
fst ([((Int, Int), Int)] -> [(Int, Int)])
-> ([[((Int, Int), Int)]] -> [((Int, Int), Int)])
-> [[((Int, Int), Int)]]
-> [(Int, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[((Int, Int), Int)]] -> [((Int, Int), Int)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[((Int, Int), Int)]] -> [(Int, Int)])
-> [[((Int, Int), Int)]] -> [(Int, Int)]
forall a b. (a -> b) -> a -> b
$ [[((Int, Int), Int)]]
xs
           | [[((Int, Int), Int)]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[((Int, Int), Int)]]
xs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
3  = (((Int, Int), Int) -> (Int, Int))
-> [((Int, Int), Int)] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map ((Int, Int), Int) -> (Int, Int)
forall a b. (a, b) -> a
fst ([((Int, Int), Int)] -> [(Int, Int)])
-> ([[((Int, Int), Int)]] -> [((Int, Int), Int)])
-> [[((Int, Int), Int)]]
-> [(Int, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[((Int, Int), Int)]] -> [((Int, Int), Int)]
forall a. [a] -> a
head ([[((Int, Int), Int)]] -> [((Int, Int), Int)])
-> ([[((Int, Int), Int)]] -> [[((Int, Int), Int)]])
-> [[((Int, Int), Int)]]
-> [((Int, Int), Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [[((Int, Int), Int)]] -> [[((Int, Int), Int)]]
forall a. Int -> [a] -> [a]
drop Int
1 ([[((Int, Int), Int)]] -> [(Int, Int)])
-> [[((Int, Int), Int)]] -> [(Int, Int)]
forall a b. (a -> b) -> a -> b
$ [[((Int, Int), Int)]]
xs
           | Bool
otherwise      = String -> [(Int, Int)]
forall a. HasCallStack => String -> a
error String
"logic error"
    where xs :: [[((Int, Int), Int)]]
xs = (((Int, Int), Int) -> ((Int, Int), Int) -> Bool)
-> [((Int, Int), Int)] -> [[((Int, Int), Int)]]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
(==) (Int -> Int -> Bool)
-> (((Int, Int), Int) -> Int)
-> ((Int, Int), Int)
-> ((Int, Int), Int)
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` ((Int, Int), Int) -> Int
forall a b. (a, b) -> b
snd) ([((Int, Int), Int)] -> [[((Int, Int), Int)]])
-> (ParaHexGrid -> [((Int, Int), Int)])
-> ParaHexGrid
-> [[((Int, Int), Int)]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((Int, Int), Int) -> ((Int, Int), Int) -> Ordering)
-> [((Int, Int), Int)] -> [((Int, Int), Int)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((((Int, Int), Int) -> Int)
-> ((Int, Int), Int) -> ((Int, Int), Int) -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing ((Int, Int), Int) -> Int
forall a b. (a, b) -> b
snd)
                 ([((Int, Int), Int)] -> [((Int, Int), Int)])
-> (ParaHexGrid -> [((Int, Int), Int)])
-> ParaHexGrid
-> [((Int, Int), Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Int) -> ((Int, Int), Int))
-> [(Int, Int)] -> [((Int, Int), Int)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Int, Int)
a -> ((Int, Int)
a,(Int, Int) -> Int
forall a b. (a, b) -> a
fst (Int, Int)
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int, Int) -> Int
forall a b. (a, b) -> b
snd (Int, Int)
a))
                 ([(Int, Int)] -> [((Int, Int), Int)])
-> (ParaHexGrid -> [(Int, Int)])
-> ParaHexGrid
-> [((Int, Int), Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Int) -> [(Int, Int)]
cartesianCentre ((Int, Int) -> [(Int, Int)])
-> (ParaHexGrid -> (Int, Int)) -> ParaHexGrid -> [(Int, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParaHexGrid -> (Int, Int)
forall g. FiniteGrid g => g -> Size g
size (ParaHexGrid -> [[((Int, Int), Int)]])
-> ParaHexGrid -> [[((Int, Int), Int)]]
forall a b. (a -> b) -> a -> b
$ ParaHexGrid
g
paraHexGrid :: Int -> Int -> ParaHexGrid
paraHexGrid :: Int -> Int -> ParaHexGrid
paraHexGrid Int
r Int
c = 
  (Int, Int) -> [(Int, Int)] -> ParaHexGrid
ParaHexGrid (Int
r,Int
c) [(Int
x, Int
y) | Int
x <- [Int
0..Int
cInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1], Int
y <- [Int
0..Int
rInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1]]