{-# OPTIONS_GHC -O2 -fno-full-laziness -fno-prof-auto #-}

module ParkBench.BenchmarkInternal
  ( whnf,
    whnfIO,
  )
where

import Control.Exception (evaluate)
import Data.Word (Word64)
import Prelude

whnf :: (a -> b) -> a -> Word64 -> IO ()
whnf :: (a -> b) -> a -> Word64 -> IO ()
whnf a -> b
f a
x =
  Word64 -> IO ()
go
  where
    go :: Word64 -> IO ()
    go :: Word64 -> IO ()
go = \case
      Word64
0 -> () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
      Word64
n -> do
        -- `f x` won't be let-floated out with -fno-full-laziness
        -- use evaluate rather than seq so both branches depend on the state token
        --   https://gitlab.haskell.org/ghc/ghc/-/issues/21948
        b
_ <- b -> IO b
forall a. a -> IO a
evaluate (a -> b
f a
x)
        Word64 -> IO ()
go (Word64
n Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
- Word64
1)
-- prevent `whnf f x` from inlining to prevent `f x` from getting let-floated
{-# NOINLINE whnf #-}

whnfIO :: IO a -> Word64 -> IO ()
whnfIO :: IO a -> Word64 -> IO ()
whnfIO IO a
io =
  Word64 -> IO ()
go
  where
    go :: Word64 -> IO ()
    go :: Word64 -> IO ()
go = \case
      Word64
0 -> () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
      Word64
n -> do
        a
result <- IO a
io
        a
result a -> IO () -> IO ()
`seq` Word64 -> IO ()
go (Word64
n Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
- Word64
1)
{-# NOINLINE whnfIO #-}