[Haskell-cafe] Optimization demonstration

Brandon Allbery allbery.b at gmail.com
Wed Feb 28 04:55:11 UTC 2018


-fext-core wasn't about exporting it, but about accepting core as *source*
("external core"). Which was always tricky and was broken for years before
the option was removed.

On Tue, Feb 27, 2018 at 1:51 PM, Neil Mayhew <
neil_mayhew at users.sourceforge.net> wrote:

> On 2018-02-27 08:19 AM, Shao Cheng wrote:
>
> Coming back to your use case, you may try avoid using raw lists and switch
> to unboxed vectors, turn on -O2 and rely on stream fusion of the vector
> package. That will result in a considerable speedup.
>
> I looked at the core that’s generated, and there’s no need for vectors.
> Fusion happens, there’s no use of lists at all and unboxed types are used.
> The code boils down to a single recursive function:
>
> let go i sum = case i of
>         100000000 -> sum + 200000000
>         _ -> go (i + 1) (sum + i * 2)in go 1 0
>
> except that the types are unboxed. The following complete program compiles
> down to almost identical core when compiled without optimization:
>
> {-# LANGUAGE MagicHash #-}
> import GHC.Exts
> main = print $ I# value
>   where
>     value =
>         let go :: Int# -> Int# -> Int#
>             go i sum = case i of
>                 100000000# -> sum +# 200000000#
>                 _ -> go (i +# 1#) (sum +# i *# 2#)
>         in go 1# 0#
>
> I think that’s impressive even if it’s not a single number. Execution time
> on my lowly i5 is only 50ms.
>
> BTW, GHC 8 seems to have removed the option for exporting core (-fext-core)
> but there’s a wonderful plugin package called dump-core
> <https://github.com/yav/dump-core> that produces HTML output with
> colouring and interactivity. You just install it from Hackage and use the
> extra options it provides.
>
> It seems to me that gcc’s compile-time evaluation of this loop is a
> special-case that matches the kind of thing that often crops up in C. I
> assume it’s not capable of doing that for every expression that could be
> evaluated at compile time, so a more complicated and realistic example
> would probably defeat it. After all, ghc could in theory evaluate any pure
> value (CAF) at compile time if it chose to, but that’s usually not what you
> want.
>
> Also, it’s worth noting that due to Haskell’s lazy evaluation, a pure
> value (CAF) will never be evaluated more than once at runtime, which isn’t
> something you get with C.
>>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
>



-- 
brandon s allbery kf8nh                               sine nomine associates
allbery.b at gmail.com                                  ballbery at sinenomine.net
unix, openafs, kerberos, infrastructure, xmonad        http://sinenomine.net
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20180227/78dbedb4/attachment.html>


More information about the Haskell-Cafe mailing list