Plain lambda inside banana brackets in the arrow notation

Hello, In a program, I have an arrow MyArr and a combinator called repeat of the following type: repeat :: Int -> (Int -> MyArr e a) -> MyArr e a My problem is that the code becomes messy when I use this combinator inside the arrow notation, and I am looking for a way to write the code in a more readable way. To explain the problem, first consider the following combinator repeat', which is less general than repeat: repeat' :: Int -> MyArr (e, Int) a -> MyArr e a repeat' n f = repeat n g where g i = arr (\e -> (e, i)) >>> f Combinator repeat' is nice to use in the arrow notation, thanks to banana brackets and the interpretation of lambda: test1 :: MyArr [Double] String test1 = proc xs -> do let y = func1 xs z <- job1 -< xs (|(repeat' 100) (\i -> job2 -< xs !! i + y + z)|) -- func1 :: [Double] -> Double -- job1 :: MyArr [Double] Double -- job2 :: MyArr Double String However, in my program, I often have to use repeat instead of repeat' like: test2 :: MyArr [Double] String test2 = proc xs -> do let y = func1 xs z <- job1 -< xs repeat 100 (\i -> proc (xs, y, z) -> job3 (i * 2) -< xs !! i + y + z) -< (xs, y, z) -- job3 :: Int -> MyArr Double String Note that variable i is used as an argument to function job3 outside MyArr, and this cannot be done with repeat'. The code for test2 looks messy to me because I have to write “(xs, y, z)”, that is, the list of variables used inside the subcomputation explicitly (and twice). It does not seem possible to use banana brackets here because the type of the subcomputation does not meet the requirements stated in http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/arrow-notation.html#i.... How can I use combinators like repeat, which takes a plain function as an argument, in the arrow notation in a more readable way? Or am I trying to do an impossible thing? Best regards, Tsuyoshi

Tsuyoshi Ito
How can I use combinators like repeat, which takes a plain function as an argument, in the arrow notation in a more readable way? Or am I trying to do an impossible thing?
To answer your question: Arrow notation has no support for what you want, so if you stick with it you will have to write the inner proc explicitly. However: The code may look much nicer, if you use applicative style for the outer computation using Applicative, Category and Profunctor [1]: test2 :: MyArr [Double] String test2 = repeat 100 rmap . liftA3 (,,) id y z where y = arr func1 z = job1 rmap i = lmap (\(xs, y, z) -> xs !! i + y + z) (job3 (i * 2)) If you prefer, you can use arrow notation for the inner computation. [1]: http://hackage.haskell.org/package/profunctors Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.

Dear Ertugrul, Thank you for your input.
To answer your question: Arrow notation has no support for what you want, so if you stick with it you will have to write the inner proc explicitly.
Oh. I was afraid of that.
However: The code may look much nicer, if you use applicative style for the outer computation using Applicative, Category and Profunctor [1]:
Thank you for the code. It looks much nicer than my code, which uses the arrow notation both for inner and outer computations.
If you prefer, you can use arrow notation for the inner computation.
This was a blind spot for me; I had not thought of mixing the arrow notation and the plain notation. This definitely helps writing a code when either the outer computation or the inner computation is simple. Unfortunately, sometimes both the outer computation and the inner computation involve many local variables, in which case I need the arrow notation for both, forcing me to write the inner proc explicitly inside the outer proc. If someone extends the arrow notation someday and makes this use case easier, that will be great. For now, avoiding the arrow notation for simple computations and writing two proc’s when both computations are complicated seems like a reasonable compromise to me. Thanks a lot! Best regards, Tsuyoshi

On Thu, Jul 05, 2012 at 10:55:07PM +0100, Tsuyoshi Ito wrote:
In a program, I have an arrow MyArr and a combinator called repeat of the following type:
repeat :: Int -> (Int -> MyArr e a) -> MyArr e a
My problem is that the code becomes messy when I use this combinator inside the arrow notation, and I am looking for a way to write the code in a more readable way. [...] It does not seem possible to use banana brackets here because the type of the subcomputation does not meet the requirements stated in http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/arrow-notation.html#i....
How can I use combinators like repeat, which takes a plain function as an argument, in the arrow notation in a more readable way? Or am I trying to do an impossible thing?
Unfortunately the arrow notation doesn't support this. There's no semantic reason why it wouldn't work with arguments of the form f (a (...(e,t1), ... tn) t) for any functor f, or even g (...(e,t1), ... tn) for any contravariant functor g. The limitation is due to Haskell's structural matching of types. Though one possibility that might get us most of the way there would be to refactor the Arrow class as class PreArrow a where premap :: (b -> b') -> a b' c -> a b c class (Category a, PreArrow a) => Arrow a where arr :: (b -> c) -> a b c arr f = premap f id first :: a b c -> a (b,d) (c,d) instance PreArrow (->) where premap f g = g . f instance PreArrow (Kleisli m) where premap f (Kleisli g) = Kleisli (g . f) instance (PreArrow a, Functor f) => PreArrow (StaticArrow f a) where premap f (StaticArrow g) = StaticArrow (fmap (premap f) g) The PreArrow class would be sufficient for the low-level translation (i.e. excluding if, case and do). You'd need to fiddle with newtypes to use it in your example, though.

On Thu, Jul 12, 2012 at 02:47:57PM +0100, Ross Paterson wrote:
Though one possibility that might get us most of the way there would be to refactor the Arrow class as
class PreArrow a where premap :: (b -> b') -> a b' c -> a b c
class (Category a, PreArrow a) => Arrow a where arr :: (b -> c) -> a b c arr f = premap f id
first :: a b c -> a (b,d) (c,d)
I've done this and the associated GHC changes locally; it yields a simple rule for determining which instances are needed, based on the keywords used: * all commands ("proc" and operator arguments) need PreArrow * "do" needs Arrow * "rec" needs ArrowLoop * "case" or "if" need ArrowChoice I'm warming to it as a worthwhile generalization (though not exactly what was asked for).

On Fri, Jul 13, 2012 at 8:11 AM, Ross Paterson
On Thu, Jul 12, 2012 at 02:47:57PM +0100, Ross Paterson wrote:
Though one possibility that might get us most of the way there would be to refactor the Arrow class as
class PreArrow a where premap :: (b -> b') -> a b' c -> a b c
class (Category a, PreArrow a) => Arrow a where arr :: (b -> c) -> a b c arr f = premap f id
first :: a b c -> a (b,d) (c,d)
I've done this and the associated GHC changes locally; it yields a simple rule for determining which instances are needed, based on the keywords used:
* all commands ("proc" and operator arguments) need PreArrow * "do" needs Arrow * "rec" needs ArrowLoop * "case" or "if" need ArrowChoice
I'm warming to it as a worthwhile generalization (though not exactly what was asked for).
Thank you for the response. This sounds exciting, but sadly, I must admit that it is a little (?) above my head, and I cannot relate this extension to my original question…. Best regards, Tsuyoshi

On Sun, Jul 15, 2012 at 06:51:07PM +0100, Tsuyoshi Ito wrote:
Thank you for the response. This sounds exciting, but sadly, I must admit that it is a little (?) above my head, and I cannot relate this extension to my original question….
Sorry about that -- I got a bit side-tracked. The combinator you wanted to use was repeat :: Int -> (Int -> MyArr e a) -> MyArr e a That won't be possible, but with this extension you could use repeat' :: Int -> StaticArrow ((->) Int) MyArr e a -> MyArr e a The definition of StaticArrow (in the arrows package) is a wrapper newtype StaticArrow f a b c = StaticArrow (f (a b c)) so StaticArrow ((->) Int) MyArr e a ~= Int -> MyArr e a. Now you could write test2 :: MyArr [Double] String test2 = proc xs -> do let y = func1 xs z <- job1 -< xs (|(repeat' 100) (StaticArrow (\i -> job3 (i * 2)) -< xs !! y + z)|) which isn't quite what you wanted, because i wouldn't be in the environment, but we could put it there as you did in your original post, or something like test2 :: MyArr [Double] String test2 = proc xs -> do let y = func1 xs z <- job1 -< xs (|(repeat' 100) (do i <- StaticArrow (arr . const) -< () StaticArrow (\i -> job3 (i * 2)) -< xs !! i + y + z)|) I did say it would be clunky, but at least there's no dumping the tuple and picking it up again.

Silly me -- that code works with the current GHC (module attached). I still think the generalization is worth doing, though. ------------------------------------------------------------------------- {-# LANGUAGE Arrows #-} module ArrowTest where import Control.Applicative import Control.Arrow import Control.Category import Prelude hiding (id, (.), repeat) -- copied from Control.Arrow.Transformer.Static (in the arrows package) newtype StaticArrow f a b c = StaticArrow (f (a b c)) instance (Category a, Applicative f) => Category (StaticArrow f a) where id = StaticArrow (pure id) StaticArrow f . StaticArrow g = StaticArrow ((.) <$> f <*> g) instance (Arrow a, Applicative f) => Arrow (StaticArrow f a) where arr f = StaticArrow (pure (arr f)) first (StaticArrow f) = StaticArrow (first <$> f) newtype MyArr b c = MyArr (b -> c) instance Category MyArr instance Arrow MyArr repeat :: Int -> (Int -> MyArr e a) -> MyArr e a repeat = undefined func1 :: [Double] -> Double func1 = undefined job1 :: MyArr [Double] Double job1 = undefined job3 :: Int -> MyArr Double String job3 = undefined repeat' :: Int -> StaticArrow ((->) Int) MyArr e a -> MyArr e a repeat' n (StaticArrow f) = repeat n f test2 :: MyArr [Double] String test2 = proc xs -> do let y = func1 xs z <- job1 -< xs (|(repeat' 100) (do i <- StaticArrow (arr . const) -< () StaticArrow (\i -> job3 (i * 2)) -< xs !! i + y + z)|)

On Sun, Jul 15, 2012 at 6:30 PM, Ross Paterson
Silly me -- that code works with the current GHC (module attached).
Aha! Now I see why the GHC documentation states “the arrows involved need not be the same” in the section about banana brackets. After all, I was wrong in thinking that banana brackets could not be used here. As you remarked, the extraction of variable i in your code is a little bit involved, but it still looks much better than listing the local variables used in the inner computation, especially when both the outer computation and the inner computation involve many local variables. Thanks a lot. Best regards, Tsuyoshi

Ross Paterson
Though one possibility that might get us most of the way there would be to refactor the Arrow class as
class PreArrow a where premap :: (b -> b') -> a b' c -> a b c
Note that you are reinventing the 'profunctors' package here. Every arrow forms a profunctor with the following identities: lmap = flip (<<^) rmap = fmap or alternatively: rmap = (^<<) Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.
participants (3)
-
Ertugrul Söylemez
-
Ross Paterson
-
Tsuyoshi Ito