
Hi Everybody, I have a function which computes a fixed point in terms of iterate: equivalenceClosure :: (Ord a) => Relation a -> Relation a equivalenceClosure = fst . List.head -- "guaranteed" to exist . List.dropWhile (uncurry (/=)) -- removes pairs that are not equal . U.List.pairwise (,) -- applies (,) to adjacent list elements . iterate ( reflexivity . symmetry . transitivity ) Can this function be written in terms of fix? It seems like there should be a transformation from this scheme to something with fix in it, but I don't see it.

Something like this? equivalenceClosure = fix $ \f e -> let e' = reflexivity . symmetry . transitivity $ e in if e' == e then e else f e' Cheers, -- Felipe.

On Thu, Jun 9, 2011 at 6:04 PM, Felipe Almeida Lessa wrote: Something like this? equivalenceClosure = fix $ \f e ->
let e' = reflexivity . symmetry . transitivity $ e
in if e' == e then e else f e' Cheers, --
Felipe. I managed something even "clearer". I still have very little intuition
about what's going on, but I had an aha moment -- which I promptly forgot
:0( -- and at least there's a mechanical translation from the iterate
version to the fix one.
equivalenceClosure :: (Ord a) => Relation a -> Relation a
equivalenceClosure = fix (\f -> reflexivity . symmetry . transitivity)

On Fri, Jun 10, 2011 at 12:05 PM, Alexander Solla
On Thu, Jun 9, 2011 at 6:04 PM, Felipe Almeida Lessa < felipe.lessa@gmail.com> wrote:
Something like this?
equivalenceClosure = fix $ \f e -> let e' = reflexivity . symmetry . transitivity $ e in if e' == e then e else f e'
Cheers,
-- Felipe.
I managed something even "clearer". I still have very little intuition about what's going on, but I had an aha moment -- which I promptly forgot :0( -- and at least there's a mechanical translation from the iterate version to the fix one.
equivalenceClosure :: (Ord a) => Relation a -> Relation a equivalenceClosure = fix (\f -> reflexivity . symmetry . transitivity)
Cancel that, it's not passing my tests.

FWIW, what you have written is equivalent to equivalenceClosure = fix (const (reflexivity . symmetry . transitivity)) and because the fixed point of `const a` is `a`, equivalenceClosure = reflexivity . symmetry . transitivity which obviously only performs a single pass on its input On Fri, Jun 10, 2011 at 12:10:16PM -0700, Alexander Solla wrote:
On Fri, Jun 10, 2011 at 12:05 PM, Alexander Solla
wrote: On Thu, Jun 9, 2011 at 6:04 PM, Felipe Almeida Lessa < felipe.lessa@gmail.com> wrote:
Something like this?
equivalenceClosure = fix $ \f e -> let e' = reflexivity . symmetry . transitivity $ e in if e' == e then e else f e'
Cheers,
-- Felipe.
I managed something even "clearer". I still have very little intuition about what's going on, but I had an aha moment -- which I promptly forgot :0( -- and at least there's a mechanical translation from the iterate version to the fix one.
equivalenceClosure :: (Ord a) => Relation a -> Relation a equivalenceClosure = fix (\f -> reflexivity . symmetry . transitivity)
Cancel that, it's not passing my tests.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, Jun 10, 2011 at 21:05, Alexander Solla
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). --Max

On Sat, Jun 11, 2011 at 3:19 AM, Max Rabkin
On Fri, Jun 10, 2011 at 21:05, Alexander Solla
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' ]

On Sat, Jun 11, 2011 at 4:21 PM, Alexander Solla
_symmetry :: (a, a) -> (a, a) _joinOn :: (Ord a) => (a,a) -> Set (a,a) -> Set (a,a)
A note on style: we use variables starting with an underline "_" just when they are not used. This kind of use is confusing. Cheers! -- Felipe.
participants (4)
-
Alexander Solla
-
Felipe Almeida Lessa
-
Max Rabkin
-
Patrick Palka