summaryrefslogtreecommitdiff
path: root/testsuite/tests/perf/should_run/T7257.hs
blob: 8907c3c918eac8b33b682e5a4a2d233157b54b07 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
{-# LANGUAGE BangPatterns #-}
module Main where

import qualified Data.ByteString as S
import Data.IORef
import Control.Monad

makeBs :: Int -> S.ByteString
makeBs n = S.replicate n (fromIntegral n)

doStuff :: IORef [S.ByteString] -> Int -> IO ()
doStuff ref n = do
    let !bs = makeBs n
    modifyIORef ref (bs:)
{-# NOINLINE doStuff #-}

undo :: IORef [S.ByteString] -> IO ()
undo ref = do
    h <- atomicModifyIORef ref (\(x:xs) -> (xs,x))
    S.length h `seq` return ()

main = do
    ref <- newIORef [S.empty]
    let fn n = do
        doStuff ref n
        when (rem 5 n /= 0 ) $ undo ref

    mapM_ fn (take 5000000 $ cycle [1..100])
    var <- readIORef ref
    print $ length var