Functors and the Visitor Pattern

So, last night, I was having this problem with my Java code where I couldn't figure out for the life of me how to write a piece of code without a big if {} else if {} else if {} ... else {} structure. I was Googling "Java Reflection" to try to determine how to "cast to the most concerete subclass at runtime." Then it dawned on me that what I was trying to do has already been solved by using the Visitor design pattern. Then, after reading the Visitor design pattern page on Wiki, it said that the visitor pattern is essentially an implementation of a functor. Aha! It totally clicked. The Visitor pattern allows you to collect code for similar operations, while spreading apart code for similar objects. Now that really sounds like a functor! Although, now I'm second guessing myself, because I can't figure out how we could create some design pattern that simulates an applicative functor. I'm pretty sure the Visitor pattern doesn't take you this far (but I am willing to be corrected). So, is there a way to create applicative functors in non-functional languages? What would that pattern look like? - Tom -- View this message in context: http://www.nabble.com/Functors-and-the-Visitor-Pattern-tp23851113p23851113.h... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Although, now I'm second guessing myself, because I can't figure out how we could create some design pattern that simulates an applicative functor. I'm pretty sure the Visitor pattern doesn't take you this far (but I am willing to be corrected). So, is there a way to create applicative functors in non-functional languages? What would that pattern look like?
Perhaps this paper can answer your question: Jeremy Gibbons, Bruno C.d.S. Oliveira The essence of the Iterator pattern http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/iterator.pd... HTH, Andres -- Andres Loeh, Universiteit Utrecht mailto:andres@cs.uu.nl mailto:mail@andres-loeh.de http://www.andres-loeh.de

The concepts are fairly closely related but each entails something the other
does not. Functor entails parametric polymorphism with respect to the
contents of the container. And a visitor can extract a result from the
traversal.
As a result you may want to think in terms of a Traversable or Foldable
functor rather than just a Functor. These will let you extract a monadic or
applicative result from your container.
Now, as for your actual question, Applicative functors are really hard to
model in other languages. With C++ templates you can probably get a weak
approximation with something like the encoding used here, possibly mixed
with some boost magic for a usable function type:
http://www.reddit.com/r/programming/comments/8bx33/a_comparison_of_c_concept...
But I can't think of anyone that would try to use it in production code,
and there are many common idioms that that style of translation can't
account for (i.e. polymorphic recursion).
-Edward Kmett
On Wed, Jun 3, 2009 at 9:10 AM, Tom.Amundsen
So, last night, I was having this problem with my Java code where I couldn't figure out for the life of me how to write a piece of code without a big if {} else if {} else if {} ... else {} structure. I was Googling "Java Reflection" to try to determine how to "cast to the most concerete subclass at runtime." Then it dawned on me that what I was trying to do has already been solved by using the Visitor design pattern.
Then, after reading the Visitor design pattern page on Wiki, it said that the visitor pattern is essentially an implementation of a functor. Aha! It totally clicked. The Visitor pattern allows you to collect code for similar operations, while spreading apart code for similar objects. Now that really sounds like a functor!
Although, now I'm second guessing myself, because I can't figure out how we could create some design pattern that simulates an applicative functor. I'm pretty sure the Visitor pattern doesn't take you this far (but I am willing to be corrected). So, is there a way to create applicative functors in non-functional languages? What would that pattern look like?
- Tom -- View this message in context: http://www.nabble.com/Functors-and-the-Visitor-Pattern-tp23851113p23851113.h... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

There was a google talk on Visitor pattern in Java and Common Lisp that you
might find interesting
http://www.youtube.com/watch?v=VeAdryYZ7ak
Daryoush
On Wed, Jun 3, 2009 at 6:10 AM, Tom.Amundsen
So, last night, I was having this problem with my Java code where I couldn't figure out for the life of me how to write a piece of code without a big if {} else if {} else if {} ... else {} structure. I was Googling "Java Reflection" to try to determine how to "cast to the most concerete subclass at runtime." Then it dawned on me that what I was trying to do has already been solved by using the Visitor design pattern.
Then, after reading the Visitor design pattern page on Wiki, it said that the visitor pattern is essentially an implementation of a functor. Aha! It totally clicked. The Visitor pattern allows you to collect code for similar operations, while spreading apart code for similar objects. Now that really sounds like a functor!
Although, now I'm second guessing myself, because I can't figure out how we could create some design pattern that simulates an applicative functor. I'm pretty sure the Visitor pattern doesn't take you this far (but I am willing to be corrected). So, is there a way to create applicative functors in non-functional languages? What would that pattern look like?
- Tom -- View this message in context: http://www.nabble.com/Functors-and-the-Visitor-Pattern-tp23851113p23851113.h... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Tom.Amundsen wrote:
So, last night, I was having this problem with my Java code where I couldn't figure out for the life of me how to write a piece of code without a big if {} else if {} else if {} ... else {} structure. I was Googling "Java Reflection" to try to determine how to "cast to the most concerete subclass at runtime." Then it dawned on me that what I was trying to do has already been solved by using the Visitor design pattern.
Then, after reading the Visitor design pattern page on Wiki, it said that the visitor pattern is essentially an implementation of a functor. Aha! It totally clicked. The Visitor pattern allows you to collect code for similar operations, while spreading apart code for similar objects. Now that really sounds like a functor!
Although, now I'm second guessing myself, because I can't figure out how we could create some design pattern that simulates an applicative functor. I'm pretty sure the Visitor pattern doesn't take you this far (but I am willing to be corrected). So, is there a way to create applicative functors in non-functional languages? What would that pattern look like?
The Visitor pattern isn't a functor, it's a collection of things. The type being visited is the functor[1], the set of methods on that type for accepting a visitor is a catamorphism[2], and the visitor itself is an algebra for the functor[3]. [1] Or rather, the coproduct of all related classes that can chain a visitor forms a type, and that type is a functor. [2] For the recursive Visitor pattern I use most often, that is. For the non-recursive version it's usually fmap. This is the part where the pattern gets a bit shaky because there are actually many different patterns all called "Visitor". The main points of interest are whether it's recursive or not, and whether it applies the visitor to itself, to its children, or both. non-recursive + itself == ($) non-recursive + children == fmap (under open-recursion interpretation of the type, aka all nodes are elements) recursive + children == fmap (under closed-recursion interpretation, aka only fringe nodes are elements) recursive + both == cata (usually, though it depends how you aggregate) recursive + itself == This is actually a variant of the Iterator pattern [3] Though again there's some variation in different "Visitor" patterns. Some variants of the pattern include some of the recursion pattern in the visitor itself rather than in the methods on the visited type. It can be harder to maintain since it's less modular, though it allows the visit methods to serve as many different functions which can be helpful if you need more than one of ($), fmap, cata, traverse,... -- Live well, ~wren

On Thu, Jun 4, 2009 at 9:13 AM, wren ng thornton
The Visitor pattern isn't a functor, it's a collection of things. The type being visited is the functor[1], the set of methods on that type for accepting a visitor is a catamorphism[2], and the visitor itself is an algebra for the functor[3].
[1] Or rather, the coproduct of all related classes that can chain a visitor forms a type, and that type is a functor.
[2] For the recursive Visitor pattern I use most often, that is. For the non-recursive version it's usually fmap. This is the part where the pattern gets a bit shaky because there are actually many different patterns all called "Visitor". The main points of interest are whether it's recursive or not, and whether it applies the visitor to itself, to its children, or both.
non-recursive + itself == ($)
non-recursive + children == fmap (under open-recursion interpretation of the type, aka all nodes are elements)
recursive + children == fmap (under closed-recursion interpretation, aka only fringe nodes are elements)
recursive + both == cata (usually, though it depends how you aggregate)
recursive + itself == This is actually a variant of the Iterator pattern
Could you be so kind to give an example for each? Cheers, Johan

Johan Tibell wrote:
wren ng thornton wrote:
[2] For the recursive Visitor pattern I use most often, that is. For the non-recursive version it's usually fmap. This is the part where the pattern gets a bit shaky because there are actually many different patterns all called "Visitor". The main points of interest are whether it's recursive or not, and whether it applies the visitor to itself, to its children, or both.
non-recursive + itself == ($)
non-recursive + children == fmap (under open-recursion interpretation of the type, aka all nodes are elements)
recursive + children == fmap (under closed-recursion interpretation, aka only fringe nodes are elements)
recursive + both == cata (usually, though it depends how you aggregate)
recursive + itself == This is actually a variant of the Iterator pattern
Could you be so kind to give an example for each?
In OOP you mean? /* nonrecursive + self == application */ class A { T app(Visitor v) { return v.visit(this); } } class B { T app(Visitor v) { return v.visit(this); } } ... // An allomorphic function :: (A | B | ...) -> T class Visitor { T visit(A a) { ... } T visit(B b) { ... } ... } This particular version often isn't too helpful because it's just reflecting the method call, we could've just called visit directly instead of calling app. But there are times where it is useful, particularly when you want to have some visitors which are recursive and some which are not. In which case it doesn't matter which method you start with, but you do need both in order to reflect back on recursion. /* nonrecursive + children == fmap (with real parametricity) */ class F<A> { Children<A> as; F(Children<A> as) { this.as = as; } F<B> fmap(Visitor v) { Children<B> bs = new Children<B>(); for (A a : this.as) bs.add( v.visit(a) ); return new F<B>(bs); } } ... interface Visitor { B visit(A a); } This is a rather Haskellish take on this version. In practice people often don't bother supporting parametricity (needed for making F a real functor). That is, usually they'll do destructive updates to F, only have endofunction visitors (so there's no change of types), or use side-effect only visitors (see below). /* recursive + children == fmap (side-effect only) */ abstract class Tree { abstract void rmap(Visitor v); } class Branch extends Tree { Children<Tree> subtrees; void rmap(Visitor v) { for (Tree t : this.subtrees) v.visit(t); } } class Leaf extends Tree { void rmap(Visitor v) { // Just in case we're the root node. v.visit(this); // Or we could do nothing instead, // depending on desired semantics } } class Visitor { void visit(Branch t) { t.rmap(this); } // reflect to recurse void visit(Leaf t) { ... } // don't reflect or you'll hit _|_ } This highlights an additional axis of variation in the many different visitor patterns, whether the "result" is returned directly (as in the previous example), whether it is accumulated in the Visitor itself (requiring explicit lookup later), or whether it's done via side-effects on global state. The accumulator and side-effect versions are a bit more general since their "return type" isn't restricted by the classes being visited. /* recursive + self/both == a kind of Iterator/catamorphism */ abstract class Tree { abstract void observe(Visitor v); } class Branch extends Tree { Children<Tree> subtrees; void observe(Visitor v) { v.visit(this); for (Tree t : this.subtrees) t.observe(v); } } class Leaf extends Tree { void observe(Visitor v) { v.visit(this); } } class Visitor { void visit(Branch t) { ... } void visit(Leaf t) { ... } } This is different from the recursive+children version because this version keeps all of the recursion code on the side of the visited classes, and it also meaningfully visits interior nodes. In the recursive+children version the visitor ignored branches (though it doesn't need to) and reflected back to initiate recursion, whereas this version will recurse no matter what the visitor does (barring exceptions, etc). This version is a push iterator which forces you to visit all nodes, rather than the more usual pull iterator where you need to call next() to get the next node. We can convert between the two varieties by using co-routines or threads or other control-flow tricks. If we reverse the order of the recursive observe and the visit(this) then we get something like a catamorphism. Whether it's actually a catamorphism depends on what the visitor does, or rather what knowledge about the shape of Branch and Leaf it makes use of. "Real" catamorphisms are fairly rare in OOP, though you often find things like using a visitor to add decoration to a tree (which is much like passing the initial algebra to cata) or maintaining some aggregation in the visitor. -- Live well, ~wren
participants (6)
-
Andres Loeh
-
Daryoush Mehrtash
-
Edward Kmett
-
Johan Tibell
-
Tom.Amundsen
-
wren ng thornton