desperately seeking RULES help

Lennart Augustsson lennart at augustsson.net
Mon Jun 9 15:06:59 EDT 2008


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 <claus.reinke at talk21.com> wrote:
> 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
>> <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
>>> >
>>> >
>>>
>>
>
>
> --------------------------------------------------------------------------------
>
>
>> _______________________________________________
>> Glasgow-haskell-users mailing list
>> Glasgow-haskell-users at haskell.org
>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>>
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>


More information about the Glasgow-haskell-users mailing list