Bogus OneShot info on recursive join point
Consider this (from this post)
module Main where
import System.IO.Unsafe
import Control.Monad
main :: IO ()
main = do
foo "test" 10
foo :: String -> Int -> IO ()
foo x n = go n
where
oops = unsafePerformIO (putStrLn "Once" >> pure (cycle x))
go 0 = return ()
go n = do
-- `oops` should be shared between loop iterations
let p = take n oops
let !_ = unsafePerformIO (putStrLn p >> pure ())
go (n-1)
You would expect it to evaluate oops
just once, displaying
Once
testtestte
testtestt
testtest
testtes
testte
testt
test
tes
te
t
But actually oops
gest inlined into go
, and we get this:
Once
testtestte
Once
testtestt
Once
testtest
Once
testtes
Once
testte
Once
testt
Once
test
Once
tes
Once
te
Once
t
Edited by sheaf