Prabhakar Ragde wrote:
main n = print . sum . map read . take n . reverse . lines =<< getContents
Could someone describe succinctly how to compute the space complexity of
this program, if there are m lines of input and m >> n? Many thanks. --PR

Good point :)

Felipe Lessa wrote:

main n = print . sum . map read . head . dropWhile (not . null . drop
n) . tails . lines =<< getContents

where I changed (take n . reverse) to (head . dropWhile (not . null .
drop n) . tails). Yes, I cheated, I'm using Data.List =). With this
version you keep only n lines in memory at any moment, so it has space
complexity of O(n).

Yes, this has O(n) space complexity since dropWhile can discard the dropped elements. Unfortunately, we now have O(m*n) time complexity since drop n is executed for every list element.

Of course, the solution is to first drop n elements and then take tails instead of dropping n elements every time.

  map (drop n) . tails = tails . drop n

       O(m*n)                 O(m)

With this, we can write a function that returns the last n elements of a list in O(m) time and O(n) space as

  lasts :: Int -> [a] -> [a]
  lasts n xs = head $ [x | (x,[]) <- zip (tails xs) (tails $ drop n xs)]

and use it as a drop-in replacement

  main n = print . sum . map read . lasts n . lines =<< getContents

Regards,
apfelmus


PS: The implementation of  lasts n  in my original version would be

  lasts n = reverse . take n . reverse

But thanks to

  map f . reverse = reverse . map f
  sum . reverse   = sum

we can leave out one reverse.

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to