3

Suppose I have some data that is organized in a grid like this (dimensions may vary, but side of a grid is always n**2):

0 1 2 3
4 5 6 7
8 9 A B
C D E F 

What I would like to achieve is to have a list with the same data represented in different ways, i.e. split into column, rows, or (most importantly) cells which is

0 1 | 2 3
4 5 | 6 7
----+----
8 9 | A B
C D | E F

So that if I do some action I will be able to get data as a following list:

[[0, 1, 4, 5],
 [2, 3, 6, 7],
 [8, 9, C, D],
 [A, B, E, F]]

Where ordering does not matter.

I would like to use this to later construct a lens, that will be able to set values considering different kinds of representations. This is something that could have been acheived with use of pointers or references in imperative languages (where applicable).

Besides specifics, I would like to know if there is a general approach to having same internal data represented differently.

Here's what I got so far, using [Int] as internal representation, and conversion function to get specific "views":

import Data.List (transpose)

data Access = Rows | Columns | Cells

isqrt :: Int -> Int
isqrt = floor . sqrt . fromIntegral

group :: Int -> [a] -> [[a]]
group _ [] = []
group n l
  | n > 0 = (take n l) : (group n (drop n l))
  | otherwise = error "inappropriate n"

representAs :: [Int] -> Access -> [[Int]]
representAs list    Rows = group (isqrt . length $ list) list
representAs list Columns = transpose $ list `representAs` Rows
representAs list   Cells = let row_width  = isqrt . length $ list
                               cell_width = isqrt row_width
                               drops = map (\x -> cell_width 
                                                  * row_width
                                                  * (x `quot` cell_width)
                                                + cell_width 
                                                  * (x `rem` cell_width)
                                           ) [0..row_width-1]
                           in  (map ( (map snd)
                                    . (filter ( (==0)
                                              . (`quot` cell_width)
                                              . (`rem` row_width)
                                              . fst)
                                      )
                                    . (zip [0..])
                                    . (take (row_width * cell_width))
                                    . (`drop` list)
                                    ) drops
                               )

main = mapM_ (putStrLn . show) ([1..16] `representAs` Cells)

My question is based on the same idea as this one, but the answer there regards only memory issues, rather than construction. Besides, if I am to store same data differently in a few representations, I will have to update all of them up setting new value, as far as I understand.

Community
  • 1
  • 1
sukhmel
  • 1,402
  • 16
  • 29
  • I would not use a list to represent this, it will be horrible inefficient. Furthermore, instead of manifesting the data in the different representations, you really should produce a lens - this would allow you to view and modify the matrix with the different views of your data without unnecessary conversion. e.g. `Access -> Lens' (Array (Int, Int) a) (Array Int a)` or `Access -> Traversal' (Array (Int, Int) a) a` – user2407038 Apr 11 '16 at 00:00
  • @user2407038 I thought that constructing a lens is only possible after I provide some kind of setter and getter, e.g using `index` function proposed by @AlexeyKuleshevich as getter, and corresponding setter. Is it possible to do it some other way? – sukhmel Apr 11 '16 at 09:15

3 Answers3

3

First of all, as user2407038 has mentioned in the comments, List is not a very efficient data structure, especially for what you are trying to do. So I will provide an implementation using a boxed Vector from vector package, which obviously has an advantage of a constant time lookup.

Secondly, you cannot think while programming in a functional language the same way you would in imperative language. In Haskell you should choose a data structure that is most efficient in how you will handle the data, and the actual representation delegate to functions that operate on that data. What I mean is (because there is no mutation, unless you really really need it) you cannot set a value and expect it to change in all representations of the data, but rather should have data stored in a single data structure and all of the functions that operate on that data, take in account it's representation.

In implementation below it always stores data as a flat Vector and lets all the functions that operate on MyGrid take in account it's current representation Access. You probably would rather pass Access around to functions, instead of making it part of MyGrid data type, but I made that choice just for simplicity.

import qualified Data.Vector as V

data Access = Rows | Columns | Cells

data MyGrid a = MyGrid { side :: Int -- square grid with each side = N
                       , view :: Access 
                       , vect :: V.Vector a }

This approach allows you to create proper constructors, that do all the sanity checks, for instance:

-- | Constructs a grid from a list, while making sure no elements are lost.
fromList :: [a] -> Access -> MyGrid a
fromList ls a = MyGrid { side = if side'*side' == length ls
                                then if even side'
                                     then side'
                                     else error "grid cannot be split in the middle"
                                else error "list cannot be represented as a square grid"
                       , view = a
                       , vect = V.fromList ls } where
  side' = floor . sqrt . fromIntegral . length $ ls

another constructor could possibly be the one that uses a function to generate elements by using indexes of the grid and current representation:

fromFunction :: Int -> Access -> ((Int, Int) -> a) -> MyGrid a

Now, here is the most important part that takes care of the representation, which is retrieving an element from the grid:

index :: MyGrid a -> (Int, Int) -> a
index grid (i, j) =
  case view grid of
    Rows    -> vect grid V.! (i * side grid + j)
    Columns -> vect grid V.! (j * side grid + i)
    Cells   -> vect grid V.! if even i then k else k - d where
      n = side grid
      d = n `div` 2
      k = (i + j `div` d) * n + j `mod` d

And now you can use that function to deal with representation of your data, for instance converting it to a list of lists, describe how it is printed, or mapped over, etc.:

toLists :: MyGrid a -> [[a]]
toLists grid = map (map (index grid)) [[(j, i) | i <- [0..n]] | j <- [0..n]]
  where n = side grid - 1

instance Show a => Show (MyGrid a) where
  show grid = unlines . map show $ toLists grid

instance Functor MyGrid where
  fmap f grid = grid { vect = V.map f $ vect grid}

Which now allows you to deal with MyGrid's current representation (through using show, fmap, etc.):

λ> fromList [0..15] Rows
[0,1,2,3]
[4,5,6,7]
[8,9,10,11]
[12,13,14,15]

λ> succ <$> fromList [0..15] Columns
[1,5,9,13]
[2,6,10,14]
[3,7,11,15]
[4,8,12,16]

λ> fromList [0..15] Cells
[0,1,4,5]
[2,3,6,7]
[8,9,12,13]
[10,11,14,15]

Here is the assumption I made about how to split the cells for a grid with side bigger than 4. Maybe the grid should have a side with powers of 2, maybe cells should be 2 by 2, I couldn't infer. Just adjust the math to what you need, but I chose to split larger grids for Cells in this way:

0  1  2  | 3  4  5 
6  7  8  | 9  10 11
---------+---------
12 13 14 | 15 16 17
18 19 20 | 21 22 23
---------+---------
24 25 26 | 27 28 29
30 31 32 | 33 34 35

If you need further help with proper cell splitting, edit the question with some examples how it should be done and I'll adjust the implementation.

Community
  • 1
  • 1
lehins
  • 9,642
  • 2
  • 35
  • 49
1

For posterity and future reference, I will post an implementation based on ideas collected. Whole answer is a literate Haskell program, and can be saved as *.lhs and be run (although due to formatting, it will need additional lines to separate code and text).

> {-# LANGUAGE TemplateHaskell, FlexibleContexts #-}

> import Control.Lens (makeLenses, lens, (^.), ix, (.~), (.=), (^?), (%~))

> import qualified Data.Vector as V
> import Data.Vector.Lens (sliced)

> import Data.Maybe (fromJust)
> import Data.Function ((&))
> import Data.List (sortBy)

Data representation accessor:

  • Cells are non-overlapping squares such that the number of elements in each is equal to grid side;
  • Rows are just data split into chunks of grid-side length;
  • Columns are rows transposed.

> data Access = Rows | Columns | Cells

Data structure itself, an sample representation would be

 1  2  3 |  4  5  6 |  7  8  9
10 11 12 | 13 14 15 | 16 17 18
19 20 21 | 22 23 24 | 25 26 27
---------+----------+---------
28 29 30 | 31 32 33 | 34 35 36
37 38 39 | 40 41 42 | 43 44 45
46 47 48 | 49 50 51 | 52 53 54
---------+----------+---------
55 56 57 | 58 59 60 | 61 62 63
64 65 66 | 67 68 69 | 70 71 72
73 74 75 | 76 77 78 | 79 80 81

Where a single cell is, e.g.

 1  2  3
10 11 12
19 20 21

A cell always holds same amount of elements as a row or column.

> data MyGrid a = MyGrid { _cell :: Int -- size of cell in grid, whole grid 
>                                       -- is a square of width `cell^2`
>                        , _vect :: V.Vector a -- internal data storage
>                        }
> makeLenses ''MyGrid 

Convert 2D index of given representation and cell size to internal

> reduce_index_dimension :: Access -> Int -> (Int, Int) -> Int
> reduce_index_dimension a s (x,y) = 
>   case a of
>     Cells   -> (y`rem`s)
>              + (x`rem`s) * s
>              + (y`quot`s) * s^2
>              + (x`quot`s) * s^3
>     Rows    -> x * s * s + y
>     Columns -> y * s * s + x

Convert internal index for given representation and cell size to 2D

> increase_index_dimension :: Access -> Int -> Int -> (Int, Int)
> increase_index_dimension a s i = 
>   case a of
>     Cells   -> ( s *   i `quot` s^3
>                +      (i  `rem` s^2) `quot` s
>                , s * ((i `quot` s^2)  `rem` s)
>                +       i  `rem` s  )
>     Rows    -> ( i  `rem` s^2
>                , i `quot` s^2)
>     Columns -> ( i `quot` s^2
>                , i  `rem` s^2)

Constructs a grid from a list, while making sure no elements are lost.

> fromList :: [a] -> MyGrid a
> fromList ls = MyGrid { _cell = if side'^2 == length ls
>                                then if cell'^2 == side'
>                                     then cell'
>                                     else error "can't represent cell as a square"
>                                else error "can't represent list as a square"
>                      , _vect = V.fromList ls } where
>   side' = floor . sqrt . fromIntegral . length $ ls  -- grid width
>   cell' = floor . sqrt . fromIntegral $ side'        -- cell width

Convert given representation to internal

> convert :: Access -> [[a]] -> [a]
> convert from list = map snd
>                   . sortBy compare_index
>                   . map reduce_index 
>                   . concatMap prepend_index 
>                   . zip [0..] $ list
>   where
>     size                        = floor . sqrt . fromIntegral . length $ list
>     prepend_index (a, xs)       = zipWith (\b c -> ((a, b), c)) [0..] xs
>     reduce_index  (i, x)        = (reduce_index_dimension from size i, x)
>     compare_index (i, _) (j, _) = compare i j

Constructs a grid from another grid, taking representation into account

> fromListsAs :: Access -> [[a]] -> MyGrid a
> fromListsAs a l = MyGrid { _cell = if allEqualLength l
>                                    then if cell'^2 == side'
>                                         then cell'
>                                         else error "can't represent cell as a square"
>                                    else error "lists have different length or do not fit"
>                          , _vect = V.fromList . convert a $ l } where
>   side' = length l
>   cell' = floor . sqrt . fromIntegral $ side'        -- cell width
>   allEqualLength xs = and $ map ((== side') . length) (tail xs)

combining lenses over same object, see Haskell use first level lenses to create complex lens

> (x ^>>= f) btofb s = f (s ^. x) btofb s

lens to focus at element poited to in given representation with given 2d index

> lens_as a i = cell ^>>= \s -> vect . sliced (reduce_index_dimension a s i) 1 . ix 0

convert to 2d representation

> toListsAs :: MyGrid a -> Access -> [[a]]
> toListsAs g a = [[fromJust $ g^?(lens_as a (x, y)) | y <- [0..n]] | x <- [0..n]]
>   where n = (g^.cell)^2 - 1

defaults

> toLists :: MyGrid a -> [[a]]
> toLists g = g `toListsAs` Rows

> instance Show a => Show (MyGrid a) where
>   show grid = unlines . map show . toLists $ grid

> instance Functor MyGrid where
>   fmap f grid = grid & vect %~ V.map f

sanity check

> main = mapM_ (putStrLn . show) (fromList [0..(+80)0] `toListsAs` Cells)
Community
  • 1
  • 1
sukhmel
  • 1,402
  • 16
  • 29
0

An inefficient implementation perhaps trigger better ideas

column,row :: Int -> [((Int,Int),a)] -> [a]
column n xs = map snd $ filter (\((_,y),_) -> y==n) xs 
row n xs = map snd $ filter (\((x,_),_) -> x==n) xs   

cell :: Int -> Int -> [((Int,Int),a)] -> [a] 
cell n m xs = map snd $ filter (\((x,y),_) -> (div x 2 == n) && (div y 2==m)) xs

here indexing the elements of 4x4 matrix

> let a = zipWith (\x y -> ((div y 4,mod y 4),x)) [0..15] [0..]

cells are 2x2 blocks

> cell 1 1 a 
[10,11,14,15]

> cell 0 0 a                                                   
[0,1,4,5]

> column 2 a                
[2,6,10,14]

> row 1 a 
[4,5,6,7]
karakfa
  • 66,216
  • 7
  • 41
  • 56