On Mon, 16 Aug 1999, Keith Wansbrough wrote:
> Hi all... has anyone implemented the Union-Find algorithm in Haskell?
> I've looked at the various libraries listed at haskell.org and found
> nothing, but don't want to re-invent the wheel if someone else has done
> it already.
>
Hmm, yes I have now isolated the disjoint set ADT (not much left).
If you want the more fancy ADT with extendable sets and combined
representation of a relation and the 'antirelation' you have to ask for it
and wait. I blush when I show my uncleaned personal hacks in public ;)
Here it is:
--------------------------------------------------------
module DisjointSet where
import ST
type DisjSet s x = STArray s Int (Maybe Int,x)
find :: Int -> DisjSet s x -> ST s Int
find n s = do (m,x) <- readSTArray s n
maybe (return n) (`find` s) m
-- a and b must be root elements
union :: Int -> Int -> DisjSet s x-> ST s ()
union a b s = do (_,x) <- readSTArray s a
(writeSTArray s a (Just b,x))
isRoot :: Int -> DisjSet s x-> ST s Bool
isRoot n s = do (m,_) <- readSTArray s n
maybe (return True) (\_ -> return False) m
mkDSet:: Int -> ST s (DisjSet s Char)
mkDSet n = newSTArray (1,n) (Nothing,'A')
test :: Int -> Int
test n = runST(
do s <- mkDSet 10
union 2 3 s
union 7 1 s
find n s
)
------------------------------------------------------------
/Lars L
If a trainstation is where the trains stop, what is then a workstation...