desperately seeking RULES help

I'm trying to do some fusion in ghc, and I'd greatly appreciate help with the code below (which is simplified from fusion on linear maps). I've tried every variation I can think of, and always something prevents the fusion. Help, please! Thanks, - Conal {-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl -ddump-simpl-stats #-} -- {-# OPTIONS_GHC -ddump-simpl-iterations #-} module F where -- | Domain of a linear map. class AsInt a where toInt :: a -> Int fromInt :: Int -> a {-# RULES "toInt/fromInt" forall m. toInt (fromInt m) = m #-} {-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f = fromInt . f . toInt test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g -- The desired result: -- -- test h g -- == onInt h . onInt g -- == (fromInt . h . toInt) . (fromInt . g . toInt) -- == \ a -> (fromInt . h . toInt) ((fromInt . g . toInt) a) -- == \ a -> (fromInt . h . toInt) (fromInt (g (toInt a))) -- == \ a -> fromInt (h (toInt (fromInt (g (toInt a))))) -- == \ a -> fromInt (h (g (toInt a)))

2008/6/7 Conal Elliott
I'm trying to do some fusion in ghc, and I'd greatly appreciate help with the code below (which is simplified from fusion on linear maps). I've tried every variation I can think of, and always something prevents the fusion.
[snip]
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f = fromInt . f . toInt
I don't know if this will help but add this to prevent GHC from inlining the definition of fromInt (or toInt) in the first phase: {-# NOINLINE [1] fromInt #-} {-# INLINE [2] fromInt #-} It might be possible to combine the both into one pragma but I don't know how. -- Johan

Interesting. The problem seems to be that GHC always inlines toInt
and fromInt early, but this means that the rewrite rule no longer
applies.
And, of course, it doesn't inline toInt and fromInt in the rewrite rule.
I have no idea if you can write a rule that will actually work,
because after toInt and fromInt have been inlined you can no longer
write rules that apply, since the types involve dictionaries and the
terms pattern match on dictionaries.
-- Lennart
2008/6/7 Conal Elliott
I'm trying to do some fusion in ghc, and I'd greatly appreciate help with the code below (which is simplified from fusion on linear maps). I've tried every variation I can think of, and always something prevents the fusion.
Help, please! Thanks, - Conal
{-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl -ddump-simpl-stats #-} -- {-# OPTIONS_GHC -ddump-simpl-iterations #-}
module F where
-- | Domain of a linear map. class AsInt a where toInt :: a -> Int fromInt :: Int -> a
{-# RULES "toInt/fromInt" forall m. toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f = fromInt . f . toInt
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
-- The desired result: -- -- test h g -- == onInt h . onInt g -- == (fromInt . h . toInt) . (fromInt . g . toInt) -- == \ a -> (fromInt . h . toInt) ((fromInt . g . toInt) a) -- == \ a -> (fromInt . h . toInt) (fromInt (g (toInt a))) -- == \ a -> fromInt (h (toInt (fromInt (g (toInt a))))) -- == \ a -> fromInt (h (g (toInt a)))
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Here's something that actually works. You need to pass
-fno-method-sharing on the command line.
Instead of using rules on methods it uses rules on global functions,
and these global functions don't get inlined until late (after the
rule has fired).
-- Lennart
module F where
-- | Domain of a linear map.
class AsInt a where
toInt' :: a -> Int
fromInt' :: Int -> a
{-# INLINE[1] toInt #-}
toInt :: (AsInt a) => a -> Int
toInt = toInt'
{-# INLINE[1] fromInt #-}
fromInt :: (AsInt a) => Int -> a
fromInt = fromInt'
{-# RULES
"toInt/fromInt" forall m . toInt (fromInt m) = m
#-}
{-# INLINE onInt #-}
onInt :: AsInt a => (Int -> Int) -> (a -> a)
onInt f x = fromInt (f (toInt x))
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a)
test h g = onInt h . onInt g
2008/6/7 Conal Elliott
I'm trying to do some fusion in ghc, and I'd greatly appreciate help with the code below (which is simplified from fusion on linear maps). I've tried every variation I can think of, and always something prevents the fusion.
Help, please! Thanks, - Conal
{-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl -ddump-simpl-stats #-} -- {-# OPTIONS_GHC -ddump-simpl-iterations #-}
module F where
-- | Domain of a linear map. class AsInt a where toInt :: a -> Int fromInt :: Int -> a
{-# RULES "toInt/fromInt" forall m. toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f = fromInt . f . toInt
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
-- The desired result: -- -- test h g -- == onInt h . onInt g -- == (fromInt . h . toInt) . (fromInt . g . toInt) -- == \ a -> (fromInt . h . toInt) ((fromInt . g . toInt) a) -- == \ a -> (fromInt . h . toInt) (fromInt (g (toInt a))) -- == \ a -> fromInt (h (toInt (fromInt (g (toInt a))))) -- == \ a -> fromInt (h (g (toInt a)))
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Thanks a million, Lennart! -fno-method-sharing was the missing piece. -
Conal
On Sat, Jun 7, 2008 at 5:07 AM, Lennart Augustsson
Here's something that actually works. You need to pass -fno-method-sharing on the command line. Instead of using rules on methods it uses rules on global functions, and these global functions don't get inlined until late (after the rule has fired).
-- Lennart
module F where
-- | Domain of a linear map. class AsInt a where toInt' :: a -> Int fromInt' :: Int -> a
{-# INLINE[1] toInt #-} toInt :: (AsInt a) => a -> Int toInt = toInt'
{-# INLINE[1] fromInt #-} fromInt :: (AsInt a) => Int -> a fromInt = fromInt'
{-# RULES "toInt/fromInt" forall m . toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f x = fromInt (f (toInt x))
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
I'm trying to do some fusion in ghc, and I'd greatly appreciate help with the code below (which is simplified from fusion on linear maps). I've
2008/6/7 Conal Elliott
: tried every variation I can think of, and always something prevents the fusion.
Help, please! Thanks, - Conal
{-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl -ddump-simpl-stats #-} -- {-# OPTIONS_GHC -ddump-simpl-iterations #-}
module F where
-- | Domain of a linear map. class AsInt a where toInt :: a -> Int fromInt :: Int -> a
{-# RULES "toInt/fromInt" forall m. toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f = fromInt . f . toInt
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
-- The desired result: -- -- test h g -- == onInt h . onInt g -- == (fromInt . h . toInt) . (fromInt . g . toInt) -- == \ a -> (fromInt . h . toInt) ((fromInt . g . toInt) a) -- == \ a -> (fromInt . h . toInt) (fromInt (g (toInt a))) -- == \ a -> fromInt (h (toInt (fromInt (g (toInt a))))) -- == \ a -> fromInt (h (g (toInt a)))
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Is it by intention that -fno-method-sharing works only from the command
line, not in an OPTIONS_GHC pragma?
On Sat, Jun 7, 2008 at 9:23 AM, Conal Elliott
Thanks a million, Lennart! -fno-method-sharing was the missing piece. - Conal
On Sat, Jun 7, 2008 at 5:07 AM, Lennart Augustsson
wrote: Here's something that actually works. You need to pass -fno-method-sharing on the command line. Instead of using rules on methods it uses rules on global functions, and these global functions don't get inlined until late (after the rule has fired).
-- Lennart
module F where
-- | Domain of a linear map. class AsInt a where toInt' :: a -> Int fromInt' :: Int -> a
{-# INLINE[1] toInt #-} toInt :: (AsInt a) => a -> Int toInt = toInt'
{-# INLINE[1] fromInt #-} fromInt :: (AsInt a) => Int -> a fromInt = fromInt'
{-# RULES "toInt/fromInt" forall m . toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f x = fromInt (f (toInt x))
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
I'm trying to do some fusion in ghc, and I'd greatly appreciate help with the code below (which is simplified from fusion on linear maps). I've
2008/6/7 Conal Elliott
: tried every variation I can think of, and always something prevents the fusion.
Help, please! Thanks, - Conal
{-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl -ddump-simpl-stats #-} -- {-# OPTIONS_GHC -ddump-simpl-iterations #-}
module F where
-- | Domain of a linear map. class AsInt a where toInt :: a -> Int fromInt :: Int -> a
{-# RULES "toInt/fromInt" forall m. toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f = fromInt . f . toInt
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
-- The desired result: -- -- test h g -- == onInt h . onInt g -- == (fromInt . h . toInt) . (fromInt . g . toInt) -- == \ a -> (fromInt . h . toInt) ((fromInt . g . toInt) a) -- == \ a -> (fromInt . h . toInt) (fromInt (g (toInt a))) -- == \ a -> fromInt (h (toInt (fromInt (g (toInt a))))) -- == \ a -> fromInt (h (g (toInt a)))
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

The -fno-method-sharing flag was supposed to be a bit experimental, which is why it takes the cheap-and-cheerful route of being a static flag. (Only dynamic flags can go in OPTIONS_GHC.)
What it does is this. When you call an overloaded function f :: C a => a -> a, in a function
g = ...f...f...
you normally get something like this
fint :: Int -> Int
fint = f Int dCInt
g = ...fint...fint...
That is, 'fint' extracts the 'f' method from dCInt::C Int, and it's then used repeatedly.
With -fno-method-sharing you get
g = ...(f Int dCInt) ... (f Int dCInt)...
So the record selection is duplicated. It shouldn't make much difference, but of course it *does* when rules are involved, because there are no rules for fint (it's a fresh, local function).
Simon
From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users-bounces@haskell.org] On Behalf Of Conal Elliott
Sent: 07 June 2008 17:26
To: glasgow-haskell-users@haskell.org
Subject: Re: desperately seeking RULES help
Is it by intention that -fno-method-sharing works only from the command line, not in an OPTIONS_GHC pragma?
On Sat, Jun 7, 2008 at 9:23 AM, Conal Elliott
I'm trying to do some fusion in ghc, and I'd greatly appreciate help with the code below (which is simplified from fusion on linear maps). I've tried every variation I can think of, and always something prevents the fusion.
Help, please! Thanks, - Conal
{-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl -ddump-simpl-stats #-} -- {-# OPTIONS_GHC -ddump-simpl-iterations #-}
module F where
-- | Domain of a linear map. class AsInt a where toInt :: a -> Int fromInt :: Int -> a
{-# RULES "toInt/fromInt" forall m. toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f = fromInt . f . toInt
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
-- The desired result: -- -- test h g -- == onInt h . onInt g -- == (fromInt . h . toInt) . (fromInt . g . toInt) -- == \ a -> (fromInt . h . toInt) ((fromInt . g . toInt) a) -- == \ a -> (fromInt . h . toInt) (fromInt (g (toInt a))) -- == \ a -> fromInt (h (toInt (fromInt (g (toInt a))))) -- == \ a -> fromInt (h (g (toInt a)))
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.orgmailto:Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Simon Peyton-Jones wrote:
The -fno-method-sharing flag was supposed to be a bit experimental, which is why it takes the cheap-and-cheerful route of being a static flag. (Only dynamic flags can go in OPTIONS_GHC.)
It's dynamic in the HEAD, see
Mon May 19 19:59:56 PDT 2008 Roman Leshchinskiy

How does method sharing interact with the ability of the rules engine to
"look through" lets? Wouldn't an f rule kick in when fint is seen, by
looking through the fint binding?
I've been wondering: will pattern matching look through a let even when the
let-bound variable is used more than once? I chose "yes" in Pan, though
somewhat nervously, since all but one of the uses are free anyway.
Cheers, - Conal
On Mon, Jun 9, 2008 at 2:38 AM, Simon Peyton-Jones
The -fno-method-sharing flag was supposed to be a bit experimental, which is why it takes the cheap-and-cheerful route of being a static flag. (Only dynamic flags can go in OPTIONS_GHC.)
What it does is this. When you call an overloaded function f :: C a => a -> a, in a function
g = ...f...f...
you normally get something like this
fint :: Int -> Int
fint = f Int dCInt
g = ...fint...fint...
That is, 'fint' extracts the 'f' method from dCInt::C Int, and it's then used repeatedly.
With -fno-method-sharing you get
g = ...(f Int dCInt) ... (f Int dCInt)...
So the record selection is duplicated. It shouldn't make much difference, but of course it **does** when rules are involved, because there are no rules for fint (it's a fresh, local function).
Simon
*From:* glasgow-haskell-users-bounces@haskell.org [mailto: glasgow-haskell-users-bounces@haskell.org] *On Behalf Of *Conal Elliott *Sent:* 07 June 2008 17:26 *To:* glasgow-haskell-users@haskell.org *Subject:* Re: desperately seeking RULES help
Is it by intention that -fno-method-sharing works only from the command line, not in an OPTIONS_GHC pragma?
On Sat, Jun 7, 2008 at 9:23 AM, Conal Elliott
wrote: Thanks a million, Lennart! -fno-method-sharing was the missing piece. - Conal
On Sat, Jun 7, 2008 at 5:07 AM, Lennart Augustsson
wrote: Here's something that actually works. You need to pass -fno-method-sharing on the command line. Instead of using rules on methods it uses rules on global functions, and these global functions don't get inlined until late (after the rule has fired).
-- Lennart
module F where
-- | Domain of a linear map. class AsInt a where toInt' :: a -> Int fromInt' :: Int -> a
{-# INLINE[1] toInt #-} toInt :: (AsInt a) => a -> Int toInt = toInt'
{-# INLINE[1] fromInt #-} fromInt :: (AsInt a) => Int -> a fromInt = fromInt'
{-# RULES "toInt/fromInt" forall m . toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a)
onInt f x = fromInt (f (toInt x))
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
2008/6/7 Conal Elliott
: I'm trying to do some fusion in ghc, and I'd greatly appreciate help with the code below (which is simplified from fusion on linear maps). I've tried every variation I can think of, and always something prevents the fusion.
Help, please! Thanks, - Conal
{-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl -ddump-simpl-stats #-} -- {-# OPTIONS_GHC -ddump-simpl-iterations #-}
module F where
-- | Domain of a linear map. class AsInt a where toInt :: a -> Int fromInt :: Int -> a
{-# RULES "toInt/fromInt" forall m. toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f = fromInt . f . toInt
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
-- The desired result: -- -- test h g -- == onInt h . onInt g -- == (fromInt . h . toInt) . (fromInt . g . toInt) -- == \ a -> (fromInt . h . toInt) ((fromInt . g . toInt) a) -- == \ a -> (fromInt . h . toInt) (fromInt (g (toInt a))) -- == \ a -> fromInt (h (toInt (fromInt (g (toInt a))))) -- == \ a -> fromInt (h (g (toInt a)))
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

GHC only "looks through" *value* bindings, because (as you note) you can get arbitrary loss of sharing otherwise. And fint isn't a value binding, since it has work to do. (Not much, I grant you -- maybe we could take account of that.)
Simon
From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users-bounces@haskell.org] On Behalf Of Conal Elliott
Sent: 09 June 2008 16:28
To: Simon Peyton-Jones
Cc: glasgow-haskell-users@haskell.org
Subject: Re: desperately seeking RULES help
How does method sharing interact with the ability of the rules engine to "look through" lets? Wouldn't an f rule kick in when fint is seen, by looking through the fint binding?
I've been wondering: will pattern matching look through a let even when the let-bound variable is used more than once? I chose "yes" in Pan, though somewhat nervously, since all but one of the uses are free anyway.
Cheers, - Conal
On Mon, Jun 9, 2008 at 2:38 AM, Simon Peyton-Jones
I'm trying to do some fusion in ghc, and I'd greatly appreciate help with the code below (which is simplified from fusion on linear maps). I've tried every variation I can think of, and always something prevents the fusion.
Help, please! Thanks, - Conal
{-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl -ddump-simpl-stats #-} -- {-# OPTIONS_GHC -ddump-simpl-iterations #-}
module F where
-- | Domain of a linear map. class AsInt a where toInt :: a -> Int fromInt :: Int -> a
{-# RULES "toInt/fromInt" forall m. toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f = fromInt . f . toInt
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
-- The desired result: -- -- test h g -- == onInt h . onInt g -- == (fromInt . h . toInt) . (fromInt . g . toInt) -- == \ a -> (fromInt . h . toInt) ((fromInt . g . toInt) a) -- == \ a -> (fromInt . h . toInt) (fromInt (g (toInt a))) -- == \ a -> fromInt (h (toInt (fromInt (g (toInt a))))) -- == \ a -> fromInt (h (g (toInt a)))
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.orgmailto:Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

could you please send the complete options/commandline and the expect final form of 'test'? i did play with Conal's example as well, but couldn't find a combination to make it work. perhaps i'm looking at the wrong output, but it seems i either get non-inlined 'onInt's in various forms or multiple matches out of the same dictionary, but with generic method names rather than the original 'fromInt'/'toInt'. claus
Thanks a million, Lennart! -fno-method-sharing was the missing piece. - Conal
On Sat, Jun 7, 2008 at 5:07 AM, Lennart Augustsson
wrote: Here's something that actually works. You need to pass -fno-method-sharing on the command line. Instead of using rules on methods it uses rules on global functions, and these global functions don't get inlined until late (after the rule has fired).
-- Lennart
module F where
-- | Domain of a linear map. class AsInt a where toInt' :: a -> Int fromInt' :: Int -> a
{-# INLINE[1] toInt #-} toInt :: (AsInt a) => a -> Int toInt = toInt'
{-# INLINE[1] fromInt #-} fromInt :: (AsInt a) => Int -> a fromInt = fromInt'
{-# RULES "toInt/fromInt" forall m . toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f x = fromInt (f (toInt x))
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
I'm trying to do some fusion in ghc, and I'd greatly appreciate help with the code below (which is simplified from fusion on linear maps). I've
2008/6/7 Conal Elliott
: tried every variation I can think of, and always something prevents the fusion.
Help, please! Thanks, - Conal
{-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl -ddump-simpl-stats #-} -- {-# OPTIONS_GHC -ddump-simpl-iterations #-}
module F where
-- | Domain of a linear map. class AsInt a where toInt :: a -> Int fromInt :: Int -> a
{-# RULES "toInt/fromInt" forall m. toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f = fromInt . f . toInt
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
-- The desired result: -- -- test h g -- == onInt h . onInt g -- == (fromInt . h . toInt) . (fromInt . g . toInt) -- == \ a -> (fromInt . h . toInt) ((fromInt . g . toInt) a) -- == \ a -> (fromInt . h . toInt) (fromInt (g (toInt a))) -- == \ a -> fromInt (h (toInt (fromInt (g (toInt a))))) -- == \ a -> fromInt (h (g (toInt a)))
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
--------------------------------------------------------------------------------
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Here it is:
{-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl #-}
-- compile with: ghc -fno-method-sharing -c F.hs
module F(test) where
-- | Domain of a linear map.
class AsInt a where
toInt' :: a -> Int
fromInt' :: Int -> a
{-# INLINE[1] toInt #-}
toInt :: (AsInt a) => a -> Int
toInt = toInt'
{-# INLINE[1] fromInt #-}
fromInt :: (AsInt a) => Int -> a
fromInt = fromInt'
{-# RULES
"toInt/fromInt" forall m . toInt (fromInt m) = m
#-}
{-# INLINE onInt #-}
onInt :: AsInt a => (Int -> Int) -> (a -> a)
onInt f x = fromInt (f (toInt x))
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a)
test h g = onInt h . onInt g
{-
Glasgow Haskell Compiler, Version 6.8.2.20080211, for Haskell 98,
stage 2 booted by GHC version 6.6.1
F.test =
\ (@ a_a6C)
($dAsInt_a6M :: F.AsInt a_a6C)
(h_a67 :: GHC.Base.Int -> GHC.Base.Int)
(g_a68 :: GHC.Base.Int -> GHC.Base.Int)
(eta_s77 :: a_a6C) ->
case $dAsInt_a6M of tpl_B1 { F.:DAsInt tpl1_B2 tpl2_B3 ->
tpl2_B3 (h_a67 (g_a68 (tpl1_B2 eta_s77)))
}
-}
On Mon, Jun 9, 2008 at 11:00 AM, Claus Reinke
could you please send the complete options/commandline and the expect final form of 'test'? i did play with Conal's example as well, but couldn't find a combination to make it work.
perhaps i'm looking at the wrong output, but it seems i either get non-inlined 'onInt's in various forms or multiple matches out of the same dictionary, but with generic method names rather than the original 'fromInt'/'toInt'.
claus
Thanks a million, Lennart! -fno-method-sharing was the missing piece. - Conal
On Sat, Jun 7, 2008 at 5:07 AM, Lennart Augustsson
wrote: Here's something that actually works. You need to pass -fno-method-sharing on the command line. Instead of using rules on methods it uses rules on global functions, and these global functions don't get inlined until late (after the rule has fired).
-- Lennart
module F where
-- | Domain of a linear map. class AsInt a where toInt' :: a -> Int fromInt' :: Int -> a
{-# INLINE[1] toInt #-} toInt :: (AsInt a) => a -> Int toInt = toInt'
{-# INLINE[1] fromInt #-} fromInt :: (AsInt a) => Int -> a fromInt = fromInt'
{-# RULES "toInt/fromInt" forall m . toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f x = fromInt (f (toInt x))
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
I'm trying to do some fusion in ghc, and I'd greatly appreciate help with the code below (which is simplified from fusion on linear maps). I've
2008/6/7 Conal Elliott
: tried every variation I can think of, and always something prevents the fusion.
Help, please! Thanks, - Conal
{-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl -ddump-simpl-stats #-} -- {-# OPTIONS_GHC -ddump-simpl-iterations #-}
module F where
-- | Domain of a linear map. class AsInt a where toInt :: a -> Int fromInt :: Int -> a
{-# RULES "toInt/fromInt" forall m. toInt (fromInt m) = m #-}
{-# INLINE onInt #-} onInt :: AsInt a => (Int -> Int) -> (a -> a) onInt f = fromInt . f . toInt
test :: AsInt a => (Int -> Int) -> (Int -> Int) -> (a -> a) test h g = onInt h . onInt g
-- The desired result: -- -- test h g -- == onInt h . onInt g -- == (fromInt . h . toInt) . (fromInt . g . toInt) -- == \ a -> (fromInt . h . toInt) ((fromInt . g . toInt) a) -- == \ a -> (fromInt . h . toInt) (fromInt (g (toInt a))) -- == \ a -> fromInt (h (toInt (fromInt (g (toInt a))))) -- == \ a -> fromInt (h (g (toInt a)))
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
--------------------------------------------------------------------------------
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Here it is:
{-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl #-} -- compile with: ghc -fno-method-sharing -c F.hs
thanks! it seems i misread the users guide (or is this a bug?). i used -frewrite-rules ("Switch on all rewrite rules"), which does not(!) work, instead of -fglasgow-exts, which does work (ghc-6.9.20080514, booted from 6.6.1). i learned something new,-) claus

claus.reinke:
Here it is:
{-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl #-} -- compile with: ghc -fno-method-sharing -c F.hs
thanks! it seems i misread the users guide (or is this a bug?). i used -frewrite-rules ("Switch on all rewrite rules"), which does not(!) work, instead of -fglasgow-exts, which does work (ghc-6.9.20080514, booted from 6.6.1).
i learned something new,-)
Right. There are two things here: 1) -frewrite-rules enables rules to fire. 2) -fglasgow-exts enables parsing of RULES pragmas, and their interpretation. You need both if you wish to both write your own rules, and have them fire. -- Don

Right. There are two things here:
1) -frewrite-rules
enables rules to fire.
2) -fglasgow-exts
enables parsing of RULES pragmas, and their interpretation.
You need both if you wish to both write your own rules, and have them fire.
nope!-) -fglasgow-exts is sufficient for the RULE to be parsed and applied in Lennart's code, -frewrite-rules doesn't seem to serve any noticable purpose. but i see now this is under re-evaluation, aptly titled: "Confusing flags for rewrite rules" http://hackage.haskell.org/trac/ghc/ticket/2213 (see simonpj's comment at the end) claus $ head -1 Rules.hs {-# OPTIONS_GHC -O2 -Wall -fglasgow-exts #-} $ /cygdrive/c/fptools/ghc/ghc-6.9.20080514/bin/ghc -fno-method-sharing -ddump-simpl-stats -c Rules. hs ==================== FloatOut stats: ==================== 0 Lets floated to top level; 0 Lets floated elsewhere; from 3 Lambda groups ==================== FloatOut stats: ==================== 0 Lets floated to top level; 0 Lets floated elsewhere; from 3 Lambda groups ==================== Grand total simplifier statistics ==================== Total ticks: 60 18 PreInlineUnconditionally 11 PostInlineUnconditionally 5 UnfoldingDone 1 RuleFired 1 toInt/fromInt 2 EtaReduction 22 BetaReduction 1 KnownBranch 11 SimplifierDone

claus.reinke:
Right. There are two things here:
1) -frewrite-rules
enables rules to fire.
2) -fglasgow-exts
enables parsing of RULES pragmas, and their interpretation.
You need both if you wish to both write your own rules, and have them fire.
nope!-) -fglasgow-exts is sufficient for the RULE to be parsed and applied in Lennart's code, -frewrite-rules doesn't seem to serve any noticable purpose.
Well, if -O is on, -frewrite-rules is already on by default. Try -fno-rewrite-rules with -O to turn them off specifically, or in ghci, -frewrite-rules can be used to help them fire even on bytecode.
but i see now this is under re-evaluation, aptly titled:
"Confusing flags for rewrite rules" http://hackage.haskell.org/trac/ghc/ticket/2213 (see simonpj's comment at the end)
Right. -- Don

nope!-) -fglasgow-exts is sufficient for the RULE to be parsed and applied in Lennart's code, -frewrite-rules doesn't seem to serve any noticable purpose.
Well, if -O is on, -frewrite-rules is already on by default. Try -fno-rewrite-rules with -O to turn them off specifically,
yep, see my note in the ticket about this confusion.
or in ghci, -frewrite-rules can be used to help them fire even on bytecode.
when i tried this earlier, the hpc ticks seemed to get in the way? claus

claus.reinke:
nope!-) -fglasgow-exts is sufficient for the RULE to be parsed and applied in Lennart's code, -frewrite-rules doesn't seem to serve any noticable purpose.
Well, if -O is on, -frewrite-rules is already on by default. Try -fno-rewrite-rules with -O to turn them off specifically,
yep, see my note in the ticket about this confusion.
or in ghci, -frewrite-rules can be used to help them fire even on bytecode.
when i tried this earlier, the hpc ticks seemed to get in the way?
HPC will break rules, yes. See: "-fhpc inteferes/prevents rewrite rules from firing" http://hackage.haskell.org/trac/ghc/ticket/2224 -- Don
participants (7)
-
Claus Reinke
-
Conal Elliott
-
Don Stewart
-
Johan Tibell
-
Lennart Augustsson
-
Roman Leshchinskiy
-
Simon Peyton-Jones