[Haskell-cafe] Client-extensible heterogeneous types

Alexander Solla ajs at 2piix.com
Wed Oct 13 21:01:09 EDT 2010


On Oct 13, 2010, at 2:18 PM, Jacek Generowicz wrote:

>> Is there any particular reason why you want to actually to mirror  
>> Python code?
>
> I don't want to: I merely have a situation in which an OO solution  
> (not necessarily a good one) immediately springs to mind, while I  
> didn't see any obvious way to do it in Haskell.

Fair enough. :0)

>
>
>> Instead of relying on a one-sized fits all solution (which only  
>> really fits one kind of problem), you write your own.  And it is  
>> typically easier to write the control structure than it is to  
>> implement it using the OO patterns, because of the notion of  
>> irreducible complexity.  For example, the Factory pattern  
>> constructs a functor.  You can write the essential semantics of  
>> doing this with a single Functor instance, instead of writing  
>> multiple classes which implement the semantics, while relying on  
>> implicit, and possibly ill-fitting semantics of method dispatch.   
>> The other OO patterns make this objection stronger.  If you can  
>> write a UML diagram, you can turn it into a commutative diagram,  
>> and write less code by implementing its arrows.
>
> Lots of stuff that sounds fascinating, but whose detailed meaning  
> is, at the moment, beyond my grasp. So let my start off by getting  
> my teeth into your example code:

>
>> An OO class hierarchy is a very specific functor over objects  
>> (which attaches methods to objects).
>
> This sounds very interesting, but, again, I'm having difficulty  
> understanding *exactly* how that is.

At a high level, a functor is a "thing" which attaches "things" to the  
elements of an algebra, in an algebraically compatible way.  The  
functor laws express the compatibility conditions.

Let's think about how non-duck typed OO systems are used (internally)  
at run-time.  First, we have an algebra of objects.  If we don't  
consider how the class hierarchy interacts with the objects, the  
objects are a lot like Haskell values.  Basically, just locations in  
memory or another similar abstraction.

Every object has a "principle class".  We can model this by creating a  
functor that attaches a "class" to each location in memory.

Some classes inherit from others.  We can model this by creating a  
functor that attaches a list (or tree) of classes to each class (that  
we have attached to an object).  Interpreting this model means  
searching for a class that has the method with the right name

With these constructs, we can recreate dynamic method dispatch.  In  
particular, a functor over a functor is a functor over the underlying  
functor's algebra.  We can use "functor combinators" to make going  
'up' and 'down' easier.


>
>> Haskell provides the Functor type class.  Write your generic  
>> functions for specific functors:
>>
>>
>> -- The varying "input" types.  Will be attached to arbitrary values  
>> by the Functor instance.
>>
>> data A = A	-- Variant 1
>> data B = B	-- Variant 2
>>
>> -- Some normalized Output type.
>> data Output = Output
>>
>> -- The new control structure. data Attaches a = AttachesA A a
>>                | AttachesB B a
>>
>> -- Stick your conditional (varying) semantics in here.  Corresponds  
>> to heterogeneousProcessor.
>
> Could you explain this a bit more? heterogeneousProcessor was  
> extremely boring: its only interesting feature was the dot between  
> "datum" and "method()" Here it is again:
>
> def heterogeneousProcessor(data):
>   return [datum.method() for datum in data]
>
> I suspect that runAttaches is (potentially) a lot more interesting  
> than that!

It is as interesting as you want it to be.  That's where you put the  
semantics for interpreting a in terms of the types A or B.  For  
example, if A contained a list of named methods of the form (a ->  
Output), your runAttaches could search through the list, find the  
right one, and apply it.

>
>> -- The output presumably depends on whether A or B is attached, so  
>> this function is not equivalent-- to something of the form fmap  
>> (f :: a -> Output) (attaches :: Attaches a)
>> runAttaches :: Attaches a -> Attaches Output
>> runAttaches = undefined
>>
>> -- This corresponds roughly to  
>> heterogeneousProcessor(heterogeneousContainer):
>> processedOutputs :: [Attaches a] -> [(Attaches Output)]
>> processedOutputs as = fmap runAttaches as
>
> Would it be correct to say that runAttaches replaces Python's  
> (Java's, C++'s etc.) dynamically dispatching dot, but also allows  
> for a greater variety of behaviour?

Yes, that's right.

>
> Alternatively, would it be interesting to compare and contrast  
> runAttach to CLOS' generic functions, or even Clojure's arbitrary  
> method selection mechanism?

I don't know, I'm not familiar with either.  On the other hand, method  
dispatch is always pretty similar.  The difference is the shape of the  
structure traversed to find the right method.

>
>> -- Functor instance.  Now you have a way to treat an (Attaches a)  
>> value just like you would an a. (modulo calling fmap)
>> instance Functor Attaches where
>>         fmap f (AttachesA A a) = (AttachesA A (f a))
>>         fmap f (AttachesB B a) = (AttachesB B (f a))
>
>
> [ Aside:
>
> Briefly returning to my original question: I don't see how, if this  
> were supplied in a library, it would allow clients to inject new  
> entities into the framework. It all seems to hinge on the Attaches  
> type, which would be defined in the library, and is not extensible  
> without modifying the library source code (unless I'm missing  
> something). Which doesn't diminish my desire to understand what you  
> are saying, in the slightest.

As designed, we wouldn't be injecting new classes into the framework.   
We would be injecting the Attaches framework into other frameworks.   
This has "the same effect".  For example:

data SuperClass = SuperClass
data Extension a = Extension SuperClass (Attaches a)

instance Functor Extension where
		fmap f (Extension s a) = (Extension s (fmap f a))

If you wanted to maybe make this a little easier, you could refactor  
Attaches to something like:

data Attaches a b = Attaches a b -- read: Attaches an a to a b

and re-do runAttaches to dispatch over the a's.  You might even want  
to use a type class to restrict the a's:

class ClassLike class

runAttaches :: (ClassLike class) => Attaches class a -> Attaches class  
Output

If you're going to be doing lots of work with functors, you might want  
to check out "category-extras".


More information about the Haskell-Cafe mailing list