module Sample where
lastPeg = 15
leftCol = [1, 2, 4, 7 , 11]
rightCol = [1, 3, 6, 10, 15]
rowData = []
makeRowData :: Integer-> Integer-> [Integer]
makeRowData row pos =
if (pos <= lastPeg) then
if (pos >= leftCol !! (fromIntegral row-1)) &&
(pos <= rightCol !! (fromIntegral row-1)) then
do
rowData ++ [row]
makeRowData row (pos + 1)
else
makeRowData (row+1) (pos)
else
rowData
What I am essentially trying to do is make a triangle-shaped vector
represented as a single vector. Given a position within the triangle
I want to return the row containing that position.
For example:
rowData [6] = 4 (Represented as the 7th position in the triangle)
desired result: rowData = [1, 2, 2, 3, 3, 3, 4, 4, 4, 4, 5, 5, 5, 5, 5]
actual result: rowData = []
What am I doing wrong? Thanks.
Your central issue is in this part of the code:
do
rowData ++ [row]
makeRowData row (pos + 1)
I wonder if someone explained the operator (++) :: [a] -> [a] -> [a] to you as “appends a list to another list”, giving you the impression that an expression like xs ++ ys modifies xs. The first problem is that this isn’t the case; in reality this operator returns a new list consisting of the two inputs concatenated together, e.g. in GHCi:
> xs = [1, 2, 3]
> ys = [4, 5]
> xs ++ ys -- Append the lists.
[1, 2, 3, 4, 5]
> xs -- The original lists aren’t modified.
[1, 2, 3]
> ys
[4, 5]
The second problem is that the do block here has misled you: it’s operating on lists, so it doesn’t do the sequencing like IO that you seem to expect. do notation can be used with lists because the list type has an instance of the Monad typeclass, but instead of sequencing like IO, the list Monad instance does iteration, exactly like a list comprehension.
A full tutorial on monads and do notation is beyond the scope of this answer, but for example, all of these are equivalent:
-- List comprehension:
[x * y | x <- [2, 3], y <- [3, 5]]
-- Equivalent ‘do’ notation:
do { x <- [2, 3]; y <- [3, 5]; pure (x * y) }
-- Desugared ‘do’ notation:
[2, 3] >>= (\ x -> [3, 5] >>= (\ y -> pure (x * y)))
-- Instances of ‘Monad’ & ‘Applicative’ for lists:
concatMap (\ x -> concatMap (\ y -> [x * y]) [3, 5]) [2, 3]
-- Result of all of the above:
[6, 10, 9, 15]
So what your do block is doing is iterating over the list rowData ++ [row], which is always the single element row, because rowData is always the empty list [], by its definition. = means equal! In that single “loop” iteration, there’s a recursive call to makeRowData, and these calls continue, counting up with the pos parameter until it reaches lastPeg, at which point the function returns rowData, which is, again, just another name for [].
There are simpler and more idiomatic ways to solve the problem, but for the sake of learning, if you want to make as small a modification as possible and keep essentially this same explicit recursive structure, then the general principle of the solution is this:
Add a helper function with an “accumulator” parameter that keeps track of your intermediate state
Call this function from makeRowData with the initial state
If necessary, perform some final processing on the result before returning it from makeRowData
For example:
makeRowData :: Integer -> Integer -> [Integer]
makeRowData initialRow initialPos
-- Start the “loop” with an initial ‘rowData’ of ‘[]’.
= makeRowDataHelper [] initialRow initialPos
makeRowDataHelper :: [Integer] -> Integer -> Integer -> [Integer]
makeRowDataHelper rowData row pos =
if (pos <= lastPeg) then
if (pos >= leftCol !! (fromIntegral row-1)) &&
(pos <= rightCol !! (fromIntegral row-1)) then
-- To “modify” the state for the next iteration,
-- recursively call ‘go’ with different values.
makeRowDataHelper (rowData ++ [row]) row (pos + 1)
else
makeRowDataHelper rowData (row+1) (pos)
else
-- To exit the iteration, just return a value.
rowData
I haven’t tested whether your logic is actually correct here, but at least this should help you get unstuck.
Beyond that, there are also a few performance and style improvements you could make here:
Appending linked lists with ++ is slow; each iteration of go above, ++ must traverse the entire left hand side to construct its result, and that argument grows with each recursive call, so this function ends up taking quadratic time O(n2) in the length of the input. That doesn’t matter so much for small lists like this, but quickly becomes too inefficient to use with larger inputs.
A common way to solve this is to instead prepend elements to the accumulator parameter using the “cons” operator (element : list) in reverse order instead of appending them (list ++ [element]), then reverse the result afterward if necessary, since this is only linear O(n).
Instead of if … then … else … at the top level of a definition, it’s generally considered more idiomatic to use guards, for example:
go rowData row pos
| pos > lastPeg
= rowData
| pos >= leftCol !! (fromIntegral row-1)
, pos <= rightCol !! (fromIntegral row-1)
= …
| otherwise
= …
You’re repeatedly using !! on lists, which also takes linear time O(n) in the value of the index to traverse the list. Consider using a different data structure, such as Data.Array or Data.Vector which have constant-time O(1) indexing, or a different algorithm that doesn’t require random-access indexing into the lists. (E.g. look into the replicate function.)
Related
Reading the book Get Programming with Haskell, one of the questions was to find if a given element is in the first half of a list. This can be done as
isInFirstHalf x xs = elem x firstHalf
where firstHalf = take (length xs `div` 2) xs
However, the problem is that here length traverses the whole list. In an imperative language, one can shortcircut the loop early by keeping track of the element index and the current counter. E.g. if the list has a million elements, and there was a match on the third element, once you finish looping through the sixth element, you can immediately return true.
My question is if there's a way to implement something like this in Haskell.
Sure.
halfAsLong (x:_:xs) = x:halfAsLong xs
halfAsLong _ = []
isInFirstHalf x xs = elem x (zipWith const xs (halfAsLong xs))
Try it out:
> isInFirstHalf 3 (1:2:3:4:5:6:undefined)
True
Exercises for the reader:
Where did the element index and current counter of your proposed imperative solution go? (They are still in there, just hidden in a way I think is a bit subtle!)
This rounds down when dividing odd lengths in half, like length xs `div` 2 does. How would the code have to change to round up, like (length xs + 1) `div` 2 does?
Daniel Wagner posted a very nice answer that shows that you don't really need indices, after all.
Still, if you do want to use indices, a solution can be crafted as follows.
We enumerate all the list elements by pairing them with their indices. This is done by using zip [0..] xs (or zip [1..] xs if you want to start counting at 1).
We find whether your x is in the list, and find its index i if it's present. One could proceed by direct recursion, or use something like dropWhile ((/= x) . fst) ... and then test the result.
Once we know i, we need to check whether there are at least i elements after that. This can be solved by direct recursion, or by dropping i-1 elements and testing whether the result is a non empty list.
There are other alternatives, of course. We could for instance skip enumerating elements with zip [0..] and use recursion by keeping track of the current index: foo n x (y:ys) = ... foo (n+1) x ys ....
Here’s another way to think of the task. An element x appears in the first half of a list xs, excluding the midpoint, if there are strictly fewer elements before the first occurrence of the element than after it.
We can write break (== x) xs using the standard function break :: (a -> Bool) -> [a] -> ([a], [a]) to split xs into two parts: those appearing before x (or all of xs, if x is not found), and the remainder (including x, if it is found).
> break (== 0) []
([], [])
> break (== 0) [0, 1]
([], [0, 1])
> break (== 0) [1, 0]
([1], [0])
> break (== 0) [1, 2, 0, 3, 4]
([1, 2], [0, 3, 4])
> break (== 0) [1, 2, 3, 4]
([1, 2, 3, 4], [])
We then want to compare the lengths of these two parts without calculating the actual lengths strictly as Int. To do so, we can compute the shape of each part by ignoring all its elements, using shape = map (const ()), a.k.a. void :: (Functor f) => f a -> f () specialised to lists.
shape :: [a] -> [()]
shape = void
The Ord instance for lists sorts them lexicographically, and all values of type () are equal—okay, the only value of type ()—so a comparison of shapes [()] is a comparison of the lengths of the lists, which is also lazy enough for our purposes. (For maximal laziness, shape could be defined as genericLength on a lazy natural number type like data N = Z | S N with an appropriate Ord instance.)
> [] < repeat ()
True
> shape [5 .. 10] >= shape [1 .. 3]
True
> shape [1 .. 3] > shape [1 ..]
False
We can also “decrement” the shape of a list using drop 1, which we’ll use to skip counting the element itself if it was found. (Alternatively, we could “increment” the shape with (() :).)
Finally, putting these elements together leads to a fairly simple solution:
isInFirstHalf :: (Eq a) => a -> [a] -> Bool
isInFirstHalf x xs = shape before < shape (drop 1 after)
where
(before, after) = break (== x) xs
Notice that if the element was not found, after will be empty, so drop 1 will have no effect, but the shape of before can’t possibly be smaller than the empty shape [], so the comparison (<) will still correctly return False.
I have an array of sequences, with infinite iterations (e.g. [6,6,6,6,6] or [23, 24, 23, 24] or [1, 2, 3, 4, 1, 2, 3, 4])
How do I iterate through each such list in Haskell and return only the first iteration? In case of the above examples: [6]; [23, 24]; [1, 2, 3, 4]
Thanks!
Edit: Sorry, I wasn't precise. The lists are indeed infinte. My goal is to return a list of the aliquot sequence of a given Integer. I have a function which returns the sum of the dividers. I started a recursive call with the first sum, and constructed the list. That resulted in lists like [6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6...].
First I wanted to solve the problem by taking the first part of the list, up to the second occurrence of the original Int. But then it hit me: It's easier to check with elem if the sum exists in the list. If yes, return the list as-is. Otherwise, append the sum and go on.
Edit 2: The code that produces the (in my definition at least) infinite list is the following chunk:
aliquot :: (Integral a) => a -> [a]
aliquot 0 = []
aliquot 1 = [1]
aliquot n = n : (aliquot $ sum $ divisors n)
divisors :: (Integral a) => a -> [a]
divisors n = filter ((0 ==) . (n `mod`)) [1 .. (n `div` 2)]
This isn't possible. Consider this sequence: [1,1,1,1,1,1,1... It looks like the answer here is [1], right? Wrong. That sequence was actually the greatest common factor of (x^17 + 9) and ((x + 1)^17 + 9), which stops being all 1s once you get to the 8424432925592889329288197322308900672459420460792433rd element. Or consider this other sequence: [1,1,1,1,1,1,1.... The world's greatest mathematicians aren't sure what the answer is for this sequence. It's the smallest number ever reached by the Collatz sequence for each starting value, and although we've never found a number where this isn't 1, we haven't been able to actually prove that it will be 1 for all numbers.
I have a given list, e.g. [2, 3, 5, 587] and I want to have a complete list of the combination. So want something like [2, 2*3,2*5, 2*587, 3, 3*5, 3*587, 5, 5*587, 587]. Since I am on beginner level with Haskell I am curious how a list manipulation would look like.
Additionally I am curious if the computation of the base list might be expensive how would this influence the costs of the function? (If I would assume the list has limit values, i.e < 20)
Rem.: The order of the list could be done afterwards, but I have really no clue if this is cheaper within the function or afterwards.
The others have explained how to make pairs, so I concern myself here with getting the combinations.
If you want the combinations of all lengths, that's just the power set of your list, and can be computed the following way:
powerset :: [a] -> [[a]]
powerset (x:xs) = let xs' = powerset xs in xs' ++ map (x:) xs'
powerset [] = [[]]
-- powerset [1, 2] === [[],[2],[1],[1,2]]
-- you can take the products:
-- map product $ powerset [1, 2] == [1, 2, 1, 2]
There's an alternative powerset implementation in Haskell that's considered sort of a classic:
import Control.Monad
powerset = filterM (const [True, False])
You could look at the source of filterM to see how it works essentially the same way as the other powerset above.
On the other hand, if you'd like to have all the combinations of a certain size, you could do the following:
combsOf :: Int -> [a] -> [[a]]
combsOf n _ | n < 1 = [[]]
combsOf n (x:xs) = combsOf n xs ++ map (x:) (combsOf (n - 1) xs)
combsOf _ _ = []
-- combsOf 2 [1, 2, 3] === [[2,3],[1,3],[1,2]]
So it seems what you want is all pairs of products from the list:
ghci> :m +Data.List
ghci> [ a * b | a:bs <- tails [2, 3, 5, 587], b <- bs ]
[6,10,1174,15,1761,2935]
But you also want the inital numbers:
ghci> [ a * b | a:bs <- tails [2, 3, 5, 587], b <- 1:bs ]
[2,6,10,1174,3,15,1761,5,2935,587]
This uses a list comprehension, but this could also be done with regular list operations:
ghci> concatMap (\a:bs -> a : map (a*) bs) . init $ tails [2, 3, 5, 587]
[2,6,10,1174,3,15,1761,5,2935,587]
The latter is a little easier to explain:
Data.List.tails produces all the suffixes of a list:
ghci> tails [2, 3, 5, 587]
[[2,3,5,587],[3,5,587],[5,587],[587],[]]
Prelude.init drops the last element from a list. Here I use it to drop the empty suffix, since processing that causes an error in the next step.
ghci> init [[2,3,5,587],[3,5,587],[5,587],[587],[]]
[[2,3,5,587],[3,5,587],[5,587],[587]]
ghci> init $ tails [2, 3, 5, 587]
[[2,3,5,587],[3,5,587],[5,587],[587]]
Prelude.concatMap runs a function over each element of a list, and combines the results into a flattened list. So
ghci> concatMap (\a -> replicate a a) [1,2,3]
[1, 2, 2, 3, 3, 3]
\(a:bs) -> a : map (a*) bs does a couple things.
I pattern match on my argument, asserting that it matches an list with at least one element (which is why I dropped the empty list with init) and stuffs the initial element into a and the later elements into bs.
This produces a list that has the same first element as the argument a:, but
Multiplies each of the later elements by a (map (a*) bs).
You can get the suffixes of a list using Data.List.tails.
This gives you a list of lists, you can then do the inner multiplications you want on this list with a function like:
prodAll [] = []
prodAll (h:t) = h:(map (* h) $ t)
You can then map this function over each inner list and concatenate the results:
f :: Num a => [a] -> [a]
f = concat . map prodAll . tails
There is a clear way to convert binary recursion to tail recursion for sets closed under a function, i.e. integers with addition for the Fibonacci sequence:
(Using Haskell)
fib :: Int -> Int
fib n = fib' 0 1 n
fib' :: Int -> Int -> Int
fib' x y n
| n < 1 = y
| otherwise = fib' y (x + y) (n - 1)
This works because we have our desired value, y, and our operation, x + y, where x + y returns an integer just like y does.
However, what if I want to use a set that is not closed under a function? I want to take a function that splits a list into two lists and then does the same to those two lists (i.e. like recursively creating a binary tree), where I stop when another function magically says when to stop when it looks at the resulting split:
[1, 2, 3, 4, 5] -> [[1, 3, 4], [2, 5]] -> [[1, 3], [4], [2], [5]]
That is,
splitList :: [Int] -> [[Int]]
splitList intList
| length intList < 2 = [intList]
| magicFunction x y > 0 = splitList x ++ splitList y
| otherwise = [intList]
where
x = some sublist of intList
y = the other sublist of intList
Now, how can this binary recursion be converted to tail recursion? The prior method won't explicitly work, as (Int + Int -> Int is the same as the inputs) but (Split [Int] -/> [[Int]] is not the same as the input). As such, the accumulator would need to be changed (I assume).
There is a general trick to make any function tail recursive: rewrite it in continuation-passing style (CPS). The basic idea behind CPS is that every function takes an additional parameter--a function to call when they're done. Then, instead of returning a value, the original functions calls the function that was passed in. This latter function is called a "continuation" because it continues the computation on to its next step.
To illustrate this idea, I'm just going to use your function as an example. Note the changes to the type signature as well as the structure of the code:
splitListCPS :: [Int] -> ([[Int]] -> r) -> r
splitListCPS intList cont
| length intList < 2 = cont [intList]
| magicFunction x y > 0 = splitListCPS x $ \ r₁ ->
splitListCPS y $ \ r₂ ->
cont $ r₁ ++ r₂
| otherwise = cont [intList]
You can then wrap this up into a normal-looking function as follows:
splitList :: [Int] -> [[Int]]
splitList intList = splitListCPS intList (\ r -> r)
If you follow the slightly convoluted logic, you'll see that these two functions are equivalent. The tricky bit is the recursive case. There, we immediately call splitListCPS with x. The function \ r₁ -> ... that tells splitListCPS what to do when it's done--in this case, call splitListCPS with the next argument (y). Finally, once we have both results, we just combine the results and pass that into the original continuation (cont). So at the end, we get the same result we had originally (namely splitList x ++ splitList y) but instead of returning it, we just use the continuation.
Also, if you look through the above code, you'll note that all the recursive calls are in tail position. At each step, our last action is always either a recursive call or using the continuation. With a clever compiler, this sort of code can actually be fairly efficient.
In a certain sense, this technique is actually similar to what you did for fib; however, instead of maintaining an accumulator value we sort of maintain an accumulator of the computation we're doing.
You don't generally want tail-recursion in Haskell. What you do want, is productive corecursion (see also this), describing what in SICP is called an iterative process.
You can fix the type inconsistency in your function by enclosing initial input in a list. In your example
[1, 2, 3, 4, 5] -> [[1, 3, 4], [2, 5]] -> [[1, 3], [4], [2], [5]]
only the first arrow is inconsistent, so change it into
[[1, 2, 3, 4, 5]] -> [[1, 3, 4], [2, 5]] -> [[1, 3], [4], [2], [5]]
which illustrates the process of iteratively applying concatMap splitList1, where
splitList1 xs
| null $ drop 1 xs = [xs]
| magic a b > 0 = [a,b] -- (B)
| otherwise = [xs]
where (a,b) = splitSomeHow xs
You want to stop if no (B) case was fired at a certain iteration.
(edit: removed the intermediate version)
But it is much better to produce the portions of the output that are ready, as soon as possible:
splitList :: [Int] -> [[Int]]
splitList xs = g [xs] -- explicate the stack
where
g [] = []
g (xs : t)
| null $ drop 1 xs = xs : g t
| magic a b > 0 = g (a : b : t)
| otherwise = xs : g t
where (a,b) = splitSomeHow xs
-- magic a b = 1
-- splitSomeHow = splitAt 2
Don't forget to compile with -O2 flag.
I'm taking my first steps into the wonderful world of Haskell. As an exercise, I would like to implement a method which finds the maximum element of a list and its index. Let's call this function "maxi". Calling maxi on a list should return the following result:
ghci> maxi [1, 3, 4, 1, 2, 3]
(4, 2)
4 is the largest int in this list, and it is located at index 2.
I have attempted to implement this function as follows:
maxim :: (Ord a) => [a] -> (a, Int)
maxim l =
let pmaxim :: (Ord a) => [a] -> Int -> (a, Int) -- Internal function to do the work
pmaxim [] _ = error "Empty list" -- List is empty, error
pmaxim [x] xi = (x, xi) -- List has one item, return it and the index
pmaxim (x:xs) xi -- More than one item, break list apart
| x > t = (x, xi) -- If current item is bigger, return it and its index
| otherwise = (t, ti) -- If list tail has a bigger item, return that
where (t, ti) = pmaxim xs (ti + 1) -- Get max of tail of the list
in pmaxim l 0 -- Call internal function with start index
When I call this, I get something really weird: ghci seems to hang after returning the max element's value.
ghci> maxi [1, 3, 4, 1, 2, 3]
(4,
I will venture a guess that this has something to do with Haskell's lazy evaluation nature, but I'm finding it difficult to figure out what is actually going on here, and how to fix it. I would also be really grateful for any tips anyone might have about how to debug in Haskell. Is there an easy way to print out values during execution without effecting behavior?
I just wanted to point out that I am aware that there are several better ways to get this behavior using built-in Haskell functions. I am implementing this from scratch to try and learn Haskell.
Thank you
It's because of a slight bug in your code. You have:
where (t, ti) = pmaxim xs (ti + 1)
... but it should actually be:
where (t, ti) = pmaxim xs (xi + 1)
This fixes your code, which now produces the correct solution:
>>> maxim [1, 2, 3, 2, 1]
(3, 2)
Your code hanged because your computation for ti results in an endless loop since you accidentally defined it in terms of itself. Note that ghc is a sufficiently smart compiler and figures out that t does not depend on the value of ti, which is why your version could still successfully compute the maximum value even if it cannot compute the index.
The standard way to debug pure computations is the Debug.Trace module.
As a side note, there is a much simpler solution:
import Data.List
import Data.Ord
maxi xs = maximumBy (comparing fst) (zip xs [0..])
Edit: Oops, I didn't see that you were deliberately implementing it from scratch, but I'll still leave that there.
I see you already got your question answered. I managed to do it without recursion, using lambda functions.
maxim xs = foldr (\ (x,y) acc -> if (x == maximum xs) then (x,y) else acc) (0,head xs) (zip xs [0..])