Skip to content

Commit 71d6575

Browse files
committed
refactor OrderedSet to use a record for better clarity and structure
1 parent dc34df6 commit 71d6575

File tree

2 files changed

+11
-10
lines changed

2 files changed

+11
-10
lines changed

ghcide/session-loader/Development/IDE/Session.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,6 @@ import Development.IDE.Types.HscEnvEq (HscEnvEq)
5656
import Development.IDE.Types.Location
5757
import Development.IDE.Types.Options
5858
import qualified HIE.Bios as HieBios
59-
import qualified HIE.Bios.Cradle.Utils as HieBios
6059
import HIE.Bios.Environment hiding (getCacheDir)
6160
import HIE.Bios.Types hiding (Log)
6261
import qualified HIE.Bios.Types as HieBios
Lines changed: 11 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
module Development.IDE.Session.OrderedSet where
22

3-
import Control.Concurrent.STM (STM, TQueue, flushTQueue,
4-
newTQueueIO)
3+
import Control.Concurrent.STM (STM, TQueue, newTQueueIO)
54
import Control.Concurrent.STM.TQueue (readTQueue, writeTQueue)
65
import Control.Monad (when)
76
import Data.Hashable (Hashable)
@@ -12,13 +11,16 @@ import qualified StmContainers.Set as S
1211
import 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
2022
insert :: 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)
2729
newIO = 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.
3537
readQueue :: 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

4244
lookup :: 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').
4850
delete :: Hashable a => a -> OrderedSet a -> STM ()
49-
delete a (_, s) = S.delete a s
51+
delete a (OrderedSet _ s) = S.delete a s
5052

5153
toHashSet :: 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

Comments
 (0)