[Haskell-cafe] Short Cut / Rewrite Rules Problem in GHC
Chris
savcak at comcast.net
Mon Oct 3 22:15:33 EDT 2005
Hi All. I am a student and a noob to Haskell. I am having some
trouble with an example from the paper "Playing by the rules:
Rewriting as a practical optimisation technique in GHC" by Simon
Peyton Jones, Andrew Tolmach and Tony Hoare, specifically, the Short-
cut Deforestation example in section 3.1. I was trying to compile the
following using GHC version 6.4 on Mac OS X 10.4. The definition for
build and the rule are from the paper (the rule also appears in the
GHC online doc in section 7.10.1).
-----------------------------------------------------
-- BOF
-- File: Main.hs
module Main where
build :: (forall b. (a->b->b) -> b -> b) -> [a]
build' g = g (:) []
{-# RULES
"foldr/build"
forall k z (g::forall b. (a->b->b) -> b -> b) .
foldr k z (build g) = g k z
#-}
main :: IO ()
main = do putStr ""
-- EOF
-----------------------------------------------------
When I enable the extensions for GHC I get the following error:
chris$ ghc -fglasgow-exts --make Main.hs
Chasing modules from: Main.hs
Compiling Main ( Main.hs, Main.o )
Main.hs:15:1: lexical error
When I don't have them enabled it gives this error:
chris$ ghc --make Main.hs
Chasing modules from: Main.hs
Compiling Main ( Main.hs, Main.o )
Main.hs:8:18: parse error on input `.'
I have also tried moving the RULES option to the top of of the file
above "module Main", but I still get the same errors.
Also, should the definition of build be:
build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
build g = g (:) []
If I try to load the Main.hs file in HUGS with the -98 option and the
above version of build (with the forall a.), it works without a
problem. However, it still gives the same errors in GHC.
Additionally, I tried this on a different version of GHC, 6.2.2 on a
x86 box running Gentoo Linux, and it yielded the same results. I am
completely lost and would greatly appreciate any help. Thanks so much.
- Chris.
More information about the Haskell-Cafe
mailing list