Posible bug while optimizing? (Was: RULES for SPECIALIZ(E)ations)

Juanma Barranquero jmbarranquero at laley.wke.es
Tue Oct 21 12:00:46 EDT 2003


On Mon, 20 Oct 2003 12:01:59 +0100
"Simon Peyton-Jones" <simonpj at microsoft.com> wrote:

> Maybe you want a rule
> 
> 	genericLength = length
> 
> which will replace a call to (genericLength at type Int) by a call to
> length?

That gave me the idea of making a module to contain general purpose
rules, so I did:

  -----------------------------------------------------------------
  module Local.Rules (genericLength) where

  import Data.List (genericLength)

  {-# RULES
  "generic/length" genericLength = length
   #-}
  -----------------------------------------------------------------

It works. (I was a bit puzzled to have to reexport genericLength, but on
insight I suppose it's logical.)

But I'm getting an error on recompilations that I don't understand. It
happens only with -O (or -On), AFAICS.

I have:

  -----------------------------------------------------------------
  module Local.Test where

  import Local.Rules
  -----------------------------------------------------------------

Then:

  D:\lib\Local> del *.hi *.o
  Deleting D:\lib\Haskell\Local\Rules.hi
  Deleting D:\lib\Haskell\Local\Test.hi
  Deleting D:\lib\Haskell\Local\Rules.o
  Deleting D:\lib\Haskell\Local\Test.o
       4 files deleted

  D:\lib\Local> ghc -fglasgow-exts --make -i.. Test.hs
  Chasing modules from: Test.hs
  Compiling Local.Rules      ( ../Local/Rules.hs, ../Local/Rules.o )
  Compiling Local.Test       ( Test.hs, ./Test.o )

  D:\lib\Local> ghc -fglasgow-exts --make -i.. Test.hs
  Chasing modules from: Test.hs
  Skipping  Local.Rules      ( ../Local/Rules.hs, ../Local/Rules.o )
  Skipping  Local.Test       ( Test.hs, ./Test.o )

but, with -O:

  D:\lib\Local> ghc -O -fglasgow-exts --make -i.. Test.hs
  Chasing modules from: Test.hs
  Compiling Local.Rules      ( ../Local/Rules.hs, ../Local/Rules.o )
  Compiling Local.Test       ( Test.hs, ./Test.o )

  D:\lib\Local> ghc -O -fglasgow-exts --make -i.. Test.hs
  Chasing modules from: Test.hs
  Skipping  Local.Rules      ( ../Local/Rules.hs, ../Local/Rules.o )

  tcLookupGlobal (id): `Data.List.genericLength' is not in scope
  When checking the transformation rule "generic/length"

Is that a bug?

                                                                Juanma




More information about the Glasgow-haskell-users mailing list