Design Patterns as Higher-Order Datatype-Generic Programs.

Jeremy Gibbons (2006). Design Patterns as Higher-Order Datatype-Generic Programs. Submitted for publication.

Design patterns are reusable abstractions in object-oriented software. However, using current programming languages, these elements can only be expressed extra-linguistically: as prose, pictures, and prototypes. We believe that this is not inherent in the patterns themselves, but evidence of a lack of expressivity in the languages of today. We expect that, in the languages of the future, design patterns will be expressible as reusable library code. Indeed, we claim that the languages of tomorrow will suffice; the future is not far away. The necessary features are higher-order and datatype-generic constructs; these features are already or nearly available now. We argue the case by presenting higher-order datatype-generic programs capturing ORIGAMI, a small pattern language of recursive data structures.

Last time this research was mentioned there were some concerns about the idea of executable patterns. Obviously, this approach is related to many older discussions about mining patterns for language features, frameworks as opposed to patterns and so on.

Hopefully, now that things are more explicit, we will be able to have a more in depth discussion.

Comment viewing options

Select your preferred way to display the comments and click "Save settings" to activate your changes.

Creational patterns - use pi?

As the author notes in section 7, "we do not see yet how to capture creational design patterns as HODGP".
He rightly observes that this might be the effect of using functional framework. Well, it looks like another justification for exploring HOF and DG in scope of calculi having notion of object creation. A great candidate would be the family of pi calculi, with an added bonus of readily supported CPS. The only problem I see is unsatisfactory treatment of types in pi - probably we need the type system to differentiate between "functional" processes (values?), and those that depend on the sequence of scheduling (evaluation strategy, but from a bit different perspective). Most type systems for pi I've seen type separate channels, while I feel for many applications we need to type sets of channels (it's tough to express an N-ary predicate as a set of N unary predicates - is it why Haskell introduced type constraints?).
If done right, that could make all W3C process management specification efforts obsolete.

loki

it should be noted that real world examples of patterns expressed as generic components have already been implemented some time ago, for example in the loki library as introduced by alexandrescu in 'modern c++ design' years ago. patterns like factory or visitor are herein abstracted and implemented as generic library components with the help of c++ template's parametric polymorphism.

the addition of concept checks and therefor generic interface specifications in the next invocation of c++ should fuel the development of more such components which currently mainly suffer from complicated usage because c++ templates rely on fragile informal interface agreements.

design patterns and programming languages

Loki offers design patterns as abstractions in the form of generic components in C++. But a more fundamental point is the idea of having patterns expressed *non-intrusively* within the language. Using Ruby or any other functional language, I can design my Strategy pattern with Closures - that's an example of non-intrusiveness, when talking about representing patterns in a language. Recently I posted a blog entry on a similar thought here.

Ruby less intrusive than c++?

To be honest,

I disagree with your (non-present) definition of non-intrusiveness. I have read your article on the blog, and while it's true that Ruby has a very clean syntax, such things can be non-intrusively in C++ as well. C++ does not only purely rely on OO, but instead relies on the much more powerful system of generics and templates which is what loki leverages to achieve strategies in a non-intrusive way. You could probably achieve similar effects with Java, standard naming of methods and introspection, however it's not done as often. Perhaps this is due to the fact that ruby and c++ rely more heavily on standard operators behaving in standard fashions.

I think you're missing the point of patterns

At the level you're talking about in that blog entry, patterns used in one generation of languages become language features of the next generation. This has always happened. It's certainly not some "dirty secret" of the patterns community.

Patterns of assembly programming were implemented in 3GLs. Think of the way one used to implement subroutines by pushing arguments and return address onto the stack.

Patterns of programming in 3GLs were implemented in OO languages. Think of the way one used to implement polymorphic objects in C by storing function pointers in structs.

Now the patterns we use in the current generation of languages are getting implemented in the next generation.

My problem with this paper is that they are using functional languages to implement OO patterns. What's the point? Document the patterns that programmers use when doing functional programming. That's more interesting.

New kinds of parameters create need for new design patterns

From: "Design Patterns for Functional Strategic Programming", Lämmel, Visser, RULE 2002:

"One might suppose that the powerful abstraction mechanisms of functional programming obviate the need for design patterns, since many pieces of program construction knowledge can be captured by reusable functions. This confusion of design patterns with reusable components misses the point: patterns start where components end, in the sense that the former describe how the latter can be constructed and used. Thus, additional abstraction *creates* the need for new design patterns."

Apart from this difference of perspective on the role of design patterns, I found Jeremy's paper a clear and interesting read. I wonder how strategic programming, or the scrap-your-boilerplate approach to generics (which, incidentally does work with mutual recursive types) would fit into the story.

naming considered harmful :)

I've just printed the paper out and am about to give it a read, but this is quite timely for me. Over the weekend I was thinking about "higher order patterns", and what kind of language support would be necessary to encode them effectively.

One of the biggest time-wasters in object-oriented programming is the naming of fields -- we require everything to be referenced by field name rather than by other distinctions (type, metadata). We are using names to address data...and all that naming just feels pretty much unnecessary most of the time. It's like writing separate functions for addition, where one knows how to add "2", another knows how to add "3", and so forth.

Methods are usually gather-compute-alter-produce. The gather phase in particular occupies a good deal of most program logic -- specifying in detail what information is to be examined. It also contains the most similarity -- the same patterns repeated over and over again. Endlessly ;)

Traversals or gathers should be first class objects within a language. They are specialized functions that find data to work on. But we should look beyond the conventional collection-walking, tree-flattening, filtering traversals. All types should support (where possible) indexed access, typed-indexed access (filter by type), and named access. We should be able to combine these into complex patterns. There should be no difference between traversing the members of an object (via introspection on its type) and traversing a collection of objects.

If we can create these traversals in a suspended (lazy) form, we can optimize them at runtime prior to execution (I think the term is hylomorphism).

To fold all this back into the pattern world, we can then develop a vocabulary of these traversals.

I don't think that generics, higher-order functions and higher-order types are enough; we need to end the fiction that a program needs anything less than complete and fully navigable information about itself available at runtime, and that said information should follow the same conventions of shape and traversal as everything else.

Right on

I might be easily led, but that all sure sounds really good to me.

This is a great paper and

This is a great paper and it really helped me understand this topic as a whole. Gibbons covers hylomorphisms and suspensions in precisely the manner I've been thinking about them. Having good knowledge about the shape of the data you're operating against is critically important. What we want is to be able to write simple functions, and have the "right" thing done for us automatically when these simple functions are used with complex shapes. A complex shape in a vector language is an array, or a matrix. In an object-oriented language the complex shape results from a traversal over an object structure; if we can form dependent types on the traversals (even dynamic) then the compiler can still do a significant amount of reasoning about the results, and do optimizations around the resulting hylomorphism.

(note what follows is discussion following from the paper, not topics necessarily covered in the paper itself)

Much of this kind of work has been done already in the vector programming community, but limited to vectors. The APL/J/K family defines adverbs that modify functions to influence behavior on shapes, but defines well-known core behavior against compatible shapes of data.

With object-oriented and functional programming we need to move beyond the indexing that most vector languages provide -- we want our shapes to be dynamically created and very flexible. I might want to dynamically create tree shape from a flat list, and I could code that directly. But that kind of code appears over and over again; what I want is to be able to declare well-typed patterns, like "all Integer members of this object", or "all numeric array members of this object whose names start with 'external'" or "the first, fifth, and sixth members from the list of members that are strings".

This is precisely what Java code does when it engages in reflection, but we've completely thrown away the ability of the compiler to help out because it's all effectively typeless at that point, and hylomorphic optimizations are no longer possible (unless you write them in your own code -- or perhaps the runtime library supports them).

P.S. It would be way cool if the standard pattern matching devices (like Scala's cases) supported such navigational patterns and were able to optimize the hylomorphism directly. A single object matches against the case's pattern; the right hand side of the pattern matching statement is a builder in Gibbons' terminology (Gibbons' builders accept a stream of objects and construct a complex type as a result -- the unfold function is such a builder). It constructs the correctly typed result for the match. Yup, in my dreams. ;)

P.P.S. In the ideal, ideal world the builder would actually be a zipper (a la Kiselyov), allowing a complex building operation to take place complete with (pseudo) destructive modifications. Then for complete and utter coolness, the CPS style of pipelining could be used to push and pull data up and down through complex (chained) hylomorphisms.

Ok...

Now I really need to read this paper...

Keeping things in perspective

I like the vision you're painting but as far as I can tell the fold/unfold formalism presented in this paper is restricted to datatypes that are not mutually recursive and are polymorphic in exactly one parameter (ie. having kind * -> *).
That's quite sufficient to demonstrate the four chosen design patterns but I think that a more general foundation would be needed in practice.

Absolutely correct -- I have

Absolutely correct -- I have something of a blur between what I've been thinking about and the contents of this paper in mind. The paper lays the foundation cleanly, I think. The lack of mutually recursive data types impairs generality, but not at the expense of the vast majority of usages. It's just good to see the vocabulary for all this stuff.

GOF patterns were all about giving names to things we mostly knew before, but didn't what to call. I think there are a new set of names for common functions based on datatype genericity. The vector languages give us a start on naming; fully general type-safe traversals handled by a compiler in hylomorphic form can yield both safety and high performance.

One of the most interesting aspects of this is the intersection between constraint programming and datatype genericity -- when conducting an algorithm over a list or pair is no different from folding it over the domain of a discrete constraint (and indeed being able to mix the two together) we get closer to a unified declarative and imperative world, where the expressiveness of both can be combined at will and brought into higher order form too.

Somebody is going to do the very hard work of figuring this intersection out. :)

Higher-order datatype generic programming in Scala

To better understand the concepts this paper is talking about, I've been trying to port the example Haskell code to Scala. My first attempt (which seems to work) is available on my homepage. (The post isn't very polished yet, sorry. I'm now working on implementing the example in section 6.5 [edited to complete this sentence])

I think the main points of interest are:

  • encoding type abstraction using trait TypeConstructor {type a; type b} and correspondingly performing type application by mixin composition, e.g. s{type a=ua; type b=ub} (this corresponds to s ua ub in Haskell), and
  • converting certain functions to methods by promoting an argument to play the role of this
  • representing rank-2 types (as needed by build) in Scala (which I haven't figure out yet)

I've listed some more preliminary thoughts and limitations on my homepage.

Suggestions for improvement greatly appreciated!

I don't know Scala, but

I don't know Scala, but would your encoding for type abstraction & application allow for recursive type synonyms?
Especially:

type Fix s a = s a (Fix s a)

which is illegal in Haskell (though I wish it wasn't). Being able to do that would make it possible to define generic operations that don't require the "In" constructor to be interleaved everywhere.
fold, unfold and map can then be defined as:

fold :: Bifunctor s => (s a b -> b) -> Fix s a -> b
fold f = f . bimap id (fold f)

unfold :: Bifunctor s => (b -> s a b) -> b -> Fix s a
unfold f = bimap id (unfold f) . f

map :: Bifunctor s => (a -> b) -> Fix s a -> Fix s b
map f = fold (bimap f id)

and using List as an example:

data List' a b = Nil | Cons a b
type List a = List' a (List a)

map (* 3) (Cons 1 (Cons 2 (Cons 3 Nil)))     -->  Cons 3 (Cons 6 (Cons 9 Nil))

which is more natural I think. As an additional benefit the need for a build operator disappears (ie. build = id).
Just mentioning this, because if it's possible, your Scala version could improve upon rather than just translate the haskell code.

Maybe, but I couldn't figure it out

Interesting suggestion, but I couldn't devise an encoding that would typecheck. I tried to use this.type as a substitute for the f in type Fix s a = μ f. s a (f s a), which should correspond to the type you gave using recursive type synonyms.

I've included my attempt anyway (along with the compiler errors), hoping that someone else might be able to improve on it or explain why it won't work :-)

My guess is that you need structural subtyping, but I must admit that I don't understand it deeply enough to be sure. (s{type a = ua; type b = Fix[s,ua]} is not seen as equivalent to Fix[s,ua], while this does seem to be the case, structurally)

  trait TypeConstructor {type a; type b} 
  trait Bifunctor[s <: Bifunctor[s]] requires s extends TypeConstructor {
      // the argument of type 's a b' in the Haskell version is implicit as 'this'
    def bimap[c, d](f :a=>c, g :b=>d) :s{type a=c; type b=d}
  } 

  trait Fix[s <: Bifunctor[s] with Fix[s,aa], aa] requires s extends Bifunctor[s] {
    type a=aa
    type b=this.type{type a=s; type b=a}
    
    def fold[fb](f :s{type a=Fix.this.a; type b=fb}=>fb) : fb = f(bimap(id, .fold(f)))
       
    //def map[mb](f :a=>mb) : Fix[s,mb] = bimap[mb, Fix[s, mb]](f, .map(f))
    //def map[mb](f :a=>mb) : Fix[s,mb] = fold[Fix[s,mb]]( .bimap[mb, Fix[s, mb]](f,id))
    // error: type mismatch;  found   : s{type a = mb; type b = Fix[s,mb]}
    //                 required: Fix[s,mb] 
  }
 
  //def unfold[s <: Bifunctor[s], ua, ub](f :ub => s{type a=ua; type b=ub})(x : ub) :Fix[s, ua] = 
  //  f(x).bimap[ua, Fix[s,ua]](id[ua], x :ub => unfold[s,ua,ub](f)(x))
  // error: type mismatch;  found   : s{type a = ua; type b = Fix[s,ua]}
  //                 required: Fix[s,ua]

Next Best thing

I've been thinking some more about how to approximate your solution (which used recursive type synonyms). While reading an excellent explanation of recursive types by Robert Harper, I finally realised that Scala's implicit conversions come in handy here:

implicit def unroll[s<: Bifunctor[s],ua](v :Fix[s,ua]) :s{type a=ua; type b=Fix[s,ua]} = v.out
implicit def roll[s<: Bifunctor[s],ra](v :s{type a=ra; type b=Fix[s,ra]}) : Fix[s,ra] = Fix(v)

When necessary, the compiler inserts calls to these methods, which witness the isomorphism between the recursive type and its unrolling, thus making the code about as easy to read as your approach; here's a snippet (more code on my homepage):

case class Fix[s <: Bifunctor[s], fa](val out :s{type a=fa; type b=Fix[s,fa]}) { 
      def map[mb](f :fa=>mb) :Fix[s,mb] = bimap(f, .map(f))
}

Two caveats, though: (1) there's currently a small bug in the Scala compiler so that implicit conversions are not applied when the target of a member selection is this. (2) Sometimes the compiler can't infer the types for a method invocation, so you have to provide those explicitly... I don't know if this is a bug or a known limit to Scala's type inference (e.g. the bimap-call should read bimap[mb,Fix[s,mb]](f, .map(f))).

Neat

Using implicit coercion to simulate equirecursive typing. I hadn't considered that possibility before (probably because Haskell doesn't offer the ability to define implicit coercions).

I must take a look at Scala.