Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

How do you build an infinite grid like data structure in Haskell?

I am trying to form an infinite grid like data structure by tying the knot.

This is my approach:

import Control.Lens

data Grid a = Grid {_val :: a,
                    _left :: Grid a,
                    _right :: Grid a,
                    _down :: Grid a,
                    _up :: Grid a}

makeLenses ''Grid

makeGrid :: Grid Bool -- a grid with all Falses
makeGrid = formGrid Nothing Nothing Nothing Nothing

formGrid :: Maybe (Grid Bool) -> Maybe (Grid Bool) -> Maybe (Grid Bool) -> Maybe (Grid Bool) -> Grid Bool
formGrid ls rs ds us = center
  where
    center = Grid False leftCell rightCell downCell upCell
    leftCell = case ls of
                Nothing -> formGrid Nothing (Just center) Nothing Nothing
                Just l ->  l
    rightCell = case rs of
                Nothing -> formGrid (Just center) Nothing Nothing Nothing
                Just r ->  r
    upCell = case us of
                Nothing -> formGrid Nothing Nothing (Just center) Nothing
                Just u ->  u
    downCell = case ds of
                Nothing -> formGrid Nothing Nothing Nothing (Just center)
                Just d ->  d

For some reason, this is not working. As seen here:

*Main> let testGrid = (set val True) . (set (right . val) True) $ makeGrid
*Main> _val $ _right $ _left testGrid
False
*Main> _val $ _left $ _right testGrid
False
*Main> _val $ testGrid
True

Where am I going wrong?

like image 306
Agnishom Chattopadhyay Avatar asked Oct 18 '17 15:10

Agnishom Chattopadhyay


2 Answers

@Fyodor's answer explains why your current approach won't work.

One common way of accomplishing this in functional languages is using zippers (not to be confused with zip or related functions).

The idea is that the zipper is a representation of the data structure focused on a particular portion (e.g., a cell in the grid). You can apply transformations to the zipper to "move" this focus around, and you can apply different transformations to query or "mutate" the data structure relative to the focus. Both types of transformations are purely functional -- they act on an immutable zipper and just create a new copy.

Here, you can start with a zipper for an infinite list with position information:

data Zipper a = Zipper [a] a Int [a] deriving (Functor)
  -- Zipper ls x n rs represents the doubly-infinite list (reverse ls ++
  -- [x] ++ rs) viewed at offset n
instance (Show a) => Show (Zipper a) where
  show (Zipper ls x n rs) =
    show (reverse (take 3 ls)) ++ " " ++ show (x,n) ++ " " ++ show (take 3 rs)

This Zipper is intended to be a representation of a doubly infinite list (i.e., a list that's infinite in both directions). An example would be:

> Zipper [-10,-20..] 0 0 [10,20..]
[-30,-20,-10] (0,0) [10,20,30]

This is intended to represent the list of all (positive and negative) integer multiples of ten focused at value 0, position 0 and it actually uses two Haskell infinite lists, one for each direction.

You can define functions to move the focus forward or back:

back, forth :: Zipper a -> Zipper a
back (Zipper (l:ls) x n rs)  = Zipper ls l (n-1) (x:rs)
forth (Zipper ls x n (r:rs)) = Zipper (x:ls) r (n+1) rs

so that:

> forth $ Zipper [-10,-20..] 0 0 [10,20..]
[-20,-10,0] (10,1) [20,30,40]
> back $ back $ Zipper [-10,-20..] 0 0 [10,20..]
[-50,-40,-30] (-20,-2) [-10,0,10]
>

Now, a Grid can be represented as a zipper of rows, with each row a zipper of values:

newtype Grid a = Grid (Zipper (Zipper a)) deriving (Functor)
instance Show a => Show (Grid a) where
  show (Grid (Zipper ls x n rs)) =
    unlines $ zipWith (\a b -> a ++ " " ++ b)
              (map show [n-3..n+3])
              (map show (reverse (take 3 ls) ++ [x] ++ (take 3 rs)))

together with a set of focus-moving functions:

up, down, right, left :: Grid a -> Grid a
up (Grid g) = Grid (back g)
down (Grid g) = Grid (forth g)
left (Grid g) = Grid (fmap back g)
right (Grid g) = Grid (fmap forth g)

You can define a getter and setter for the focused element:

set :: a -> Grid a -> Grid a
set y (Grid (Zipper ls row n rs)) = (Grid (Zipper ls (set' row) n rs))
  where set' (Zipper ls' x m rs') = Zipper ls' y m rs'

get :: Grid a -> a
get (Grid (Zipper _ (Zipper _ x _ _) _ _)) = x

and it may be convenient to add a function that moves the focus back to the origin for display purposes:

recenter :: Grid a -> Grid a
recenter g@(Grid (Zipper _ (Zipper _ _ m _) n _))
  | n > 0 = recenter (up g)
  | n < 0 = recenter (down g)
  | m > 0 = recenter (left g)
  | m < 0 = recenter (right g)
  | otherwise = g

Finally, with a function that creates an all-False grid:

falseGrid :: Grid Bool
falseGrid =
  let falseRow = Zipper falses False 0 falses
      falses = repeat False
      falseRows = repeat falseRow
  in  Grid (Zipper falseRows falseRow 0 falseRows)

you can do things like:

> let (&) = flip ($)
> let testGrid = falseGrid & set True & right & set True & recenter
> testGrid
-3 [False,False,False] (False,0) [False,False,False]
-2 [False,False,False] (False,0) [False,False,False]
-1 [False,False,False] (False,0) [False,False,False]
0 [False,False,False] (True,0) [True,False,False]
1 [False,False,False] (False,0) [False,False,False]
2 [False,False,False] (False,0) [False,False,False]
3 [False,False,False] (False,0) [False,False,False]

> testGrid & right & left & get
True
> testGrid & left & right & get
True
> testGrid & get
True
>

The full example:

{-# LANGUAGE DeriveFunctor #-}

module Grid where

data Zipper a = Zipper [a] a Int [a] deriving (Functor)
  -- Zipper ls x n rs represents the doubly-infinite list (reverse ls ++
  -- [x] ++ rs) viewed at offset n
instance (Show a) => Show (Zipper a) where
  show (Zipper ls x n rs) =
    show (reverse (take 3 ls)) ++ " " ++ show (x,n) ++ " " ++ show (take 3 rs)

back, forth :: Zipper a -> Zipper a
back (Zipper (l:ls) x n rs)  = Zipper ls l (n-1) (x:rs)
forth (Zipper ls x n (r:rs)) = Zipper (x:ls) r (n+1) rs

newtype Grid a = Grid (Zipper (Zipper a)) deriving (Functor)
instance Show a => Show (Grid a) where
  show (Grid (Zipper ls x n rs)) =
    unlines $ zipWith (\a b -> a ++ " " ++ b)
              (map show [n-3..n+3])
              (map show (reverse (take 3 ls) ++ [x] ++ (take 3 rs)))

up, down, right, left :: Grid a -> Grid a
up (Grid g) = Grid (back g)
down (Grid g) = Grid (forth g)
left (Grid g) = Grid (fmap back g)
right (Grid g) = Grid (fmap forth g)

set :: a -> Grid a -> Grid a
set y (Grid (Zipper ls row n rs)) = (Grid (Zipper ls (set' row) n rs))
  where set' (Zipper ls' x m rs') = Zipper ls' y m rs'

get :: Grid a -> a
get (Grid (Zipper _ (Zipper _ x _ _) _ _)) = x

recenter :: Grid a -> Grid a
recenter g@(Grid (Zipper _ (Zipper _ _ m _) n _))
  | n > 0 = recenter (up g)
  | n < 0 = recenter (down g)
  | m > 0 = recenter (left g)
  | m < 0 = recenter (right g)
  | otherwise = g

falseGrid :: Grid Bool
falseGrid =
  let falseRow = Zipper falses False 0 falses
      falses = repeat False
      falseRows = repeat falseRow
  in  Grid (Zipper falseRows falseRow 0 falseRows)

(&) = flip ($)

testGrid :: Grid Bool
testGrid = falseGrid & set True & right & set True & recenter

main = do
  print $ testGrid & get
  print $ testGrid & left & get
  print $ testGrid & left & right & get
  print $ testGrid & right & left & get
like image 113
K. A. Buhr Avatar answered Oct 31 '22 23:10

K. A. Buhr


The key insight is: when you set val True, you're not modifying in place, but creating a copy.

makeGrid constructs a grid where everything is False, including _left $ _right center. When you set val True on the center, you're creating a copy center' where val center' == True. However, this copy still points to the same _right, which in turn still points to the same _left, in other words:

_right center' == _right center

and therefore:

_left $ _right center' == _left $ _right center == center

so that:

_val . _left $ _right center' == _val . _left $ _right center == False
like image 3
Fyodor Soikin Avatar answered Oct 31 '22 23:10

Fyodor Soikin