{-# LANGUAGE ViewPatterns #-} -- | Places. module Place ( -- * Size Size -- * Place , Place , place , coords -- * For performance , hashPlace , unHashPlace , placesInAColumn -- * Useful functions , neighbours ) where import Data.Bits ----------- -- | Size of a board. type Size = (Int, Int) -- | Place on a board (with fixed width). -- -- Simpler but slower implementation: -- -- > data Place = P !Int !Int -- > deriving (Eq, Ord, Show) newtype Place = P Int deriving (Eq, Ord) instance Show Place where show (coords -> (x, y)) = "place " ++ show x ++ " " ++ show y place :: Int -> Int -> Place place i j = P $ shiftL i 8 .|. j coords :: Place -> (Int, Int) coords (P i) = (shiftR i 8, i .&. 255) -- | Perfect hash function. hashPlace :: Place -> Int hashPlace (P i) = i unHashPlace :: Int -> Place unHashPlace = P placesInAColumn :: Int -> (Int, Int) -> [Place] placesInAColumn i (j1, j2) = map P $ [i' + j1 .. i' + j2] where i' = shiftL i 8 -- | Neighbours of a place. -- -- Examples: -- -- > neighbours (8, 8) (place 2 3) -- > == [place 1 2, place 1 3, place 1 4, place 2 2, place 2 4, place 3 2, place 3 3, place 3 4] -- -- > neighbours (8, 8) (place 2 1) -- > == [place 1 1, place 1 2, place 2 2, place 3 1, place 3 2] neighbours :: Size -> Place -> [Place] neighbours (xS, yS) p@(P q) = f' q ++ (if j > 1 then f (q-1) else []) ++ (if j < yS then f (q+1) else []) where (i, j) = coords p f r = P r: (if i > 1 then [P (r - 256)] else []) ++ (if i < xS then [P (r + 256)] else []) f' r = (if i > 1 then [P (r - 256)] else []) ++ (if i < xS then [P (r + 256)] else [])