Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-17 Thread damodar kulkarni
Thanks again for the detailed and explanatory answer.

That's the reason I'm writing these huge responses, because I hope I can
> shorten this journey for others.
>

This has certainly helped me grasp some aspects in this regard.

While Monad Transformers are awesome and can solve many problems quite
> easily, I'm pretty sure that there is almost always a nicer, "more
> functional" way to solve such a problem.


Incidentally, I happened to bump in to this paper, it claims they have
found a way that allows us get rid of the need of monad transformers in a
more systematic manner, by using what they call "Monad coproduct". The
paper titled "Composing Monads Using Coproducts" is here. [1]

I haven't understood it much till now, and it seems I will have to try real
hard to read this paper.

Ref.
[1] http://isi.uni-bremen.de/~cxl/habil/papers/icfp02.pdf


Thanks and regards,
-Damodar Kulkarni
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-17 Thread David Menendez
On Sat, Aug 17, 2013 at 8:23 AM, Mathijs Kwik wrote:

> damodar kulkarni  writes:
>
> > Thanks for this nice analogy and explanation. This brings "monad
> > transformers" to my mind.
> > "without" monad transformers, the monads are bit crippled in their
> > applicability (please correct me if I am wrong)
> > and
> > "with" monad transformers the code becomes to some extent ugly (again,
> > please correct me if I am wrong)
> >
> > I wonder, where and how the Monad transformers fit in here?
>
> Well, I'm glad you all liked my explanation =)
>
> Let me first correct 1 stupid mistake I wrote in the first paragraph:
> - Every idiom is an arrow and every arrow is a monad, but not the other
>   way around.
> should obviously be:
> + Every Monad is an Arrow (with ArrowApply) and every Arrow is an Idiom,
>   but not the other way around.
>

Every Idiom defines a static arrow:

newtype Static f a b = Static (f (a -> b))

instance Applicative f => Arrow (Static f)


Similarly, every arrow defines an idiom:

newtype WrappedArrow a b c = WrappedArrow (a b c)

instance Arrow a => Applicative (WrappedArrow a b)


The difference is that WrappedArrow (Static f) () is essentially the same
as f, but Static (WrappedArrow a ()) is not necessarily the same as a.

Basically, if an arrow can be made an instance of ArrowDelay, then it is no
more powerful than an Idiom (meaning anything you can write using the arrow
combinators can also be written with just the Applicative combinators):

class Arrow a => ArrowDelay a where
delay :: a b c -> a () (b -> c)

-- 
Dave Menendez 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-17 Thread Mathijs Kwik
damodar kulkarni  writes:

> Thanks for this nice analogy and explanation. This brings "monad
> transformers" to my mind.
> "without" monad transformers, the monads are bit crippled in their
> applicability (please correct me if I am wrong)
> and
> "with" monad transformers the code becomes to some extent ugly (again,
> please correct me if I am wrong)
>
> I wonder, where and how the Monad transformers fit in here?

Well, I'm glad you all liked my explanation =)

Let me first correct 1 stupid mistake I wrote in the first paragraph:
- Every idiom is an arrow and every arrow is a monad, but not the other
  way around. 
should obviously be:
+ Every Monad is an Arrow (with ArrowApply) and every Arrow is an Idiom,
  but not the other way around.

Monad transformers are not really related to the subjects discussed thus
far, but through them I thought of 1 more distinction between Monad,
Arrow and Idiom that doesn't get mentioned often.

First I want to stress that Transformers are not some way to
uncripple/clean Monads. There is nothing unclean/cripple to begin
with. It's just that they lead to very dynamic assemble-on-the-go
factories, which does not seem to be necessary for most applications.

I should have pointed out the line that Dan Burton mentions as it is
really important. The idioms-arrows-monads paper words this as:
> monads allay the distinction between terms and commands
Which I pictured as workers reorganizing the factory, assembly-lines
arriving in a box and why not just package up the workers themselves to
deliver them to a spot they can start working.

Now, Monad transformers do not change anything about this, they are not
meant to lead this into more strict bounds or anything. There is no way
to do this anyway, given by the sheer fact that monads use (a -> m b), a
function, on every step, so anything can happen.


So what _are_ transformers for?
They are for composing Monads. Let's say we want to express a process
that can fail, but can deliver multiple values as well. Maybe [Int] for
example.

As a first thought we might try to just connect 2 factories, the list
factory and the maybe factory. First we'll find out that there is no
generic way to just connect 2 monadic factories, simply because there is
no generic way to get a value (box) out. Remember, all we have is
return :: a -> m a
fmap   :: (a -> b) -> m a -> m b -- inherited from Functor
(>>=)  :: m a (a -> m b) -> m b
So no generic way to get from (m a -> a). In other words, to look inside
a box, you have to be in the factory and promise to package up your
result in the same factory.

Even if we had such a magical way to connect 2 factories, it wouldn't do
us much good. If a box would roll from a State factory, to a Maybe
factory, then into another State factory, we end up with 2 different
state factories, both with their own "state cupboard", while the purpose
of state was to have something available during the entire process!
The same way, workers in List and State don't know how to signal/handle
failure (Maybe) and Maybe and State workers cannot handle
multiple-result boxes.

So instead of trying this, Monad Transformers allow you to build 1 big
factory, with - at every step - workers from all combined monads.
At any stage in the assembly line, those workers work together to share
their expertise. Envision them lined up behind each other, because their
order is very important. If the failure-dude (Maybe) is first in line
(next to the assembly line, he is the one opening boxes and packaging
results), with multi-answer-dude(List) behind him, the result is quite
different from doing it the other way around.
Possible results the first way:
- Just [12, 14]
- Nothing
Possible results the other way around:
- [Just 6, Nothing, Just 8]
- []
Basically every worker has a way of passing boxes to the workers
standing behind them, so they do not need to know about the special
effect. The List-worker will just unpack all values and repack them in
1-value boxes and hand them 1-by-1 to the worker behind. So for the
worker behind him, there is no way to know if these values came from 1
big multi-value box (List) or arrived one by one over the assembly line.
Maybe-guy removes Just when passing stuff backwards, and in case of
Nothing he just acts as if no boxes arrived. State guy might walk to the
cupboard before handing boxes backwards, you get the idea.
The way back works similar, Maybe guy just wraps Just around values,
List guy had to remember he gave 4 boxes backwards, so he waits for 4
results and packages them up in 1 multi-value box.

So, how do transformers get the workers to cooperate?
The main trick is to "upgrade" normal workers with 1 extra special
effect called "lift". For our factory this can be called "pass
backwards". So a program will basically have a number of "lift"
instructions at every step, to address the right worker in the line, so
an instruction like "get" is not gonna end up at Maybe-guy, who does not
know how to handle it.
This

Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread damodar kulkarni
Thanks for this nice analogy and explanation. This brings "monad
transformers" to my mind.
"without" monad transformers, the monads are bit crippled in their
applicability (please correct me if I am wrong)
and
"with" monad transformers the code becomes to some extent ugly (again,
please correct me if I am wrong)

I wonder, where and how the Monad transformers fit in here?

Thanks and regards,
-Damodar Kulkarni


On Sat, Aug 17, 2013 at 1:07 AM, Mathijs Kwik wrote:

> Thiago Negri  writes:
>
> > I just stumbled upon the Applicative term.
> > Arrows are quite difficult for me to understand at the moment.
> > I guess it needs time to digest.
> >
> > But, as I understand so far, Applicative and Arrows looks like the same
> > thing.
> >
> > Please, enlight me.
>
> I would like to point out this paper:
> http://homepages.inf.ed.ac.uk/slindley/papers/idioms-arrows-monads.pdf
>
> In short: arrows are a bit more powerful than idioms (applicative) but a
> bit less than monads. However, power sometimes comes at a price.
> All 3 have to do with combining / sequencing effects, but they differ in
> subtle but important ways. Every idiom is an arrow and every arrow is a
> monad, but not the other way around.
>
> I will first give an overview of the differences, then try to explain
> what I mean... (my terminology might be a bit awkward/wrong)
>
> Idiom:
> Basic combining strategy: i (a -> b) -> i a -> i b
> Sequencing: effects are applied in sequence
> values (stuff "inside") are isolated
> Shape depends on values: no
>
> Arrow:
> Basic combining strategy: a b c -> a c d -> a b d
> Sequencing: effects are applied in sequence
> values are sequenced too
> values can "see" upstream results
> Shape depends on values: static choices only
>
> Monad:
> Basic combining strategy: m a -> (a -> m b) -> m b
> Sequencing: effects are applied in sequence
> values are sequenced too
> values can "see" upstream results
> Shape depends on values: yes, fully dynamic
>
>
> Now, what do I mean by all this?
> Basically these 3 abstractions consist of 3 things:
> - effects
> - values
> - shape
> Effects can be things like "carries state around"(State), "can
> fail"(Maybe), "multiple answers"(List) and more. Values are the pure
> stuff "inside", and what I call 'shape' is the general control flow of a
> computation.
> Furthermore, I visualize these abstractions by thinking of a factory
> hall with boxes (values), people (effects) and an assembly line
> (shape).
>
>
> Idioms are fully static: values cannot see/depend on each other or on
> the result of effects. Basically the computation is split into 2 phases:
> - effects+gather
> - apply gathered results
> example:
> pure (+) <*> Just 3 <*> Just 5
> The first phase just works through the parts (in sequence) and collects
> the (pure) contents. In this case (Maybe) this means looking for the
> Just constructor to continue, or halting on Nothing. The content inside
> is being treated like a black box. It is not made aware of the effects
> (whether or not Nothing was found somewhere) and it is not being
> examined to choose a different codepath.
> Then if everything worked out (no Nothings were found), the collected
> results are taken out of their black boxes and applied. In this phase
> these results (the +, the 3 and the 5) don't know anything about the
> effects that happened.
>
> In "factory visualization": every part of the computation (stuff between
> <*>) is a person that will need to perform some task(effect) and deliver
> some result in a box. They will only start performing their task when
> they see a box passing by from the person upstream. They cannot look in
> that box or make decisions based on it or take it off. At the end of the
> line, some manager receives all the boxes and opens them to combine the
> results.
>
> This is fine for a whole lot of applications and has the advantage that
> the shape of the entire assembly line is clear even before starting
> it. This means (static) optimization can be performed and it's easy to
> reason about the program/costs. Garbage collection (sending workers
> home) is easier, because it's very clear what data is needed where and
> when. I will talk a bit more about these optimizations a bit further
> down. Of course this assembly line is not flexible enough for more
> advanced cases.
>
> Let's see an example of that(State):
> pure const <*> get <*> put 8
> This is a perfectly fine idiom, albeit not very useful.
> When run (with initial state 4) the first worker will package up a box
> with "const" and send it downstream. The second worker gets the seeded
> state from the "state cupboard" and put it in a box (4). When that box
> passes by worker 3, he will walk to the state cupboard and put 8 in
> it. Then to signal he's ready, he packs a box with (). At the end of the
> line, someone opens the boxes "const" "4" and "()", which computes to
> just 4. So we end up with the answer 4 and 

Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread Dan Burton
Reading that blog post Mathijs linked, I had a big "ah-hah" moment when I
read this:

This is why arrow-notation creates two scopes. Between the <- -< symbols,
> only values that were in scope before execution of the Arrow are in scope.
> Outside the <- -<, values that appear during the execution of the Arrow are
> also in scope.


This really helped solidify the idea in my head that the "shape of the
factory" only makes static choices, because all of the Arrow-y "processing"
happens between <- and -<


-- Dan Burton


On Fri, Aug 16, 2013 at 12:37 PM, Mathijs Kwik wrote:

> Thiago Negri  writes:
>
> > I just stumbled upon the Applicative term.
> > Arrows are quite difficult for me to understand at the moment.
> > I guess it needs time to digest.
> >
> > But, as I understand so far, Applicative and Arrows looks like the same
> > thing.
> >
> > Please, enlight me.
>
> I would like to point out this paper:
> http://homepages.inf.ed.ac.uk/slindley/papers/idioms-arrows-monads.pdf
>
> In short: arrows are a bit more powerful than idioms (applicative) but a
> bit less than monads. However, power sometimes comes at a price.
> All 3 have to do with combining / sequencing effects, but they differ in
> subtle but important ways. Every idiom is an arrow and every arrow is a
> monad, but not the other way around.
>
> I will first give an overview of the differences, then try to explain
> what I mean... (my terminology might be a bit awkward/wrong)
>
> Idiom:
> Basic combining strategy: i (a -> b) -> i a -> i b
> Sequencing: effects are applied in sequence
> values (stuff "inside") are isolated
> Shape depends on values: no
>
> Arrow:
> Basic combining strategy: a b c -> a c d -> a b d
> Sequencing: effects are applied in sequence
> values are sequenced too
> values can "see" upstream results
> Shape depends on values: static choices only
>
> Monad:
> Basic combining strategy: m a -> (a -> m b) -> m b
> Sequencing: effects are applied in sequence
> values are sequenced too
> values can "see" upstream results
> Shape depends on values: yes, fully dynamic
>
>
> Now, what do I mean by all this?
> Basically these 3 abstractions consist of 3 things:
> - effects
> - values
> - shape
> Effects can be things like "carries state around"(State), "can
> fail"(Maybe), "multiple answers"(List) and more. Values are the pure
> stuff "inside", and what I call 'shape' is the general control flow of a
> computation.
> Furthermore, I visualize these abstractions by thinking of a factory
> hall with boxes (values), people (effects) and an assembly line
> (shape).
>
>
> Idioms are fully static: values cannot see/depend on each other or on
> the result of effects. Basically the computation is split into 2 phases:
> - effects+gather
> - apply gathered results
> example:
> pure (+) <*> Just 3 <*> Just 5
> The first phase just works through the parts (in sequence) and collects
> the (pure) contents. In this case (Maybe) this means looking for the
> Just constructor to continue, or halting on Nothing. The content inside
> is being treated like a black box. It is not made aware of the effects
> (whether or not Nothing was found somewhere) and it is not being
> examined to choose a different codepath.
> Then if everything worked out (no Nothings were found), the collected
> results are taken out of their black boxes and applied. In this phase
> these results (the +, the 3 and the 5) don't know anything about the
> effects that happened.
>
> In "factory visualization": every part of the computation (stuff between
> <*>) is a person that will need to perform some task(effect) and deliver
> some result in a box. They will only start performing their task when
> they see a box passing by from the person upstream. They cannot look in
> that box or make decisions based on it or take it off. At the end of the
> line, some manager receives all the boxes and opens them to combine the
> results.
>
> This is fine for a whole lot of applications and has the advantage that
> the shape of the entire assembly line is clear even before starting
> it. This means (static) optimization can be performed and it's easy to
> reason about the program/costs. Garbage collection (sending workers
> home) is easier, because it's very clear what data is needed where and
> when. I will talk a bit more about these optimizations a bit further
> down. Of course this assembly line is not flexible enough for more
> advanced cases.
>
> Let's see an example of that(State):
> pure const <*> get <*> put 8
> This is a perfectly fine idiom, albeit not very useful.
> When run (with initial state 4) the first worker will package up a box
> with "const" and send it downstream. The second worker gets the seeded
> state from the "state cupboard" and put it in a box (4). When that box
> passes by worker 3, he will walk to the state cupboard and put 8 in
> it. Then to signal he's ready, he packs a box with (). At the end of the
> line,

Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread Albert Y. C. Lai

On 13-08-16 03:29 PM, Dan Burton wrote:

Idioms are oblivious, arrows are meticulous, monads are promiscuous
http://homepages.inf.ed.ac.uk/wadler/papers/arrows-and-idioms/arrows-and-idioms.pdf


I much recommend this paper. Underrated, underknown, pinpointing, unifying.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread Thiago Negri
You just made my day.
I was trying to understand these things so hard and couldn't get it.
Your analogies were brilliant.

I'll read all links/papers posted here to get a deeper understanding of
these things.
I'll just skip dependently typed stuff for now, heh.

Thank you,
Thiago.



2013/8/16 Mathijs Kwik 

> Thiago Negri  writes:
>
> > I just stumbled upon the Applicative term.
> > Arrows are quite difficult for me to understand at the moment.
> > I guess it needs time to digest.
> >
> > But, as I understand so far, Applicative and Arrows looks like the same
> > thing.
> >
> > Please, enlight me.
>
> I would like to point out this paper:
> http://homepages.inf.ed.ac.uk/slindley/papers/idioms-arrows-monads.pdf
>
> In short: arrows are a bit more powerful than idioms (applicative) but a
> bit less than monads. However, power sometimes comes at a price.
> All 3 have to do with combining / sequencing effects, but they differ in
> subtle but important ways. Every idiom is an arrow and every arrow is a
> monad, but not the other way around.
>
> I will first give an overview of the differences, then try to explain
> what I mean... (my terminology might be a bit awkward/wrong)
>
> Idiom:
> Basic combining strategy: i (a -> b) -> i a -> i b
> Sequencing: effects are applied in sequence
> values (stuff "inside") are isolated
> Shape depends on values: no
>
> Arrow:
> Basic combining strategy: a b c -> a c d -> a b d
> Sequencing: effects are applied in sequence
> values are sequenced too
> values can "see" upstream results
> Shape depends on values: static choices only
>
> Monad:
> Basic combining strategy: m a -> (a -> m b) -> m b
> Sequencing: effects are applied in sequence
> values are sequenced too
> values can "see" upstream results
> Shape depends on values: yes, fully dynamic
>
>
> Now, what do I mean by all this?
> Basically these 3 abstractions consist of 3 things:
> - effects
> - values
> - shape
> Effects can be things like "carries state around"(State), "can
> fail"(Maybe), "multiple answers"(List) and more. Values are the pure
> stuff "inside", and what I call 'shape' is the general control flow of a
> computation.
> Furthermore, I visualize these abstractions by thinking of a factory
> hall with boxes (values), people (effects) and an assembly line
> (shape).
>
>
> Idioms are fully static: values cannot see/depend on each other or on
> the result of effects. Basically the computation is split into 2 phases:
> - effects+gather
> - apply gathered results
> example:
> pure (+) <*> Just 3 <*> Just 5
> The first phase just works through the parts (in sequence) and collects
> the (pure) contents. In this case (Maybe) this means looking for the
> Just constructor to continue, or halting on Nothing. The content inside
> is being treated like a black box. It is not made aware of the effects
> (whether or not Nothing was found somewhere) and it is not being
> examined to choose a different codepath.
> Then if everything worked out (no Nothings were found), the collected
> results are taken out of their black boxes and applied. In this phase
> these results (the +, the 3 and the 5) don't know anything about the
> effects that happened.
>
> In "factory visualization": every part of the computation (stuff between
> <*>) is a person that will need to perform some task(effect) and deliver
> some result in a box. They will only start performing their task when
> they see a box passing by from the person upstream. They cannot look in
> that box or make decisions based on it or take it off. At the end of the
> line, some manager receives all the boxes and opens them to combine the
> results.
>
> This is fine for a whole lot of applications and has the advantage that
> the shape of the entire assembly line is clear even before starting
> it. This means (static) optimization can be performed and it's easy to
> reason about the program/costs. Garbage collection (sending workers
> home) is easier, because it's very clear what data is needed where and
> when. I will talk a bit more about these optimizations a bit further
> down. Of course this assembly line is not flexible enough for more
> advanced cases.
>
> Let's see an example of that(State):
> pure const <*> get <*> put 8
> This is a perfectly fine idiom, albeit not very useful.
> When run (with initial state 4) the first worker will package up a box
> with "const" and send it downstream. The second worker gets the seeded
> state from the "state cupboard" and put it in a box (4). When that box
> passes by worker 3, he will walk to the state cupboard and put 8 in
> it. Then to signal he's ready, he packs a box with (). At the end of the
> line, someone opens the boxes "const" "4" and "()", which computes to
> just 4. So we end up with the answer 4 and an updated cupboard
> containing 8.
>
> Why is this not very useful? Well we would probably want to be able to
> put state in that depends on certain stuff we g

Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread Mathijs Kwik
Thiago Negri  writes:

> I just stumbled upon the Applicative term.
> Arrows are quite difficult for me to understand at the moment.
> I guess it needs time to digest.
>
> But, as I understand so far, Applicative and Arrows looks like the same
> thing.
>
> Please, enlight me.

I would like to point out this paper:
http://homepages.inf.ed.ac.uk/slindley/papers/idioms-arrows-monads.pdf

In short: arrows are a bit more powerful than idioms (applicative) but a
bit less than monads. However, power sometimes comes at a price.
All 3 have to do with combining / sequencing effects, but they differ in
subtle but important ways. Every idiom is an arrow and every arrow is a
monad, but not the other way around.

I will first give an overview of the differences, then try to explain
what I mean... (my terminology might be a bit awkward/wrong)

Idiom:
Basic combining strategy: i (a -> b) -> i a -> i b
Sequencing: effects are applied in sequence
values (stuff "inside") are isolated
Shape depends on values: no

Arrow:
Basic combining strategy: a b c -> a c d -> a b d
Sequencing: effects are applied in sequence
values are sequenced too
values can "see" upstream results
Shape depends on values: static choices only

Monad:
Basic combining strategy: m a -> (a -> m b) -> m b
Sequencing: effects are applied in sequence
values are sequenced too
values can "see" upstream results
Shape depends on values: yes, fully dynamic


Now, what do I mean by all this?
Basically these 3 abstractions consist of 3 things: 
- effects
- values
- shape
Effects can be things like "carries state around"(State), "can
fail"(Maybe), "multiple answers"(List) and more. Values are the pure
stuff "inside", and what I call 'shape' is the general control flow of a
computation. 
Furthermore, I visualize these abstractions by thinking of a factory
hall with boxes (values), people (effects) and an assembly line
(shape).


Idioms are fully static: values cannot see/depend on each other or on
the result of effects. Basically the computation is split into 2 phases:
- effects+gather
- apply gathered results
example:
pure (+) <*> Just 3 <*> Just 5
The first phase just works through the parts (in sequence) and collects
the (pure) contents. In this case (Maybe) this means looking for the
Just constructor to continue, or halting on Nothing. The content inside
is being treated like a black box. It is not made aware of the effects
(whether or not Nothing was found somewhere) and it is not being
examined to choose a different codepath.
Then if everything worked out (no Nothings were found), the collected
results are taken out of their black boxes and applied. In this phase
these results (the +, the 3 and the 5) don't know anything about the
effects that happened.

In "factory visualization": every part of the computation (stuff between
<*>) is a person that will need to perform some task(effect) and deliver
some result in a box. They will only start performing their task when
they see a box passing by from the person upstream. They cannot look in
that box or make decisions based on it or take it off. At the end of the
line, some manager receives all the boxes and opens them to combine the
results.

This is fine for a whole lot of applications and has the advantage that
the shape of the entire assembly line is clear even before starting
it. This means (static) optimization can be performed and it's easy to
reason about the program/costs. Garbage collection (sending workers
home) is easier, because it's very clear what data is needed where and
when. I will talk a bit more about these optimizations a bit further
down. Of course this assembly line is not flexible enough for more
advanced cases.

Let's see an example of that(State):
pure const <*> get <*> put 8
This is a perfectly fine idiom, albeit not very useful.
When run (with initial state 4) the first worker will package up a box
with "const" and send it downstream. The second worker gets the seeded
state from the "state cupboard" and put it in a box (4). When that box
passes by worker 3, he will walk to the state cupboard and put 8 in
it. Then to signal he's ready, he packs a box with (). At the end of the
line, someone opens the boxes "const" "4" and "()", which computes to
just 4. So we end up with the answer 4 and an updated cupboard
containing 8.

Why is this not very useful? Well we would probably want to be able to
put state in that depends on certain stuff we got out earlier, instead
of just supplying a hard coded 8 that was known before starting the
line. Unfortunately, this is not possible with idioms as workers cannot
open each other's boxes.


Now, let's skip Arrows for a minute and move straight to Monads:


get >>= \x -> put (x + 1) >> return x
As you can see, monads tackle this issue by putting everything in
sequence. Not just the effects, but values too. Like this, they can
"see" upstream values and upstream effects and influence the effects and
sh

Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread Dan Burton
You may be interested in this paper:

Idioms are oblivious, arrows are meticulous, monads are promiscuous
http://homepages.inf.ed.ac.uk/wadler/papers/arrows-and-idioms/arrows-and-idioms.pdf

"Idioms" refers to the Applicative class.

To put it briefly, if you have an instance of Arrow, you also have an
automatic instance for Applicative, which I brought up about a month ago on
reddit:
http://www.reddit.com/r/haskell/comments/1ivd23/default_functor_and_applicative_instances_for/


-- Dan Burton


On Fri, Aug 16, 2013 at 7:52 AM, Brandon Allbery wrote:

> On Fri, Aug 16, 2013 at 10:49 AM, Tom Ellis <
> tom-lists-haskell-cafe-2...@jaguarpaw.co.uk> wrote:
>
>> On Fri, Aug 16, 2013 at 10:26:42AM -0400, Brandon Allbery wrote:
>> > My understanding is that there's a rework of Arrow in progress that may
>> > change this in the future, since *theoretical* Arrows are more distinct,
>> > flexible and useful than the current implementation.
>>
>> I'd like to know more about that if you can provide any references.  I am
>> using
>> arrows very heavily.
>>
>
> It's been mentioned (but not much more) in #haskell IRC, so I don't know
> details. I also expect it's not going to simply replace the current one, at
> least not initially; and I think it's supposed to maintain compatibility
> with the current Arrow because that's just a specialization to the function
> arrow.
>
> --
> brandon s allbery kf8nh   sine nomine
> associates
> allber...@gmail.com
> ballb...@sinenomine.net
> unix, openafs, kerberos, infrastructure, xmonad
> http://sinenomine.net
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread Brandon Allbery
On Fri, Aug 16, 2013 at 10:49 AM, Tom Ellis <
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk> wrote:

> On Fri, Aug 16, 2013 at 10:26:42AM -0400, Brandon Allbery wrote:
> > My understanding is that there's a rework of Arrow in progress that may
> > change this in the future, since *theoretical* Arrows are more distinct,
> > flexible and useful than the current implementation.
>
> I'd like to know more about that if you can provide any references.  I am
> using
> arrows very heavily.
>

It's been mentioned (but not much more) in #haskell IRC, so I don't know
details. I also expect it's not going to simply replace the current one, at
least not initially; and I think it's supposed to maintain compatibility
with the current Arrow because that's just a specialization to the function
arrow.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread Tom Ellis
On Fri, Aug 16, 2013 at 10:26:42AM -0400, Brandon Allbery wrote:
> My understanding is that there's a rework of Arrow in progress that may
> change this in the future, since *theoretical* Arrows are more distinct,
> flexible and useful than the current implementation.

I'd like to know more about that if you can provide any references.  I am using
arrows very heavily.

Tom

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread Brandon Allbery
On Fri, Aug 16, 2013 at 10:04 AM, Thiago Negri  wrote:

> I just stumbled upon the Applicative term.
> Arrows are quite difficult for me to understand at the moment.
> I guess it needs time to digest.
>
> But, as I understand so far, Applicative and Arrows looks like the same
> thing.
>

Practically, that's not too far off. Arrows, at least as implemented
currently, have a number of significant restrictions based on the need for
the `arr` combinator to accomplish much of anything; Applicative has, as a
result, largely taken over the spot in the Haskell ecosystem that Arrow was
originally intended to fill.

My understanding is that there's a rework of Arrow in progress that may
change this in the future, since *theoretical* Arrows are more distinct,
flexible and useful than the current implementation.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread satvik chauhan
Whenever I am confused I refer to this article

http://www.haskell.org/haskellwiki/Typeclassopedia#Arrow

-Satvik


On Fri, Aug 16, 2013 at 7:34 PM, Thiago Negri  wrote:

> I just stumbled upon the Applicative term.
> Arrows are quite difficult for me to understand at the moment.
> I guess it needs time to digest.
>
> But, as I understand so far, Applicative and Arrows looks like the same
> thing.
>
> Please, enlight me.
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread Thiago Negri
I just stumbled upon the Applicative term.
Arrows are quite difficult for me to understand at the moment.
I guess it needs time to digest.

But, as I understand so far, Applicative and Arrows looks like the same
thing.

Please, enlight me.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe