Ultra-newbie Question

Hello Haskell Community - I am a professional programmer with 11 years experience, yet I just do not seem to be able to get the hang of even simple things in Haskell. I am trying to write a function that takes a list and returns the last n elements. There may be a function which I can just call that does that, but I am trying to roll my own just to understand the concept. Let's call the function n_lastn and, given a list [1,2,3,4,5], I would like n_lastn 3 = [3,4,5] Seems like it would be something like: n_lastn:: [a]->Int->[a] n_lastn 1 (xs) = last(xs) n_lastn n (x:xs) = ???? The issue is I do not see how you can store the last elements of the list. Thanks in advance. ctauss

On 18 September 2010 17:51, Christopher Tauss
Hello Haskell Community -
I am a professional programmer with 11 years experience, yet I just do not seem to be able to get the hang of even simple things in Haskell. I am trying to write a function that takes a list and returns the last n elements.
There may be a function which I can just call that does that, but I am trying to roll my own just to understand the concept.
Let's call the function n_lastn and, given a list [1,2,3,4,5], I would like n_lastn 3 = [3,4,5]
Seems like it would be something like:
n_lastn:: [a]->Int->[a] n_lastn 1 (xs) = last(xs) n_lastn n (x:xs) = ????
The issue is I do not see how you can store the last elements of the list.
Easiest way I can think of: n_lastn n = reverse . take n . reverse Alternatively: n_lastn n xs = drop (len - n) xs where len = length xs -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Thanks you Ivan and David for clarifying this. Best Regards, Chris On Sat, Sep 18, 2010 at 3:55 AM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
Hello Haskell Community -
I am a professional programmer with 11 years experience, yet I just do not seem to be able to get the hang of even simple things in Haskell. I am trying to write a function that takes a list and returns the last n elements.
There may be a function which I can just call that does that, but I am trying to roll my own just to understand the concept.
Let's call the function n_lastn and, given a list [1,2,3,4,5], I would
n_lastn 3 = [3,4,5]
Seems like it would be something like:
n_lastn:: [a]->Int->[a] n_lastn 1 (xs) = last(xs) n_lastn n (x:xs) = ????
The issue is I do not see how you can store the last elements of the
On 18 September 2010 17:51, Christopher Tauss
wrote: like list. Easiest way I can think of:
n_lastn n = reverse . take n . reverse
Alternatively:
n_lastn n xs = drop (len - n) xs where len = length xs
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com http://ivanmiljenovic.wordpress.com/

Here is a more manual way to do it, hopefully this shows the approach
required. You don't need to store anything, just keep removing the
head of the list until its of the size you want.
n_lastn :: Int -> [a] -> [a]
n_lastn n xs =
let len = length xs - n
drp = if len < 0 then 0 else len
rmv 0 ys = ys
rmv m (y:ys) = rmv (m - 1) ys
in rmv drp xs
Cheers,
David
On 18 September 2010 17:51, Christopher Tauss
Hello Haskell Community -
I am a professional programmer with 11 years experience, yet I just do not seem to be able to get the hang of even simple things in Haskell. I am trying to write a function that takes a list and returns the last n elements.
There may be a function which I can just call that does that, but I am trying to roll my own just to understand the concept.
Let's call the function n_lastn and, given a list [1,2,3,4,5], I would like n_lastn 3 = [3,4,5]
Seems like it would be something like:
n_lastn:: [a]->Int->[a] n_lastn 1 (xs) = last(xs) n_lastn n (x:xs) = ????
The issue is I do not see how you can store the last elements of the list.
Thanks in advance.
ctauss _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 09/18/2010 02:51 AM, Christopher Tauss wrote:
I am trying to write a function that takes a list and returns the last n elements.
This may just be for the sake of learning, in which case this is fine, but usually, needing to do this would be a sign that you are using lists improperly (since this is a O(n) time operation).
Let's call the function n_lastn and, given a list [1,2,3,4,5], I would like n_lastn 3 = [3,4,5]
n_lastn n = reverse . take n . reverse - Jake

On Saturday 18 September 2010 19:44:38, Jake McArthur wrote:
On 09/18/2010 02:51 AM, Christopher Tauss wrote:
I am trying to write a function that takes a list and returns the last n elements.
This may just be for the sake of learning, in which case this is fine, but usually, needing to do this would be a sign that you are using lists improperly (since this is a O(n) time operation).
By which he meant O(length list), not the number of elements you're asking for.
Let's call the function n_lastn and, given a list [1,2,3,4,5], I would like n_lastn 3 = [3,4,5]
n_lastn n = reverse . take n . reverse
Which is the most elegant definition, but it's an O(length list) space operation (as are all others proposed so far). That will be a problem for long lists (consider n_lastn 10 [1 .. 10^8]). You can implement it as an O(n) [the number of elements you want] *space* operation, provided that the list is generated lazily and not referred to by anything else, but the code is decidedly less nice: The first idea would be to keep a window of n elements and move it to the end of the list: n_lastn n xs = case splitAt n xs of (ys,[]) -> ys -- the list contains at most n elements, yay (ys,zs) -> loop ys zs where loop window [] = window loop window (v:vs) = loop (tail window ++ [v]) vs The space behaviour is now fine (if compiled with optimisations), but unfortunately, the time complexity has become O(n*length list) because the (++)-calls are left-nested: Suppose n = 4, loop (1:2:3:4:[]) [5 .. end] ~> loop ((2:3:4:[]) ++ [5]) [6 .. end] ~> loop (2:((3:4:[]) ++ [5])) [6 .. end] ~> loop (((3:4:[]) ++ [5]) ++ [6]) [7 .. end] The strictness analyser has been smart enough to transform the call to tail into a strict pattern match on window, as if we'd written loop (_:twindow) (v:vs) = loop (twindow ++ [v]) vs so the first few tails go fast, but later, we have to go through more layers to get at the head of the window to discard it ~> loop ((3:((4:[]) ++ [5])) ++ [6]) [7 .. end] ~> loop (3:(((4:[]) ++ [5]) ++ [6])) [7 .. end] -- finally! ~> loop ((((4:[]) ++ [5]) ++ [6]) ++ [7]) [8 .. end] -- bubble the 4 through four layers of parentheses: ~> loop(((4:([] ++ [5])) ++ [6]) ++ [7]) [8 .. end] ~> loop ((4:(([] ++ [5]) ++ [6])) ++ [7]) [8 .. end] ~> loop (4:((([] ++ [5]) ++ [6]) ++ [7])) [8 .. end] ~> loop (((([] ++ [5]) ++ [6]) ++ [7]) ++ [8]) [9 .. end] -- phew -- form now on, it's uniform, on each step we have to match an expression (((([] ++ [a]) ++ [b]) ++ [c]) ++ [d]) against (_:rest) 1. check whether ((([] ++ [a]) ++ [b]) ++ [c]) is empty, for that, 2. check whether (([] ++ [a]) ++ [b]) is empty, for that, 3. check whether ([] ++ [a]) is empty, for that, 4. check whether [] is empty, it is, hence [] ++ [a] = [a], 5. check whether [a] is empty, it's not, it's (a:[]), hence 6. (...) ++ [b] = a:([] ++ [b]), so 2's not empty, and 7. (...) ++ [c] = a:(([] ++ [b]) ++ [c]), so 1's not empty and 8. (...) ++ [d] = a:((([] ++ [b]) ++ [c]) ++ [d]) 9. at last, a can be dropped and we get to loop (((([] ++ [b]) ++ [c]) ++ [d]) ++ [e]) remainingList Blech! Appending to the end of a list is bad if it leads to left-nested parentheses (it's okay if the parentheses are right-nested). So we might be tempted to keep the window reversed and cons each element to the front, dropping the last. No good, removing an element from the end is O(length window) too. One possibility to fix it is to use a 'list-like' type with O(1) appending at the end and dropping from the front. Data.Sequence is such a type, import qualified Data.Sequence as Seq import Data.Foldable (toList) import Data.Sequence (ViewL(..), (|>)) n_lastn' :: Int -> [a] -> [a] n_lastn' k _ | k <= 0 = [] n_lastn' k xs = case splitAt k xs of (ys,[]) -> ys (ys,zs) -> go (Seq.fromList ys) zs where go acc [] = toList acc go acc (v:vs) = case Seq.viewl acc of _ :< keep -> go (keep |> v) vs _ -> error "teh impossible jus hapnd" fixes space and time behaviour. But the constant factors for Sequence are larger than those for lists, so we can beat it with lists: n_lastn :: Int -> [a] -> [a] n_lastn k _ | k <= 0 = [] n_lastn k xs = case splitAt k xs of (ys,[]) -> ys (ys,zs) -> go k (reverse ys) zs where m = k-1 go _ acc [] = reverse $ take k acc go 0 acc (v:vs) = case splitAt m acc of (keep,release) -> release `seq` go k (v:keep) vs go h acc (v:vs) = go (h-1) (v:acc) vs Every k steps, we perform the O(k) operation of removing the last (k+1) elements from a (2k)-element list, making the removal from the end an amortized O(1) operation. You can trade some space for speed and clip the window in larger intervals, say every (3*k) or every (10*k) steps.

I think this is O(n) time, O(1) space (!).
lastk :: Int -> [a] -> [a]
lastk k xs = last $ zipWith const (properTails xs) (drop k xs)
where properTails = tail . tails
Luke
On Sat, Sep 18, 2010 at 1:51 PM, Daniel Fischer
On Saturday 18 September 2010 19:44:38, Jake McArthur wrote:
On 09/18/2010 02:51 AM, Christopher Tauss wrote:
I am trying to write a function that takes a list and returns the last n elements.
This may just be for the sake of learning, in which case this is fine, but usually, needing to do this would be a sign that you are using lists improperly (since this is a O(n) time operation).
By which he meant O(length list), not the number of elements you're asking for.
Let's call the function n_lastn and, given a list [1,2,3,4,5], I would like n_lastn 3 = [3,4,5]
n_lastn n = reverse . take n . reverse
Which is the most elegant definition, but it's an O(length list) space operation (as are all others proposed so far). That will be a problem for long lists (consider n_lastn 10 [1 .. 10^8]). You can implement it as an O(n) [the number of elements you want] *space* operation, provided that the list is generated lazily and not referred to by anything else, but the code is decidedly less nice:
The first idea would be to keep a window of n elements and move it to the end of the list:
n_lastn n xs = case splitAt n xs of (ys,[]) -> ys -- the list contains at most n elements, yay (ys,zs) -> loop ys zs where loop window [] = window loop window (v:vs) = loop (tail window ++ [v]) vs
The space behaviour is now fine (if compiled with optimisations), but unfortunately, the time complexity has become O(n*length list) because the (++)-calls are left-nested:
Suppose n = 4,
loop (1:2:3:4:[]) [5 .. end] ~> loop ((2:3:4:[]) ++ [5]) [6 .. end] ~> loop (2:((3:4:[]) ++ [5])) [6 .. end] ~> loop (((3:4:[]) ++ [5]) ++ [6]) [7 .. end]
The strictness analyser has been smart enough to transform the call to tail into a strict pattern match on window, as if we'd written loop (_:twindow) (v:vs) = loop (twindow ++ [v]) vs so the first few tails go fast, but later, we have to go through more layers to get at the head of the window to discard it
~> loop ((3:((4:[]) ++ [5])) ++ [6]) [7 .. end] ~> loop (3:(((4:[]) ++ [5]) ++ [6])) [7 .. end] -- finally! ~> loop ((((4:[]) ++ [5]) ++ [6]) ++ [7]) [8 .. end] -- bubble the 4 through four layers of parentheses: ~> loop(((4:([] ++ [5])) ++ [6]) ++ [7]) [8 .. end] ~> loop ((4:(([] ++ [5]) ++ [6])) ++ [7]) [8 .. end] ~> loop (4:((([] ++ [5]) ++ [6]) ++ [7])) [8 .. end] ~> loop (((([] ++ [5]) ++ [6]) ++ [7]) ++ [8]) [9 .. end] -- phew -- form now on, it's uniform, on each step we have to match an expression
(((([] ++ [a]) ++ [b]) ++ [c]) ++ [d])
against (_:rest) 1. check whether ((([] ++ [a]) ++ [b]) ++ [c]) is empty, for that, 2. check whether (([] ++ [a]) ++ [b]) is empty, for that, 3. check whether ([] ++ [a]) is empty, for that, 4. check whether [] is empty, it is, hence [] ++ [a] = [a], 5. check whether [a] is empty, it's not, it's (a:[]), hence 6. (...) ++ [b] = a:([] ++ [b]), so 2's not empty, and 7. (...) ++ [c] = a:(([] ++ [b]) ++ [c]), so 1's not empty and 8. (...) ++ [d] = a:((([] ++ [b]) ++ [c]) ++ [d]) 9. at last, a can be dropped and we get to loop (((([] ++ [b]) ++ [c]) ++ [d]) ++ [e]) remainingList
Blech!
Appending to the end of a list is bad if it leads to left-nested parentheses (it's okay if the parentheses are right-nested). So we might be tempted to keep the window reversed and cons each element to the front, dropping the last. No good, removing an element from the end is O(length window) too.
One possibility to fix it is to use a 'list-like' type with O(1) appending at the end and dropping from the front. Data.Sequence is such a type,
import qualified Data.Sequence as Seq import Data.Foldable (toList) import Data.Sequence (ViewL(..), (|>))
n_lastn' :: Int -> [a] -> [a] n_lastn' k _ | k <= 0 = [] n_lastn' k xs = case splitAt k xs of (ys,[]) -> ys (ys,zs) -> go (Seq.fromList ys) zs where go acc [] = toList acc go acc (v:vs) = case Seq.viewl acc of _ :< keep -> go (keep |> v) vs _ -> error "teh impossible jus hapnd"
fixes space and time behaviour. But the constant factors for Sequence are larger than those for lists, so we can beat it with lists:
n_lastn :: Int -> [a] -> [a] n_lastn k _ | k <= 0 = [] n_lastn k xs = case splitAt k xs of (ys,[]) -> ys (ys,zs) -> go k (reverse ys) zs where m = k-1 go _ acc [] = reverse $ take k acc go 0 acc (v:vs) = case splitAt m acc of (keep,release) -> release `seq` go k (v:keep) vs go h acc (v:vs) = go (h-1) (v:acc) vs
Every k steps, we perform the O(k) operation of removing the last (k+1) elements from a (2k)-element list, making the removal from the end an amortized O(1) operation. You can trade some space for speed and clip the window in larger intervals, say every (3*k) or every (10*k) steps. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Saturday 18 September 2010 22:42:57, Luke Palmer wrote:
I think this is O(n) time, O(1) space (!).
lastk :: Int -> [a] -> [a] lastk k xs = last $ zipWith const (properTails xs) (drop k xs) where properTails = tail . tails
Luke
No, it's O(k) too. You zip [[x_n, x_{n+1}, ... ], ... ] with [x_{n+k}, ... ], so all of [x_n, ..., x_{n+k}] stays in memory. It's *very* nice though, and scales better than my stuff (but my stuff is faster for small k [< 1000, here, YMMV]).

I like this one! Here's a variant using fold: lastk :: Int -> [a] -> [a] lastk k xs = foldl' (const.tail) xs (drop k xs) or point free: lastk = ap (foldl' (const. tail)). drop Hallo Luke Palmer, je schreef op 18-09-10 22:42:
I think this is O(n) time, O(1) space (!).
lastk :: Int -> [a] -> [a] lastk k xs = last $ zipWith const (properTails xs) (drop k xs) where properTails = tail . tails
-- Met vriendelijke groet, =@@i

Luke Palmer schrieb:
I think this is O(n) time, O(1) space (!).
lastk :: Int -> [a] -> [a] lastk k xs = last $ zipWith const (properTails xs) (drop k xs) where properTails = tail . tails
If (drop k xs) is empty, this yields an error when calling 'last'. This might be a bug or a feature.

2010/9/18 Daniel Fischer
n_lastn n = reverse . take n . reverse
Which is the most elegant definition, but it's an O(length list) space operation (as are all others proposed so far). T
No!. You forget laziness!. it is 0(n) with n= the parameter passed to n_lastn. It is not O(length list). the reversed and de-reversed elements are just the ones being taken , not the whole list. (please kill me if I´m wrong. I don´t want to live in a world where beauty is inneficient) ;)

Hi Alberto, On 20.09.2010, at 10:53, Alberto G. Corona wrote:
2010/9/18 Daniel Fischer
n_lastn n = reverse . take n . reverse
Which is the most elegant definition, but it's an O(length list) space operation (as are all others proposed so far). T
No!. You forget laziness!. it is 0(n) with n= the parameter passed to n_lastn.
It is not O(length list).
the reversed and de-reversed elements are just the ones being taken , not the whole list.
(please kill me if I´m wrong. I don´t want to live in a world where beauty is inneficient)
I am afraid you are argumentation is wrong. Let's see:
f :: [a] -> a f = head . reverse
This is a function running in O(n) time, where n is the length of given list. That is, because f has to follow at least n pointers in order to reach the end of the parameter list. It might be much more expensive if the list has to be computed, because f got only a thunk to cumpute a list instead of a finished list. Lazyness helps helps to reduce work if your input list is lazily constructed and your function forces the returned element. Then you don't have to force all elements of the list, only the last one. Let's say l = [e_0, ..., e_n]. All the e_i are expensive calculations.
g :: [a] -> a g xs = x `seq` x where x = head (reverse xs)
In order to compute g l you only have to evaluate e_n, not all the other e_i. Hope this helps. Jean

On Sep 20, 2010, at 5:10 AM, Jean-Marie Gaillourdet wrote:
Hi Alberto,
On 20.09.2010, at 10:53, Alberto G. Corona wrote:
2010/9/18 Daniel Fischer
n_lastn n = reverse . take n . reverse
Which is the most elegant definition, but it's an O(length list) space operation (as are all others proposed so far). T
No!. You forget laziness!. it is 0(n) with n= the parameter passed to n_lastn.
It is not O(length list).
the reversed and de-reversed elements are just the ones being taken , not the whole list.
(please kill me if I´m wrong. I don´t want to live in a world where beauty is inneficient)
I am afraid you are argumentation is wrong.
Let's see:
f :: [a] -> a f = head . reverse
This is a function running in O(n) time, where n is the length of given list. That is, because f has to follow at least n pointers in order to reach the end of the parameter list. It might be much more expensive if the list has to be computed, because f got only a thunk to cumpute a list instead of a finished list.
I don't believe he was claiming O(n) time, only O(n) space, which I am inclined to believe. Your 'f' should also run in O(1) space. In general, there can be no function depending in any way on the location of the end of the list that isn't O(length list) time, because if nothing else the end of the list must be discovered, which requires that much time no matter what the algorithm.
Lazyness helps helps to reduce work if your input list is lazily constructed and your function forces the returned element. Then you don't have to force all elements of the list, only the last one. Let's say l = [e_0, ..., e_n]. All the e_i are expensive calculations.
g :: [a] -> a g xs = x `seq` x where x = head (reverse xs)
Can "x `seq` x" have any different strictness than just plain x? I may be wrong, but I don't think so. Essentially, it's saying that "when x is needed, evaluate x to WHNF and then return x". -- James

Hi James, On 20.09.2010, at 15:20, James Andrew Cook wrote:
Lazyness helps helps to reduce work if your input list is lazily constructed and your function forces the returned element. Then you don't have to force all elements of the list, only the last one. Let's say l = [e_0, ..., e_n]. All the e_i are expensive calculations.
g :: [a] -> a g xs = x `seq` x where x = head (reverse xs)
Can "x `seq` x" have any different strictness than just plain x? I may be wrong, but I don't think so. Essentially, it's saying that "when x is needed, evaluate x to WHNF and then return x".
Yes, I think you are right. I was trying to force evaluation of the returned element. Something like that:
{-# LANGUAGE BangPatterns #-}
g :: [a] -> a g xs = x where !x = head (reverse xs)
-- Jean

On Monday 20 September 2010 15:20:53, James Andrew Cook wrote:
On Sep 20, 2010, at 5:10 AM, Jean-Marie Gaillourdet wrote:
Hi Alberto,
On 20.09.2010, at 10:53, Alberto G. Corona wrote:
2010/9/18 Daniel Fischer
n_lastn n = reverse . take n . reverse
Which is the most elegant definition, but it's an O(length list) space operation (as are all others proposed so far). T
No!. You forget laziness!. it is 0(n) with n= the parameter passed to n_lastn.
It is not O(length list).
the reversed and de-reversed elements are just the ones being taken , not the whole list.
(please kill me if I´m wrong. I don´t want to live in a world where beauty is inneficient)
I am afraid you are argumentation is wrong.
Let's see:
f :: [a] -> a f = head . reverse
This is a function running in O(n) time, where n is the length of given list. That is, because f has to follow at least n pointers in order to reach the end of the parameter list. It might be much more expensive if the list has to be computed, because f got only a thunk to cumpute a list instead of a finished list.
I don't believe he was claiming O(n) time, only O(n) space,
Right.
which I am inclined to believe. Your 'f' should also run in O(1) space.
Alas, no. At least with GHC (and I don't see how it could be otherwise), reverse is always an O(length xs) space operation. reverse :: [a] -> [a] #ifdef USE_REPORT_PRELUDE reverse = foldl (flip (:)) [] #else reverse l = rev l [] where rev [] a = a rev (x:xs) a = rev xs (x:a) #endif Both, the report-reverse and the other version, build the reversed list as an accumulation parameter of a tail-recursive function. The entire reversed list is returned in one piece once the end is reached. The only way to make functions using reverse run in less than O(length xs) space is, as far as I know, using rewrite rules (e.g. head . reverse = last).
In general, there can be no function depending in any way on the location of the end of the list that isn't O(length list) time, because if nothing else the end of the list must be discovered, which requires that much time no matter what the algorithm.
Lazyness helps helps to reduce work if your input list is lazily constructed and your function forces the returned element. Then you don't have to force all elements of the list, only the last one. Let's say l = [e_0, ..., e_n]. All the e_i are expensive calculations.
g :: [a] -> a g xs = x `seq` x where x = head (reverse xs)
Can "x `seq` x" have any different strictness than just plain x?
No, "x `seq` x" is exactly equivalent to x.
I may be wrong, but I don't think so. Essentially, it's saying that "when x is needed, evaluate x to WHNF and then return x".
Exactly. In "x `seq` y", the seq forces evaluation of x to WHNF precisely if/when y has to be evaluated to WHNF.
-- James

Have we put off the ultra-newbie by derailing his simple question into a
discussion on subtle issues he shouldn't care about this early on?
On Mon, Sep 20, 2010 at 3:49 PM, Daniel Fischer
On Monday 20 September 2010 15:20:53, James Andrew Cook wrote:
On Sep 20, 2010, at 5:10 AM, Jean-Marie Gaillourdet wrote:
Hi Alberto,
On 20.09.2010, at 10:53, Alberto G. Corona wrote:
2010/9/18 Daniel Fischer
n_lastn n = reverse . take n . reverse
Which is the most elegant definition, but it's an O(length list) space operation (as are all others proposed so far). T
No!. You forget laziness!. it is 0(n) with n= the parameter passed to n_lastn.
It is not O(length list).
the reversed and de-reversed elements are just the ones being taken , not the whole list.
(please kill me if I´m wrong. I don´t want to live in a world where beauty is inneficient)
I am afraid you are argumentation is wrong.
Let's see:
f :: [a] -> a f = head . reverse
This is a function running in O(n) time, where n is the length of given list. That is, because f has to follow at least n pointers in order to reach the end of the parameter list. It might be much more expensive if the list has to be computed, because f got only a thunk to cumpute a list instead of a finished list.
I don't believe he was claiming O(n) time, only O(n) space,
Right.
which I am inclined to believe. Your 'f' should also run in O(1) space.
Alas, no. At least with GHC (and I don't see how it could be otherwise), reverse is always an O(length xs) space operation.
reverse :: [a] -> [a] #ifdef USE_REPORT_PRELUDE reverse = foldl (flip (:)) [] #else reverse l = rev l [] where rev [] a = a rev (x:xs) a = rev xs (x:a) #endif
Both, the report-reverse and the other version, build the reversed list as an accumulation parameter of a tail-recursive function. The entire reversed list is returned in one piece once the end is reached.
The only way to make functions using reverse run in less than O(length xs) space is, as far as I know, using rewrite rules (e.g. head . reverse = last).
In general, there can be no function depending in any way on the location of the end of the list that isn't O(length list) time, because if nothing else the end of the list must be discovered, which requires that much time no matter what the algorithm.
Lazyness helps helps to reduce work if your input list is lazily constructed and your function forces the returned element. Then you don't have to force all elements of the list, only the last one. Let's say l = [e_0, ..., e_n]. All the e_i are expensive calculations.
g :: [a] -> a g xs = x `seq` x where x = head (reverse xs)
Can "x `seq` x" have any different strictness than just plain x?
No, "x `seq` x" is exactly equivalent to x.
I may be wrong, but I don't think so. Essentially, it's saying that "when x is needed, evaluate x to WHNF and then return x".
Exactly. In "x `seq` y", the seq forces evaluation of x to WHNF precisely if/when y has to be evaluated to WHNF.
-- James
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sep 20, 2010, at 9:49 AM, Daniel Fischer wrote:
which I am inclined to believe. Your 'f' should also run in O(1) space.
Alas, no. At least with GHC (and I don't see how it could be otherwise), reverse is always an O(length xs) space operation.
reverse :: [a] -> [a] #ifdef USE_REPORT_PRELUDE reverse = foldl (flip (:)) [] #else reverse l = rev l [] where rev [] a = a rev (x:xs) a = rev xs (x:a) #endif
Good point, I guess I hadn't really thought that one through. It should have occurred to me that the garbage collector has no idea what 'head' does, and so at the time that the list is forced to WHNF for matching in 'head', everything that reverse _could_ return must be retained, which is the whole list. I think I had a poorly-formed notion that the GC should somehow know that only the (eventual) head of the list would ever be needed. On Sep 20, 2010, at 10:22 AM, Daniel Peebles wrote:
Have we put off the ultra-newbie by derailing his simple question into a discussion on subtle issues he shouldn't care about this early on?
Probably. It's both a joy and a curse having a community so enthusiastic about their language. It's a lot like when people talk perl and everything somehow turns into code golf or just plain obfuscation contests ;) -- James

On Sat, 2010-09-18 at 03:51 -0400, Christopher Tauss wrote:
Hello Haskell Community -
I am a professional programmer with 11 years experience, yet I just do not seem to be able to get the hang of even simple things in Haskell. I am trying to write a function that takes a list and returns the last n elements.
There may be a function which I can just call that does that, but I am trying to roll my own just to understand the concept.
Let's call the function n_lastn and, given a list [1,2,3,4,5], I would like n_lastn 3 = [3,4,5]
Seems like it would be something like:
n_lastn:: [a]->Int->[a] n_lastn 1 (xs) = last(xs) n_lastn n (x:xs) = ????
The issue is I do not see how you can store the last elements of the list.
Thanks in advance.
ctauss
I'll add my $0.03 - unless you are doing it to learn about lists rethink your approach. Taking k elements from end of n-element list will be O(n) operation. For example with appropriate structures (like finger trees) it would look like O(k) operation. Regards

Translation: Look at Data.Sequence sometime. On 9/18/10 11:15 AM, Maciej Piechotka wrote:
On Sat, 2010-09-18 at 03:51 -0400, Christopher Tauss wrote:
Hello Haskell Community -
I am a professional programmer with 11 years experience, yet I just do not seem to be able to get the hang of even simple things in Haskell. I am trying to write a function that takes a list and returns the last n elements.
There may be a function which I can just call that does that, but I am trying to roll my own just to understand the concept.
Let's call the function n_lastn and, given a list [1,2,3,4,5], I would like n_lastn 3 = [3,4,5]
Seems like it would be something like:
n_lastn:: [a]->Int->[a] n_lastn 1 (xs) = last(xs) n_lastn n (x:xs) = ????
The issue is I do not see how you can store the last elements of the list.
Thanks in advance.
ctauss I'll add my $0.03 - unless you are doing it to learn about lists rethink your approach. Taking k elements from end of n-element list will be O(n) operation.
For example with appropriate structures (like finger trees) it would look like O(k) operation.
Regards
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Translation: Look at Data.Sequence sometime. On 9/18/10 11:15 AM, Maciej Piechotka wrote:
On Sat, 2010-09-18 at 03:51 -0400, Christopher Tauss wrote:
Hello Haskell Community -
I am a professional programmer with 11 years experience, yet I just do not seem to be able to get the hang of even simple things in Haskell. I am trying to write a function that takes a list and returns the last n elements.
There may be a function which I can just call that does that, but I am trying to roll my own just to understand the concept.
Let's call the function n_lastn and, given a list [1,2,3,4,5], I would like n_lastn 3 = [3,4,5]
Seems like it would be something like:
n_lastn:: [a]->Int->[a] n_lastn 1 (xs) = last(xs) n_lastn n (x:xs) = ????
The issue is I do not see how you can store the last elements of the list.
Thanks in advance.
ctauss I'll add my $0.03 - unless you are doing it to learn about lists rethink your approach. Taking k elements from end of n-element list will be O(n) operation.
For example with appropriate structures (like finger trees) it would look like O(k) operation.
Regards
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sep 18, 2010, at 12:51 AM, Christopher Tauss wrote:
I am a professional programmer with 11 years experience, yet I just do not seem to be able to get the hang of even simple things in Haskell. I am trying to write a function that takes a list and returns the last n elements.
Note that keeping just the suffix is the same as dropping the prefix. Consider your data: A finite list. The length of the suffix to keep. An algebraic relationship between lengths of lists, suffixes, and their prefixes: length(prefix) + length(suffix) = legnth(list) Putting all of this together: n_tail n list = drop (prefix_length) list where prefix_length = length list - n You may be interested in how drop is carrying around some state: drop n xs | n <= 0 = xs drop _ [] = [] drop n (_:xs) = drop (n-1) xs

Christopher Tauss schrieb:
I am a professional programmer with 11 years experience, yet I just do not seem to be able to get the hang of even simple things in Haskell. I am trying to write a function that takes a list and returns the last n elements.
Looking through the glasses of lazy evaluation, I would use my utility-ht:Data.List.Match module and write lastn n xs = ListMatch.drop (drop n xs) xs (ListMatch.drop ls xs) drops as many elements from xs as are in ls in the most lazy way.

On Sep 18, 2010, at 7:51 PM, Christopher Tauss wrote:
Hello Haskell Community -
I am a professional programmer with 11 years experience, yet I just do not seem to be able to get the hang of even simple things in Haskell. I am trying to write a function that takes a list and returns the last n elements.
There may be a function which I can just call that does that, but I am trying to roll my own just to understand the concept.
Let's call the function n_lastn and, given a list [1,2,3,4,5], I would like n_lastn 3 = [3,4,5]
Seems like it would be something like:
n_lastn:: [a]->Int->[a] n_lastn 1 (xs) = last(xs) n_lastn n (x:xs) = ????
The issue is I do not see how you can store the last elements of the list.
Part of the reason why you may be having trouble is that you are thinking about things like "how you can store the last elements of the list". I'm having trouble imagining what that might mean. Let's look at this in completely abstract terms. A list is a sequence. A (finite) sequence has a length, and there is a length function to find it. We can split a sequence into pieces, and there are take and drop functions to do it. We have these building blocks: length :: [t] -> Int --length of sequence take :: Int -> [t] -> [t] --first n elements drop :: Int -> [t] -> [t] --all BUT the first n elements The only one of these that gives us a suffix of a list is 'drop'. So we are going to need n_lastn :: Int -> [t] -> [t] n_lastn count list = drop ???? list What is the first argument of drop going to be? drop wants the number to DISCARD. You have the number to KEEP. The number to discard + the number to keep is the total length. So you will discard (length list - count) elements. And here we go with a complete answer: n_lastn count list = drop (length list - count) list This is a mathematical definition about (finite) sequences. We could write it and reason about it even if there had never been any such thing as a computer. It doesn't actually matter in the least HOW a list is stored; this definition will be RIGHT. Whether it is *efficient* does depend on how a list is stored. There are questions like - how often does the sequence have to be traversed (with lists, determining the length involves walking along the whole list until the end is found, although it does not involve looking at the elements) - how much copying is done (with arrays, you'd have to make a new array of count elements and copy the last count elements of list to it, with lists you don't have to copy anything) I can make this point another way. n_lastn is a bad name, because really, it's just the same as `take` except working from the other end. So we can define reverse_take n = reverse . take n . reverse reverse_drop n = reverse . drop n . reverse "the last n items of a sequence are the first n items of its reversal, reversed" "all but the last n items of a sequence are all but the first n items of its reversal, reversed" and your n_lastn is just reverse_take. This definition does three list traversals and two copies. There's a trick I found very useful in Prolog, and that is to exploit the homomorphism between lists and natural numbers, where a list can be used to represent its own length. Let's take `take` and `drop`. take (n+1) (x:xs) = x : take n xs take _ _ = [] drop (n+1) (_:xs) = drop n xs drop _ xs = xs Instead of passing a natural number as first argument, we'll pass a list, and the analogue of (n+1) is then (_:k). list_take, list_drop :: [any] -> [t] -> [t] list_take (_:k) (x:xs) = x : list_take k xs list_take _ _ = [] list_drop (_:k) (_:xs) = list_drop k xs list_drop _ xs = xs (drop count list) is a list, whose length is the number of elements we want to discard from the beginning of list. So we can define reverse_take count list = list_drop (drop count list) list and this does O(length list) work; ONE list traversal and NO copies. reverse_drop count list = list_take (drop count list) list This code was tested thus: *Main> [reverse_take n "abcd" | n <- [0..4]] ["","d","cd","bcd","abcd"] *Main> [reverse_drop n "abcd" | n <- [0..4]] ["abcd","abc","ab","a",""]

Thanks Richard and the others who responded to my query.
I truly appreciate you taking the time and effort to respond to me (and the
community) with your thoughts.
I had been reading about recursion, and was thinking only of that approach
to solve this.
My main reson for looking into Haskell is because I am intruiged that
Haskell does not allow side effects. I have literally seen code (not my
own, of course!) that is nothing but side effects, and over time such code
becomes very expensive to maintain and extend. I wonder if functional
programming may be the paradigm of the future just because it is in the
longer run cost effective.
Anyway, thanks again, and Best Regards
Chris Tauss
On Mon, Sep 20, 2010 at 6:11 PM, Richard O'Keefe
On Sep 18, 2010, at 7:51 PM, Christopher Tauss wrote:
Hello Haskell Community -
I am a professional programmer with 11 years experience, yet I just do not seem to be able to get the hang of even simple things in Haskell. I am trying to write a function that takes a list and returns the last n elements.
There may be a function which I can just call that does that, but I am trying to roll my own just to understand the concept.
Let's call the function n_lastn and, given a list [1,2,3,4,5], I would like n_lastn 3 = [3,4,5]
Seems like it would be something like:
n_lastn:: [a]->Int->[a] n_lastn 1 (xs) = last(xs) n_lastn n (x:xs) = ????
The issue is I do not see how you can store the last elements of the list.
Part of the reason why you may be having trouble is that you are thinking about things like "how you can store the last elements of the list". I'm having trouble imagining what that might mean.
Let's look at this in completely abstract terms. A list is a sequence. A (finite) sequence has a length, and there is a length function to find it. We can split a sequence into pieces, and there are take and drop functions to do it. We have these building blocks:
length :: [t] -> Int --length of sequence take :: Int -> [t] -> [t] --first n elements drop :: Int -> [t] -> [t] --all BUT the first n elements
The only one of these that gives us a suffix of a list is 'drop'. So we are going to need
n_lastn :: Int -> [t] -> [t] n_lastn count list = drop ???? list
What is the first argument of drop going to be? drop wants the number to DISCARD. You have the number to KEEP. The number to discard + the number to keep is the total length. So you will discard (length list - count) elements. And here we go with a complete answer:
n_lastn count list = drop (length list - count) list
This is a mathematical definition about (finite) sequences. We could write it and reason about it even if there had never been any such thing as a computer. It doesn't actually matter in the least HOW a list is stored; this definition will be RIGHT.
Whether it is *efficient* does depend on how a list is stored. There are questions like - how often does the sequence have to be traversed (with lists, determining the length involves walking along the whole list until the end is found, although it does not involve looking at the elements) - how much copying is done (with arrays, you'd have to make a new array of count elements and copy the last count elements of list to it, with lists you don't have to copy anything)
I can make this point another way. n_lastn is a bad name, because really, it's just the same as `take` except working from the other end. So we can define
reverse_take n = reverse . take n . reverse reverse_drop n = reverse . drop n . reverse
"the last n items of a sequence are the first n items of its reversal, reversed" "all but the last n items of a sequence are all but the first n items of its reversal, reversed"
and your n_lastn is just reverse_take. This definition does three list traversals and two copies.
There's a trick I found very useful in Prolog, and that is to exploit the homomorphism between lists and natural numbers, where a list can be used to represent its own length.
Let's take `take` and `drop`.
take (n+1) (x:xs) = x : take n xs take _ _ = []
drop (n+1) (_:xs) = drop n xs drop _ xs = xs
Instead of passing a natural number as first argument, we'll pass a list, and the analogue of (n+1) is then (_:k).
list_take, list_drop :: [any] -> [t] -> [t]
list_take (_:k) (x:xs) = x : list_take k xs list_take _ _ = []
list_drop (_:k) (_:xs) = list_drop k xs list_drop _ xs = xs
(drop count list) is a list, whose length is the number of elements we want to discard from the beginning of list. So we can define
reverse_take count list = list_drop (drop count list) list
and this does O(length list) work; ONE list traversal and NO copies.
reverse_drop count list = list_take (drop count list) list
This code was tested thus: *Main> [reverse_take n "abcd" | n <- [0..4]] ["","d","cd","bcd","abcd"] *Main> [reverse_drop n "abcd" | n <- [0..4]] ["abcd","abc","ab","a",""]
participants (17)
-
Aai
-
Alberto G. Corona
-
Alexander Solla
-
Christopher Tauss
-
Daniel Fischer
-
Daniel Peebles
-
David Terei
-
Gregory Crosswhite
-
Henning Thielemann
-
Ivan Lazar Miljenovic
-
Jake McArthur
-
James Andrew Cook
-
Jean-Marie Gaillourdet
-
Luke Palmer
-
Maciej Piechotka
-
Nils Schweinsberg
-
Richard O'Keefe