[Haskell-cafe] Fixed points

Alexander Solla alex.solla at gmail.com
Sat Jun 11 21:21:47 CEST 2011


On Sat, Jun 11, 2011 at 3:19 AM, Max Rabkin <max.rabkin at gmail.com> wrote:

> On Fri, Jun 10, 2011 at 21:05, Alexander Solla <alex.solla at gmail.com>
> wrote:
> > equivalenceClosure :: (Ord a) => Relation a -> Relation a
> > equivalenceClosure = fix (\f -> reflexivity . symmetry . transitivity)
>
> If you want to learn about fix, this won't help you, but if you're
> just want the best way to calculate equivalence closures of relations,
> then it's probably
>
> equivalenceClosure = transitivity . symmetry . reflexivity
>
> assuming those are the transitive, symmetric and reflexive closure
> functions. You still need some kind of iteration to get the transitive
> closure. The algorithm I know of for that is Warshall's Algorithm,
> which is O(N^3) (possibly with a log N factor for pure data
> structures).


Cool, thanks for the suggestion.  I was iterating all of them, since an
iteration of "transitive" introduces new pairs to the relation (which are
not guaranteed to have symmetric "complements" in my implementation).  I
suppose I can get away with not iterating "reflexive", for something like an
O(n) speed up for each iteration.

This is a summary of the code.  I haven't done order analysis on it.
 Relation is a newtype over a Set of pairs:

-- | Iterate 'transitivity' to compute the transitive closure for a
relation.
transitivity :: (Ord a) => Relation a -> Relation a
transitivity (Relation set) = Relation $ (Set.fold _joinOn set) (set)

-- | Compute the reflexive closure for a relation.  In other words, take a
set
--   containing @(a,b)@, @(c,d)@, ... into one containing the originals and
--   @(b,a)@, @(d,c)@, and so on.
reflexivity :: (Ord a) => Relation a -> Relation a
reflexivity (Relation set) = Relation $ Set.unions [ set
                                                   , (Set.map (\(x,_) ->
(x,x)) set)
                                                   , (Set.map (\(_,y) ->
(y,y)) set)
                                                   ]

-- | Compute the symmetric closure for a relation.
symmetry :: (Ord a) => Relation a -> Relation a
symmetry (Relation set) = Relation $ Set.union set (Set.map _symmetry set)

_symmetry :: (a, a) -> (a, a)
_symmetry (a, b) = (b, a)


_joinOn :: (Ord a) => (a,a) -> Set (a,a) -> Set (a,a)
_joinOn (a,b) set =
    let fst' = Set.filter ((b ==) . fst)  $ set
        snd' = Set.filter ((a ==) . snd)  $ set
     in Set.unions [ set
                   , Set.map (\(x,y) -> (a,y)) fst'
                   , Set.map (\(x,y) -> (x,b)) snd'
                   ]
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110611/393d2b09/attachment.htm>


More information about the Haskell-Cafe mailing list