Hi,

I've been trying to get a certain type of programs compiled into efficient
code, but I haven't been able to find a good way to do it, so I'm asking
for help.

Specifically, it involves a library that defines a newtype whose
representation is a function. Attached Lib.hs is an example of such a
library. It defines a newtype (Builder), and functions (fromInt, mappend)
that deal with it.

In user code I want to write a (often-recursive) function that produces a
value of the newtype (the 'upto' function in arity.hs is an example). The
problem is that I know that the resulting value will be used only once, and
I'd like GHC to take advantage of it. In other words, I want the 'upto'
function to get compiled into something that takes 4 arguments (Int#, Int#,
Addr# and State#), rather than a binary function that returns a lambda.

I understand that GHC does not do this by default for a good reason. It
avoids potentially calling 'slightlyExpensive' more than once. However I
need some way to get the larger arity, because the performance difference
can be rather large (for example, this problem can add a lot of boxing to
an otherwise allocation-free loop).

One of my attempts was to have the library expose a function with which the
user can tell GHC that re-computation is okay. Lib.rebuild is such a
function, and the 'upto_rebuild' function demonstrates how to use it.
Unfortunately this approach only worked when the full-laziness optimization
was explicitly disabled.

This problem happened many times to me. In particular Reader and State
monads often triggered it.

I'm using GHC 7.6.3.

Any advice?

Thank you,
Takano Akio
module Lib where

import Control.Monad
import Data.Monoid
import Foreign.Ptr
import Foreign.Storable

newtype Builder = Builder (Ptr () -> IO (Ptr ()))

instance Monoid Builder where
  mempty = Builder return
  mappend (Builder x) (Builder y) = Builder $ x >=> y

fromInt :: Int -> Builder
fromInt n = Builder $ \p -> do
  poke (castPtr p) n
  return $! p `plusPtr` sizeOf n

rebuild :: (() -> Builder) -> Builder
rebuild f = Builder $ \ptr -> case f () of
  Builder f' -> f' ptr
{-# LANGUAGE BangPatterns #-}
module Foo (upto, upto_rebuild) where

import Data.Monoid
import qualified Lib

upto :: Int -> Int -> Lib.Builder
upto low high
  | low >= high = mempty
  | otherwise = Lib.fromInt (slightlyExpensive low) <> upto (low + 1) high

upto_rebuild :: Int -> Int -> Lib.Builder
upto_rebuild !low !high = Lib.rebuild $ \() ->
  if low >= high
    then mempty
    else Lib.fromInt (slightlyExpensive low) <> upto_rebuild (low + 1) high

slightlyExpensive :: Int -> Int
slightlyExpensive = gcd 120
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to