Splitting a list into two parts

I want split a list into two list S and E and I want to find all possibilities to do so.
So my idea was to map a filter function over a calculated power set, but I have quiet a few beginners trouble with this:

-- powerset code from https://medium.com/@angerman/powersets-in-haskell-1df9684db52a
powerset :: [a] -> [[a]]
powerset [] = [[]]
powerset (x:xs) = map (x:) (powerset xs) ++ powerset xs
findSAndE ts = do
 ps <- powerset ts
 return map [[x | x<-not (x `elem` p)], p] ps

First problem it keeps telling me p not in scope but that is exactly the variable name I want to use in this map function for the element of the power set.

Hello pyibthcmm,
in the code you pasted there are two functions, powerset, which is working, and findSAndE, which is not. So let us examine the latter:

findSAndE ts = do
    ps <- powerset ts
    return map [[x | x<-not (x `elem` p)], p] ps

In the second line, (return map…), what is p? You have not declared it so the compiler correctly complains. Here is a refresher on list comprehensions.

p would be the elements from the powerset. I was trying to write a lambda function.
So I tried a correction:
findSAndE ts = do
ps <- powerset ts
return map (\p->[[x | x<-ts, not (x elem p)], p]) ps

But it didn’t do much for me:
Prelude> :load powerset_haskell.hs
[1 of 1] Compiling Main ( powerset_haskell.hs, interpreted )

powerset_haskell.hs:7:2: error:
• Couldn’t match type ‘[a0] -> [b0]’ with ‘[b]’
Expected type: ([t] -> [[t]]) -> [t] -> [b]
Actual type: ([t] -> [[t]]) -> (a0 -> b0) -> [a0] -> [b0]
• The function ‘return’ is applied to three arguments,
but its type ‘((a0 -> b0) -> [a0] -> [b0])
-> ([t] -> [[t]]) -> (a0 -> b0) -> [a0] -> [b0]’
has only four
In a stmt of a ‘do’ block:
return map (\ p -> [[x | x <- ts, not (x elem p)], p]) ps
In the expression:
do { ps <- powerset ts;
return map (\ p -> [[x | x <- ts, not (x elem p)], …]) ps }
• Relevant bindings include
findSAndE :: [t] -> [b] (bound at powerset_haskell.hs:5:1)
Failed, modules loaded: none.
Prelude>
(Just as a note line 7 is the last line the file and the return line.)
These types make my query.

I haven’t read everything, but return map [[x | x<-not (x `elem` p)], p] ps should be return (map [[x | x<-not (x `elem` p)], p] ps) (with explicit parentheses). The compiler is complaining about that.

Not totally I tried two versions:
findSAndE ts = do
ps <- powerset ts
return (map (\p->[[x | x<-ts, not (x elem p)], p]) ps)
Error:

Prelude> :load powerset_haskell.hs
[1 of 1] Compiling Main ( powerset_haskell.hs, interpreted )

powerset_haskell.hs:7:55: error:
• Occurs check: cannot construct the infinite type: t ~ [t]
Expected type: [[t]]
Actual type: [t]
• In the second argument of ‘map’, namely ‘ps’
In the first argument of ‘return’, namely
‘(map (\ p -> [[x | x <- ts, not (x elem p)], p]) ps)’
In a stmt of a ‘do’ block:
return (map (\ p -> [[x | x <- ts, not (x elem p)], p]) ps)
• Relevant bindings include
ps :: [t] (bound at powerset_haskell.hs:6:2)
ts :: [t] (bound at powerset_haskell.hs:5:11)
findSAndE :: [t] -> [[[[t]]]] (bound at powerset_haskell.hs:5:1)
Failed, modules loaded: none.
Prelude>

Second variant:
findSAndE ts = do
ps <- powerset ts
return (map (\p->[[x | x<-ts, not (x elem p)], [p]]) ps)

Error:
Prelude> :load powerset_haskell.hs
[1 of 1] Compiling Main ( powerset_haskell.hs, interpreted )

powerset_haskell.hs:7:55: error:
• Occurs check: cannot construct the infinite type: t ~ [t]
Expected type: [[t]]
Actual type: [t]
• In the second argument of ‘map’, namely ‘ps’
In the first argument of ‘return’, namely
‘(map (\ p -> [[x | x <- ts, not (x elem p)], p]) ps)’
In a stmt of a ‘do’ block:
return (map (\ p -> [[x | x <- ts, not (x elem p)], p]) ps)
• Relevant bindings include
ps :: [t] (bound at powerset_haskell.hs:6:2)
ts :: [t] (bound at powerset_haskell.hs:5:11)
findSAndE :: [t] -> [[[[t]]]] (bound at powerset_haskell.hs:5:1)
Failed, modules loaded: none.
Prelude>

I’ve read some more, but I don’t actually understand what you’re trying to do. Do you just want all partitions that have length 2, such that you get two sublists S and E? In that case you could naively do something like filter (\t -> length t == 2) (partitions ts), but looking at your code it doesn’t seem like that is what you want. Can you explain it in English? I mistook powerset for partitions please ignore this paragraph.

One thing that will also help is to write the type of your findSAndE function. I’m not sure if it should be findSAndE :: Eq a => [a] -> [[a]] or findSAndE :: Eq a => [a] -> [[[a]]] or findSAndE :: Eq a => [a] -> [[[[a]]]]] (this last option probably isn’t it, but that is what GHC infers from your code). And if you want to find pairs S and E then I would choose findSAndE :: Eq a => [a] -> [([a], [a])] with explicit tuples that always have exactly two elements. By the way if this Eq a is confusing you then I would suggest you just pick a concrete type like Int, e.g. findSAndE :: [Int] -> [([Int], [Int])].

I would also suggest to not use the list monad (that is what you’re using with the do and <- notation). Try to write your functions using let and concatMap instead. I think this actually is your problem. This works:

findSAndE ts =
    let ps = powerset ts
    in map (\p->[[x | x<-ts, not (x `elem` p)], p]) ps

You can also bind multiple variables and functions in one let binding, e.g.:

findSAndE ts =
    let ps = powerset ts
        remaining p = [x | x<-ts, not (x `elem` p)]
    in map (\p -> [remaining p, p]) ps
2 Likes

Thanks this works now (I have used the first variant for now) however the returned result doesn’t seem indexed.
*Main> fe=findSAndE [1…3]
*Main> fe[0]

:9:1: error:
• Couldn’t match expected type ‘[Integer] -> t’
with actual type ‘[[[Integer]]]’
• The function ‘fe’ is applied to one argument,
but its type ‘[[[Integer]]]’ has none
In the expression: fe [0]
In an equation for ‘it’: it = fe [0]
• Relevant bindings include it :: t (bound at :9:1)
*Main> fe
[[[],[1,2,3]],[[3],[1,2]],[[2],[1,3]],[[2,3],[1]],[[1],[2,3]],[[1,3],[2]],[[1,2],[3]],[[1,2,3],[]]]
*Main>

Indexing lists is done with !! in haskell, so fe !! 0 gives the first element of a list, like fe[0] in C-style languages.

The error you get is a bit confusing because fe[0] also has meaning in Haskell: it means applying the value [0] (a list containing the value zero) to the function fe, but fe is not a function so you get an error.

1 Like

Thanks this clears it up.