Inlining removes join point?

Can function inlining remove join points? That seems to be the case on the test I made. I expected a bigger difference between test1 and test2, but test1 is only 15 microseconds faster than test2.

Test.hs

module Test where

find1 :: (Int -> Bool) -> [Int] -> Maybe Int
find1 p = go
  where
  go :: [Int] -> Maybe Int
  go [] = Nothing
  go (x:xs) = if p x then Just x else go xs

find2 :: (Int -> Bool) -> [Int] -> Maybe Int
find2 _ [] = Nothing
find2 p (x:xs) = if p x then Just x else find2 p xs

even' :: Int -> Bool
even' = even
{-# NOINLINE even' #-}

test1, test2 :: [Int] -> Maybe Int
test1 = find1 even'
test2 = find2 even'

Main.hs

module Main where

import Test

import Control.DeepSeq
import Criterion.Main

list1, list2 :: [Int]
list1 = [1,3..19999]
list2 = [1,3..19999] ++ [2]

main :: IO ()
main = list1 `deepseq` list2 `deepseq` defaultMain
  [ bgroup "test1"
    [ bench "list1" $ whnf test1 list1 -- 60.9 μs
    , bench "list2" $ whnf test1 list2 -- 60.9 μs
    ]
  , bgroup "test2"
    [ bench "list1" $ whnf test2 list1 -- 75.7 μs
    , bench "list2" $ whnf test2 list2 -- 74.8 μs
    ]
  ]

Looking at the simplifier output, find1 compiles to a join point and find2 doesn’t as expected.

-- RHS size: {terms: 20, types: 18, coercions: 0, joins: 1/1}
find1 :: (Int -> Bool) -> [Int] -> Maybe Int
find1
  = \ (p_aum :: Int -> Bool) (eta_B0 :: [Int]) ->
      joinrec {
        go_s1t0 :: [Int] -> Maybe Int
        go_s1t0 (ds_d1rU :: [Int])
          = case ds_d1rU of {
              [] -> Nothing;
              : x_auo xs_aup ->
                case p_aum x_auo of {
                  False -> jump go_s1t0 xs_aup;
                  True -> Just x_auo
                }
            }; } in
      jump go_s1t0 eta_B0

Rec {
-- RHS size: {terms: 17, types: 12, coercions: 0, joins: 0/0}
find2 :: (Int -> Bool) -> [Int] -> Maybe Int
find2
  = \ (ds_d1rN :: Int -> Bool) (ds1_d1rO :: [Int]) ->
      case ds1_d1rO of {
        [] -> Nothing;
        : x_aur xs_aus ->
          case ds_d1rN x_aur of {
            False -> find2 ds_d1rN xs_aus;
            True -> Just x_aur
          }
      }
end Rec }

Also as expected, find1 gets inlined and find2 doesn’t. But the join point is gone!

Rec {
-- RHS size: {terms: 15, types: 10, coercions: 0, joins: 0/0}
test1_go :: [Int] -> Maybe Int
test1_go
  = \ (ds_d1rU :: [Int]) ->
      case ds_d1rU of {
        [] -> Nothing;
        : x_auo xs_aup ->
          case even' x_auo of {
            False -> test1_go xs_aup;
            True -> Just x_auo
          }
      }
end Rec }

-- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0}
test1 :: [Int] -> Maybe Int
test1 = \ (eta_B0 :: [Int]) -> test1_go eta_B0

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
test2 :: [Int] -> Maybe Int
test2 = find2 even'

I looked at the STG output and the only join point (let-no-escape) was, again, in find1. I tried investigating the C–, but I can’t comprehend it well enough to justify the effort.

Is my intuition that the difference between test1 and test2 be bigger if test1 didn’t lose its join point wrong? Does the Rec syntax imply a join point on tail recursive calls? If the join point is gone, how can I write find even as a tight loop?

Compiler flags used:

$ ghc --version # `ghc-static` Arch Linux package (which is a bit outdated).
The Glorious Glasgow Haskell Compilation System, version 9.0.2
$ ghc -O2 -ddump-to-file -ddump-simpl -ddump-stg-final -ddump-cmm -dsuppress-all -dno-suppress-type-signatures -c Test.hs
$ ghc -O2 -dynamic Main.hs
1 Like

It sounds to me like you are confusing join points and tail recursion. It is true that every recursive join point is tail recursive and hence fast. But GHC always does (a kind of) tail recursion elimination for every function, so even normal tail recursive functions can be compiled to tight loops and avoid blowing up the stack. It is not necessary to add join points to the mix.

1 Like

I see. I thought GHC will compile a join point to something like a jump but only may compile tail recursion to a jump. My understanding was wrong. Thanks for the reply!