11module Development.IDE.Session.OrderedSet where
22
3- import Control.Concurrent.STM (STM , TQueue , flushTQueue ,
4- newTQueueIO )
3+ import Control.Concurrent.STM (STM , TQueue , newTQueueIO )
54import Control.Concurrent.STM.TQueue (readTQueue , writeTQueue )
65import Control.Monad (when )
76import Data.Hashable (Hashable )
@@ -12,13 +11,16 @@ import qualified StmContainers.Set as S
1211import StmContainers.Set (Set )
1312
1413
15- type OrderedSet a = (TQueue a , Set a )
14+ data OrderedSet a = OrderedSet
15+ { insertionOrder :: TQueue a
16+ , elements :: Set a
17+ }
1618
1719-- | Insert an element into the ordered set.
1820-- If the element is not already present, it is added to both the queue and set.
1921-- If the element already exists, ignore it
2022insert :: Hashable a => a -> OrderedSet a -> STM ()
21- insert a (que, s) = do
23+ insert a (OrderedSet que s) = do
2224 (_, inserted) <- S. focus (Focus. testingIfInserts $ Focus. insert () ) a s
2325 -- if already in the set
2426 when inserted $ writeTQueue que a
@@ -27,26 +29,26 @@ newIO :: Hashable a => IO (OrderedSet a)
2729newIO = do
2830 que <- newTQueueIO
2931 s <- S. newIO
30- return (que, s)
32+ return (OrderedSet que s)
3133
3234-- | Read the first element from the queue.
3335-- If an element is not in the set, it means it has been deleted,
3436-- so we retry until we find a valid element that exists in the set.
3537readQueue :: Hashable a => OrderedSet a -> STM a
36- readQueue rs@ (que, s) = do
38+ readQueue rs@ (OrderedSet que s) = do
3739 f <- readTQueue que
3840 b <- S. lookup f s
3941 -- retry if no files are left in the queue
4042 if b then return f else readQueue rs
4143
4244lookup :: Hashable a => a -> OrderedSet a -> STM Bool
43- lookup a (_, s) = S. lookup a s
45+ lookup a (OrderedSet _ s) = S. lookup a s
4446
4547-- | Delete an element from the set.
4648-- The queue is not modified directly; stale entries are filtered out lazily
4749-- during reading operations (see 'readQueue').
4850delete :: Hashable a => a -> OrderedSet a -> STM ()
49- delete a (_, s) = S. delete a s
51+ delete a (OrderedSet _ s) = S. delete a s
5052
5153toHashSet :: Hashable a => OrderedSet a -> STM (Data.HashSet. HashSet a )
52- toHashSet (_, s) = Data.HashSet. fromList <$> LT. toList (S. listT s)
54+ toHashSet (OrderedSet _ s) = Data.HashSet. fromList <$> LT. toList (S. listT s)
0 commit comments