GHC is bad at CSE.  Of course, in general CSE might not be a good idea, but with strict computations it is.  So someone needs to add a CSE pass.

On Sat, Mar 29, 2008 at 2:23 AM, Don Stewart <dons@galois.com> wrote:
conal:
>    I'd like to know if it's possible to get GHC to perform some simple CSE
>    for function-level programming.  Here's a simple example:
>
>        liftA2 (*) sin sin :: Double -> Double
>
>    which inlines and simplifies to
>
>      \ t -> sin t * sin t
>
>    A more realistic, equivalent, example:
>
>        let b = sin <$> id in liftA2 (*) b b
>
>    Can GHC be nudged into computing 'sin t' once rather than twice?
>

So GHC does do some light CSE, but not in this case, as far as I could
see.

I had a go with a rewrite rule that I felt should have matched, but it
didn't seem to want to fire. Possibly the dictionaries were getting in
the way.


   import System.Environment
   import Prelude hiding (sin)
   import qualified Prelude

   sin :: Double -> Double
   sin x = Prelude.sin x
   {-# NOINLINE sin #-}

   times :: Double -> Double -> Double
   times x y = x * y
   {-# NOINLINE times #-}

   {-# RULES

   "sin/cse" forall x.
       times (sin x) (sin x) = case Prelude.sin x of y -> y * y

     #-}


   main = do
       [x] <- getArgs
       let n = read x
       print $ sin n `times` sin n


_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users