RULES pragmas
Simon Peyton-Jones
simonpj at microsoft.com
Fri Jul 14 07:51:56 EDT 2006
I've started a Wiki page, attached to GHC's collaborative documentation,
as a place to collect advice about RULES.
http://haskell.org/haskellwiki/GHC/Using_Rules
Please feel free to elaborate it.
Simon
| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org
[mailto:glasgow-haskell-users-bounces at haskell.org]
| On Behalf Of Donald Bruce Stewart
| Sent: 12 July 2006 01:41
| To: Malcolm Wallace
| Cc: glasgow-haskell-users at haskell.org
| Subject: Re: RULES pragmas
|
| Malcolm.Wallace:
| > I have a question about {-# RULES #-} pragmas. Here is a very
simple
| > attempt to use them:
| >
| > module Simplest where
| > {-# RULES
| > "simplestRule" forall x. id (id x) = x
| > #-}
| > myDefn = id (id 42)
| >
| > I want to verify whether ghc-6.4.1 does actually fire this rule, but
| > have so far been unable to do so. According to the manual (section
| > 7.10.5), the flag -ddump-rules should list "simplestRule" if it has
been
| > parsed correctly, and -ddump-simpl-stats should list the number of
times
| > it has fired. But it does not appear in either listing.
| >
| > Reasoning that I have the syntax wrong, I have tried numerous
variations
| > on the indentation, added type signatures, etc., all to no avail.
| >
| > So what am I doing wrong? And is there any way to ask the compiler
to
| > give a warning if the RULES pragma contains errors?
|
| In this case, it's because it's missing -fglasgow-exts, I think.
| The following works for me with both 6.4 and 6.5 compilers:
|
| module Simplest where
|
| {-# RULES
| "simplestRule" forall x. id (id x) = x
| #-}
|
| myDefn = id (id 42)
|
| when compiled with:
| $ ghc-6.4.2 -fglasgow-exts -c -ddump-simpl-stats A.hs
|
| ==================== Grand total simplifier statistics
| Total ticks: 11
|
| 2 PreInlineUnconditionally
| 3 PostInlineUnconditionally
| 1 UnfoldingDone
| 1 RuleFired
| 1 simplestRule
| 4 BetaReduction
| 2 SimplifierDone
|
| However, in general, you need to be careful that your identifiers
| weren't inlined in the first phase. To control this we add an INLINE
[1]
| pragma to identifiers we want to match in rules, to ensure they
haven't
| disappeared by the time the rule matching comes around.
|
| Also, you need -O to have rules kick in locally.
|
| So,
| module Simplest where
|
| {-# RULES
| "simplestRule" forall x. myid (myid x) = x
| #-}
|
| myDefn = myid (myid 42)
|
| myid x = x
| {-# INLINE [1] myid #-}
|
| And:
| $ ghc-6.4.2 -fglasgow-exts -O -c -ddump-simpl-stats A.hs
|
| ==================== Grand total simplifier statistics
====================
| Total ticks: 15
|
| 6 PreInlineUnconditionally
| 2 UnfoldingDone
| 1 RuleFired
| 1 simplestRule
| 5 BetaReduction
| 1 KnownBranch
| 8 SimplifierDone
|
| Cheers,
| 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