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

Juanma Barranquero jmbarranquero at laley.wke.es
Wed Oct 22 11:58:01 EDT 2003


An even simpler example, with just one module:

-------------------------------------------------------
  module Test where

  import Data.List (genericLength)

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

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

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

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

Surely that *must* be a bug, mustn't?



                                                                Juanma




More information about the Glasgow-haskell-users mailing list