{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE BangPatterns #-}
module Data.Equality.Graph.ReprUnionFind
( ReprUnionFind
, emptyUF
, makeNewSet
, unionSets
, findRepr
) where
import Data.Equality.Graph.Classes.Id
#if __GLASGOW_HASKELL__ >= 902
import qualified Data.Equality.Utils.IntToIntMap as IIM
import GHC.Exts ((+#), Int(..), Int#)
type RUFSize = Int#
data ReprUnionFind = RUF IIM.IntToIntMap
RUFSize
#else
import qualified Data.IntMap.Internal as IIM (IntMap(..))
import qualified Data.IntMap.Strict as IIM
data ReprUnionFind = RUF (IIM.IntMap Int)
{-# UNPACK #-} !Int
#endif
instance Show ReprUnionFind where
show :: ReprUnionFind -> String
show (RUF IntToIntMap
_ RUFSize
_) = String
"Warning: Incomplete show: ReprUnionFind"
newtype Repr
= Represented { Repr -> Int
unRepr :: ClassId }
deriving Int -> Repr -> ShowS
[Repr] -> ShowS
Repr -> String
(Int -> Repr -> ShowS)
-> (Repr -> String) -> ([Repr] -> ShowS) -> Show Repr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Repr -> ShowS
showsPrec :: Int -> Repr -> ShowS
$cshow :: Repr -> String
show :: Repr -> String
$cshowList :: [Repr] -> ShowS
showList :: [Repr] -> ShowS
Show
emptyUF :: ReprUnionFind
emptyUF :: ReprUnionFind
emptyUF = IntToIntMap -> RUFSize -> ReprUnionFind
RUF IntToIntMap
IIM.Nil
#if __GLASGOW_HASKELL__ >= 902
RUFSize
1#
#else
1
#endif
makeNewSet :: ReprUnionFind
-> (ClassId, ReprUnionFind)
#if __GLASGOW_HASKELL__ >= 902
makeNewSet :: ReprUnionFind -> (Int, ReprUnionFind)
makeNewSet (RUF IntToIntMap
im RUFSize
si) = ((RUFSize -> Int
I# RUFSize
si), IntToIntMap -> RUFSize -> ReprUnionFind
RUF (RUFSize -> RUFSize -> IntToIntMap -> IntToIntMap
IIM.insert RUFSize
si RUFSize
0# IntToIntMap
im) ((RUFSize
si RUFSize -> RUFSize -> RUFSize
+# RUFSize
1#)))
#else
makeNewSet (RUF im si) = (si, RUF (IIM.insert si 0 im) (si + 1))
#endif
{-# SCC makeNewSet #-}
unionSets :: ClassId
-> ClassId
-> ReprUnionFind
-> (ClassId, ReprUnionFind)
#if __GLASGOW_HASKELL__ >= 902
unionSets :: Int -> Int -> ReprUnionFind -> (Int, ReprUnionFind)
unionSets a :: Int
a@(I# RUFSize
a#) (I# RUFSize
b#) (RUF IntToIntMap
im RUFSize
si) = (Int
a, IntToIntMap -> RUFSize -> ReprUnionFind
RUF (RUFSize -> RUFSize -> IntToIntMap -> IntToIntMap
IIM.insert RUFSize
b# RUFSize
a# IntToIntMap
im) RUFSize
si)
#else
unionSets a b (RUF im si) = (a, RUF (IIM.insert b a im) si)
#endif
{-# SCC unionSets #-}
findRepr :: ClassId -> ReprUnionFind
-> ClassId
#if __GLASGOW_HASKELL__ >= 902
findRepr :: Int -> ReprUnionFind -> Int
findRepr v :: Int
v@(I# RUFSize
v#) (RUF IntToIntMap
m RUFSize
s) =
case {-# SCC "findRepr_TAKE" #-} IntToIntMap
m IntToIntMap -> RUFSize -> RUFSize
IIM.! RUFSize
v# of
RUFSize
0# -> Int
v
RUFSize
x -> Int -> ReprUnionFind -> Int
findRepr (RUFSize -> Int
I# RUFSize
x) (IntToIntMap -> RUFSize -> ReprUnionFind
RUF IntToIntMap
m RUFSize
s)
#else
findRepr v (RUF m s) =
case {-# SCC "findRepr_TAKE" #-} m IIM.! v of
0 -> v
x -> findRepr x (RUF m s)
#endif
{-# SCC findRepr #-}