Hi,

The inlining behaviour of `any @[]` and `elem @[]` differs in a way that I am not sure is intentional, and it is affecting Clash (see https://github.com/clash-lang/clash-compiler/issues/1691). I would think that if it is a good idea to inline `any` then inlining `elem` would be just as good an idea, or vice versa.

However, `any` is defined polymorphically over `Foldable`, via `foldMap` using `foldr`, with all steps between (and `foldr @[]`!) marked as `INLINE`. The result is that if you use `any (x ==) [1, 5, 7]` you get the following beautiful Core:

```
topEntity
  = \ (x_agAF :: Int) ->
      case x_agAF of { GHC.Types.I# y_ahao ->
      case y_ahao of {
        __DEFAULT -> GHC.Types.False;
        1# -> GHC.Types.True;
        5# -> GHC.Types.True;
        7# -> GHC.Types.True
      }
      }
```

As the kids these days would say: *chef's kiss*.


`elem`, on the other hand, is a typeclass method of `Foldable`, with a default implementation in terms of `any`, but overridden for lists with the following implementation:

```
GHC.List.elem :: (Eq a) => a -> [a] -> Bool
GHC.List.elem _ []       = False
GHC.List.elem x (y:ys)   = x==y || GHC.List.elem x ys
{-# NOINLINE [1] elem #-}
{-# RULES
"elem/build"    forall x (g :: forall b . Eq a => (a -> b -> b) -> b -> b)
   . elem x (build g) = g (\ y r -> (x == y) || r) False
 #-}
```

This is marked as non-inlineable until phase 1 (so that `elem/build` has a chance of firing), but it seems that when build fusion doesn't apply (since `[1, 5, 7]` is, of course, not built via `build`), no inlining happens AT ALL, even in later phases, so we end up with this:

```
topEntity
  = \ (x_agAF :: Int) ->
      GHC.List.elem
        @ Int
        GHC.Classes.$fEqInt
        x_agAF
        (GHC.Types.:
           @ Int
           (GHC.Types.I# 1#)
           (GHC.Types.:
              @ Int
              (GHC.Types.I# 5#)
              (GHC.Types.: @ Int (GHC.Types.I# 7#) (GHC.Types.[] @ Int))))
```

So not only does it trip up Clash, it would also result in less efficient code in software when using "normal" GHC.

Is this all intentional? Wouldn't it make more sense to mark `GHC.List.elem` as `INLINE [1]` instead of `NOINLINE [1]`, so that any calls remaining after build fusion would be inlined?

Thanks,
        Gergo
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Reply via email to