Difference between revisions of "Idiom brackets"

From HaskellWiki
Jump to navigation Jump to search
(neat `idiom brackets' example)
 
(also link to Applicative Programming with Effects)
 
Line 1: Line 1:
 
[[Category:Idioms]]
 
[[Category:Idioms]]
   
In July 2007, Conor McBride described `idiom brackets':
+
In July 2007, Conor McBride described `idiom brackets'.
  +
  +
See also the 2008 paper [http://www.staff.city.ac.uk/~ross/papers/Applicative.html Applicative programming with effects] by Conor Mcbride and Ross Paterson.
   
 
== Motivation ==
 
== Motivation ==

Latest revision as of 18:50, 19 September 2017


In July 2007, Conor McBride described `idiom brackets'.

See also the 2008 paper Applicative programming with effects by Conor Mcbride and Ross Paterson.

Motivation

Using Control.Applicative you could write:

f <$> x <*> y

Since f is not a pure function, it's f :: x -> y -> m c. The correct form would be

join $ f <$> x <*> y

But maybe some type-class hackery can be used to eliminate the join.

Idiom brackets

Type class hackery to eliminate the 'join':

class Applicative i => Idiomatic i f g | g -> f i where
   idiomatic :: i f -> g

iI :: Idiomatic i f g => f -> g
iI = idiomatic . pure

data Ii  =  Ii

instance Applicative i    => Idiomatic i x (Ii -> i x) where
  idiomatic xi Ii     = xi

instance Idiomatic i f g  => Idiomatic i (s -> f) (i s -> g) where
  idiomatic sfi si    = idiomatic (sfi <*> si)

So that

  iI f x y Ii = f <$> x <*> y

Now add

data Ji = Ji

instance (Monad i, Applicative i)    => Idiomatic i (i x) (Ji -> i x) where
  idiomatic xii Ji = join xii

and you've got

  iI f x y Ji = join $ f <$> x <*> y

or, more flexibly,

data J   = J

instance (Monad i, Idiomatic i f g) => Idiomatic i (i f) (J -> g) where
  idiomatic fii J = idiomatic (join fii)

so you can insert joins wherever you like, thus:

  iI f x y J z Ii = join (f <$> x <*> y) <*> z
     = do {x' <- x; y' <- y; f' <- f x y; z' <- z; return (f' z')}

Of course, the implementation is an ugly hack, made uglier still by ASCII. Worse, for reasons I have never entirely understood, the type-class hackery doesn't allow these brackets to nest as they should. Even so, I find them a considerable convenience. I always assumed that was down to peculiarity on my part.

I thought I'd present it as a curio illustrating part of the design space, but I don't imagine there's that big a market for an "idiom brackets done properly" proposal.