summaryrefslogtreecommitdiff
path: root/ghc/tests/programs/jeff-bug/BoundedSet.hs
blob: 0583ba6f54d8b19a086568108fba12a590fbece5 (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
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
module BoundedSet
  ( new
  , readBound
  , readSize
  , read  
  , clear
  , insert
  , spaceAvail
  , rmSuch 
  , rmSuchN
  , BoundedSet
  , iterateSet
  ) where

import LazyST
import Prelude hiding (read)
import List


new        :: Int -> ST s (BoundedSet s a)
readBound  :: BoundedSet s a -> ST s Int
readSize   :: BoundedSet s a -> ST s Int
read       :: BoundedSet s a -> ST s [a]
clear      :: BoundedSet s a -> ST s [a]
insert     :: BoundedSet s a -> [a] -> ST s ()
spaceAvail :: BoundedSet s a -> ST s Int
rmSuch     :: BoundedSet s a -> (a -> Bool) -> ST s [a]
rmSuchN    :: BoundedSet s a -> Int -> (a -> Bool) -> ST s [a]
iterateSet :: BoundedSet s a -> (a -> a) -> ST s ()


-- Implementation ----------------------------------------------------
type BoundedSet s a = (STRef s [a],Int)


iterateSet s f =
   do { set <- read s
      ; write s (map f set)
      }

read (s,n) = readSTRef s

rmSuch s f
  = do { set <- read s
       ; let (yes,no) = partition f set
       ; write s no
       ; return yes
       }

rmSuchN s n f 
  = do { such <- rmSuch s f
       ; let (big,small) = splitAt n such
       ; insert s small
       ; return big
       }

write    :: BoundedSet s a -> [a] -> ST s ()
write (s,n) x = writeSTRef s x


readBound (s,n) = return n

new n 
  = do { set <- newSTRef []
       ; return (set,n)
       }

clear s =
  do { set <- read s
     ; write s []
     ; return set
     }

readSize s =
  do { set <- read s
     ; return ( length set)
     }
	
spaceAvail s
  = do { bnd <- readBound s
       ; sz  <- readSize s
       ; return (bnd - sz)
       }
      

insert s l
  = do { set <- read s
       ; n <- readBound s
       ; write s $ take n (set ++ l)
       }