2012-08-07 117 views
12

什么是代表LoL a类型的好方法,是a的列表 的列表?嵌套级别是任意的,但在外部列表的所有元素中是统一的。列表清单列表

我想到的情况是对 列表的成员应用一个分组,然后对每个子组应用下一个分组,等等。它不知道前面将会有多少个分组需要应用。因此:基于所述第i个数字

rGroupBy [deweyGroup 1, deweyGroup 2] 
     ["1.1", "1.2.1", "1.2.2", "2.1", "2.2", "3"] 

假设deweyGroup i组中的元素:

rGroupBy :: [(a -> a -> Bool)] -> [a] -> [...[a]...] 

rGroupBy ;-)

实施例的类型签名附加印象分给出:

[ [ [ "1.1" ], [ "1.2.1", "1.2.2" ] ], 
    [ [ "2.1" ], [ "2.2" ] ], 
    [ [ "3" ] ] 
] 

后记

一天后,我们有4个优秀的和互补的解决方案。我很满意答案;谢谢你们。

+0

有趣的问题。当你说“它不是预先知道的”,你的意思是在编译时?如果是这样,那么你可能会失败,因为haskell是静态类型的。 – jberryman 2012-08-07 17:17:34

+0

在C/C++中一个列表通常是一个数组,一个数组通常是一个2维矩阵,使得数组列表意味着你正在增加维数1,从2到3,数组列表是一个3D矩阵从抽象的角度来看);我不知道Haskell,但可能你的问题只是矩阵/矢量的维度。 – user827992 2012-08-07 17:23:47

+0

@ user827992,在Haskell中,列表是一个列表,而不是一个数组。(这是一个单链表,准确地说) – dflemstr 2012-08-07 17:42:28

回答

3

我相信下面的例子应该是接近你脑子里想的是什么。首先我们声明类型级自然数。然后我们定义矢量,它们的长度为幻像类型(请参见Fixed-length vectors in Haskell, Part 1: Using GADTs)。然后我们定义一个嵌套的清单列表...的结构,它将深度作为幻像类型。最后我们可以正确定义rGroupBy

{-# LANGUAGE GADTs #-} 
{-# LANGUAGE EmptyDataDecls #-} 

import Data.List (groupBy) 

data Zero 
data Succ n 

data Vec n a where 
    Nil ::     Vec Zero a 
    Cons :: a -> Vec n a -> Vec (Succ n) a 

data LList n a where 
    Singleton :: a   -> LList Zero a 
    SuccList :: [LList n a] -> LList (Succ n) a 

-- Not very efficient, but enough for this example. 
instance Show a => Show (LList n a) where 
    showsPrec _ (Singleton x) = shows x 
    showsPrec _ (SuccList lls) = shows lls 

rGroupBy :: Vec n (a -> a -> Bool) -> [a] -> LList (Succ n) a 
rGroupBy Nil 
    = SuccList . map Singleton 
rGroupBy (Cons f fs) 
    = SuccList . map (rGroupBy fs) . groupBy f 

-- TEST ------------------------------------------------------------ 

main = do 
    let input = ["1.1", "1.2.1", "1.2.2", "2.1", "2.2", "3"] 

    -- don't split anything 
    print $ rGroupBy Nil input 
    -- split on 2 levels 
    print $ rGroupBy (Cons (deweyGroup 1) 
          (Cons (deweyGroup 2) Nil)) 
       input 
    where 
    deweyGroup :: Int -> String -> String -> Bool 
    deweyGroup i a b = a!!idx == b!!idx where idx = 2*(i-1) 
9

你真正拥有的是一棵树。尝试用递归数据结构,代表它:

data LoL a = SoL [a] | MoL [LoL a] deriving (Eq, Show) 

rGroupBy :: [(a -> a -> Bool)] -> [a] -> LoL a 
rGroupBy (f:fs) = MoL . map (rGroupBy fs) . groupBy f 
rGroupBy []  = SoL 

deweyGroup :: Int -> String -> String -> Bool 
deweyGroup i a b = a!!idx == b!!idx where idx = 2*(i-1) 

rGroupBy [deweyGroup 1, deweyGroup 2] ["1.1", "1.2.1", "1.2.2", "2.1", "2.2", "3.0"]给出:

MoL [MoL [SoL ["1.1"], 
      SoL ["1.2.1","1.2.2"]], 
    MoL [SoL ["2.1"], 
      SoL ["2.2"]], 
    MoL [SoL ["3.0"]] 
    ] 
+0

我自己不能说得更好。 – crockeea 2012-08-07 18:15:06

+1

另外,看看玫瑰树。 http://hackage.haskell.org/package/containers-0.5.0.0 – 2012-08-07 18:18:57

+3

非常好的解决方案。我看到的唯一问题是树结构不会强制统一深度。 – 2012-08-07 18:26:33

7

如果你想强制执行统一的深度,有一个(相当)标准的技巧来做到涉及多态递归。我们要做的是有“更深”的构造函数告诉列表如何深度嵌套的,那么最终的“这里”构造与深度嵌套列表脊柱:

data GroupList a = Deeper (GroupList [a]) | Here a deriving (Eq, Ord, Show, Read) 

实际上,所定义的类型有一个美学选择,你可能希望在你的代码中有所不同:Here构造函数只需要一个a而不是一个a s的列表。这个选择的结果在这个答案的其余部分中是分散的。

下面是这种展示列表清单的值的示例;它具有与深度两筑巢,它有两个Deeper构造函数:

> :t Deeper (Deeper (Here [[1,2,3], []])) 
Num a => GroupList a 

这里看到了几样功能。

instance Functor GroupList where 
    fmap f (Here a) = Here (f a) 
    fmap f (Deeper as) = Deeper (fmap (fmap f) as) 
    -- the inner fmap is at []-type 

-- this type signature is not optional 
flatten :: GroupList [a] -> GroupList a 
flatten (Here a) = Deeper (Here a) 
flatten (Deeper as) = Deeper (flatten as) 

singleGrouping :: (a -> a -> Bool) -> GroupList [a] -> GroupList [a] 
singleGrouping f = flatten . fmap (groupBy f) 

rGroupBy :: [a -> a -> Bool] -> [a] -> GroupList [a] 
rGroupBy fs xs = foldr singleGrouping (Here xs) fs 
+0

谢谢。关于审美方面:我相信菲尔弗里曼的解决方案采取了另一种选择。我发现他的代码更容易理解,尽管你对“构造者的脊椎”的解释最初也在那里帮了很大忙。实际上,代码中的注释暗示了一些重要的非显而易见的细节,例如'flatten'使内部类型扁平化,但增加了一个'Deeper'构造函数(我想知道为什么它不叫“深化”);并且你使用嵌套的'fmap'来遍历GroupLists和普通列表。微妙! – sleepyMonad 2012-08-08 18:41:53

11

另一种方式来执行,所有分公司具有同等深度的约束是使用嵌套的数据类型:

data LoL a = One [a] | Many (LoL [a]) 

mapLoL :: ([a] -> [b]) -> LoL a -> LoL b 
mapLoL f (One xs) = One (f xs) 
mapLoL f (Many l) = Many $ mapLoL (map f) l 

rGroupBy :: [a -> a -> Bool] -> [a] -> LoL a 
rGroupBy [] xs = One xs 
rGroupBy (f:fs) xs = Many $ mapLoL (groupBy f) $ rGroupBy fs xs 

扩大LoL的定义,我们可以看到,非正式,

LoL a = [a] | [[a]] | [[[a]]] | ... 

然后我们可以说,例如:

ghci> rGroupBy [(==) `on` fst, (==) `on` (fst . snd)] [ (i,(j,k)) | i<-[1..3], j<-[1..3], k<-[1..3]] 

找回

Many (Many (One [[[(1,(1,1)),(1,(1,2)),(1,(1,3))]],[[(1,(2,1)),(1,(2,2)),(1,(2,3)), ... 
+0

也很好。我花了一段时间才意识到groupBy f的类型为[a] - > [[a]],并且每个连续的map应用都会添加一个额外的嵌套层次(例如map。map。groupBy f :: [[[a ]]] - > [[[[a]]]])。 – sleepyMonad 2012-08-08 17:23:05

1

作为一种类型两轮牛车的锻炼,可以与标准的列表,以实现这一点。

所有我们需要的是一个任意深度groupStringsBy功能:

{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, 
    UndecidableInstances, IncoherentInstances, 
    TypeFamilies, ScopedTypeVariables #-} 

import Data.List 
import Data.Function 

class StringGroupable a b where 
    groupStringBy :: Pred -> a -> b 

instance (StringGroupable a b, r ~ [b]) => StringGroupable [a] r where 
    groupStringBy f = map (groupStringBy f) 

instance (r ~ [[String]]) => StringGroupable [String] r where 
    groupStringBy p = groupBy p 

这是这样的:

*Main> let lst = ["11","11","22","1","2"] 
*Main> groupStringBy ((==) `on` length) lst 
[["11","11","22"],["1","2"]] 
*Main> groupStringBy (==) . groupStringBy ((==) `on` length) $ lst 
[[["11","11"],["22"]],[["1"],["2"]]] 

因此,我们可以直接使用此功能(尽管它必须被放置在相反的顺序):

inp = ["1.1", "1.2.1", "1.2.2", "2.1", "2.2", "3"] 

deweyGroup :: Int -> String -> String -> Bool 
deweyGroup i a b = a!!idx == b!!idx where idx = 2*(i-1) 

-- gives: [[["1.1"],["1.2.1","1.2.2"]],[["2.1"],["2.2"]],[["3"]]] 
test1 = groupStringBy (deweyGroup 2) . groupStringBy (deweyGroup 1) $ inp 

但是,如果你想使用你的原始样本,我们也可以破解它。 首先,我们需要一个变量参数功能,管道的所有参数,但通过.最后一个以相反的顺序,然后应用所产生的函数的最后一个参数:

class App a b c r where 
    app :: (a -> b) -> c -> r 

instance (b ~ c, App a d n r1, r ~ (n -> r1)) => App a b (c -> d) r where 
    app c f = \n -> app (f . c) n 

instance (a ~ c, r ~ b) => App a b c r where 
    app c a = c a 

是这样工作的:

*Main> app not not not True 
False 
*Main> app (+3) (*2) 2 
10 

type Pred = String -> String -> Bool 

instance (StringGroupable b c, App a c n r1, r ~ (n -> r1)) => App a b Pred r where 
    app c p = app ((groupStringBy p :: b -> c) . c) 

最后宽:

然后用我们的谓词类型type Pred = String -> String -> Bool自定义规则展开说唱它在rGroupBy(供给id功能是在管道中的第一个):

rGroupBy :: (App [String] [String] Pred r) => Pred -> r 
rGroupBy p = app (id :: [String] -> [String]) p 

现在应该用于任何数目的分组Pred类型谓词产生深度等于提供谓词数量列表的工作:

-- gives: [["1.1","1.2.1","1.2.2"],["2.1","2.2"],["3"]] 
test2 = rGroupBy (deweyGroup 1) inp 

-- gives: [[["1.1"],["1.2.1","1.2.2"]],[["2.1"],["2.2"]],[["3"]]] 
test3 = rGroupBy (deweyGroup 1) (deweyGroup 2) inp 

-- gives: [[[["1.1"]],[["1.2.1","1.2.2"]]],[[["2.1"]],[["2.2"]]],[[["3"]]]] 
test4 = rGroupBy (deweyGroup 1) (deweyGroup 2) (deweyGroup 1) inp 

因此,有可能(也可能可以简化),但一如既往地与这类两轮牛车不推荐用于任何东西,但锻炼。