12

什么是表示类型的好方法LoL a,作为...的列表列表a?嵌套级别是任意的,但在外部列表的所有元素上都是统一的。

我想到的情况是对列表的成员应用分组,然后对每个子组应用下一个分组,依此类推。预先不知道一个人必须申请多少个分组。因此:

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

类型签名的额外布朗尼点rGroupBy;-)

例子:

假设deweyGroup i根据第 i 个数字对元素进行分组

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

给出:

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

后记

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

4

5 回答 5

13

强制所有分支具有相同深度的约束的另一种方法是使用嵌套数据类型:

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)), ...
于 2012-08-07T21:22:35.593 回答
10

你实际上拥有的是一棵树。尝试用递归数据结构表示它:

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"]]
    ]
于 2012-08-07T17:58:51.083 回答
7

如果你想强制执行统一深度,有一个(相当)标准的技巧可以做到这一点,涉及多态递归。我们要做的是有一个“更深”的构造函数来告诉列表嵌套的深度,然后是一个带有深度嵌套列表的最终“here”构造函数:

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

实际上,定义的类型有一个美学选择,您可能希望在代码中有所不同:Here构造函数采用单个a而不是as 列表。这种选择的后果有点分散在这个答案的其余部分。

这是一个显示列表列表的此类值的示例;它有两个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
于 2012-08-07T21:18:45.217 回答
3

我相信下面的例子应该接近你的想法。首先我们声明类型级别的自然数。然后我们定义向量,将它们的长度作为幻像类型(参见Haskell 中的固定长度向量,第 1 部分:使用 GADT)。然后我们为 ... 的列表的嵌套列表定义一个结构,该结构将深度作为幻像类型。最后我们可以定义正确的类型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)
于 2012-08-07T19:37:54.400 回答
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

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)

最后将其包装起来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

所以这是可能的(并且可能可以简化),但与往常一样,不建议将这种黑客用于除练习之外的任何事情。

于 2012-08-09T04:15:30.497 回答