Parse error on pattern - haskell

Trying to implement a function that will return a list of ints the represent an ordering of each list of doubles, e.g.:
orderings [ [1.0, 2.0, 3.0], [3.0, 2.0, 1.0] ]
> [ [0, 1, 2], [2, 1, 0] ]
However, having trouble with my pattern matching for some reason:
import Data.List
-- Return a list of orderings for each list of doubles
orderings:: [[Double]] -> [Int]
orderings [] = []
orderings x:xs = (ordering x):(orderings xs)
ordering:: [Double] -> [Int]
ordering xs = [i | (i, _) <- sorted] where
sorted = sortBy (\(i1, e1) (i2,e2) -> compare e1 e2) $ zip [0..] xs
Error is:
Parse error in pattern: orderings
Can't see the error for the life of me!

Two more problems (in addition to the missing parentheses around x:xs):
the type of orderings is wrong; I suspect it should be [[Double]] -> [[Int]]
x is not in scope in ordering; I suspect it should be xs
Here's the corrected code:
import Data.List
-- Return a list of orderings for each list of doubles
orderings:: [[Double]] -> [[Int]] -- changed type
orderings [] = []
orderings (x:xs) = (ordering x):(orderings xs)
ordering:: [Double] -> [Int]
ordering xs = [i | (i, _) <- sorted] where
sorted = sortBy (\(i1, e1) (i2,e2) -> compare e1 e2) $ zip [0..] xs -- xs not x!

The result of orderings should be [[Int]] as pointed out previously. However, the implementation of the functions can be simplified to:
import Data.List
-- Return a list of orderings for each list of doubles
orderings :: [[Double]] -> [[Int]]
orderings = map ordering
ordering :: [Double] -> [Int]
ordering = map snd . sort . flip zip [0..]

You have to put parenthesis around the x:xs pattern:
orderings (x:xs) = ...

There are 3 errors:
In the line orderings x:xs = (ordering x):(orderings xs) you try to cons (:) a list and a list (but cons generates list with the given value prepended) and you forget the parens around the x:xs cons pattern match.
The type of : is:
Prelude> :type (:)
(:) :: a -> [a] -> [a]
The correct form of the line is:
orderings (x:xs) = (ordering x) ++ (orderings xs)
since ++ concats to lists:
Prelude> :type (++)
(++) :: [a] -> [a] -> [a]
The last error is that in the last line, it should be xs instead of x

Related

Generating a set using higher order functions and unions

I am studying a past exam and I came across a question where I must write a function called setFunc to generate a set where I apply a function on each element in a list of tuples (which are a result of the Cartesian product operation)
First I implemented a helper function to take the union of sets:
Then I tried to implement the main function:
setFunc x y = f x y
setFunc (x:xs) (y:ys) = (f x y) OrdUnion (setFunc f xt ys)
Help on fixing setFunc would be appreciated.
I must use ordUnion somehow and I am not permitted to use sort.
This sort of constraint is expected to appear within the body of the question.
A core part of the problem is that we want the output list to be sorted (from your example), but we are told nothing about possible order-preserving properties of the argument function. So we must accept that the f x y output values will be produced in some unpredictable random order.
For example, we expect this equality to hold:
setFunc (*) [-7,2] [-7,3] == [-21,-14,6,49]
that is, the maximal output value results from the two minimal input values.
Hence, we are somewhat coerced into solving the problem in 2 steps:
produce the f x y output values in whatever order
sort the list produced in step 1.
Let's call the step 1 function cartesianFunc. It is easy to write it in recursive fashion:
cartesianFunc :: Ord c => (a -> b -> c) -> [a] -> [b] -> [c]
cartesianFunc f [] ys = []
cartesianFunc f (x:xs) ys = (map (f x) ys) ++ (cartesianFunc f xs ys)
Note that we have dropped the useless Ord constraints on types b and c.
Testing:
$ ghci
GHCi, version 8.8.4: https://www.haskell.org/ghc/ :? for help
...
λ>
λ> :load q13784671.hs
[1 of 1] Compiling Main ( q13784671.hs, interpreted )
Ok, one module loaded.
λ>
λ> cartesianFunc (*) [1,2,4] [1,3,9]
[1,3,9,2,6,18,4,12,36]
λ>
Now for step 2:
We may not use the library sort function. But we have to use function ordUnion, which merges two ordered lists into a bigger ordered list.
Assuming we had yet another function, say splitHalf, which could split a list into two roughly equal parts, we could obtain our own sort function by:
splitting the input list
recursively sorting its two halves
combining our two sorted halves using the merging ordUnion function.
To split a list, we can use the well-know tortoise-hare algorithm where at each iteration, the first part advances by one step and the second part advances by two steps.
This gives this code:
ordUnion :: (Ord a) => [a] -> [a] -> [a]
ordUnion a [] = a
ordUnion [] b = b
ordUnion (x:xs) (y:ys) = case compare x y of
LT -> x : ordUnion xs (y:ys)
EQ -> x : ordUnion xs ys
GT -> y : ordUnion (x:xs) ys
splitHalfTH :: [a] -> ([a],[a])
splitHalfTH xs = th xs xs
where
th (y:ys) (_:_:zs) = let (as,bs) = th ys zs in (y:as, bs)
th ys _ = ([],ys)
mySort :: (Ord a) => [a] -> [a]
mySort [] = []
mySort [a] = [a]
mySort xs = let (as,bs) = splitHalfTH xs in ordUnion (mySort as) (mySort bs)
and finally we can come up with our setFunc function by combining mySort and cartesianFunc:
setFunc :: Ord c => (a -> b -> c) -> [a] -> [b] -> [c]
setFunc fn xs ys = mySort (cartesianFunc fn xs ys)
Testing:
λ>
λ> cartesianFunc (*) [1,2,4] [1,3,9]
[1,3,9,2,6,18,4,12,36]
λ>
λ> mySort $ cartesianFunc (*) [1,2,4] [1,3,9]
[1,2,3,4,6,9,12,18,36]
λ>
λ> setFunc (*) [1,2,4] [1,3,9]
[1,2,3,4,6,9,12,18,36]
λ>

Pattern match(es) are non-exhaustive In an equation for ‘convertTuple’: Patterns not matched: []

I wrote a function that Convert my list of lists of Int to a list of Tuples containing the items to display.
For example:
[[43525,5,2],[7455,3,4],[25545,7,5]] --> [(1,43525,5),(2,7455,3),(3, 25545.7)]
But i get this warning :
Pattern match(es) are non-exhaustive In an equation for ‘convertTuple’: Patterns not matched: []compile(-Wincomplete-patterns)
My function :
convertTuple :: [[Int]] -> [(Int, Int, Int)]
convertTuple (x:xs) = zipWith (curry (\x -> (fst x,head (snd x), snd x!!2))) [1..] (x:xs)
What is the cause of the warning ?
Your convertTuple only works for non-empty lists. Indeed, convertTuple [] will not work since (x:xs) only pattern matches with non-empty lists with x the first item of the list, and xs the remaining items. You however do not need such pattern, you can simply use xs.
But furthermore your function contains some anti-patterns. For example you use another variable x that is more locally scoped, creating confusion between the the two variables. You can work with:
convertTuple :: [[Int]] -> [(Int, Int, Int)]
convertTuple = zipWith (\i (a:b:_) -> (i, a, b)) [1..]
Although this still can result in problems if a sublist of the list contains less than two elements. You thus might want to pattern match only if it contains at least or exactly two elements, for example with list comprehension:
{-# LANGUAGE ParallelListComp #-}
convertTuple :: [[Int]] -> [(Int, Int, Int)]
convertTuple xs = [ (i, a, b) | i <- [1..] | (a:b:_) <- xs ]

interleaving two strings, preserving order: functional style

In this question, the author brings up an interesting programming question: given two string, find possible 'interleaved' permutations of those that preserves order of original strings.
I generalized the problem to n strings instead of 2 in OP's case, and came up with:
-- charCandidate is a function that finds possible character from given strings.
-- input : list of strings
-- output : a list of tuple, whose first value holds a character
-- and second value holds the rest of strings with that character removed
-- i.e ["ab", "cd"] -> [('a', ["b", "cd"])] ..
charCandidate xs = charCandidate' xs []
charCandidate' :: [String] -> [String] -> [(Char, [String])]
charCandidate' [] _ = []
charCandidate' ([]:xs) prev =
charCandidate' xs prev
charCandidate' (x#(c:rest):xs) prev =
(c, prev ++ [rest] ++ xs) : charCandidate' xs (x:prev)
interleavings :: [String] -> [String]
interleavings xs = interleavings' xs []
-- interleavings is a function that repeatedly applies 'charCandidate' function, to consume
-- the tuple and build permutations.
-- stops looping if there is no more tuple from charCandidate.
interleavings' :: [String] -> String -> [String]
interleavings' xs prev =
let candidates = charCandidate xs
in case candidates of
[] -> [prev]
_ -> concat . map (\(char, ys) -> interleavings' ys (prev ++ [char])) $ candidates
-- test case
input :: [String]
input = ["ab", "cd"]
-- interleavings input == ["abcd","acbd","acdb","cabd","cadb","cdab"]
it works, however I'm quite concerned with the code:
it is ugly. no point-free!
explicit recursion and additional function argument prev to preserve states
using tuples as intermediate form
How can I rewrite the above program to be more "haskellic", concise, readable and more conforming to "functional programming"?
I think I would write it this way. The main idea is to treat creating an interleaving as a nondeterministic process which chooses one of the input strings to start the interleaving and recurses.
Before we start, it will help to have a utility function that I have used countless times. It gives a convenient way to choose an element from a list and know which element it was. This is a bit like your charCandidate', except that it operates on a single list at a time (and is consequently more widely applicable).
zippers :: [a] -> [([a], a, [a])]
zippers = go [] where
go xs [] = []
go xs (y:ys) = (xs, y, ys) : go (y:xs) ys
With that in hand, it is easy to make some non-deterministic choices using the list monad. Notionally, our interleavings function should probably have a type like [NonEmpty a] -> [[a]] which promises that each incoming string has at least one character in it, but the syntactic overhead of NonEmpty is too annoying for a simple exercise like this, so we'll just give wrong answers when this precondition is violated. You could also consider making this a helper function and filtering out empty lists from your top-level function before running this.
interleavings :: [[a]] -> [[a]]
interleavings [] = [[]]
interleavings xss = do
(xssL, h:xs, xssR) <- zippers xss
t <- interleavings ([xs | not (null xs)] ++ xssL ++ xssR)
return (h:t)
You can see it go in ghci:
> interleavings ["abc", "123"]
["abc123","ab123c","ab12c3","ab1c23","a123bc","a12bc3","a12b3c","a1bc23","a1b23c","a1b2c3","123abc","12abc3","12ab3c","12a3bc","1abc23","1ab23c","1ab2c3","1a23bc","1a2bc3","1a2b3c"]
> interleavings ["a", "b", "c"]
["abc","acb","bac","bca","cba","cab"]
> permutations "abc" -- just for fun, to compare
["abc","bac","cba","bca","cab","acb"]
This is fastest implementation I've come up with so far. It interleaves a list of lists pairwise.
interleavings :: [[a]] -> [[a]]
interleavings = foldr (concatMap . interleave2) [[]]
This horribly ugly mess is the best way I could find to interleave two lists. It's intended to be asymptotically optimal (which I believe it is); it's not very pretty. The constant factors could be improved by using a special-purpose queue (such as the one used in Data.List to implement inits) rather than sequences, but I don't feel like including that much boilerplate.
{-# LANGUAGE BangPatterns #-}
import Data.Monoid
import Data.Foldable (toList)
import Data.Sequence (Seq, (|>))
interleave2 :: [a] -> [a] -> [[a]]
interleave2 xs ys = interleave2' mempty xs ys []
interleave2' :: Seq a -> [a] -> [a] -> [[a]] -> [[a]]
interleave2' !prefix xs ys rest =
(toList prefix ++ xs ++ ys)
: interleave2'' prefix xs ys rest
interleave2'' :: Seq a -> [a] -> [a] -> [[a]] -> [[a]]
interleave2'' !prefix [] _ = id
interleave2'' !prefix _ [] = id
interleave2'' !prefix xs#(x : xs') ys#(y : ys') =
interleave2' (prefix |> y) xs ys' .
interleave2'' (prefix |> x) xs' ys
Using foldr over interleave2
interleave :: [[a]] -> [[a]]
interleave = foldr ((concat .) . map . iL2) [[]] where
iL2 [] ys = [ys]
iL2 xs [] = [xs]
iL2 (x:xs) (y:ys) = map (x:) (iL2 xs (y:ys)) ++ map (y:) (iL2 (x:xs) ys)
Another approach would be to use the list monad:
interleavings xs ys = interl xs ys ++ interl ys xs where
interl [] ys = [ys]
interl xs [] = [xs]
interl xs ys = do
i <- [1..(length xs)]
let (h, t) = splitAt i xs
map (h ++) (interl ys t)
So the recursive part will alternate between the two lists, taking all from 1 to N elements from each list in turns and then produce all possible combinations of that. Fun use of the list monad.
Edit: Fixed bug causing duplicates
Edit: Answer to dfeuer. It turned out tricky to do code in the comment field. An example of solutions that do not use length could look something like:
interleavings xs ys = interl xs ys ++ interl ys xs where
interl [] ys = [ys]
interl xs [] = [xs]
interl xs ys = splits xs >>= \(h, t) -> map (h ++) (interl ys t)
splits [] = []
splits (x:xs) = ([x], xs) : map ((h, t) -> (x:h, t)) (splits xs)
The splits function feels a bit awkward. It could be replaced by use of takeWhile or break in combination with splitAt, but that solution ended up a bit awkward as well. Do you have any suggestions?
(I got rid of the do notation just to make it slightly shorter)
Combining the best ideas from the existing answers and adding some of my own:
import Control.Monad
interleave [] ys = return ys
interleave xs [] = return xs
interleave (x : xs) (y : ys) =
fmap (x :) (interleave xs (y : ys)) `mplus` fmap (y :) (interleave (x : xs) ys)
interleavings :: MonadPlus m => [[a]] -> m [a]
interleavings = foldM interleave []
This is not the fastest possible you can get, but it should be good in terms of general and simple.

Haskell - How can I make this lists into tuple function pair with all elements?

So i have
pair:: [a] -> [b] -> [(a,b)]
pair[] _ = []
pair(x:xs) (y:ys) = (x, y) : prod xs ys
But the result are only like the following:
>> pair [1,2] [3,4]
>> [(1,3),(2,4)]
How can I make this so it pairs like:
[(1,3),(1,4),(2,3),(2,4)]
You can use the list applicative (or monad) instance:
λ> liftA2 (,) [1,2] [3,4]
[(1,3),(1,4),(2,3),(2,4)]
Or, equivalently,
f = do
x <- [1,2]
y <- [3,4]
return (x,y)
You can also use a list comprehension:
[ (x,y) | x <- [1,3], y <- [2,4] ]
Although there is already a much more elegant answer, i think it is worthwhile to show how this would be achieved in a simple straightforward way. If you want to get all pairs, you obviously need to visit every element of one list for an element in the other.
pair :: [a] -> [b] -> [(a, b)]
pair [] _ = []
pair (x:xs) ys = pair' x ys ++ pair xs ys where
pair' :: a -> [b] -> [(a, b)]
pair' _ [] = []
pair' x (y:ys) = (x,y) : pair' x ys
But of course using the pair = liftA2 (,) or [1,3] >>= \x -> [2,4] >>= \y -> (x,y) in its do notation or list comprehension notation is much better. Also ++ isn't what you normally want to do. So maybe you can build the lists as pair' would do, keep them in a list and then concat them.
concat $ map (\x -> map (\y -> (x,y)) ys) xs

map of all successors for each element in haskell

Given a sequence of elements, I want to find a list of all the direct successors for each element:
Example:
"AABAABAAC"
Should return something like (using Data.Map):
fromList [('A',"ABABA"), ('B',"AA"), ('C', "")]
I am aware of the fromListWith function but I can't seem to get the list comprehension right:
succs :: Ord a => [a] -> M.Map a [a]
succs xs = M.fromListWith (++) [(x, ???) | ??? ]
Does this help?
succs xs#(_:xss) = M.fromListWith (++) $ zip xs (map (:[]) xss ++ [[]])
I think it returns ('A',"ABABAC")..., your example has no C.
(:[]) is a point-free version of
singleton :: a -> [a]
singleton x = [x]
How did I get to this solution? I find this definition for the fibonacci numbers fascinating: [1] [2]
fibs = fibs = 0:1:zipWith (+) fibs (tail fibs)
A similar thing can pair up every element with its successor:
let x = "AABAABAAC"
zip x (tail x)
[('A','A'),('A','B'),('B','A'),('A','A'),('A','B'),('B','A'),('A','A'),('A','C')]
This type almost matches the input to
M.fromListWith :: Ord k => (a -> a -> a) -> [(k, a)] -> M.Map k a
Now turn the characters into singleton lists and add an empty list to not suppress ('C',"").
You can split the problem into two parts. First, find the edges between two elements of a list.
edges :: [a] -> [(a, a)]
edges (x:y:zs) = (x,y):edges (y:zs)
edges _ = []
Then build a map to all the items that are the immediate successors of an item with fromListWith.
succs :: Ord a => [a] -> M.Map a [a]
succs = M.fromListWith (++) . map (\(x,y) -> (x,[y])) . edges
This doesn't give quite exactly what you desire. There's no entry for 'C' since it has no immediate successors.
succs "AABAABAAC" = fromList [('A',"CABABA"),('B',"AA")]
Instead we can make a less general-purpose version of edges that includes an item for the last item in the list.
succs :: Ord a => [a] -> M.Map a [a]
succs = M.fromListWith (++) . edges
where
edges (x:y:zs) = (x,[y]):edges (y:zs)
edges (x:zs) = (x,[] ):edges zs
edges _ = []

Resources