desperately seeking RULES help

Conal Elliott conal at conal.net
Mon Jun 9 11:27:53 EDT 2008


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 <simonpj at microsoft.com>
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.)
>
>
>
> 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 at haskell.org [mailto:
> glasgow-haskell-users-bounces at haskell.org] *On Behalf Of *Conal Elliott
> *Sent:* 07 June 2008 17:26
> *To:* glasgow-haskell-users at 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 <conal at conal.net> wrote:
>
> Thanks a million, Lennart!  -fno-method-sharing was the missing piece.  -
> Conal
>
>
>
> On Sat, Jun 7, 2008 at 5:07 AM, Lennart Augustsson <lennart at augustsson.net>
> 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 <conal at conal.net>:
>
> > 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 at haskell.org
> > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> >
> >
>
>
>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20080609/a7a0aebf/attachment.htm


More information about the Glasgow-haskell-users mailing list