Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Lists of lists of lists

Tags:

haskell

What is a good way to represent the type LoL a, being a list of lists of ... of a? The nesting level is arbitrary, but uniform over all elements of the outer list.

The case I have in mind is to apply a grouping on the members of a list, and then to apply a next grouping on each subgroup, and so on. It is not known up front how many groupings one will have to apply. Hence:

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

Extra brownie points for the type signature of rGroupBy ;-)

Example:

Suppose deweyGroup i groups the elements based on the i-th number

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

gives:

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

Postscript

One day later, we have 4 excellent and complementary solutions. I'm very pleased with the answers; thank you all.

like image 289
sleepyMonad Avatar asked Aug 07 '12 17:08

sleepyMonad


People also ask

Does a list of lists contain itself?

It is a little tricky, so you may want to read this carefully and slowly. If you have a list of lists that do not list themselves, then that list must list itself, because it doesn't contain itself. However, if it lists itself, it then contains itself, meaning it cannot list itself.

How many things are in Wikipedia?

The English Wikipedia has 6,560,657 articles, 44,248,295 registered editors, and 114,533 active editors.

What is not Wikipedia?

Wikipedia articles are not: Definitions. Articles should begin with a good definition or description, but articles that contain nothing more than a definition should be expanded with additional encyclopedic content. If they cannot be expanded beyond a definition, Wikipedia is not the place for them.


5 Answers

Another way to enforce the constraint that all branches have equal depth is to use a nested datatype:

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

Expanding the definition of LoL, we see that informally,

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

Then we can say, for example:

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

to get back

Many (Many (One [[[(1,(1,1)),(1,(1,2)),(1,(1,3))]],[[(1,(2,1)),(1,(2,2)),(1,(2,3)), ...
like image 67
Phil Freeman Avatar answered Oct 18 '22 22:10

Phil Freeman


What you actually have is a tree. Try representing it with a recursive data structure:

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"] gives:

MoL [MoL [SoL ["1.1"],
          SoL ["1.2.1","1.2.2"]],
     MoL [SoL ["2.1"],
          SoL ["2.2"]],
     MoL [SoL ["3.0"]]
    ]
like image 25
helami Avatar answered Oct 18 '22 21:10

helami


If you want to enforce uniform depth, there is a (fairly) standard trick to do that involving polymorphic recursion. What we'll do is have a spine of "deeper" constructors telling how deeply nested the list is, then a final "here" constructor with the deeply-nested list:

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

Actually, the type as defined has one aesthetic choice that you may wish to vary in your code: the Here constructor takes a single a and not a list of as. The consequences of this choice are sort of scattered through the rest of this answer.

Here's an example of a value of this type exhibiting lists-of-lists; it has two Deeper constructors corresponding to the depth-two nesting that it has:

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

Here's see a few sample functions.

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
like image 27
Daniel Wagner Avatar answered Oct 18 '22 22:10

Daniel Wagner


I believe the following example should be close to what you had in mind. First we declare type-level natural numbers. Then we define vectors, which carry their length as a phantom type (see Fixed-length vectors in Haskell, Part 1: Using GADTs). And then we define a structure for nested lists of lists of ... which carries the depth as a phantom type. Finally we can define correctly typed 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)
like image 26
Petr Avatar answered Oct 18 '22 21:10

Petr


As a type-hackery exercise it is possible to implement this with standard lists.

All we need is an arbitrary depth groupStringsBy function:

{-# 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

Which works like this:

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

So we can use this function directly (although it has to be put in reverse order):

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

But if you want to use your original sample, we can hack it too. First we need a variable argument function which pipelines all the arguments but the last one in reverse order via . and then applies the resulting function to the last argument:

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

Works like this:

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

Then expand it with a custom rule for our predicate type 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)

And finally wrap it in rGroupBy (supplying id function to be the first in the pipeline):

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

Now it should work for any number of grouping predicates of type Pred producing the list of the depth equal to the number of supplied predicates:

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

So it is possible (and probably can be simplified) but as always with this sort of hackery is not recommended to be used for anything but the exercise.

like image 33
Ed'ka Avatar answered Oct 18 '22 20:10

Ed'ka