[Haskell-cafe] Performance of delete-and-return-last-element
Petr Pudlák
petr.mvd at gmail.com
Sat Aug 31 14:35:49 CEST 2013
One solution would be to fold over a specific semigroup instead of a
recursive function:
|import Data.Semigroup
import Data.Foldable(foldMap)
import Data.Maybe(maybeToList)
data Darle a =Darle {getInit :: [a],getLast ::a }
deriving Show
instance Semigroup (Darle a)where
~(Darle xs1 l1) <> ~(Darle xs2 l2) =Darle (xs1 ++ [l1] ++ xs2) l2
darle :: [a] ->Darle a
darle = foldr1 (<>) . map (Darle [])|
It's somewhat more verbose, but the core idea is clearly expressed in
the one line that defines |<>|, and IMHO it better shows /what/ are we
doing rather than /how/. It's sufficiently lazy so that you can do
something like |head . getInit $ darle [1..]|.
Best regards,
Petr
Dne 08/30/2013 08:18 PM, Lucas Paul napsal(a):
> Suppose I need to get an element from a data structure, and also
> modify the data structure. For example, I might need to get and delete
> the last element of a list:
>
> darle xs = ((last xs), (rmlast xs)) where
> rmlast [_] = []
> rmlast (y:ys) = y:(rmlast ys)
>
> There are probably other and better ways to write rmlast, but I want
> to focus on the fact that darle here, for lack of a better name off
> the top of my head, appears to traverse the list twice. Once to get
> the element, and once to remove it to produce a new list. This seems
> bad. Especially for large data structures, I don't want to be
> traversing twice to do what ought to be one operation. To fix it, I
> might be tempted to write something like:
>
> darle' [a] = (a, [])
> darle' (x:xs) = let (a, ys) = darle' xs in (a, (x:ys))
>
> But this version has lost its elegance. It was also kind of harder to
> come up with, and for more complex data structures (like the binary
> search tree) the simpler expression is really desirable. Can a really
> smart compiler transform/optimize the first definition into something
> that traverses the data structure only once? Can GHC?
>
> - Lucas
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130831/c098c03e/attachment.htm>
More information about the Haskell-Cafe
mailing list