Implementing Goldbach's conjecture in Haskell, lots of restrictions - list

The point of this assignment is to understand list comprehensions.
Implementing Goldbach's conjecture for some natural number (otherwise the behavior does not matter) using several pre-defined functions and under the following restrictions:
no auxiliary functions
no use of where or let
only one defining equation on the left-hand side and the right-hand side must be a list comprehension
the order of the pairs in the resulting list is irrelevant
using functions from Prelude is allowed
-- This part is the "library"
dm :: Int -> [ Int ] -> [ Int ]
dm x xs = [ y | y <- xs , y `mod ` x /= 0]
da :: [ Int ] -> [ Int ]
da ( x : xs ) = x : da ( dm x xs )
primes :: [ Int ]
primes = da [2 ..]
-- Here is my code
goldbach :: Int -> [(Int,Int)]
-- This is my attempt 1
goldbach n = [(a, b) | n = a + b, a <- primes, b <- primes, a < n, b < n]
-- This is my attempt 2
goldbach n = [(a, b) | n = a + b, a <- takeWhile (<n) primes, b <- takeWhile (<n) primes]
Expected result: a list of all pairs summing up to the specified integer. But GHC complains that in the comprehension, n is not known. My gut tells me I need some Prelude function(s) to achieve what I need, but which one?
Update
parse error on input ‘=’
Perhaps you need a 'let' in a 'do' block?
e.g. 'let n = 5' instead of 'n = 5'

Disregarding the weird error you are talking about, I think that the problem you actually have is the following:
As mentioned by #chi and me, you can't use a and b in your final comprehension before you define a and b.
so you have to move it to the and.
Also: equality of integers is checked with (==) not (=) in haskell.
So you also need to change that.
This would be the complete code for your final approach:
goldbach n = [(a, b) | a <- takeWhile (<n) primes, b <- takeWhile (<n) primes, n == a + b]
A small test yields:
*Main> goldbach 5
[(2,3),(3,2)]
Update
If you want to achieve what you wrote in your comment, you can just add another condition to your comprehension
n `mod` 2 == 0
or even better: Define your funtion with a guard like this:
goldbach n
| n `mod` 2 == 0 = [(a, b) | a <- takeWhile (<n) primes, b <- takeWhile (<n) primes, n == a + b]
| otherwise = []
However, if I am not mistaken this has nothing to do with the actual Godbach conjecture.

Related

Count non-empty lists in a lists of lists

I am trying to count the number of non-empty lists in a list of lists with recursive code.
My goal is to write something simple like:
prod :: Num a => [a] -> a
prod [] = 1
prod (x:xs) = x * prod xs
I already have the deifniton and an idea for the edge condition:
nonEmptyCount :: [[a]] -> Int
nonEmptyCount [[]] = 0
I have no idea how to continue, any tips?
I think your base case, can be simplified. As a base-case, we can take the empty list [], not a singleton list with an empty list. For the recursive case, we can consider (x:xs). Here we will need to make a distinction between x being an empty list, and x being a non-empty list. We can do that with pattern matching, or with guards:
nonEmptyCount :: [[a]] -> Int
nonEmptyCount [] = 0
nonEmptyCount (x:xs) = -- …
That being said, you do not need recursion at all. You can first filter your list, to omit empty lists, and then call length on that list:
nonEmptyCount :: [[a]] -> Int
nonEmptyCount = length . filter (…)
here you still need to fill in ….
Old fashion pattern matching should be:
import Data.List
nonEmptyCount :: [[a]] -> Int
nonEmptyCount [] = 0
nonEmptyCount (x:xs) = if null x then 1 + (nonEmptyCount xs) else nonEmptyCount xs
The following was posted in a comment, now deleted:
countNE = sum<$>(1<$)<<<(>>=(1`take`))
This most certainly will look intimidating to the non-initiated, but actually, it is equivalent to
= sum <$> (1 <$) <<< (>>= (1 `take`))
= sum <$> (1 <$) . (take 1 =<<)
= sum . fmap (const 1) . concatMap (take 1)
= sum . map (const 1) . concat . map (take 1)
which is further equivalent to
countNE xs = sum . map (const 1) . concat $ map (take 1) xs
= sum . map (const 1) $ concat [take 1 x | x <- xs]
= sum . map (const 1) $ [ r | x <- xs, r <- take 1 x]
= sum $ [const 1 r | (y:t) <- xs, r <- take 1 (y:t)] -- sneakiness!
= sum [const 1 r | (y:_) <- xs, r <- [y]]
= sum [const 1 y | (y:_) <- xs]
= sum [ 1 | (_:_) <- xs] -- replace each
-- non-empty list
-- in
-- xs
-- with 1, and
-- sum all the 1s up!
= (length . (take 1 =<<)) xs
= (length . filter (not . null)) xs
which should be much clearer, even if in a bit sneaky way. It isn't recursive in itself, yes, but both sum and the list-comprehension would be implemented recursively by a given Haskell implementation.
This reimplements length as sum . (1 <$), and filter p xs as [x | x <- xs, p x], and uses the equivalence not (null xs) === (length xs) >= 1.
See? Haskell is fun. Even if it doesn't yet feel like it, but it will be. :)

How to make a sorted list of multiples for several numbers?

I'm having trouble with an assignment from my Haskell class. I have already solved a partial problem of this task: I have to write a function that takes an Int and creates an infinite list with the multiples of that Int.
function :: Int -> [Int]
function d = [d*x | x <- [1..]]
Console:
ghci> take 10 (function 3)
gives
[3,6,9,12,15,18,21,24,27,30]
In the second task I have to extend the function so that it accepts a list of numbers and uses each value of that list as a factor (d previously). For example:
ghci> take 10 (function [3, 5])
should give
[3,5,6,9,10,12,15,18,20,21]
Already tried a list comprehension like
function d = [y*x | y <- [1..], x <- d]
but the function returns the list in an unsorted form:
[3,5,6,10,9,15,12,20,15,25]
We got the tip that we should use the modulo function of Haskell, but I have no real idea how to proceed exactly. Do you have a good tip for me?
If you think of d being a factor not as
y = x * d
but instead
y `mod` d == 0,
then you can source the list comprehension from the list [1..] and add a predicate function, for example:
function ds
| null ds = [1..]
| otherwise = [ x | x <- [1..], qualifies x ]
where
qualifies x = any (==0) $ (flip mod) <$> ds <*> [x]
A more expressive version which is perhaps easier to grasp in the beginning:
function' ds
| null ds = [1..]
| otherwise = [ x | x <- [1..], divByAnyIn ds x ]
where
divByAnyIn ds x =
case ds of
(d:ds') -> if x `mod` d == 0 then True
else divByAnyIn ds' x
_ -> False
I have a one liner.
import Data.List (nub)
f xs = nub [x|x<-[1..], d<-xs, x `mod` d == 0]
take 10 $ f [3,5] -- [3,5,6,9,10,12,15,18,20,21]
runtime should be O(n² + n*d) from the resulting list. The nub runs in O(n²). Would be nice to get rid of it.
g xs = [x |x<-[1..], let ys = map (mod x) xs in 0 `elem` ys]
This performs pretty ok. It should run in O (n*d). I also have this version which I thought performs at least as well as g, but apparently it performs better than f and worse than g.
h xs = [x |x<-[1..], or [x `mod` d == 0 |d<-xs] ]
I am not sure why that is, or is lazy as far as I can tell and I don`t see any reason why it should run slower. It especially does not scale as well when you increase the length of the input list.
i xs = foldr1 combine [[x, x+x ..] |x<- sort xs]
where
combine l [] = l
combine [] r = r
combine l#(x:xs) r#(y:ys)
| x < y = (x: combine xs r)
| x > y = (y: combine l ys)
| otherwise = (x: combine xs ys)
Not a one liner anymore, but the fastest I could come up with. I am not a hundred percent sure why it makes such a big difference on runtime if you right or left fold and if you sort the input list in advance. But it should not make a difference on the result since:
commutative a b = combine [a] [b] == combine [b] [a]
I find it completely insane to think about this Problem in terms of folding a recursive function over a list of endless lists of multiples of input coefficients.
On my System it is still about a factor of 10 slower than another solution presented here using Data.List.Ordered.
The answer here just shows the idea, it is not a optimized solution, there may exists many way to implement it.
Firstly, calculate all the value of each factors from the inputted list:
map (\d->[d*x|x<-[1..]]) xs
For example: xs = [3, 5] gives
[[3, 6, 9, ...], [5, 10, 15, ...]]
then, find the minimum value of 1st element of each list as:
findMinValueIndex::[(Int, [Int])]->Int
findMinValueIndex xss = minimum $
map fst $
filter (\p-> (head $ snd p) == minValue) xss
where minValue = minimum $ map (head . snd) xss
Once we found the list hold the minimum value, return it and remove the minimum value from list as:
sortMulti xss =
let idx = findMinValueIndex $ zip [0..] xss
in head (xss!!idx):sortMulti (updateList idx (tail $ xss!!idx) xss
So, for example, after find the first value (i.e. 3) of the result, the lists for find next value is:
[[6, 9, ...], [5, 10, 15, ...]]
repeat above steps we can construct the desired list. Finally, remove the duplicated values. Here is the completed coding:
import Data.Sequence (update, fromList)
import Data.Foldable (toList)
function :: [Int] -> [Int]
function xs = removeDup $ sortMulti $ map (\d->[d*x|x<-[1..]]) xs
where sortMulti xss =
let idx = findMinValueIndex $ zip [0..] xss
in head (xss!!idx):sortMulti (updateList idx (tail $ xss!!idx) xss)
removeDup::[Int]->[Int]
removeDup [] = []
removeDup [a] = [a]
removeDup (x:xs) | x == head xs = removeDup xs
| otherwise = x:removeDup xs
findMinValueIndex::[(Int, [Int])]->Int
findMinValueIndex xss = minimum $
map fst $
filter (\p-> (head $ snd p) == minValue) xss
where minValue = minimum $ map (head . snd) xss
updateList::Int->[Int]->[[Int]]->[[Int]]
updateList n xs xss = toList $ update n xs $ fromList xss
There is a pretty nice recursive solution
function' :: Int -> [Int]
function' d = [d * x | x <- [1..]]
braid :: [Int] -> [Int] -> [Int]
braid [] bs = bs
braid as [] = as
braid aa#(a:as) bb#(b:bs)
| a < b = a:braid as bb
| a == b = a:braid as bs # avoid duplicates
| otherwise = b:braid aa bs
function :: [Int] -> [Int]
function ds = foldr braid [] (map function' ds)
braid function builds the desired list "on the fly" using only input's head and laziness
If you want to do it with the modulo function, you can define a simple one-liner
foo ds = filter (\x -> any (== 0) [mod x d | d <- ds]) [1..]
or, in the more readable form,
foo ds = filter p [1..]
where
p x = any id [ mod x d == 0 | d <- ds]
= any (== 0) [ mod x d | d <- ds]
= not $ null [ () | d <- ds, mod x d == 0]
= null [ () | d <- ds, mod x d /= 0]
= null [ () | d <- ds, rem x d > 0]
With this, we get
> take 20 $ foo [3,5]
[3,5,6,9,10,12,15,18,20,21,24,25,27,30,33,35,36,39,40,42]
But, it is inefficient: last $ take 20 $ foo [300,500] == 4200, so to produce those 20 numbers this code tests 4200. And it gets worse the bigger the numbers are.
We should produce n numbers in time roughly proportional to n, instead.
For this, first write each number's multiples in their own list:
[ [d*x | x <- [1..]] | d <- ds ] ==
[ [d, d+d ..] | d <- ds ]
Then, merge these ordered increasing lists of numbers in an ordered fashion to produce one ordered non-decreasing list of numbers. The package data-ordlist has many functions to deal with this kind of lists:
import qualified Data.List.Ordered as O
import Data.List (sort)
bar :: (Ord a, Num a, Enum a) => [a] -> [a]
bar ds = foldr O.merge [] [ [d, d+d ..] | d <- ds ]
= O.foldt' O.merge [] [ [d, d+d ..] | d <- ds ] -- more efficient,
= O.mergeAll [ [d, d+d ..] | d <- sort ds ] -- tree-shaped folding
If we want the produced list to not contain any duplicates, i.e. create an increasing list, we can change it to
baz ds = O.nub $ foldr O.merge [] [ [d, d+d ..] | d <- ds ]
= foldr O.union [] [ [d, d+d ..] | d <- ds ]
= O.foldt' O.union [] [ [d, d+d ..] | d <- ds ]
= O.unionAll [ [d, d+d ..] | d <- sort ds ]
= (O.unionAll . map (iterate =<< (+)) . sort) ds
Oh, and, unlike the quadratic Data.List.nub, Data.List.Ordered.nub is linear, spends O(1) time on each element of the input list.

Haskell - Defining result as a list and returning null

listX n = xs
if sum[x | x <- [2, 4..n-1], y <- [1..n-1], y `rem` x == 0] == y
then insert y xs
else return ()
Alright, first time trying to work with Haskell, and only having novice Java knowledge has led to some problems.
What I was trying to do, was to define the result of the function listX n as a list called xs.
My idea was that the program would grab every number of from 1 to n, and check if it was equal to the sum of its positive divisors.
Clearly, I have failed horribly and need help, pointers to concepts I haven't understood is extremely appreciated.
Your main problem seems to be that you still think imperative (with the insert) - also () is the value unit - you probably wanted to write [] (the empty list) instead - but still the xs here is totally undefined so you would have to fix this too (and I don't see how to be honest).
perfect numbers
I think I can see a basic idea in there, and I think the best way to fix this is to go full list-comprehension (as you seem to understand them quite well) - here is a version that should work:
listX n = [ x | x <- [1..n], sum [ y | y <- [1..x-1], x `mod` y == 0] == x]
As you can see I changed this a bit - first I check all x from 1 to n if they could be perfect - and I do this by checking by summing up all proper divisors and checking if the sum is equal to x (that's the job of the sum [...] == x part) - in case you don't know this works because you can add guards to list comprehensions (the sum [..] == x filters out all values of x where this is true).
a nicer version
to make this a bit more readable (and separate the concerns) I would suggest writing it that way:
properDivisors :: Integer -> [Integer]
properDivisors n = [ d | d <- [1..n-1], n `mod` d == 0]
isPerfect :: Integer -> Bool
isPerfect n = sum (properDivisors n) == n
perfectNumbers :: [Integer]
perfectNumbers = filter isPerfect [1..]
perfectNumbersUpTo :: Integer -> [Integer]
perfectNumbersUpTo n = takeWhile (<= n) perfectNumbers

haskell infinite list of incrementing pairs

Create an infinite list pairs :: [(Integer, Integer)] containing pairs of the form (m,n),
where each of m and n is a member of [0 ..]. An additional requirement is that if (m,n)
is a legit member of the list, then (elem (m,n) pairs) should return True in finite time.
An implementation of pairs that violates this requirement is considered a non- solution.
****Fresh edit Thank you for the comments, Lets see if I can make some progress****
pairs :: [(Integer, Integer)]
pairs = [(m,n) | t <- [0..], m <- [0..], n <-[0..], m+n == t]
Something like this? I just don't know where it's going to return True in finite time.
I feel the way the question is worded elem doesn't have to be part of my answer. Just if you call (elem (m,n) pairs) it should return true. Sound right?
Ignoring the helper method, the list comprehension you have will list out all pairs but the order of elements is a problem. You'll have a infinitely many pairs like (0, m) which are followed by infinitely many pairs like (1, m). Of course elem will forever iterate all the (0, m) pairs never reaching (1, m) or (2, m) etc.
I'm not sure why you have the helper method -- with it, you are only building a list of pairs like [(0,0), (1,1), (2,2), ...] because you've filtered on m = n. Was that part of the requirements?
Like #hammar suggested, start with 0 = m + n and list out the pairs (m, n). Then list pairs (m, n) where 1 = m + n. Then your list will look like [(0,0), (0,1), (1,0), (0,2), (1,1), (2,0), ...].
The helper function ensures that pairs is a list of the form [ (0,0) , (1,1) , (2,2) ... ].
So elem ( m , n ) pairs can be implemented as:
elem (m , n) _ | m == n = True
| otherwise = False
This is a constant time implementation.
I first posted
Prelude> let pairs = [(m, n) | t <- [0..]
, let m = head $ take 1 $ drop t [0..]
, let n = head $ take 1 $ drop (t + 1) [0..]]
Which, I believed answered the three conditions set by the professor. But hammar pointed out that if I chose this list as an answer, that is, the list of pairs of the form (t, t+1), then I might as well choose the list
repeat [(0,0)]
Well, both of these do seem to answer the professor's question, considering there seems to be no mention of the list having to contain all combinations of [0..] and [0..].
That aside, hammer helped me see how you can list all combinations, facilitating the evaluation of elem in finite time by building the infinite list from finite lists. Here are two other finite lists - less succinct than Hammar's suggestion of the diagonals - that seem to build all combinations of [0..] and [0..]:
edges = concat [concat [[(m,n),(n,m)] | let m = t, n <- take m [0..]] ++ [(t,t)]
| t <- [0..]]
*Main> take 9 edges
[(0,0),(1,0),(0,1),(1,1),(2,0),(0,2),(2,1),(1,2),(2,2)]
which construct the edges (t, 0..t) (0..t, t), and
oddSpirals size = concat [spiral m size' | m <- n] where
size' = if size < 3 then 3 else if even size then size - 1 else size
n = map (\y -> (fst y * size' + div size' 2, snd y * size' + div size' 2))
[(x, t-x) | let size' = 5, t <- [0..], x <- [0..t]]
spiral seed size = spiral' (size - 1) "-" 1 [seed]
spiral' limit op count result
| count == limit =
let op' = if op == "-" then (-) else (+)
m = foldl (\a b -> a ++ [(op' (fst $ last a) b, snd $ last a)]) result (replicate count 1)
nextOp = if op == "-" then "+" else "-"
nextOp' = if op == "-" then (+) else (-)
n = foldl (\a b -> a ++ [(fst $ last a, nextOp' (snd $ last a) b)]) m (replicate count 1)
n' = foldl (\a b -> a ++ [(nextOp' (fst $ last a) b, snd $ last a)]) n (replicate count 1)
in n'
| otherwise =
let op' = if op == "-" then (-) else (+)
m = foldl (\a b -> a ++ [(op' (fst $ last a) b, snd $ last a)]) result (replicate count 1)
nextOp = if op == "-" then "+" else "-"
nextOp' = if op == "-" then (+) else (-)
n = foldl (\a b -> a ++ [(fst $ last a, nextOp' (snd $ last a) b)]) m (replicate count 1)
in spiral' limit nextOp (count + 1) n
*Main> take 9 $ oddSpirals 3
[(1,1),(0,1),(0,2),(1,2),(2,2),(2,1),(2,0),(1,0),(0,0)]
which build clockwise spirals of length 'size' squared, superimposed on hammar's diagonals algorithm.
I believe the solution to your task is:
pairs = [(x,y) | u <- [0..], x <- [0..u], y <-[0..u] , u == x+y]

all possibilities of dividing a list in two in Haskell

What's the most direct/efficient way to create all possibilities of dividing one (even) list into two in Haskell? I toyed with splitting all permutations of the list but that would add many extras - all the instances where each half contains the same elements, just in a different order. For example,
[1,2,3,4] should produce something like:
[ [1,2], [3,4] ]
[ [1,3], [2,4] ]
[ [1,4], [2,3] ]
Edit: thank you for your comments -- the order of elements and the type of the result is less important to me than the concept - an expression of all two-groups from one group, where element order is unimportant.
Here's an implementation, closely following the definition.
The first element always goes into the left group. After that, we add the next head element into one, or the other group. If one of the groups becomes too big, there is no choice anymore and we must add all the rest into the the shorter group.
divide :: [a] -> [([a], [a])]
divide [] = [([],[])]
divide (x:xs) = go ([x],[], xs, 1,length xs) []
where
go (a,b, [], i,j) zs = (a,b) : zs -- i == lengh a - length b
go (a,b, s#(x:xs), i,j) zs -- j == length s
| i >= j = (a,b++s) : zs
| (-i) >= j = (a++s,b) : zs
| otherwise = go (x:a, b, xs, i+1, j-1) $ go (a, x:b, xs, i-1, j-1) zs
This produces
*Main> divide [1,2,3,4]
[([2,1],[3,4]),([3,1],[2,4]),([1,4],[3,2])]
The limitation of having an even length list is unnecessary:
*Main> divide [1,2,3]
[([2,1],[3]),([3,1],[2]),([1],[3,2])]
(the code was re-written in the "difference-list" style for efficiency: go2 A zs == go1 A ++ zs).
edit: How does this work? Imagine yourself sitting at a pile of stones, dividing it into two. You put the first stone to a side, which one it doesn't matter (so, left, say). Then there's a choice where to put each next stone — unless one of the two piles becomes too small by comparison, and we thus must put all the remaining stones there at once.
To find all partitions of a non-empty list (of even length n) into two equal-sized parts, we can, to avoid repetitions, posit that the first element shall be in the first part. Then it remains to find all ways to split the tail of the list into one part of length n/2 - 1 and one of length n/2.
-- not to be exported
splitLen :: Int -> Int -> [a] -> [([a],[a])]
splitLen 0 _ xs = [([],xs)]
splitLen _ _ [] = error "Oops"
splitLen k l ys#(x:xs)
| k == l = [(ys,[])]
| otherwise = [(x:us,vs) | (us,vs) <- splitLen (k-1) (l-1) xs]
++ [(us,x:vs) | (us,vs) <- splitLen k (l-1) xs]
does that splitting if called appropriately. Then
partitions :: [a] -> [([a],[a])]
partitions [] = [([],[])]
partitions (x:xs)
| even len = error "Original list with odd length"
| otherwise = [(x:us,vs) | (us,vs) <- splitLen half len xs]
where
len = length xs
half = len `quot` 2
generates all the partitions without redundantly computing duplicates.
luqui raises a good point. I haven't taken into account the possibility that you'd want to split lists with repeated elements. With those, it gets a little more complicated, but not much. First, we group the list into equal elements (done here for an Ord constraint, for only Eq, that could still be done in O(length²)). The idea is then similar, to avoid repetitions, we posit that the first half contains more elements of the first group than the second (or, if there is an even number in the first group, equally many, and similar restrictions hold for the next group etc.).
repartitions :: Ord a => [a] -> [([a],[a])]
repartitions = map flatten2 . halves . prepare
where
flatten2 (u,v) = (flatten u, flatten v)
prepare :: Ord a => [a] -> [(a,Int)]
prepare = map (\xs -> (head xs, length xs)) . group . sort
halves :: [(a,Int)] -> [([(a,Int)],[(a,Int)])]
halves [] = [([],[])]
halves ((a,k):more)
| odd total = error "Odd number of elements"
| even k = [((a,low):us,(a,low):vs) | (us,vs) <- halves more] ++ [normalise ((a,c):us,(a,k-c):vs) | c <- [low + 1 .. min half k], (us,vs) <- choose (half-c) remaining more]
| otherwise = [normalise ((a,c):us,(a,k-c):vs) | c <- [low + 1 .. min half k], (us,vs) <- choose (half-c) remaining more]
where
remaining = sum $ map snd more
total = k + remaining
half = total `quot` 2
low = k `quot` 2
normalise (u,v) = (nz u, nz v)
nz = filter ((/= 0) . snd)
choose :: Int -> Int -> [(a,Int)] -> [([(a,Int)],[(a,Int)])]
choose 0 _ xs = [([],xs)]
choose _ _ [] = error "Oops"
choose need have ((a,k):more) = [((a,c):us,(a,k-c):vs) | c <- [least .. most], (us,vs) <- choose (need-c) (have-k) more]
where
least = max 0 (need + k - have)
most = min need k
flatten :: [(a,Int)] -> [a]
flatten xs = xs >>= uncurry (flip replicate)
Daniel Fischer's answer is a good way to solve the problem. I offer a worse (more inefficient) way, but one which more obviously (to me) corresponds to the problem description. I will generate all partitions of the list into two equal length sublists, then filter out equivalent ones according to your definition of equivalence. The way I usually solve problems is by starting like this -- create a solution that is as obvious as possible, then gradually transform it into a more efficient one (if necessary).
import Data.List (sort, nubBy, permutations)
type Partition a = ([a],[a])
-- Your notion of equivalence (sort to ignore the order)
equiv :: (Ord a) => Partition a -> Partition a -> Bool
equiv p q = canon p == canon q
where
canon (xs,ys) = sort [sort xs, sort ys]
-- All ordered partitions
partitions :: [a] -> [Partition a]
partitions xs = map (splitAt l) (permutations xs)
where
l = length xs `div` 2
-- All partitions filtered out by the equivalence
equivPartitions :: (Ord a) => [a] -> [Partition a]
equivPartitions = nubBy equiv . partitions
Testing
>>> equivPartitions [1,2,3,4]
[([1,2],[3,4]),([3,2],[1,4]),([3,1],[2,4])]
Note
After using QuickCheck to test the equivalence of this implementation with Daniel's, I found an important difference. Clearly, mine requires an (Ord a) constraint and his does not, and this hints at what the difference would be. In particular, if you give his [0,0,0,0], you will get a list with three copies of ([0,0],[0,0]), whereas mine will give only one copy. Which of these is correct was not specified; Daniel's is natural when considering the two output lists to be ordered sequences (which is what that type is usually considered to be), mine is natural when considering them as sets or bags (which is how this question seemed to be treating them).
Splitting The Difference
It is possible to get from an implementation that requires Ord to one that doesn't, by operating on the positions rather than the values in a list. I came up with this transformation -- an idea which I believe originates with Benjamin Pierce in his work on bidirectional programming.
import Data.Traversable
import Control.Monad.Trans.State
data Labelled a = Labelled { label :: Integer, value :: a }
instance Eq (Labelled a) where
a == b = compare a b == EQ
instance Ord (Labelled a) where
compare a b = compare (label a) (label b)
labels :: (Traversable t) => t a -> t (Labelled a)
labels t = evalState (traverse trav t) 0
where
trav x = state (\i -> i `seq` (Labelled i x, i + 1))
onIndices :: (Traversable t, Functor u)
=> (forall a. Ord a => t a -> u a)
-> forall b. t b -> u b
onIndices f = fmap value . f . labels
Using onIndices on equivPartitions wouldn't speed it up at all, but it would allow it to have the same semantics as Daniel's (up to equiv of the results) without the constraint, and with my more naive and obvious way of expressing it -- and I just thought it was an interesting way to get rid of the constraint.
My own generalized version, added much later, inspired by Will's answer:
import Data.Map (adjust, fromList, toList)
import Data.List (groupBy, sort)
divide xs n evenly = divide' xs (zip [0..] (replicate n [])) where
evenPSize = div (length xs) n
divide' [] result = [result]
divide' (x:xs) result = do
index <- indexes
divide' xs (toList $ adjust (x :) index (fromList result)) where
notEmptyBins = filter (not . null . snd) $ result
partlyFullBins | evenly == "evenly" = map fst . filter ((<evenPSize) . length . snd) $ notEmptyBins
| otherwise = map fst notEmptyBins
indexes = partlyFullBins
++ if any (null . snd) result
then map fst . take 1 . filter (null . snd) $ result
else if null partlyFullBins
then map fst. head . groupBy (\a b -> length (snd a) == length (snd b)) . sort $ result
else []