Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

How can I get my rule to fire?

Tags:

haskell

ghc

I'm working on list fusion rules for fromListN in Data.Primitive.Array, and I'm a bit stuck. The function looks like this:

fromListNArray :: Int -> [a] -> Array a
fromListNArray !n l =
  createArray n fromListN_too_short $ \mi ->
    let go i (x:xs)
          | i < n = writeArray mi i x >> go (i+1) xs
          | otherwise = fromListN_too_long
        go i [] = unless (i == n) fromListN_too_short
     in go 0 l
{-# NOINLINE fromListNArray #-}

fromListN_too_short and fromListN_too_long are just error calls.

My rewrite rules are

{-# RULES
"fromListNArray/foldr" [~1] forall n xs.
  fromListNArray n xs = createArray n fromListN_too_short $ \mary ->
    foldr (fillArray_go n mary) (fillArray_stop n) xs 0

"fillArrayN/list" [1] forall n mary xs i.
  foldr (fillArray_go n mary) (fillArray_stop n) xs i = fillArrayN n mary xs i
 #-}

where the helpers are defined

fillArrayN :: Int -> MutableArray s a -> [a] -> Int -> ST s ()
fillArrayN !n !mary xs0 !i0 = go i0 xs0
  where
    go i (x:xs)
      | i < n = writeArray mary i x >> go (i+1) xs
      | otherwise = fromListN_too_long
    go i [] = unless (i == n) fromListN_too_short
{-# NOINLINE fillArrayN #-}

fillArray_go :: Int
             -> MutableArray s a
             -> a
             -> (Int -> ST s ())
             -> Int
             -> ST s ()
fillArray_go !n !mary = \x r i ->
  if i < n
    then writeArray mary i x >> r (i + 1)
    else fromListN_too_long
{-# INLINE CONLIKE [0] fillArray_go #-}

fillArray_stop :: Int -> Int -> ST s ()
fillArray_stop !n = \i -> unless (i == n) fromListN_too_short
{-# INLINE [0] fillArray_stop #-}

The first rewrite rule seems to do okay. The second, write-back, rule is the problem. I can never seem to get it to fire. Can anyone offer a suggestion?


Note: I know I could just fuse directly with build and augment to avoid having to write back, but it's ... not a pretty sight.

like image 230
dfeuer Avatar asked Mar 22 '18 05:03

dfeuer


1 Answers

The main problem appears to be a mistake on my part. In

"fillArrayN/list" [1] forall n mary xs i.
  foldr (fillArray_go n mary) (fillArray_stop n) xs i = fillArrayN n mary xs i

the foldr is Data.Foldable.foldr, which is a class method and therefore doesn't work on the LHS of a rule. Fixing this problem makes the write-back rule work in simple cases.

Unfortunately, when fromListNArray fuses with augment (which typically happens when it's applied to appended lists), the rule fails to fire for another reason. GHC creates a function for fillArray_go n mary, and doesn't inline it. I still don't understand why this happens.

like image 98
dfeuer Avatar answered Nov 18 '22 09:11

dfeuer