Arrows that are also Functors

Tyson Whitehead twhitehead at gmail.com
Wed Apr 20 05:22:12 CEST 2011


On April 19, 2011 12:22:39 Maciej Marcin Piechotka wrote:
> On Tue, 2011-04-19 at 17:29 +0200, Henning Thielemann wrote:
> > Is it common to make a type an instance of both Arrow and Functor type
> > class? If a type is both instance of Arrow and Functor, would you expect
> > that fmap = (^<<) ? If yes, how about adding this as expected law to the
> > Control.Arrow documentation? Same question for Applicative functors and
> > liftA2 (,) = (&&&). (Btw. Control.Arrow haddock documentation does not
> > mention any Arrow law so far.)
> 
> I believe reading in some paper/monad reader article that Arrow is
> equivalent to Category that is Functor.

I think that is actually an Applicative Category (just a bit more power) valid 
for all source types.  The first I was exposed to this idea was Patai's blog.  
If you know of another source, I would like to know as I've been working to 
ensure the laws follow from the parametricity and write up a little summary.

Anyway, assuming the laws are all okay, the applicative side of it is 
especially clear if you look at an alternative definition for applicative

  class Functor m => Applicative' m where
    order :: m a -> m a -> m (a,b)

This alternative definition puts emphasis on the fundamental operation of 
pairwise ordering.  The order aspect is usually a bit hidden by the fact that 
(<*>) does it when sticking them into a closure.

  f <*> x = fmap ap $ f `order` x
    where ap (f,x) = f x

Thinking of the fundamental Applicative operation as ordering really reveals 
why it (and Monad) is so useful for IO.  An ordering combinator is the  
critical element required for determinism in the face of side effects.

All the arrow stuff falls out pretty easy given this definition.  Let ''' be 
used to indicate the standard operations on underlying category.

  id' = Control.Category.id
  (.') = (Control.Category..)

  arr f =  fmap f id'

  fst' = arr fst
  snd' = arr snd

  first f = (f .' fst') `order` snd'
  second g = fst' `order` (g .' snd')

  f *** g = (f .' fst') `order` (g .' snd')
  f &&& g = f `order` g

The extended Arrow functionality is similarly obtained from extended 
Applicative functionality.  For example, ArrowApply comes from Monad

  app' = join $ arr (.' snd') .' fst'

ArrowLoop from MonadFix

  loop' f = fst' .' loop'' (f .' arr' (second snd))
    where loop'' f = mfix (\y -> f .' arr' (,y))

and so on.

Cheers!  -Tyson

PS:  Note that "second snd = \(x,(_,y)) -> (x,y)" as (->) is an Arrow.
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 490 bytes
Desc: This is a digitally signed message part.
URL: <http://www.haskell.org/pipermail/libraries/attachments/20110419/7ae97b66/attachment.pgp>


More information about the Libraries mailing list