summaryrefslogtreecommitdiff
path: root/testsuite/tests/concurrent/prog003/ImmList.hs
blob: 70d81633d2605fa3c4ac301b984ea3adf8a0c189 (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
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
{-# LANGUAGE CPP,PatternGuards #-}
module ImmList where

import Control.Concurrent
import Data.IORef
import qualified Data.Sequence as S
import Data.Sequence (Seq, (|>), (<|), (><), ViewL(..))
import Data.Maybe
import Data.Foldable

#if 0
newtype ListHandle a = ListHandle (IORef (Seq a))

newList :: IO (ListHandle a)
newList = do
  r <- newIORef S.empty
  return (ListHandle r)

addToTail :: Eq a => ListHandle a -> a -> IO ()
addToTail (ListHandle r) x = 
  atomicModifyIORef r $ \s -> (s |> x, ())

find :: Eq a => ListHandle a -> a -> IO Bool
find (ListHandle r) x = do
  s <- readIORef r
  return (isJust (S.elemIndexL x s))

delete :: Eq a => ListHandle a -> a -> IO Bool
delete (ListHandle r) x = atomicModifyIORef r $ \s ->
  case S.breakl (== x) s of
    (xs, ys) | c :< zs <- S.viewl ys, c == x -> (xs >< zs, True)
             | otherwise                     -> (xs >< ys, False)

printList :: Show a => ListHandle a -> IO ()
printList (ListHandle r) = do
  s <- readIORef r
  print (toList s)

cntList :: Show a => ListHandle a -> IO Int
cntList (ListHandle r) = readIORef r >>= return . S.length
#else
newtype ListHandle a = ListHandle (IORef [a])

newList :: IO (ListHandle a)
newList = do
  r <- newIORef []
  return (ListHandle r)

addToTail :: Eq a => ListHandle a -> a -> IO ()
addToTail (ListHandle r) x = 
  atomicModifyIORef r $ \s -> (s ++ [x], ())

find :: Eq a => ListHandle a -> a -> IO Bool
find (ListHandle r) x = do
  s <- readIORef r
  return (x `Prelude.elem` s)

delete :: Eq a => ListHandle a -> a -> IO Bool
delete (ListHandle r) x = atomicModifyIORef r $ \s ->
  case break (== x) s of
    (xs, ys) | (c:zs) <- ys, c == x -> (xs ++ zs, True)
             | otherwise            -> (xs ++ ys, False)

printList :: Show a => ListHandle a -> IO ()
printList (ListHandle r) = do
  s <- readIORef r
  print s

cntList :: Show a => ListHandle a -> IO Int
cntList (ListHandle r) = readIORef r >>= return . length
#endif