simple rewrite rule example
Don Stewart
dons at galois.com
Tue Jun 22 02:38:43 EDT 2010
jac:
> Hi,
>
> I'd like to learn how to use ghc rewrite rules. I simply want to replace
> a function called f by a function called g. I do not unterstand why the
> rule f->g does not fire.
>
> Cheers, Jan
>
>
> module Main where
>
>
> {-# RULES
> "f->g" forall x. f x = g x
> #-}
>
>
> main :: IO ()
> main = print (f 1)
>
>
> {-# NOINLINE f #-}
> f :: a -> Bool
> f _ = False
>
>
> g :: a -> Bool
> g _ = True
>
>
Did you enable rewrite rules?
$ ghc -fenable-rewrite-rules A.hs --make
$ time ./A
True
./A 0.01s user 0.00s system 88% cpu 0.011 total
Using ghc-core:
1 RuleFired
1 f->g
-- Don
More information about the Glasgow-haskell-users
mailing list