Re: [Haskell-cafe] Rewrite rules for enumFromTo

2012-04-19 Thread Michael Snoyman
On Thu, Apr 19, 2012 at 11:47 AM, Joachim Breitner
 wrote:
> Hi Michael,
>
> Am Mittwoch, den 18.04.2012, 19:21 +0300 schrieb Michael Snoyman:
>> I'm quite a novice at rewrite rules; can anyone recommend an approach
>> to get my rule to fire first?
>
> I’m not an expert of rewrite rules either, but from some experimentation
> and reading -dverbose-core2core (which is not a very nice presentation,
> unfortunately), I think that one reason why your rules won’t fire is
> that yieldMany is inlined too early.
>
> diff --git a/conduit/Data/Conduit/Internal.hs 
> b/conduit/Data/Conduit/Internal.hs
> index bf2de63..8050c2c 100644
> --- a/conduit/Data/Conduit/Internal.hs
> +++ b/conduit/Data/Conduit/Internal.hs
> @@ -353,7 +353,7 @@ yieldMany =
>   where
>     go [] = Done Nothing ()
>     go (o:os) = HaveOutput (go os) (return ()) o
> -{-# INLINE yieldMany #-}
> +{-# INLINE [1] yieldMany #-}
>
>  {-# RULES
>     "yield/bind" forall o (p :: Pipe i o m r). yield o >> p = yieldBind o p
>
> changes that.
>
> It might be hard to actually match on [1...1000], as that is very early
> replaced by the specific instance method which then takes part in the
> foldr/build-rewrite-reign. But maybe instead of specializing enumFromTo,
> you already get good and more general results in hooking into that?
> Juding from the code, you are already trying to do so, as you have a
> yieldMany/build rule that fires with above change:
>
> $ cat Test.hs
> module Test where
>
> import Data.Conduit
> import qualified Data.Conduit.List as CL
>
> x :: Pipe i Integer IO ()
> x = mapM_ yield [1..1000]
>
> $ ghc -O -fforce-recomp -ddump-rule-firings Test.hs
> [1 of 1] Compiling Test             ( Test.hs, Test.o )
> Rule fired: Class op enumFromTo
> Rule fired: mapM_ yield
> Rule fired: yieldMany/build
>
> Oh, and as you can see, you don’t have to export the functions ocurring
> in the rules, as you did with yieldMany and yieldBuild.
>
> I don’t know conduits well, but you should check whether this also
> affects you:
> http://www.haskell.org/pipermail/haskell-cafe/2011-October/095985.html
> If conduits are constructed like in steam fusion, the build rule might
> not be of any use.
>
> Greetings,
> Joachim
>
> --
> Joachim "nomeata" Breitner
>  m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
>  xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

That's exactly what I was looking for, thank you! With that change,
`mapM_ yield [1..1000]` is neck-and-neck with the raw version
(38.98505 us versus 38.75267 us).

Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Rewrite rules for enumFromTo

2012-04-19 Thread Joachim Breitner
Hi Michael,

Am Mittwoch, den 18.04.2012, 19:21 +0300 schrieb Michael Snoyman:
> I'm quite a novice at rewrite rules; can anyone recommend an approach
> to get my rule to fire first?

I’m not an expert of rewrite rules either, but from some experimentation
and reading -dverbose-core2core (which is not a very nice presentation,
unfortunately), I think that one reason why your rules won’t fire is
that yieldMany is inlined too early. 

diff --git a/conduit/Data/Conduit/Internal.hs b/conduit/Data/Conduit/Internal.hs
index bf2de63..8050c2c 100644
--- a/conduit/Data/Conduit/Internal.hs
+++ b/conduit/Data/Conduit/Internal.hs
@@ -353,7 +353,7 @@ yieldMany =
   where
 go [] = Done Nothing ()
 go (o:os) = HaveOutput (go os) (return ()) o
-{-# INLINE yieldMany #-}
+{-# INLINE [1] yieldMany #-}
 
 {-# RULES
 "yield/bind" forall o (p :: Pipe i o m r). yield o >> p = yieldBind o p

changes that.

It might be hard to actually match on [1...1000], as that is very early
replaced by the specific instance method which then takes part in the
foldr/build-rewrite-reign. But maybe instead of specializing enumFromTo,
you already get good and more general results in hooking into that?
Juding from the code, you are already trying to do so, as you have a
yieldMany/build rule that fires with above change:

$ cat Test.hs 
module Test where

import Data.Conduit
import qualified Data.Conduit.List as CL

x :: Pipe i Integer IO ()
x = mapM_ yield [1..1000]

$ ghc -O -fforce-recomp -ddump-rule-firings Test.hs 
[1 of 1] Compiling Test ( Test.hs, Test.o )
Rule fired: Class op enumFromTo
Rule fired: mapM_ yield
Rule fired: yieldMany/build

Oh, and as you can see, you don’t have to export the functions ocurring
in the rules, as you did with yieldMany and yieldBuild.

I don’t know conduits well, but you should check whether this also
affects you:
http://www.haskell.org/pipermail/haskell-cafe/2011-October/095985.html
If conduits are constructed like in steam fusion, the build rule might
not be of any use. 

Greetings,
Joachim

-- 
Joachim "nomeata" Breitner
  m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
  xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Rewrite rules for enumFromTo

2012-04-18 Thread Michael Snoyman
Hi all,

Following a little thread on Reddit[1], I'm trying to add rewrite
rules to conduit to make some simple usages of `yield` more efficient.
I've pushed these changes to a branch on Github[2]. However, I'm not
able to fully optimize the following program:

import Data.Conduit
import qualified Data.Conduit.List as CL

main :: IO ()
main = do
x <- mapM_ yield [1..1000] $$ CL.fold (+) 0
print (x :: Int)

Ideally, I would like to rewrite the entirety of `mapM_ yield
[1..1000]` to `Data.Conduit.List.enumFromTo 1 1000` and thereby avoid
the intermediate list. However, whenever I add such a rule, it doesn't
fire. Instead, -ddump-rule-firings tells me:

Rule fired: Class op enumFromTo
Rule fired: mapM_ yield
Rule fired: Class op +
Rule fired: Class op >>=
Rule fired: Class op show
Rule fired: eftIntList

I'm quite a novice at rewrite rules; can anyone recommend an approach
to get my rule to fire first?

Thanks,
Michael

PS: In case you're wondering, the `mapM_ yield` rule turns `mapM_
yield` into `yieldMany`. So ideally, I'd like to have another rule
that turns `yieldMany [x..y]` into `Data.Conduit.List.enumFromTo x y`.

[1] 
http://www.reddit.com/r/haskell/comments/sdzmx/many_ways_to_skin_a_conduit/c4dftb9
[2] https://github.com/snoyberg/conduit/tree/rewrite

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Rewrite rules not firing for rules matching multiple instance methods

2012-03-21 Thread Acshi Haggenmiller

Hi,

I have some rewrite rules set up and am finding that in the case where 
my rule pattern matches to instance methods and there are more than one 
of them, my rules do not fire. If they are simply taken out from being 
instance methods, they match just fine. I have posted more details and a 
code example to 
http://stackoverflow.com/questions/9811294/rewrite-rules-not-firing-for-rules-matching-multiple-instance-methods


I appreciate the help,
Acshi

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Roman Leshchinskiy
Max Bolingbroke wrote:
> On 15 February 2011 16:45, Roman Leshchinskiy  wrote:
>
>> Only if foo has an INLINE pragma. Otherwise, GHC uses whatever RHS is
>> available when it wants to inline.
>
> Ah, I see! Well yes, in that case my workaround is indeed broken in
> the way you describe, and there is no way to repair it because in my
> proposal you wouldn't be able to write an INLINE pragma on the actual
> default method definition.

There is an alternative, actually. When compiling a module with a function
that doesn't have an INLINE pragma, GHC uses its optimised rhs for
inlining in every stage and then records its unfolding for use in other
modules if it is small enough to be inlined. This has some unfortunate
(IMO) implications. Consider the following code:

{-# INLINE [1] f #-}
f = 
g = f
h = g

Will  be inlined into h? This depends on the module that h is defined
in. If it's in the same module as g, then g will most likely be inlined
into h in phase 2, i.e., before f has been inlined into g. Then, f will be
inlined into both g and h in phase 1. However, after f is inlined into g,
g's rhs becomes too big for inlining. So if h is defined in a different
module, g won't be inlined into it.

We could just as well say that a function's rhs should be recorded forever
as soon as it becomes small enough to be considered for inlining. So GHC
could notice that g is very small in phase 2 and basically add an
INLINABLE pragma to it at that point, regardless of what happens to its
rhs afterwards. This would ensure that inlining isn't affected by
splitting things into modules and would probably also make your proposal
work. But it would also result in a lot more inlining compared to now.

Roman




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Max Bolingbroke
On 15 February 2011 16:45, Roman Leshchinskiy  wrote:
> Only if foo has an INLINE pragma. Otherwise, GHC uses whatever RHS is
> available when it wants to inline.

Ah, I see! Well yes, in that case my workaround is indeed broken in
the way you describe, and there is no way to repair it because in my
proposal you wouldn't be able to write an INLINE pragma on the actual
default method definition.

Thanks for pointing out my error.

Max

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Roman Leshchinskiy
Max Bolingbroke wrote:
> On 15 February 2011 15:12, Roman Leshchinskiy  wrote:
>
>> Ah, but you assume that bar won't be inlined into foo first. Consider
>> that it is perfectly acceptable for GHC to generate this:
>>
>> foo =  {-# INLINE bar #-}
>> bar = 
>>
>> We did ask to inline bar, after all.
>>
>
> Well, yes, but when considering the use site for foo don't we now
> inline the *original RHS* of foo? This recent change means that it doesn't
> matter whether bar gets inlined into foo first - use sites of foo will
> only get a chance to inline the "bar" RHS.

Only if foo has an INLINE pragma. Otherwise, GHC uses whatever RHS is
available when it wants to inline.

Roman




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Max Bolingbroke
On 15 February 2011 15:12, Roman Leshchinskiy  wrote:
> Ah, but you assume that bar won't be inlined into foo first. Consider that
> it is perfectly acceptable for GHC to generate this:
>
> foo = 
> {-# INLINE bar #-}
> bar = 
>
> We did ask to inline bar, after all.

Well, yes, but when considering the use site for foo don't we now
inline the *original RHS* of foo? This recent change means that it
doesn't matter whether bar gets inlined into foo first - use sites of
foo will only get a chance to inline the "bar" RHS.

Cheers,
Max

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Roman Leshchinskiy
Max Bolingbroke wrote:
> On 15 February 2011 11:23, Roman Leshchinskiy  wrote:
>
>> I wouldn't necessarily expect this to guarantee inlining for the same
>> reason that the following code doesn't guarantee that foo gets rewritten
>>  to :
>>
>> foo = bar
>> {-# INLINE bar #-}
>> bar = 
>>
>> It might work with the current implementation (I'm not even sure if it
>> does) but it would always look dodgy to me.
>
> In this case there doesn't seem to be any point inlining anyway,
> because nothing is known about the context into which you are inlining.
> Nonetheless, what will happen (I think) is that any users of
> "foo" will get the definition of "foo" inlined (because that doesn't
> increase program size) so now they refer to "bar" instead. Now GHC can look
> at the use site of bar and the definition of bar and decide whether it is
> a good idea to inline.

Ah, but you assume that bar won't be inlined into foo first. Consider that
it is perfectly acceptable for GHC to generate this:

foo = 
{-# INLINE bar #-}
bar = 

We did ask to inline bar, after all.

> Basically, I expect the small RHS for the default in my class
> declaration to be inlined unconditionally, and then GHCs heuristics will
> determine how and when to inline the "actual" default definition (e.g.
> default_foo).

As soon as GHC generates a Core term for the RHS of the default method all
bets are off because it might inline default_foo into that term which
would make it too big to be inlined somewhere else. I thought you were
suggesting to treat "foo = default_foo" specially by not generating a
separate RHS for the default definition of foo and just rewriting it to
default_foo instead.

What it basically comes down to is a staging problem. You don't want
default_foo to be inlined into the RHS of foo before the latter is inlined
but the only way to achieve this is by marking foo as INLINE which is
precisely what you want to avoid.

Roman




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Max Bolingbroke
On 15 February 2011 11:23, Roman Leshchinskiy  wrote:
> I wouldn't necessarily expect this to guarantee inlining for the same
> reason that the following code doesn't guarantee that foo gets rewritten
> to :
>
> foo = bar
> {-# INLINE bar #-}
> bar = 
>
> It might work with the current implementation (I'm not even sure if it
> does) but it would always look dodgy to me.

In this case there doesn't seem to be any point inlining anyway,
because nothing is known about the context into which you are
inlining. Nonetheless, what will happen (I think) is that any users of
"foo" will get the definition of "foo" inlined (because that doesn't
increase program size) so now they refer to "bar" instead. Now GHC can
look at the use site of bar and the definition of bar and decide
whether it is a good idea to inline.

Basically, I expect the small RHS for the default in my class
declaration to be inlined unconditionally, and then GHCs heuristics
will determine how and when to inline the "actual" default definition
(e.g. default_foo). This differs from the current story in that with
the present setup you can write the INLINE and default method directly
in the class definition, and then GHC does not need to inline the
small RHS of the default to get a chance to apply its inlining
heuristics on the "actual" default method.

However, given that these small RHSes *should* be inlined eagerly and
ubiquitously, there shouldn't be a detectable difference writing
default methods directly and the proposed pattern for adding INLINE
pragmas to default methods.

> Also, what if I write:
>
> class MyClass a where
>  foo :: a -> a
>  foo x = default_foo x
>
> I assume this wouldn't guarantee inlining?

I don't know about any guarantee -- again personally I would only hope
the inlining would only occur should GHC decide it is worth it -- but
this still looks like it should be OK under the no-size-increase
inlining heuristic. I think the simplifier will probably avoid
actually inlining unless foo is applied to at least 1 arg to avoid
increasing allocation, but any interesting use site will meet that
condition.

I do not really know what the simplifier does in enough detail to know
exactly what will happen here, though. This is just an educated guess
as to what will happen, which makes me think that my proposed pattern
is OK.

Cheers,
Max

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Roman Leshchinskiy
Max Bolingbroke wrote:
> 2011/2/15 Simon Peyton-Jones :
>
>> but currently any pragmas in a class decl are treated as attaching to
>> the *default method*, not to the method selector:
>
> I see. I didn't realise that that was what was happening. Personally I
> find this a bit surprising, but I can see the motivation. Of course, a
> sensible alternative design would be to have them control the selectors,
> and then you could declare that you want your default methods to be
> inlined like this:
>
> {{{
> class MyClass a where
>   foo :: a -> a
>   foo = default_foo
>
> {-# INLINE default_foo #-}
> default_foo = ... big expression ...
> }}}

I wouldn't necessarily expect this to guarantee inlining for the same
reason that the following code doesn't guarantee that foo gets rewritten
to :

foo = bar
{-# INLINE bar #-}
bar = 

It might work with the current implementation (I'm not even sure if it
does) but it would always look dodgy to me.

Also, what if I write:

class MyClass a where
  foo :: a -> a
  foo x = default_foo x

I assume this wouldn't guarantee inlining?

> In any event, perhaps it would be worth warning if you write an INLINE
> pragma for some identifier in a class declaration where no corresponding
> default method has been declared, in just the same way you would if you
> wrote an INLINE pragma for a non-existant binding?

+1

Roman




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Max Bolingbroke
2011/2/15 Simon Peyton-Jones :
> but currently any pragmas in a class decl are treated as attaching to the 
> *default method*, not to the method selector:

I see. I didn't realise that that was what was happening. Personally I
find this a bit surprising, but I can see the motivation. Of course, a
sensible alternative design would be to have them control the
selectors, and then you could declare that you want your default
methods to be inlined like this:

{{{
class MyClass a where
  foo :: a -> a
  foo = default_foo

{-# INLINE default_foo #-}
default_foo = ... big expression ...
}}}

I think this design+workaround is slightly preferable to your proposal
because it avoids clients of a library defining a class from having to
write instances with decorated names. But maybe it's not such a big
win as to be worth making the change.

In any event, perhaps it would be worth warning if you write an INLINE
pragma for some identifier in a class declaration where no
corresponding default method has been declared, in just the same way
you would if you wrote an INLINE pragma for a non-existant binding?

Cheers,
Max

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread José Pedro Magalhães
Hello,

2011/2/15 Simon Peyton-Jones 

>
> but currently any pragmas in a class decl are treated as attaching to the
> *default method*, not to the method selector:
>
>
Thanks for this clarification, I had wondered about this for a while. I
think it would also be nice to mention this in the user's guide; currently,
http://www.haskell.org/ghc/docs/latest/html/users_guide/rewrite-rules.htmlsays
nothing about the semantics of rewrite rules in classes/instances.


Cheers,
Pedro
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Simon Peyton-Jones
What happens is this. From the (Foo Bool) instance GHC generates

dFooBool :: Foo Bool
dFooBool = DFoo fooBool barBool foo_barBool

barBool :: Bool -> Bool
barBool = not

Now when GHC sees
bar dFooBool
it rewrites it to
barBool

Moreover there is currently no way to say "don't do that rewrite until phase 
1".  It's an "always-on" rewrite.  For all other rewrite rules you can control 
which phase(s) the rule is active in.

What you want in this case is to avoid doing the bar/dFooBool rewrite until the 
"foo/bar" rule has had a chance to fire.

There's no fundamental difficulty with doing this, except a syntactic one: 
since the rule is implicit, how can we control it's phase?  You could imagine 
saying

class Foo a where
  bar :: a -> a
  {-# NOINLINE [1] bar #-}

but currently any pragmas in a class decl are treated as attaching to the 
*default method*, not to the method selector:

class Foo a where
  bar :: a -> a

bar x = x
{-# NOINLINE [1] bar #-}

So we need another notation for the latter.  

As a workaround, you can say

class Foo a where
  _bar :: a -> a
  _foo :: a -> a

{-# NOINLINE [1] foo #-}
foo = _foo

{- NOINLINE [1] bar #-}
bar = _bar

Given the workaround, and the syntactic question, I wonder whether the feature 
is worth the cost.

Simon


| -Original Message-
| From: haskell-cafe-boun...@haskell.org [mailto:haskell-cafe-
| boun...@haskell.org] On Behalf Of Max Bolingbroke
| Sent: 15 February 2011 09:08
| To: Gábor Lehel
| Cc: Haskell Cafe
| Subject: Re: [Haskell-cafe] rewrite rules to specialize function according to
| type class?
| 
| 2011/2/15 Gábor Lehel :
| > This is a semi-related question I've been meaning to ask at some
| > point: I suppose this also means it's not possible to write a class,
| > write some rules for the class, and then have the rules be applied to
| > every instance? (I.e. you'd have to write them separately for each?)
| 
| This does work, because it doesn't require the simplifier to lookup up
| class instances. However, it's a bit fragile. Here is an example:
| 
| """
| class Foo a where
|   foo :: a -> a
|   bar :: a -> a
|   foo_bar :: a -> a
| 
| {-# RULES "foo/bar" forall x. foo (bar x) = foo_bar x #-}
| 
| 
| instance Foo Bool where
| foo = not
| bar = not
| foo_bar = not
| 
| instance Foo Int where
| foo = (+1)
| bar x = x - 1
| foo_bar = (+2)
| 
| 
| {-# NOINLINE foo_barish #-}
| foo_barish :: Foo a => a -> a
| foo_barish x = foo (bar x)
| 
| 
| main = do
| print $ foo (bar False)   -- False if rule not applied, True
| otherwise
| print $ foo (bar (2 :: Int))  -- 2 if rule not applied, 4, otherwise
| print $ foo_barish False  -- False if rule not applied, True
| otherwise
| print $ foo_barish (2 :: Int) -- 2 if rule not applied, 4, otherwise
| """
| 
| With GHC 7, the RULE successfully rewrites the foo.bar composition
| within foo_barish to use foo_bar. However, it fails to rewrite the two
| foo.bar compositions inlined directly in main. Thus the output is:
| 
| """
| False
| 2
| True
| 4
| """
| 
| The reason it cannot rewrite the calls in main is (I think) because
| the foo/bar class selectors are inlined before the rule matcher gets
| to spot them. By using NOINLINE on foo_barish, and ensuring that
| foo_barish is overloaded, we prevent the simplifier from doing this
| inlining and hence allow the rule to fire.
| 
| What is more interesting is that I can't get the foo (bar x) rule to
| fire on the occurrences within main even if I add NOINLINE pragmas to
| the foo/bar names in both the class and instance declarations.
| Personally I would expect writing NOINLINE on the class declaration
| would prevent the class selector being inlined, allowing the rule to
| fire, but that is not happening for some reason.
| 
| Perhaps this is worth a bug report on the GHC trac? It would at least
| give it a chance of being fixed.
| 
| Max
| 
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Max Bolingbroke
2011/2/15 Gábor Lehel :
> This is a semi-related question I've been meaning to ask at some
> point: I suppose this also means it's not possible to write a class,
> write some rules for the class, and then have the rules be applied to
> every instance? (I.e. you'd have to write them separately for each?)

This does work, because it doesn't require the simplifier to lookup up
class instances. However, it's a bit fragile. Here is an example:

"""
class Foo a where
  foo :: a -> a
  bar :: a -> a
  foo_bar :: a -> a

{-# RULES "foo/bar" forall x. foo (bar x) = foo_bar x #-}


instance Foo Bool where
foo = not
bar = not
foo_bar = not

instance Foo Int where
foo = (+1)
bar x = x - 1
foo_bar = (+2)


{-# NOINLINE foo_barish #-}
foo_barish :: Foo a => a -> a
foo_barish x = foo (bar x)


main = do
print $ foo (bar False)   -- False if rule not applied, True otherwise
print $ foo (bar (2 :: Int))  -- 2 if rule not applied, 4, otherwise
print $ foo_barish False  -- False if rule not applied, True otherwise
print $ foo_barish (2 :: Int) -- 2 if rule not applied, 4, otherwise
"""

With GHC 7, the RULE successfully rewrites the foo.bar composition
within foo_barish to use foo_bar. However, it fails to rewrite the two
foo.bar compositions inlined directly in main. Thus the output is:

"""
False
2
True
4
"""

The reason it cannot rewrite the calls in main is (I think) because
the foo/bar class selectors are inlined before the rule matcher gets
to spot them. By using NOINLINE on foo_barish, and ensuring that
foo_barish is overloaded, we prevent the simplifier from doing this
inlining and hence allow the rule to fire.

What is more interesting is that I can't get the foo (bar x) rule to
fire on the occurrences within main even if I add NOINLINE pragmas to
the foo/bar names in both the class and instance declarations.
Personally I would expect writing NOINLINE on the class declaration
would prevent the class selector being inlined, allowing the rule to
fire, but that is not happening for some reason.

Perhaps this is worth a bug report on the GHC trac? It would at least
give it a chance of being fixed.

Max

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-14 Thread Gábor Lehel
On Tue, Feb 15, 2011 at 12:48 AM, Max Bolingbroke
 wrote:
> On 14 February 2011 21:43, Patrick Bahr  wrote:
>> Am I doing something wrong or is it not possible for GHC to dispatch a rule
>> according to type class constraints?
>
> As you have discovered this is not possible. You can write the rule
> for as many *particular* types as you like, but you can't write it in
> a way that abstracts over the exact type class instance you mean. This
> is a well known and somewhat tiresome issue.
>
> I think the reason that this is not implemented is because it would
> require the rule matcher to call back into the type checking machinery
> to do instance lookup.

This is a semi-related question I've been meaning to ask at some
point: I suppose this also means it's not possible to write a class,
write some rules for the class, and then have the rules be applied to
every instance? (I.e. you'd have to write them separately for each?)

>
> Cheers,
> Max
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Work is punishment for failing to procrastinate effectively.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-14 Thread Max Bolingbroke
On 14 February 2011 21:43, Patrick Bahr  wrote:
> Am I doing something wrong or is it not possible for GHC to dispatch a rule
> according to type class constraints?

As you have discovered this is not possible. You can write the rule
for as many *particular* types as you like, but you can't write it in
a way that abstracts over the exact type class instance you mean. This
is a well known and somewhat tiresome issue.

I think the reason that this is not implemented is because it would
require the rule matcher to call back into the type checking machinery
to do instance lookup.

Cheers,
Max

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-14 Thread Patrick Bahr

Hi all,

I am trying to get a GHC rewrite rule that specialises a function 
according to the type of the argument of the function. Does anybody know 
whether it is possible to do that not with a concrete type but rather a 
type class?


Consider the following example:

> class A a where
> toInt :: a -> Int
> {-# NOINLINE toInt #-}

> class B a where
> toInt' :: a -> Int

The idea is to use the method of type class A unless the type is also an 
instance of type class B. Let's say that Bool is an instance of both A 
and B:


> instance A Bool where
> toInt True = 1
> toInt False = 0

> instance B Bool where
> toInt' True = 0
> toInt' False = 1

Now we add a rule that says that if the argument to "toInt" happens to 
be an instance of type class B as well, use the method "toInt'" instead:


> {-# RULES
>   "toInt" forall (x :: B a => a) . toInt x = toInt' x
>   #-}

Unfortunately, this does not work (neither with GHC 6.12 or GHC 7.0). 
Expression "toInt True" gets evaluated to "1". If the rewrite rule is 
written with a concrete type it works as expected:


> {-# RULES
>   "toInt" forall (x :: Bool) . toInt x = toInt' x
>   #-}

Now "toInt True" is evaluated to "0".

Am I doing something wrong or is it not possible for GHC to dispatch a 
rule according to type class constraints?


Thanks,
Patrick

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules

2009-06-24 Thread Sjoerd Visscher

Ah, thanks.

It turns out that this works:

  transform t l = error "urk"

but this doesn't:

  transform t l = FM $ error "urk"

So it has something to do with the newtype FMList. They are probably  
already gone when rewrite rules fire?


Sjoerd

On Jun 24, 2009, at 6:32 PM, Ryan Ingram wrote:


Your FMLists are defaulting to Integer, so the rule (which
specifically mentions Int) doesn't apply.  Simon's code doesn't have
this problem because of the explicit signature on "upto"; you could do
the same by limiting "singleton" to Int.

 -- ryan

On Wed, Jun 24, 2009 at 12:44 AM, Sjoerd  
Visscher wrote:

Thanks for looking into this.

Your code does give me 2 firings. But not when I replace [] with  
FMList. See

the attached code.





Sjoerd

On Jun 23, 2009, at 5:59 PM, Simon Peyton-Jones wrote:


| I have a rewrite rule as follows:
|
| {-# RULES
| "transform/transform" forall (f::forall m. Monoid m => (a -> m) - 
> (b -

|  > m))
|   (g::forall m. Monoid m => (b -> m)  
-> (c

| -> m))
|   (l::FMList c). transform f  
(transform g

| l) = transform (g.f) l
|#-}
|
| It fires on this code:
|
|print $ transform (. (*2)) (transform (. (+1)) (upto 10))
|
| But it doesn't fire on this code:
|
|print $ map (*2) (map (+1) (upto 10)))

That's odd. It works for me.

Specifically, I compiled the attached code with GHC 6.10, and I  
get two

firings of transform/transform.

Does that not happen for you?

Simon




--
Sjoerd Visscher
sjo...@w3future.com




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe






--
Sjoerd Visscher
sjo...@w3future.com



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules

2009-06-24 Thread Ryan Ingram
Your FMLists are defaulting to Integer, so the rule (which
specifically mentions Int) doesn't apply.  Simon's code doesn't have
this problem because of the explicit signature on "upto"; you could do
the same by limiting "singleton" to Int.

  -- ryan

On Wed, Jun 24, 2009 at 12:44 AM, Sjoerd Visscher wrote:
> Thanks for looking into this.
>
> Your code does give me 2 firings. But not when I replace [] with FMList. See
> the attached code.
>
>
>
>
>
> Sjoerd
>
> On Jun 23, 2009, at 5:59 PM, Simon Peyton-Jones wrote:
>
>> | I have a rewrite rule as follows:
>> |
>> | {-# RULES
>> | "transform/transform" forall (f::forall m. Monoid m => (a -> m) -> (b -
>> |  > m))
>> |                               (g::forall m. Monoid m => (b -> m) -> (c
>> | -> m))
>> |                               (l::FMList c). transform f (transform g
>> | l) = transform (g.f) l
>> |    #-}
>> |
>> | It fires on this code:
>> |
>> |    print $ transform (. (*2)) (transform (. (+1)) (upto 10))
>> |
>> | But it doesn't fire on this code:
>> |
>> |    print $ map (*2) (map (+1) (upto 10)))
>>
>> That's odd. It works for me.
>>
>> Specifically, I compiled the attached code with GHC 6.10, and I get two
>> firings of transform/transform.
>>
>> Does that not happen for you?
>>
>> Simon
>>
>> 
>
> --
> Sjoerd Visscher
> sjo...@w3future.com
>
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules

2009-06-24 Thread Sjoerd Visscher

Thanks for looking into this.

Your code does give me 2 firings. But not when I replace [] with  
FMList. See the attached code.




Rules.hs
Description: Binary data




Sjoerd

On Jun 23, 2009, at 5:59 PM, Simon Peyton-Jones wrote:


| I have a rewrite rule as follows:
|
| {-# RULES
| "transform/transform" forall (f::forall m. Monoid m => (a -> m) ->  
(b -

|  > m))
|   (g::forall m. Monoid m => (b -> m) - 
> (c

| -> m))
|   (l::FMList c). transform f  
(transform g

| l) = transform (g.f) l
|#-}
|
| It fires on this code:
|
|print $ transform (. (*2)) (transform (. (+1)) (upto 10))
|
| But it doesn't fire on this code:
|
|print $ map (*2) (map (+1) (upto 10)))

That's odd. It works for me.

Specifically, I compiled the attached code with GHC 6.10, and I get  
two firings of transform/transform.


Does that not happen for you?

Simon




--
Sjoerd Visscher
sjo...@w3future.com



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] rewrite rules

2009-06-23 Thread Simon Peyton-Jones
| I have a rewrite rule as follows:
| 
| {-# RULES
| "transform/transform" forall (f::forall m. Monoid m => (a -> m) -> (b -
|  > m))
|   (g::forall m. Monoid m => (b -> m) -> (c
| -> m))
|   (l::FMList c). transform f (transform g
| l) = transform (g.f) l
|#-}
| 
| It fires on this code:
| 
|print $ transform (. (*2)) (transform (. (+1)) (upto 10))
| 
| But it doesn't fire on this code:
| 
|print $ map (*2) (map (+1) (upto 10)))

That's odd. It works for me.

Specifically, I compiled the attached code with GHC 6.10, and I get two firings 
of transform/transform.

Does that not happen for you?

Simon



Rules.hs
Description: Rules.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules

2009-06-22 Thread Ryan Ingram
Not 100% sure (especially without source/core), but my guess is that
the higher-rank types make the rule unlikely to fire.

Try -ddump-simpl to see the core output, and look for places where you
expect the rule to fire.  I suspect you will find that the types of f
and g are not "forall" at that point in the code, but have already
been specialized.

Is there a reason you cannot use this simpler rule?

{-# RULES "transform/tranform" forall f g l. transform f (transform g
l) = transform (g.f) l #-}

  -- ryan

On Mon, Jun 22, 2009 at 2:41 AM, Sjoerd Visscher wrote:
> Hi all,
>
> I have a rewrite rule as follows:
>
> {-# RULES
> "transform/transform" forall (f::forall m. Monoid m => (a -> m) -> (b -> m))
>                             (g::forall m. Monoid m => (b -> m) -> (c -> m))
>                             (l::FMList c). transform f (transform g l) =
> transform (g.f) l
>  #-}
>
> It fires on this code:
>
>  print $ transform (. (*2)) (transform (. (+1)) (upto 10))
>
> But it doesn't fire on this code:
>
>  print $ map (*2) (map (+1) (upto 10)))
>
> with
>
>  map g x = transform (. g) x
>
> and with or without {-# INLINE map #-}.
>
> What am I doing wrong?
>
> --
> Sjoerd Visscher
> sjo...@w3future.com
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules

2009-06-22 Thread Sjoerd Visscher


On Jun 22, 2009, at 6:38 PM, Ryan Ingram wrote:


Not 100% sure (especially without source/core), but my guess is that
the higher-rank types make the rule unlikely to fire.

Try -ddump-simpl to see the core output, and look for places where you
expect the rule to fire.  I suspect you will find that the types of f
and g are not "forall" at that point in the code, but have already
been specialized.

Is there a reason you cannot use this simpler rule?

{-# RULES "transform/tranform" forall f g l. transform f (transform g
l) = transform (g.f) l #-}



Yes, this is the reason:

Inferred type is less polymorphic than expected
  Quantified type variable `m' is mentioned in the environment:
f :: (a -> m) -> b -> m (bound at Data/FMList.hs:124:29)
In the first argument of `transform', namely `f'
In the expression: transform f (transform g l)
When checking the transformation rule "transform/transform"

This is the function:

transform :: (forall m. Monoid m => (a -> m) -> (b -> m)) -> FMList b - 
> FMList a

transform t l = FM $ \f -> unFM l (t f)

I'll have to clean things up before the core output becomes manageable.

Sjoerd


 -- ryan

On Mon, Jun 22, 2009 at 2:41 AM, Sjoerd  
Visscher wrote:

Hi all,

I have a rewrite rule as follows:

{-# RULES
"transform/transform" forall (f::forall m. Monoid m => (a -> m) ->  
(b -> m))
(g::forall m. Monoid m => (b -> m) ->  
(c -> m))
(l::FMList c). transform f (transform g  
l) =

transform (g.f) l
 #-}

It fires on this code:

 print $ transform (. (*2)) (transform (. (+1)) (upto 10))

But it doesn't fire on this code:

 print $ map (*2) (map (+1) (upto 10)))

with

 map g x = transform (. g) x

and with or without {-# INLINE map #-}.

What am I doing wrong?

--
Sjoerd Visscher
sjo...@w3future.com



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe





--
Sjoerd Visscher
sjo...@w3future.com



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] rewrite rules

2009-06-22 Thread Daniel Schüssler
Hi Sjoerd,

I don't know the cause of the problem, but if I add this rule, it works:

{-# RULES
   "inline_map" forall g x. map g x = transform (. g) x
 -#}

maybe, for whatever reason, the 'map' is inlined "too late" for the 
transform/transform rule to see it?


Greetings,
Daniel

On Monday 22 June 2009 11:41:33 Sjoerd Visscher wrote:
> Hi all,
>
> I have a rewrite rule as follows:
>
> {-# RULES
> "transform/transform" forall (f::forall m. Monoid m => (a -> m) -> (b -
>
>  > m))
>
>   (g::forall m. Monoid m => (b -> m) -> (c
> -> m))
>   (l::FMList c). transform f (transform g
> l) = transform (g.f) l
>#-}
>
> It fires on this code:
>
>print $ transform (. (*2)) (transform (. (+1)) (upto 10))
>
> But it doesn't fire on this code:
>
>print $ map (*2) (map (+1) (upto 10)))
>
> with
>
>map g x = transform (. g) x
>
> and with or without {-# INLINE map #-}.
>
> What am I doing wrong?
>
> --
> Sjoerd Visscher
> sjo...@w3future.com
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] rewrite rules

2009-06-22 Thread Sjoerd Visscher

Hi all,

I have a rewrite rule as follows:

{-# RULES
"transform/transform" forall (f::forall m. Monoid m => (a -> m) -> (b - 
> m))
 (g::forall m. Monoid m => (b -> m) -> (c  
-> m))
 (l::FMList c). transform f (transform g  
l) = transform (g.f) l

  #-}

It fires on this code:

  print $ transform (. (*2)) (transform (. (+1)) (upto 10))

But it doesn't fire on this code:

  print $ map (*2) (map (+1) (upto 10)))

with

  map g x = transform (. g) x

and with or without {-# INLINE map #-}.

What am I doing wrong?

--
Sjoerd Visscher
sjo...@w3future.com



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Rewrite rules

2008-10-16 Thread Henning Thielemann


On Thu, 16 Oct 2008, George Pollard wrote:


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:


Perhaps {-# INLINE rlist #-}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Rewrite rules

2008-10-16 Thread George Pollard
On Thu, 2008-10-16 at 09:01 +0100, Ryan Ingram wrote:
> Isn't this an unsound rewrite?

Yeah, hence the just for fun :)

> 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).

Okay, thanks :)


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Rewrite rules

2008-10-16 Thread Ryan Ingram
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 <[EMAIL PROTECTED]>:
> 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@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Rewrite rules

2008-10-15 Thread George Pollard
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


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe