desperately seeking RULES help

Lennart Augustsson lennart at augustsson.net
Sat Jun 7 08:07:29 EDT 2008


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


More information about the Glasgow-haskell-users mailing list