Haskell:为相同的数据创建不同的表示

时间:2016-04-10 20:29:47

标签: haskell data-representation

假设我有一些像这样的网格组织的数据(尺寸可能会有所不同,但网格的一边总是n**2):

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

我想要实现的是使用不同方式表示相同数据的列表,即分成列,行或(最重要的)单元格

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

因此,如果我采取某些行动,我将能够将数据作为以下列表获取:

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

订货无关紧要。

我想用它来后来构建一个镜头,它能够设置考虑不同类型表示的值。这可以通过使用命令式语言中的指针或引用来实现(适用时)。

除了细节之外,我想知道是否有一种通用的方法来使相同的内部数据表示不同。

这是我到目前为止所做的,使用[Int]作为内部表示,转换函数获取特定的“视图”:

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)

我的问题基于与this one相同的想法,但答案仅涉及记忆问题,而不是构造。此外,如果我要在一些表示中以不同的方式存储相同的数据,我将不得不更新所有这些数据,并根据我的理解设置新值。

2 个答案:

答案 0 :(得分:1)

对于后人和未来的参考,我将根据收集的想法发布实施。整个答案是一个literate Haskell程序,可以保存为*.lhs并运行(虽然由于格式化,它需要额外的行来分隔代码和文本)。

> {-# 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 Access = Rows | Columns | Cells

数据结构本身,样本表示将是

 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

单个细胞的位置,例如

 1  2  3
10 11 12
19 20 21

单元格总是包含与行或列相同数量的元素。

> 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 

将给定表示和单元格大小的2D索引转换为内部

> 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

将给定表示和单元格大小的内部索引转换为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)

从列表构造网格,同时确保没有元素丢失。

> 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 :: 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

从另一个网格构建网格,将表示纳入帐户

> 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)

将镜头组合在同一物体上,请参阅Haskell use first level lenses to create complex lens

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

镜头聚焦于给定2d索引的给定表示中的元素。

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

转换为2d表示

> 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

默认

> 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

健全检查

> main = mapM_ (putStrLn . show) (fromList [0..(+80)0] `toListsAs` Cells)

答案 1 :(得分:0)

低效的实施可能会触发更好的想法

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

这里索引4x4矩阵的元素

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

细胞是2x2块

> 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]