Proposal: Add Compositor class as superclass of Arrow

Twan van Laarhoven twanvl at gmail.com
Thu Oct 25 20:21:19 EDT 2007


apfelmus wrote:

> Twan van Laarhoven wrote:
> 
>> My proposal would be the following. The important things are that:
>>  1. It incorporates Conal's deep arrow,
>>  2. as well as everything that is needed for functional 
>> references/lenses and bijective/invertible functions.
> 
> 
> I'd opt for more research for that proposal to answer the following 
> essential questions

Indeed. I have started a project/library at
   http://code.haskell.org/category/
for this purpose.

It contains implementations of functional references and invertible 
functions as test subjects, and the laws are tested using quickcheck.

> - Do the classes correspond to already-known categories, i.e. are the 
> class names optimal?
> - What laws do we expect to hold?

I have found an example of a law you'd expect to hold, that doesn't. 
This is: left id == id. For functional references it is not too hard to 
implement 'left', but it does not satisfy that law, since for the set 
operation you need two values with the same 'side'. There is no way to 
get a 'left' value from
     set (left id) (Left 'a') (Right 'b') = Right 'b'
because a might differ from the result type for functions other than id, yet
     set id (Left 'a') (Right 'b') = Left 'a'


> - Are the signatures minimal, i.e. does there exist a smaller set of 
> combinators that still achieves the intended effect? Are the signatures 
> complete, i.e. can the intended effect always expressed with the given 
> combinators?

The big culprit here are the structural combinators: mirror, swap, 
assoc* and most of CategoryFun (and id). All of these can be written 
using 'arrInv'. So the questiong becomes: Are there arrows that allow 
structural manipulation of functions, products and sums, that do not 
support all bijections?

Similairly, injection (inl/inr) and selection (fst/snd) can be written 
using 'arrRef'. So again: Are there arrows that do not contain the 
functional references, that do allow inl/inr and fst/snd.

A likely candidate for both is Conal's DeepArrow.

Another thing I don't like about these functions is that they are 
specific to (,) and Either. This becomes important once you add 
syntactic sugar. Case expressions can only be desugared when you have 
'arrInv'.

Perhaps there can be a superclass of InvArrow with the same type 
signature, but with the additional requirement that it may only be used 
for structural isomorphisms.

> - Plenty and useful examples? At least enough examples that fit in the 
> fine grained hierarchy but cannot be fit into a coarser grained one so 
> as to demonstrate the necessity of a fine grained hierarchy.
> 
> These questions likely have nice answers for many of the classes, but 
> CategoryZero, CategoryPlus

CategoryZero and CategoryPlus just give a monoid structure, exactly the 
same as MonadZero and MonadPlus. They could be put into a single class 
like the current MonadPlus. The only reason we need these things are 
needed is because Haskell doesn't allow universaly quantified contexts
    f :: CategoryPlus cat => ...
    f :: (Category cat, forall a b. Monoid (cat a b)) => ...

 > .. CategoryChoice ..

As mentioned before, CategoryChoice is the dual to CategoryPair. So it 
is just as reasonable.

 > and in particular CategoryFun may be hard nuts.

(note: I am brainstorming here)

Asside from result, curry, uncurry and funR (aka flip) which can all be 
expressed with arrInv/arrIso, there are funF and funS which can not. I 
see no sane way to implement them in anything below ArrowFun. Perhaps 
these two functions can together form a class

   class CategoryPair cat => CategoryFunPair cat where
         funF :: cat (c -> a, b) (c -> (a, b))
         funS :: cat (a, c -> b) (c -> (a, b))

         funS = result swap . funF . swap

And dually

   class CategoryChoice cat => CategoryFunChoice cat where
         funL :: cat (Either (c -> a) b) (c -> (Either a b))
         funR :: cat (Either a (c -> b)) (c -> (Either a b))

I expect the problem with these classes comes from the fact that they 
use *two* categories, cat and (->), and a monad. Generalizing to other 
monads gives for instance

         funLst :: cat [c -> a] (c -> [a])

Alternatively, it's one category and two monads / applicative functors. 
Then we get:

         sequence :: cat (f (g a)) (g (f a))

Now the question becomes: does sequencing in a category cat ever differ 
from sequencing in (->)? Clearly it can be a subset, but is there 
anything other than the cases:
     - f and g commute (f . g = g . f), sequence can be done in IsoArrow
     - g only sequences through f, we may need a new class for this; 
otherwise Arrow will do. For some cases RefArrow might be enough.
     - f and g don't commute, nothing happens.

Again I look at Conal for a likely source of examples. Look at 
Data.Traversable.sequence for this function in (->).


> Also, the proposed subclass chain InvArrow => RefArrow => FunArrow may 
> be cumbersome in practice since it would mean to define three functions 
> instead of just  arr  when declaring an Arrow.

There are examples of all three, and I think it is important to ensure 
that the instances of the superclasses are available for the subclasses. 
Otherwise changing a function from, say, FunArrow to RefArrow does not 
make it more general.

Twan


More information about the Libraries mailing list