module Util.Grid where type Position = (Int, Int) type Direction = (Int, Int) addpos :: Position -> Position -> Position (x1, y1) `addpos` (x2, y2) = (x1 + x2, y1 + y2) subpos :: Position -> Position -> Position (x1, y1) `subpos` (x2, y2) = (x1 - x2, y1 - y2) neighbours :: Position -> [Position] neighbours (x, y) = [ (x-1,y-1), (x,y-1), (x+1,y-1), (x-1,y), (x+1,y), (x-1,y+1), (x,y+1), (x+1,y+1) ] neighbours_and_self :: Position -> [Position] neighbours_and_self pos = pos : neighbours pos -- next_steps are the neighbours that are not directly reachable from -- the parent. next_steps :: Position -> Position -> [Position] next_steps parent pos@(x, y) = case pos `subpos` parent of (0, 1) -> [ (x,y+1), (x-1,y+1), (x+1,y+1) ] (0, -1) -> [ (x,y-1), (x-1,y-1), (x+1,y-1) ] (1, 0) -> [ (x+1,y), (x+1,y-1), (x+1,y+1) ] (-1, 0) -> [ (x-1,y), (x-1,y-1), (x-1,y+1) ] (1, 1) -> [ (x+1,y+1), (x,y+1), (x+1,y), (x-1,y+1), (x+1,y-1) ] (1, -1) -> [ (x+1,y-1), (x,y-1), (x+1,y), (x-1,y-1), (x+1,y+1) ] (-1, 1) -> [ (x-1,y+1), (x,y+1), (x-1,y), (x+1,y+1), (x-1,y-1) ] (-1, -1) -> [ (x-1,y-1), (x,y-1), (x-1,y), (x+1,y-1), (x-1,y+1) ] _ -> [ (x,y+1), (x+1,y), (x,y-1), (x-1,y), (x+1,y+1), (x+1,y-1), (x-1,y+1), (x-1,y-1) ] posdist :: Position -> Position -> Int (x1, y1) `posdist` (x2, y2) = max (abs (x1 - x2)) (abs (y1 - y2)) is_neighbour :: Position -> Position -> Bool is_neighbour p1 p2 = (p1 `posdist` p2) <= 1