GHC rewrite rules pragma
Simon Peyton-Jones
simonpj at microsoft.com
Fri May 30 10:44:20 EDT 2008
| 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.
I'll add a note in the user manual about this.
In general, GHC tries RULES before inlining. In this particular example that fails for a tiresome internal reason -- but in any case the solution Don mentions is noticeably more robust.
Simon
|
| 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