[Haskell-cafe] Rewrite rules

Ryan Ingram ryani.spam at gmail.com
Thu Oct 16 04:01:28 EDT 2008


Isn't this an unsound rewrite?

> cycle [(0 :: Integer)..] !! 100 => 100
> [(0 :: Integer) ..] !! (100 `mod` length [(0::Integer)..]) => _|_

Anyways, the reason for inlining not being done if an expression is
used more than once is that it duplicates work that you explicitly
specified should only be done once (by placing it in a let).  If you
want these declarations to get inlined so rules can fire, you should
be able to do something like this:

> let rlist = cycle list
>     {-# INLINE rlist #-}
> print ...

  -- ryan

2008/10/16 George Pollard <porges at porg.es>:
> Section 8.13.2 of the GHC manual[1] states:
>
>> GHC keeps trying to apply the rules as it optimises the program. For
>> example, consider:
>>
>> let s = map f
>>       t = map g
>>   in
>>   s (t xs)
>>
>> The expression s (t xs) does not match the rule "map/map", but GHC
>> will substitute for s and t, giving an expression which does match. If
>> s or t was (a) used more than once, and (b) large or a redex, then it
>> would not be substituted, and the rule would not fire.
>>
> The part I'm interested in here is (a); if an expression is used more
> than one then it cannot be substituted for. Is there any way to work
> around this or force it?
>
> The reason I ask is that as a bit of fun (and inspired by Joachim
> Breitner's blog post [2]) I was going to try writing a rewrite rule for
> the first time. What I had in mind was this:
>
> {-# RULES
>  "index cycled list" forall list n. cycle list !! n =
>        list !! (n `mod` length list)
>  #-}
>
> However, in the case he has written about this won't fire, since the LHS
> cannot be substituted as `cycle list` is used more than once:
>
>> let rlist = cycle list
>> print ( rlist !! (10^9), rlist !! 0 )
>
> I can get it to fire again if I write it like this:
>
>> {-# RULES
>>  "!!/cycle" forall list. (!!) (cycle list)  = (\n -> list !! (n `mod` length list))
>>  #-}
>>
>> ...
>>
>> let rlist = (!!) (cycle list)
>> print (rlist (10^9), rlist 0)
>
> But this is non-obvious and I'd rather have it fire in the first case
> (i.e. when used naïvely). So, back to my question; is there a workaround
> or force for this... or does it break too many things if done?
>
> [1]
> http://www.haskell.org/ghc/docs/latest/html/users_guide/rewrite-rules.html#id414792
>
> [2]
> http://www.joachim-breitner.de/blog/archives/308-guid.html
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


More information about the Haskell-Cafe mailing list