summaryrefslogtreecommitdiff
path: root/compiler/utils
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/utils')
-rw-r--r--compiler/utils/UniqDFM.hs2
-rw-r--r--compiler/utils/UniqDSet.hs1
-rw-r--r--compiler/utils/Util.hs6
3 files changed, 8 insertions, 1 deletions
diff --git a/compiler/utils/UniqDFM.hs b/compiler/utils/UniqDFM.hs
index 38bf79df24..82a67f351b 100644
--- a/compiler/utils/UniqDFM.hs
+++ b/compiler/utils/UniqDFM.hs
@@ -145,9 +145,11 @@ emptyUDFM = UDFM M.empty 0
unitUDFM :: Uniquable key => key -> elt -> UniqDFM elt
unitUDFM k v = UDFM (M.singleton (getKey $ getUnique k) (TaggedVal v 0)) 1
+-- The new binding always goes to the right of existing ones
addToUDFM :: Uniquable key => UniqDFM elt -> key -> elt -> UniqDFM elt
addToUDFM m k v = addToUDFM_Directly m (getUnique k) v
+-- The new binding always goes to the right of existing ones
addToUDFM_Directly :: UniqDFM elt -> Unique -> elt -> UniqDFM elt
addToUDFM_Directly (UDFM m i) u v
= UDFM (M.insertWith tf (getKey u) (TaggedVal v i) m) (i + 1)
diff --git a/compiler/utils/UniqDSet.hs b/compiler/utils/UniqDSet.hs
index 0f81a5bc1a..aa53194331 100644
--- a/compiler/utils/UniqDSet.hs
+++ b/compiler/utils/UniqDSet.hs
@@ -49,6 +49,7 @@ unitUniqDSet x = unitUDFM x x
mkUniqDSet :: Uniquable a => [a] -> UniqDSet a
mkUniqDSet = foldl' addOneToUniqDSet emptyUniqDSet
+-- The new element always goes to the right of existing ones.
addOneToUniqDSet :: Uniquable a => UniqDSet a -> a -> UniqDSet a
addOneToUniqDSet set x = addToUDFM set x x
diff --git a/compiler/utils/Util.hs b/compiler/utils/Util.hs
index 9523c08ff2..c348f79888 100644
--- a/compiler/utils/Util.hs
+++ b/compiler/utils/Util.hs
@@ -4,6 +4,7 @@
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE TupleSections #-}
-- | Highly random utility functions
--
@@ -47,7 +48,7 @@ module Util (
-- * Tuples
fstOf3, sndOf3, thdOf3,
- firstM, first3M,
+ firstM, first3M, secondM,
fst3, snd3, third3,
uncurry3,
liftFst, liftSnd,
@@ -271,6 +272,9 @@ firstM f (x, y) = liftM (\x' -> (x', y)) (f x)
first3M :: Monad m => (a -> m d) -> (a, b, c) -> m (d, b, c)
first3M f (x, y, z) = liftM (\x' -> (x', y, z)) (f x)
+secondM :: Monad m => (b -> m c) -> (a, b) -> m (a, c)
+secondM f (x, y) = (x,) <$> f y
+
{-
************************************************************************
* *