GHC rewrite rules pragma
Jan Jakubuv
jakubuv at gmail.com
Tue May 27 15:29:05 EDT 2008
Thanks lot, it works now. Now, I have just a simple question:
Is there any chance to make rewriting working in ghci ?
jan.
2008/5/27 Don Stewart <dons at galois.com>:
> jakubuv:
>> Hi,
>>
>> I'm trying to find out how the GHC rewrite rules pragma work, but I'm
>> not able to make it working. I have this simple example, where I would
>> like to specialize the function gen to spec on strings:
>>
>> {-# OPTIONS -O2 -fglasgow-exts #-}
>>
>> gen :: [a] -> a
>> gen = head
>>
>> {-# RULES "gen/Char" gen=spec #-}
>> spec :: [Char] -> Char
>> spec x = 'x'
>>
>> main :: IO ()
>> main = putStr (gen "aaa":"\n")
>>
>> -- EOF
>>
>> I compile it as:
>> ghc -O2 -fglasgow-exts spec.hs
>>
>> but as a result, is always prints 'a' while I expect 'x'. Is it right?
>> What is the problem here? I would be glad for any answer. I'm using
>> GHC 6.8.2.
>>
>> Sincerely,
>> Jan.
>
> This is the main wibble people forget when writing rules -- inlining.
> In your example, 'gen' is so cheap, it is immediately
> inlined, so it won't be available to match on in your rule.
>
> Anything you want to match should have its inlining delayed:
>
> {-# OPTIONS -O2 -fglasgow-exts #-}
>
> gen :: [a] -> a
> gen = head
> {-# INLINE [1] gen #-}
>
> {-# RULES
> "gen/Char" gen = spec
> #-}
>
> spec :: [Char] -> Char
> spec x = 'x'
>
> main :: IO ()
> main = putStr (gen "aaa":"\n")
>
> Running this in ghc-core, we see:
>
> RuleFired
> 1 gen/Char
>
> Good.
> And the program prints out:
>
> $ ./A
> x
>
> There was some discussion of adding a warning for any function
> used in the left hand side of a rewrite rule, that doesn't have
> precise inlining control added. That would have caught this.
>
> -- Don
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
More information about the Glasgow-haskell-users
mailing list