defining last using foldr

Hi, I am trying to do the exercise which asks to define built-in functions 'last' and 'init' using 'foldr' function, such as last "Greggery Peccary" = 'y' the type for my function is: myLast :: [Char] -> Char I am not generalizing type so that make it less complicated. But what ever i am trying would not work. The only function type foldr takes as an argument is either (a->a->a) or (a->b->b) and none of the functions i found that would match this type from Char to Char. So in other words should be (Char->Char-Char). I can define the function without foldr but that misses the point of the exercise. Any hint will be appreciated, Thank you -- View this message in context: http://www.nabble.com/defining-last-using-foldr-tf4269357.html#a12151145 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On 2007-08-14, Alexteslin
Hi,
I am trying to do the exercise which asks to define built-in functions 'last' and 'init' using 'foldr' function, such as last "Greggery Peccary" = 'y'
the type for my function is:
myLast :: [Char] -> Char
I am not generalizing type so that make it less complicated. But what ever i am trying would not work. The only function type foldr takes as an argument is either (a->a->a) or (a->b->b) and none of the functions i found that would match this type from Char to Char. So in other words should be (Char->Char-Char). I can define the function without foldr but that misses the point of the exercise.
Folds replace the "cons" operator (:) with the function you pass it. If you want the tail of the list, you want what is on the right hand side of every cons (unless that's []). -- Aaron Denney -><-

Well, i have tried cons (:) operator but when it passed to foldr doesn't work because cons operator operates first character and then the list but the foldr argument takes a function (a->a->a). Maybe i am missing the point here? Aaron Denney wrote:
On 2007-08-14, Alexteslin
wrote: Hi,
I am trying to do the exercise which asks to define built-in functions 'last' and 'init' using 'foldr' function, such as last "Greggery Peccary" = 'y'
the type for my function is:
myLast :: [Char] -> Char
I am not generalizing type so that make it less complicated. But what ever i am trying would not work. The only function type foldr takes as an argument is either (a->a->a) or (a->b->b) and none of the functions i found that would match this type from Char to Char. So in other words should be (Char->Char-Char). I can define the function without foldr but that misses the point of the exercise.
Folds replace the "cons" operator (:) with the function you pass it. If you want the tail of the list, you want what is on the right hand side of every cons (unless that's []).
-- Aaron Denney -><-
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- View this message in context: http://www.nabble.com/defining-last-using-foldr-tf4269357.html#a12151694 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

2007/8/14, Alexteslin
Well, i have tried cons (:) operator but when it passed to foldr doesn't work because cons operator operates first character and then the list but the foldr argument takes a function (a->a->a). Maybe i am missing the point here?
What Aaron was saying was that in this list : 1 : 2 : 3 : 4 : [] A fold replaced the cons (:) by another function (and [] by another constant). Your problem isn't so easy to do with a foldr, a foldl would be easier and a foldr1 or foldl1 even better. Are you sure you can't use one of those other folds ? -- Jedaï

On 2007-08-14, Chaddaï Fouché
2007/8/14, Alexteslin
: Well, i have tried cons (:) operator but when it passed to foldr doesn't work because cons operator operates first character and then the list but the foldr argument takes a function (a->a->a). Maybe i am missing the point here?
What Aaron was saying was that in this list : 1 : 2 : 3 : 4 : [] A fold replaced the cons (:) by another function (and [] by another constant).
Your problem isn't so easy to do with a foldr, a foldl would be easier and a foldr1 or foldl1 even better. Are you sure you can't use one of those other folds ?
The problem with foldl is that you can't easily make it polymorphic because of how the null case is handled. foldl1 and foldr1 are trivial, true. -- Aaron Denney -><-

2007/8/14, Aaron Denney
The problem with foldl is that you can't easily make it polymorphic because of how the null case is handled. foldl1 and foldr1 are trivial, true.
The original "last" fail on empty list, it's far easier to obtain the same semantic with foldl than with foldr, in fact it isn't hard at all to make it polymorphic without hassle (contrary to the foldr case) _if_ you remember that there _is_ a value in Haskell wich belongs to every type. -- Jedaï

On 2007-08-14, Chaddaï Fouché
2007/8/14, Aaron Denney
: The problem with foldl is that you can't easily make it polymorphic because of how the null case is handled. foldl1 and foldr1 are trivial, true.
The original "last" fail on empty list, it's far easier to obtain the same semantic with foldl than with foldr, in fact it isn't hard at all to make it polymorphic without hassle (contrary to the foldr case) _if_ you remember that there _is_ a value in Haskell wich belongs to every type.
Hah. True. That does simplify things considerably. Still, I'd call that an infelicity in last (and head, for that matter), and would rather have such errors handled at the call site than making the entire program fall over. -- Aaron Denney -><-

2007/8/15, Aaron Denney
The original "last" fail on empty list, it's far easier to obtain the same semantic with foldl than with foldr, in fact it isn't hard at all to make it polymorphic without hassle (contrary to the foldr case) _if_ you remember that there _is_ a value in Haskell wich belongs to every type.
Hah. True. That does simplify things considerably. Still, I'd call that an infelicity in last (and head, for that matter), and would rather have such errors handled at the call site than making the entire program fall over.
Control.Exception.catch (evaluate $ myLast []) print (in GHC it works) Still I don't see why foldl would make it harder to use Maybe than foldr (in fact it's easier). -- Jedaï

You can consider foldr to be continual modification of a state. The
initial state is given as an argument, and then the (a -> b -> b)
function is passed the next element of the list and the current state,
and it returns the new state. foldr will then return the final state,
from which the result can be extracted. Does that help?
On 14/08/07, Alexteslin
Well, i have tried cons (:) operator but when it passed to foldr doesn't work because cons operator operates first character and then the list but the foldr argument takes a function (a->a->a). Maybe i am missing the point here?
Aaron Denney wrote:
On 2007-08-14, Alexteslin
wrote: Hi,
I am trying to do the exercise which asks to define built-in functions 'last' and 'init' using 'foldr' function, such as last "Greggery Peccary" = 'y'
the type for my function is:
myLast :: [Char] -> Char
I am not generalizing type so that make it less complicated. But what ever i am trying would not work. The only function type foldr takes as an argument is either (a->a->a) or (a->b->b) and none of the functions i found that would match this type from Char to Char. So in other words should be (Char->Char-Char). I can define the function without foldr but that misses the point of the exercise.
Folds replace the "cons" operator (:) with the function you pass it. If you want the tail of the list, you want what is on the right hand side of every cons (unless that's []).
-- Aaron Denney -><-
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- View this message in context: http://www.nabble.com/defining-last-using-foldr-tf4269357.html#a12151694 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

(Quoting reformatted. Try to have your responses below what you are
responding to. It makes it easier to read as a conversation.)
On 2007-08-14, Alexteslin
Aaron Denney wrote:
Folds replace the "cons" operator (:) with the function you pass it. If you want the tail of the list, you want what is on the right hand side of every cons (unless that's []).
Well, i have tried cons (:) operator but when it passed to foldr doesn't work because cons operator operates first character and then the list but the foldr argument takes a function (a->a->a). Maybe i am missing the point here?
I didn't say to use (:), I said foldr works by replacing (:) with some other function. foldr also takes a function of type (a -> b -> b). foldr f e replaces (first : (middle : (last : []))) with (first `f` (middle `f` (last `f` e))) You want last to be kept, so f x e = x this causes the overall pattern to reduce to (first `f` (middle `f` last)) This time you need f y last = last This means you need to discriminate between "e" and "last". If you make "e" the same type as last, you could accidentally compare them equal. So instead of using the same type, we want one with one more value. There is a standard one: "Maybe a", with constructors "Just a" and "Nothing". And you also need to promote last to this type with the constructor Just, because the result gets fed in on the right. -- Aaron Denney -><-

Aaron Denney wrote:
(Quoting reformatted. Try to have your responses below what you are responding to. It makes it easier to read as a conversation.)
On 2007-08-14, Alexteslin
wrote: Aaron Denney wrote:
Folds replace the "cons" operator (:) with the function you pass it. If you want the tail of the list, you want what is on the right hand side of every cons (unless that's []).
Well, i have tried cons (:) operator but when it passed to foldr doesn't work because cons operator operates first character and then the list but the foldr argument takes a function (a->a->a). Maybe i am missing the point here?
I didn't say to use (:), I said foldr works by replacing (:) with some other function.
foldr also takes a function of type (a -> b -> b).
foldr f e replaces (first : (middle : (last : []))) with (first `f` (middle `f` (last `f` e)))
You want last to be kept, so f x e = x
this causes the overall pattern to reduce to (first `f` (middle `f` last))
This time you need f y last = last
This means you need to discriminate between "e" and "last".
If you make "e" the same type as last, you could accidentally compare them equal. So instead of using the same type, we want one with one more value. There is a standard one: "Maybe a", with constructors "Just a" and "Nothing". And you also need to promote last to this type with the constructor Just, because the result gets fed in on the right.
-- Aaron Denney -><-
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
I am really sorry, but i still can't define the function. The chapter the exercise is in precedes algebraic types or Maybe a types. And is seems that must being easy to define. I answered some exercises on using foldr such as summing for example, but this one i am trying: myLast :: [Int] -> Int myLast (x:xs) = foldr (some function) x xs. With summing as i understood foldr goes through the list and sums up by (+) operator and one argument like 0. Like: foldr (+) 0 xs -- View this message in context: http://www.nabble.com/defining-last-using-foldr-tf4269357.html#a12169661 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Alexteslin
I am really sorry, but i still can't define the function. The chapter the exercise is in precedes algebraic types or Maybe a types. And is seems that must being easy to define. I answered some exercises on using foldr such as summing for example, but this one i am trying:
myLast :: [Int] -> Int myLast (x:xs) = foldr (some function) x xs.
With summing as i understood foldr goes through the list and sums up by (+) operator and one argument like 0. Like: foldr (+) 0 xs
You can think of foldr f e [a,b,c] as a `f` (b `f` (c `f` e)) so myLast [x,a,b,c] is going to be a `f` (b `f` (c `f` x)) so you need an f so that c `f` x is c (for any c and x) and yet (b `f` c) is c for any c and b -- this is impossible (or I'm asleep). So your skeleton above isn't going to work. You can do something like myLast l = unpick (foldr toLast [] l) where unpick ... toLast ... The above contains a strong hint as to the type of toLast (and hence unpick) -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

2007/8/15, Alexteslin
I am really sorry, but i still can't define the function. The chapter the exercise is in precedes algebraic types or Maybe a types. And is seems that must being easy to define.
If you don't have Maybe, you still have it's older brother, namely lists (as strongly hinted by Jon Fairbairn).
so you need an f so that c `f` x is c (for any c and x) and yet (b `f` c) is c for any c and b -- this is impossible (or I'm asleep).
Well, it isn't "impossible" but quite hard (and not even standard H98 if I'm not mistaken) and obviously not in the range of the possibilities here. Still you could "approximate" it, and in fact I believe the [Char] -> Char requirement is hinting at such a (arguably and IMO ugly) solution. For example you could assume there would be no "NUL" character in a string ([Char] is a synonym for String, or vice-versa), and then get a simple myLast for String in this restrictive case (and looking exactly like Alexteslin sample). -- Jedaï

"Chaddaï Fouché"
so you need an f so that c `f` x is c (for any c and x) and yet (b `f` c) is c for any c and b -- this is impossible (or I'm asleep).
Well, it isn't "impossible" but quite hard (and not even standard H98 if I'm not mistaken)
If it is possible, I'm very sad that we've allowed things to get into the language that make that kind of reasoning faulty.
Still you could "approximate" it, and in fact I believe the [Char] -> Char requirement is hinting at such a (arguably and IMO ugly) solution. For example you could assume there would be no "NUL" character in a string ([Char] is a synonym for String, or vice-versa), and then get a simple myLast for String in this restrictive case (and looking exactly like Alexteslin sample).
I certainly wouldn't count such a thing as a valid solution. It's always amazed me that C uses as standard a mechanism of ending strings that is so obviously an error-prone hack. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

16 Aug 2007 10:11:24 +0100, Jon Fairbairn
snip my quote
I certainly wouldn't count such a thing as a valid solution. It's always amazed me that C uses as standard a mechanism of ending strings that is so obviously an error-prone hack.
I'm completely with you on that ! Which is why I don't like the suggestion of doing it only for Char...
Well, it isn't "impossible" but quite hard (and not even standard H98 if I'm not mistaken)
If it is possible, I'm very sad that we've allowed things to get into the language that make that kind of reasoning faulty.
I spoke too fast on this one, it _is_ impossible (I think ?), but you can use the same trick as for Char to get a polymorphic function, arguably a little bit more useful than the Char one, since if you have a undefined as the last element of your list, there's a good chance anyway that your program is already in a bad state. Still it's an ugly hack altogether... Your suggestion is of course the right answer if there is an obligation to use a foldr and not just any fold. -- Jedaï

On 8/15/07, Alexteslin
I am really sorry, but i still can't define the function. The chapter the exercise is in precedes algebraic types or Maybe a types. And is seems that must being easy to define. I answered some exercises on using foldr such as summing for example, but this one i am trying:
myLast :: [Int] -> Int myLast (x:xs) = foldr (some function) x xs.
With summing as i understood foldr goes through the list and sums up by (+) operator and one argument like 0. Like: foldr (+) 0 xs
I don't think you can do it directly using just foldr. However, you can use foldr to build up a function that, when applied to the list, will evaluate to the last element. foldr will be acting like a function composition engine that evaluates to a function to process the list. I got the idea for this from the article titled "Getting a Fix from the Right Fold" in The Monad Read Issue 6 (http://www.haskell.org/sitewiki/images/1/14/TMR-Issue6.pdf). See if reading that article helps. In particular, Solution 2 described in the article is the one with the structure I'm talking about. (Solution 3 fixes a space leak in Solution 2, if you want a bit more complexity.)

Kurt Hutchinson wrote:
On 8/15/07, Alexteslin
wrote: I am really sorry, but i still can't define the function. The chapter the exercise is in precedes algebraic types or Maybe a types. And is seems that must being easy to define. I answered some exercises on using foldr such as summing for example, but this one i am trying:
myLast :: [Int] -> Int myLast (x:xs) = foldr (some function) x xs.
With summing as i understood foldr goes through the list and sums up by (+) operator and one argument like 0. Like: foldr (+) 0 xs
I don't think you can do it directly using just foldr. However, you can use foldr to build up a function that, when applied to the list, will evaluate to the last element. foldr will be acting like a function composition engine that evaluates to a function to process the list.
Something like this? (spoiler warning) http://hpaste.org/2283

Let's start by reminding ourselves what foldr does. foldr f z [x1,x2,...,xn] = f x1 (f x2 ... (f xn z) ...) Now let's ask about last: last [] = error ... last [x1,...,xn] = xn We're going to have to keep track of whether we have a last element or not. The obvious candidate for this is Maybe x. Initially there is no element, Nothing. f x Empty = Just x f x (Just y) = Just y This picks up a new value (x) when there wasn't one (Nothing) and keeps the old last element (Just y) when there was one (Just y). But this gives us a Maybe x, when we want an x, so we'll have to finish off with a fromJust. last = fromJust . foldr f Nothing where f _ r@(Just _) = r f x Nothing = Just x

On 8/16/07, ok
We're going to have to keep track of whether we have a last element or not. The obvious candidate for this is Maybe x. Initially there is no element, Nothing. f x Empty = Just x f x (Just y) = Just y This picks up a new value (x) when there wasn't one (Nothing) and keeps the old last element (Just y) when there was one (Just y). But this gives us a Maybe x, when we want an x, so we'll have to finish off with a fromJust.
last = fromJust . foldr f Nothing where f _ r@(Just _) = r f x Nothing = Just x
I had this idea as well, but the questioner said the chapter with the exercise preceded any use of Maybe, although I admit my suggestion of using foldr to compose a processing function is more complicated for a beginner. Here's a way to use the above idea without Maybe: myLast = head . foldr f [] where f x [] = [x] f _ [x] = [x]

For a really good article to see how foldr is in fact very powerful and how you can make it do some funny tricks, see the Monad.Reader 6th issue : http://www.haskell.org/sitewiki/images/1/14/TMR-Issue6.pdf I'll point out that you can write a lazy dropWhile with foldr in the style of the first example of the article just by using a non-refutable pattern in the combine function : dWLazy p = snd . foldr (\a ~(x, y) -> if p a then (a : x, y) else (a : x, a : x)) ([], []) -- Jedaï

2007/8/18, Chaddaï Fouché
For a really good article to see how foldr is in fact very powerful and how you can make it do some funny tricks, see the Monad.Reader 6th issue : http://www.haskell.org/sitewiki/images/1/14/TMR-Issue6.pdf
I just saw this was already linked in this thread, sorry for the noise... -- Jedaï

I've found a way to do it, but it's not pretty.
Hint: The function in the foldr first get the last value, and will
need to keep it the whole way through. How can it tell if it is being
given the last item or an earlier item?
I'm generally not too good at the Socratic method, so feel free to
email for some more help or my answer.
On 14/08/07, Alexteslin
Hi,
I am trying to do the exercise which asks to define built-in functions 'last' and 'init' using 'foldr' function, such as last "Greggery Peccary" = 'y'
the type for my function is:
myLast :: [Char] -> Char
I am not generalizing type so that make it less complicated. But what ever i am trying would not work. The only function type foldr takes as an argument is either (a->a->a) or (a->b->b) and none of the functions i found that would match this type from Char to Char. So in other words should be (Char->Char-Char). I can define the function without foldr but that misses the point of the exercise.
Any hint will be appreciated, Thank you -- View this message in context: http://www.nabble.com/defining-last-using-foldr-tf4269357.html#a12151145 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (8)
-
Aaron Denney
-
Al Falloon
-
Alexteslin
-
Chaddaï Fouché
-
Jon Fairbairn
-
Kurt Hutchinson
-
ok
-
Rodrigo Queiro