my RULES don't fire

2011-02-09 Thread Sebastian Fischer
Hello,

I want to use the RULES pragma and cannot get my rules to fire. Here is a
simplified example of what I'm trying.

I define my own version of foldMap for lists:

fold :: Monoid m = (a - m) - [a] - m
fold f = foldr mappend mempty . map f
-- alternative, trying to avoid interference with foldr/build fusion
-- fold _ [] = mempty
-- fold f (x:xs) = f x `mappend` fold f xs
{-# NOINLINE fold #-}

I try using a NOINLINE pragma to make the firing of my rules (which involve
fold) more robust. But they don't fire with or without NOINLINE. Also the
uncommented version does not make a difference.

I also define a function that creates a singleton list:

single :: a - [a]
single x = [x]
{-# NOINLINE single #-}

Now I want to replace calls of `fold f . g single` (or eta-expanded versions
of this) by `g f` using the following rules:

{-# RULES
  monoid fusion pointfree
forall f (g :: forall m . Monoid m = (a - m) - b - m) .
  fold f . g single = g f;

  monoid fusion pointed, general
forall f (g :: forall m . Monoid m = (a - m) - b - m) b .
  fold f (g single b) = g f b;

  monoid fusion pointed, for lists
forall f (g :: forall m . Monoid m = (a - m) - [a] - m) xs .
  fold f (g single xs) = g f xs;
  #-}

The variations of type signatures (including no signatures at all) for the
pattern variables that I tried did not change anything for the better.

I wrote the third rule only because the second gives a warning that I don't
quite understand:

Warning: Forall'd type variable b is not bound in RULE lhs
   fold @ m @ a $dMonoid f (g @ [a] $dMonoid (single @ a) b)

I try out the rules using the following function that takes the role of `g`
in the rules:

idGen :: Monoid m = (a - m) - [a] - m
idGen _ [] = mempty
idGen f (x:xs) = f x `mappend` idGen f xs
{-# NOINLINE idGen #-}

Again, I use NOINLINE just in case that would help the rules fire. Here is a
main function where the rules should fire:

main :: IO ()
main =
  do print ((fold id . idGen single) [[()]])
 print (fold id (idGen single [[()]]))

But they don't.

Why don't the rules fire, what can I change such that they do, and what to
get rid of the warning for the second rule (which I think is the one I
should use)?

Best regards,
Sebastian

Here is the output of -ddump-simple-stats (once with -fenable-rewrite-rules
only and once with -O):

# ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.0.1

# ghc -fenable-rewrite-rules -fforce-recomp -ddump-simpl-stats --make rules
[1 of 1] Compiling Main ( rules.hs, rules.o )

 Grand total simplifier statistics 
Total ticks: 0

1 SimplifierDone
1

# ghc -O -fforce-recomp -ddump-simpl-stats --make rules
[1 of 1] Compiling Main ( rules.hs, rules.o )

 FloatOut stats: 
0 Lets floated to top level; 0 Lets floated elsewhere; from 4 Lambda groups



 FloatOut stats: 
10 Lets floated to top level; 1 Lets floated elsewhere; from 5 Lambda groups



 Grand total simplifier statistics 
Total ticks: 144

34 PreInlineUnconditionally
1 eta_Xp5
1 g_amr
1 eta_amx
1 k_amJ
1 z_amK
1 f_amQ
1 g_amR
1 x_amS
1 k_an9
1 z_ana
1 g_anb
1 f_anf
1 xs_ang
1 eta_aoA
2 $dShow_aKW
2 x_aKX
1 ys_aVd
1 c_dmm
1 n_dmn
1 a_snX
1 a_so1
1 lvl_sod
1 lvl_soe
1 lvl_sof
1 lvl_sog
1 lvl_soh
1 lvl_soi
1 lvl_soj
1 a_son
1 a_sop
1 a_sV0
1 a_sV2
17 PostInlineUnconditionally
1 k_amv
1 f_amQ
1 g_amR
1 c_ani
1 n_anj
1 m_anI
1 k_anJ
2 $dShow_aoy
2 x_aoz
1 c_aVa
1 f_aVb
1 x_aVc
1 a_snV
1 a_snZ
1 lvl_sVA
15 UnfoldingDone
1 GHC.Base.build
1 GHC.Base.foldr
2 System.IO.print
1 GHC.TopHandler.runMainIO
2 GHC.Base..
1 GHC.Base.mapFB
1 GHC.Base.$fMonadIO_$c
2 Main.main
2 System.IO.print1
2 GHC.Show.$fShow[]_$cshow
8 RuleFired
1 Class op 
2 Class op show
2 Class op showList
1 fold/build
1 foldr/nil
1 map
8 LetFloatFromLet
8
62 BetaReduction
1 eta_Xp5
1 a_amq
1 g_amr
1 a_amt
1 b_amu
1 k_amv
1 z_amw
1 eta_amx
1 b_amH
1 a_amI
1 k_amJ
1 z_amK
2 b_amN
2 c_amO
2 a_amP
2 f_amQ
2 g_amR
1 x_amS
1 a_an7
1 b_an8
1 k_an9
1 z_ana
1 g_anb
1 a_and
1 a1_ane
1 f_anf
1 xs_ang
1 b_anh
1 c_ani
1 n_anj
1 a_anG
1 b_anH
1 m_anI
1 k_anJ
2 a_aox
2 $dShow_aoy
2 x_aoz
1 eta_aoA
2 a_aKV
2 $dShow_aKW
2 x_aKX
1 elt_aV7
1 lst_aV8
1 a_aV9
1 c_aVa
1 f_aVb
1 x_aVc
1 ys_aVd
1 a_dml
1 c_dmm
1 n_dmn
13 SimplifierDone
13

Re: my RULES don't fire

2011-02-09 Thread Daniel Fischer
On Wednesday 09 February 2011 16:23:15, Sebastian Fischer wrote:
 Why don't the rules fire, what can I change such that they do, and what
 to get rid of the warning for the second rule (which I think is the one
 I should use)?

Didn't spot that, sorry.


 Best regards,
 Sebastian

 Here is the output of -ddump-simple-stats (once with
 -fenable-rewrite-rules only and once with -O):

Users guide says:

(NB: enabling -fenable-rewrite-rules without -O may not do what you expect, 
though, because without -O GHC ignores all optimisation information in 
interface files;



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: my RULES don't fire

2011-02-09 Thread Daniel Fischer
On Wednesday 09 February 2011 16:23:15, Sebastian Fischer wrote:
 Why don't the rules fire,

Because the 'match' is at the wrong type. In main, idGen appears as

idGen_anJ :: ([()] - [[()]]) - [[()]] - [[()]]

at some point (yay for ghc -v4), so it doesn't match g's polymorphic type.

 what can I change such that they do,

Type signatures.

 and what to get rid of the warning for the second rule (which I think
 is the one I should use)?

I'll let that for somebody else.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: my RULES don't fire

2011-02-09 Thread Sebastian Fischer

  Why don't the rules fire,

 Because the 'match' is at the wrong type.


This was the correct hint, thanks!


  what can I change such that they do,

 Type signatures.


Initially, I thought that just leaving out the polymorphic signature should
fix the problem. But I think it cannot be fixed by changing type signatures
only because once the type of `g` in the rule is fixed, the rule is no
longer type correct!

To overcome this, I have defined

gen :: (forall m . Monoid m = (a - m) - b - m) - b - [a]
gen g = g single
{-# NOINLINE gen #-}

and changed the rules to

{-# RULES
  monoid fusion pointfree
forall f (g :: forall m . Monoid m = (a - m) - b - m) .
  fold f . gen g = g f;

  monoid fusion pointed
forall f (g :: forall m . Monoid m = (a - m) - b - m) b .
  fold f (gen g b) = g f b;
  #-}

and now they fire. Seems a bit roundabout but I don't see how to avoid this
indirection.


  and what to get rid of the warning for the second rule (which I think
  is the one I should use)?

 I'll let that for somebody else.


My new rules don't cause this warning. I'm still interested in what the
warning meant, although my code does not depend on an answer anymore.

Probably because, GHC inlines function composition in the first line of

main = do print ((fold id . gen idGen) [[()]])
  print (fold id (gen idGen [[()]]))

the pointed rule fires twice if I remove the point-free one.

Does it make sense to keep the point-free rule just in case that `fold f .
gen g` is passed to a higher-order function and does not get an argument
after inlining?

Sebastian
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users