2012-08-07 164 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 

因此,有可能(也可能可以簡化),但一如既往地與這類兩輪牛車不推薦用於任何東西,但鍛鍊。