[Haskell-cafe] Performance of delete-and-return-last-element

Harald Bögeholz bo at ct.de
Sun Sep 1 21:13:50 CEST 2013


Am 31.08.13 14:35, schrieb Petr Pudlák:
> 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..]|.

I am wondering why you put the Semigroup instance there and what the
other imports are for. Doesn't this work just as well?

data  Darle  a = Darle  {getInit  :: [a], getLast  :: a}
  deriving  Show

~(Darle  xs1 l1) <> ~(Darle  xs2 l2) = Darle  (xs1 ++ [l1] ++ xs2) l2

darle  :: [a] ->Darle  a
darle  = foldr1 (<>) . map (Darle  [])

Seems to work here. I am still puzzled, though, if this is really a good
idea performance-wise. I am afraid I don't understand it well enough.


Harald

-- 
Harald Bögeholz    <bo at ct.de> (PGP key available from servers)
Redaktion c't      Tel.: +49 511 5352-300  Fax: +49 511 5352-417
                   http://www.ct.de/

                   int f[9814],b,c=9814,g,i;long a=1e4,d,e,h;
                   main(){for(;b=c,c-=14;i=printf("%04d",e+d/a),e=d%a)
                   while(g=--b*2)d=h*b+a*(i?f[b]:a/5),h=d/--g,f[b]=d%g;}
                                                          (Arndt/Haenel)

                   Affe Apfel Vergaser

/* Heise Zeitschriften Verlag GmbH & Co. KG * Karl-Wiechert-Allee 10 *
   30625 Hannover * Registergericht: Amtsgericht Hannover HRA 26709 *
   Persönlich haftende Gesellschafterin: Heise Zeitschriften Verlag *
   Geschäftsführung GmbH * Registergericht: Amtsgericht Hannover, HRB
   60405 * Geschäftsführer: Ansgar Heise, Dr. Alfons Schräder */




More information about the Haskell-Cafe mailing list