[Haskell-cafe] Work on Collections Processing Arrows?

David Barbour dmbarbour at gmail.com
Wed May 11 17:59:36 CEST 2011


I wonder if I need something like your use of 'representation' types, i.e.
to restrict what sort of elements can be stored in a collection.

I've just recently hit on the idea of using a barrier type 'V' to wrap a
synchronous value. A 'synchronous value' is one that can be observed at a
single time and place, without any further communication or delay. In a
sense, any Haskell value might be a synchronous value, since (barring
suspicious use of unsafePerformIO) even lazy or parallel values are
observable without further communication effects.

So, in an implementation, I might get a set of constructors that look
something like this:
  arr :: (x->y) -> A (V x) (V y)
  synch :: A ((V x) :*: (V y)) (V (x,y))
  constant :: t -> A (V ()) (V t)   -- 'u' = (V ()) for product

Your use of representation types in GArrowReify, GArrowConstant, etc. really
help for capturing these constructors.

While I'm happy in my case to allow asynchronous collections of asynchronous
types, I can imagine the possibility of someone wanting to impose a
restriction on what sort of types can be generated inside a collection, i.e.
such that we have:

  mapA :: a (V x) (V y) -> a (c x) (c y)

This would block, for example, the possibility that 'c' will itself contain
asynchronous collections, sums, or products.

I'll admit to some reluctance, however, to clutter up several typeclasses
with four more types. What are your thoughts regarding this issue?

Regards,

Dave


On Tue, May 10, 2011 at 1:25 PM, Adam Megacz <megacz at cs.berkeley.edu> wrote:

>
> > class (GArrow a (**) u c) => GArrowMap a (**) u c where
> >    mapA :: a d r -> a (c d) (c r)
>
> > class (GArrow a (**) u) => GArrowUnion a (**) u c where
> >    union :: a ((c r) ** (c r)) (c r)
>
> > class (GArrowMap a (**) u c) => GArrowJoin a (**) u c where
> >    join :: a d (c r) -> a (c d) (c r)
>
> I like these; I think you're on the right track.  The last one reminds
> me of concatMap.
>
>
> > class (GArrowDrop a (**) u) => GArrowMap_ a (**) u c where
> >    mapA_ :: a d u -> a (c d) u
>
> I don't think you want to ask for a GArrowDrop instance here -- if
> you've got that, you might as well just ignore the argument and say:
>
>     mapA_ = \x -> ga_drop
>
> Perhaps what you want is
>
>     gac_drop :: a (c u) u
>
> ... which is a bit like ga_cancell and ga_cancelr, but for a whole
> collection rather than one input at a time.
>
> By the way, I've started [2] using type families for the "aggregate"
> GArrow classes like GArrowSTLC.  This greatly reduces the syntactic
> noise in the types -- you only have one type parameter instead of four.
> The price is that a single type can't be an instance of these classes in
> more than one way (see Section 3.6.1 of [3] for why this is important).
>
> I tend to think of type classes in terms of dictionary-passing (like in
> Coq), so I often get myself into trouble in situations where I know
> which dictionary to pass, but can't get Haskell's instance inference to
> do what I want.  I welcome suggestions on ways to improve the
> user-friendliness of the GArrow classes -- there are probably a bunch of
> cool Haskell type class tricks I ought to be using but don't know about.
>
>
> > In my own case, 'c' might be representing an asynchronous or
> > distributed, reactive collection, so the ability to restrict
> > expressiveness is important for performance.
>
> Certainly.  The multiplicative disjunction [4] of linear logic is the
> "binary" version of this: (A \bindnasrepma B) is sort of like an A and a
> B in geographically distant locations; if you have a (Int \bindnasrepma
> Int) you have two Int's, but in order to (for example) add them together
> you must use some sort of communication primitive to get them both to
> the same place.
>
> It sounds like you want a sort of "collection version" of multiplicative
> disjunction.  I bet Data Paralell Haskell's parallel array type-former
> (([::]) :: * -> *) would be an instance of this class.
>
>  - a
>
>
> [1] http://dx.doi.org/10.1145/581690.581695
>
> [2] http://git.megacz.com/?p=ghc-base.git;a=commitdiff;h=47c002441ab30c48
>
> [3] http://arxiv.org/pdf/1007.2885v2
>
> [4] http://en.wikipedia.org/wiki/Linear_logic#The_resource_interpretation
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110511/4e28c163/attachment.htm>


More information about the Haskell-Cafe mailing list