[Haskell-cafe] Applicative banana brackets

S. Doaitse Swierstra doaitse at swierstra.net
Mon Dec 14 14:16:02 UTC 2015


In the Idioms module of uu-parsinglib:

https://hackage.haskell.org/package/uu-parsinglib-2.9.1/docs/Text-ParserCombinators-UU-Idioms.html

I show how you can achieve what you want without any preprocessors. The idea is to overload based on the type of the operand:

{-# LANGUAGE RankNTypes,
             MultiParamTypeClasses,
             FunctionalDependencies,
             FlexibleInstances,
             UndecidableInstances,
             FlexibleContexts,
             CPP #-}

module Idiomatic where
    
-- | The  `Ii` is to be pronounced as @stop@
data Ii = Ii 

-- | The function `iI` is to be pronounced as @start@
iI ::Idiomatic  (a -> a) g => g
iI = idiomatic (pure id)

class Idiomatic f g  | g -> f   where
    idiomatic :: [f] -> g
    
instance  Idiomatic x  (Ii -> [x]) where
    idiomatic ix Ii = ix


instance  Idiomatic f g  => Idiomatic  (a -> f) ([a]  -> g) where
    idiomatic isf is = idiomatic (isf <*> is)

instance Idiomatic f g => Idiomatic ((a -> b) -> f)  ((a -> b) -> g) where
    idiomatic isf f = idiomatic (isf <*> (pure f))

t :: [Int]
t = iI (\ a b c -> a + b +c) [3] [1,2] [5,0,7] Ii 

So you get:

*Idiomatic> show t
"[9,4,11,10,5,12]"
*Idiomatic> 


  


> On 14 Dec 2015, at 14:53 , martin <monkleyon at googlemail.com> wrote:
> 
>> I don't know how the arrow syntax works, but you can get banana brackets
>> for applicatives with a preprocessor—the Strathclyde Haskell Enhancement
>> (SHE)[1]. [...]
> I hadn't looked into preprocessors yet, but that sounds like a great
> idea. Thanks!
>> Personally, playing around with it convinced me that banana brackets aren't
>> quite as nice in practice as they look. [...] Of course, those more complicated cases end up being the
>> most common. [...]
> I only played around with arrow brackets yet, but that sounds familiar.
> They can make your code really beautiful - but only rarely. I'm
> currently trying to convert some of my overcomplicated arrow structures
> to simpler applicative ones, which is one of my motivations here. But if
> it's of so little use, and with liftAn's already there...
>> A particular problem I had is that, by necessity, $ works differently
>> inside banana brackets than normally. [...]
> That sounds like it might not have been a problem for me yet because the
> natural composition of arrows is through (>>>) anyway. Interesting.
>> I don't want to discourage you too much. 
> Don't worry. There are always things to play around with and projects to
> try. It was just that I thought I might have found something far simpler
> that what I usually come up with, and thus something I could actually
> finish and share some day. ;)
>> Also, they'd be somewhat redundant with ApplicativeDo.
> Yet another thing I hadn't thought of. I'm not a huge fan of do-notation
> and arrow-notation myself. They are useful, but can be overly verbose
> and distracting. So maybe I'll get more use out of brackets? Only one
> way to find out...
> 
> Anyway, thanks for all the great information. These are definitely
> things I'll consider!
> 
>>> Hi,
>>> 
>>> while learning about all the type classes and their relationships I came
>>> across something I found weird.
>>> If I understand it correctly, banana brackets where originally developed
>>> for Applicatives. The intent was to enable us to write something like
>>> 
>>> (| (\a b c -> a + b + c), [3], [1,2], [5,0,7] |)
>>> 
>>> and have it translated to
>>> 
>>> liftA3 (\a b c -> a + b + c) [3] [1,2] [5,0,7]
>>> 
>>> or alternatively, to allow us to write something like
>>> 
>>> (| (pure $ \a b c -> a + b + c), [3], [1,2], [5,0,7] |)
>>> 
>>> and have it translated directly to
>>> 
>>> pure (\a b c -> a + b + c) <*> [3] <*> [1,2] <*> [5,0,7]
>>> 
>>> A variant of banana brackets is implemented in ghc, but only for Arrows
>>> as part of -XArrowSyntax. Arrows are just the intersection of
>>> Applicative and Category, so this implementation seems to be a
>>> specialization. What's worse, I don't think -XRebindableSyntax extends
>>> to banana brackets.
>>> But why? Is it hard to have the notation work with both? (After all, the
>>> relationship between Arrows and Applicatives is not easily expressed in
>>> Haskell.) Was the demand for (Applicative) bananas not big enough? Is it
>>> just a relic?
>>> And more to the point: I have not looked at the ghc code base at all
>>> yet, but it's on my bucket list to hack on it one day. Right now, a
>>> generalization of banana brackets seems like a simple enough low
>>> pressure first project, but I fear that it might break code or that
>>> there is some pitfall I'm not seeing.
>>> 
>>> Can anybody shed a bit of light on this?
>>> 
>>> Thanks and cheers,
>>> Martin L.
>>> 
>>> P.S.: If the list receives this mail several times, I apologize. The
>>> list management tool seems to be confused by gmail vs. googlemail.
>>> That's what you get for using non-Haskell software. ;)
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>> 
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list