[Haskell-cafe] Applicative is like an Arrow

Mathijs Kwik mathijs at bluescreen303.nl
Sat Aug 17 14:23:01 CEST 2013


damodar kulkarni <kdamodar2000 at gmail.com> 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 is exactly where the "transformers" package leaves us.
Pure transformers-using code will indeed be a bit ugly because of the
lifts everywhere. Of course if you know State-guy is third in line you
can alias get' = lift . lift $ get
But with a lot of effectful functions, this gets ugly too.
Fortunately, Haskell's type system is smart enough to be able to figure
these things out itself, but it needs an extension like type-families or
functional-dependencies to do so. That's why the transformers concept
was split into multiple packages. "transformers" is pure haskell98, so
lift everything yourself. "mtl" uses functional dependencies to
"automatically" build appropriately lifted versions of effectful
functions, and lastly "monads-tf" does the same thing, but using type
families. This distinction does not matter much, the main idea is that
some day functional dependencies might not be needed (and removed from
the language), having type families as full blown alternative, but don't
expect this to happen before 2020 :)

This is all nice, but gets messy when you have 2 Maybe guys in the same
stack, or - perhaps more commonly - 2 Reader guys or 2 State guys. The
type system cannot figure out which of the 2 is being addressed, so you
have to manually lift once again.

One last word about the "upgrade" (List to ListT, Maybe to MaybeT)...
The stack has to end with a "normal" guy (without lift), so you can use
ListT Maybe, or MaybeT List. But since you would probably like to be
able to shuffle the line order a bit without changing the "special" T
status of the people in it, there's a useful (Control.Monad.)Identity
worker, whose sole purpose is to be not special, so he can stand at the
end of a line, so we can swap ListT MaybeT Identity to MaybeT ListT
Identity, without adding/removing any special powers.
In a way, we could say that List is just ListT Identity and Maybe is
just MaybeT Identity, but to keep sources/ideas somewhat readable the
prelude just uses ordinary simple versions.



Now, you might not be surprised to learn that there are also Arrow
Transformers, provided by the "arrows" package. They work almost the
same way (lift), but chose not to split up the package to a haskell98
part, so it's all in one with automagically applied lifting.



Before looking at combining Idioms, please consider this:
If you think transformers are somewhat scary and feel a bit like a
workaround with artificial "lift" all over the place, you are right!
This is not to say they are not a brilliant finding or that they are
expensive (compiler is smart), and surely I use them a lot too. But they
still make up for the fact that Monads or Arrows, by themselves, are
*not* composable.
So indeed, to be generally useful, a Monad author has to provide a Monad
Transformer instance as well. And this instance is specially tailored
for his structure, not a generic "oh, and add transformability" spell.



So how do Idioms do? Very fine, thank you :)
I hope email does not mess this up...

newtype Cmp f g a = Cmp { dc :: f (g a) } deriving (Show)

instance (Functor f, Functor g) => Functor (Cmp f g) where
    fmap f = Cmp . fmap (fmap f) . dc

instance (Applicative f, Applicative g) => Applicative (Cmp f g) where
    pure = Cmp . pure . pure
    a <*> b = Cmp $ liftA2 (<*>) (dc a) (dc b)
newtype Cmp f g a = Cmp { dc :: f (g a) } deriving (Show)

instance (Functor f, Functor g) => Functor (Cmp f g) where
    fmap f = Cmp . fmap (fmap f) . dc

instance (Applicative f, Applicative g) => Applicative (Cmp f g) where
    pure = Cmp . pure . pure
    a <*> b = Cmp $ liftA2 (<*>) (dc a) (dc b)

See? A generic Cmp (compose) that is able to compose any 2 Applicatives
without altering them or giving them special lifting powers.

type MaybeList a = Cmp [] Maybe a
type ListMaybe a = Cmp Maybe [] a

So, after all we did find an advantage that idioms have over arrows :)



To wrap up... some "newbie advice"
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. For me, using Haskell (and FP
in general) is about limiting possibilities to rule out edge cases and
to gain more insights into your code and problem domain. That's why
haskell does not have mutable state all over the place and does not
allow IO everywhere.
With Monad Transformers it becomes all too easy to just figure out "what
do I need for this program?", throw together a big monad Transformer
that has State, IO, error handling, some Reader for config stuff, and
then write your whole program in it.
While even this is a multitude of times better than using an imperative
language, you will miss out on all the good parts and you will find out
the code is not very reusable. They are fine for a "top level" program
definition to lay out the different parts and wire them up. But don't
let them bubble all the way down. In the end, you are still programming
this step-by-step factory with the wacky
let-the-workers-reorganize-whatever-they-like policy, and by adding
(even implicitly) the lift-lift-lift behavior of monad transformers, it
even more feels like some strange virtual machine that you are
"commanding", while you should be "describing".

I remember my journey for answers about these same subjects (control
flow, program layout) and how hard it is to get a good understanding and
come up with analogies that work. That's the reason I'm writing these
huge responses, because I hope I can shorten this journey for others.
In short I would say: Idioms are beautiful, and "small". If they suffice
for (part of) a problem: use them.
Arrows: I think there is a lot more to these we still need to find out,
but for some reason I find them not very elegant (syntax is probably a
reason) and a lot of people/libraries seem to focus more on monads, so
you always feel left out when you use arrows. Still, interesting to use
every now and then and for some problem domains (like FRP) they feel
more suitable.
Monads (+ transformers): use them when you need to get something done
that you would know how to do in an imperative language. Deadline? use
monads, they feel natural when you come from other languages. Just take
some time afterwards to explore alternatives because in the end you can
do without this crazy virtual-machine factory.

So what do I recommend as alternatives? That, I cannot say.
There is no single silver-bullet, the main point is to keep exploring,
I learned a lot from trying to grasp the basics of category theory
(which I still don't understand at all, but it gave me insights after
all), found that algebras (especially f-algebras), catamorphisms
(generic folds) can be tools to get the same behaviors that transformers
provide. This is strange at first, because they seem subjects that are
related to data structures, but you will quickly develop insights that
teach you that with functional programming there is no distinction
between data structures and control flow and you should embrace this. Of
course you already see this a bit when using the List monad, it's far
more about trying multiple solutions than about lists. Maybe is not
about "adding failure to a type", but about a terminate-early control
flow. Well, you can take this a step further when you realize your
entire program/problem is just some DSL in your head that you can
express as a syntax tree (AST). Hey, that's data you can walk over :)
Many times when you think you need state, you actually have a future
function with a hole in it. Try a continuation passing style sometime.
All these things, combined with haskell's laziness let you express
things that are almost magic, but are a far more clear specification of
what you actually want to describe. In other words: the journey only
starts when you look past step-by-step monadic code.

2 nice links that can help develop feeling with those subjects:
- http://www.cs.uu.nl/wiki/pub/Center/CompilerConstructionInHaskell/C11-AG-icfp2012.pdf
  first chapter about attribute grammars talks about a different way to
  compose all kinds of aspects of a program and shows how some monads
  (reader/writer/state) are actually embedded into these lazy-folds.
- http://matthew.brecknell.net/post/btree-gadt/
  nice video tutorial showing how some new type system extensions help
  produce better code, while writing less checks and caring less about
  edge cases. The reason I mention it here is because it uses
  continuation-passing-style in a few key places, where my natural
  feeling would have come up with some ugly state-like solution.
  Don't feel bad if you have to pause the video a lot =)

Regards,
Mathijs






>
> Thanks and regards,
> -Damodar Kulkarni
>
>
> On Sat, Aug 17, 2013 at 1:07 AM, Mathijs Kwik <mathijs at bluescreen303.nl>wrote:
>
>> Thiago Negri <evohunz at gmail.com> 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
>> shape of things to come further "downstream".
>> Another example (State again):
>>
>> do x <- get
>>    if x > 100
>>      then do put 0
>>              return "overflow"
>>      else do put (x+1)
>>              executeBatch x
>>              return "normal operation"
>>
>> This example shows nicely how the entire shape is dynamically chosen
>> when using a Monad, influencing both which effects will apply (will the
>> batch job run?) and result (status string).
>>
>> But let's look a bit closer at how Monad performs this trick:
>> get >>= (\x -> put (x + 1) >>= (\_ -> return x))
>> get >>= (\x ->
>>   if x > 100 then (put 0 >>= (\_ -> return "overflow"))
>>              else (put (x+1) >>= (\_ ->
>>                     executeBatch x >>= (\_ ->
>>                     return "normal operation"))))
>> I've added parentheses to clearly show the "parts" involved.
>> Basically both these cases look like
>> get >>= xyz  (only 2 parts, get and some unknown xyz)
>> So what can we say about xyz? Not a whole lot. xyz is a function that
>> will return a new monadic value when given an input. But we cannot
>> really statically inspect a function without applying it to an input
>> value. So basically we don't know what will happen next until we are
>> already running.
>>
>> To look at it from the factory-visualization perspective, we have
>> divided the assembly-line into a lot of separate parts. Worker 1 gets
>> the state from the state cupboard and puts it on the line. But the line
>> is very short and just flows to worker 2. Worker 2 then receives the
>> box, opens it and then starts to reorganize the factory to proceed. He
>> might need to place new pieces of assemly-line to new parts of the
>> factory, phone workers to come to work, whatever. Basically the entire
>> factory is 1 big black box except for the task/effect of worker 1.
>>
>> This is extremely powerful, as worker 2 can decide truly dynamically
>> what to do. But we lose our possibility to optimize things at compile
>> time and to reason about the shape and possible outcomes from the
>> language itself. Sure, by looking at the sources we (and the compiler)
>> can figure out a bit about what's going on, but far less well than with
>> idioms, as things really depend on runtime inputs now.
>>
>>
>>
>> Now, let's look at Arrows and how they tackle the same problem:
>>
>> get >>> arr (\x -> (x + 1, x) ) >>> first put >>> arr snd
>> or using arrow syntax:
>> proc _ -> do
>>   r <- get -< ()
>>   put -< r + 1
>>   returnA -< r
>> In factory-visualization: workers can look inside each other's boxes or
>> take them off the line.
>> Worker 1 gets the state from the cupboard and puts it in a box.
>> Worker 2 looks at this box, calculates +1 and updates the state
>> cupboard.
>> When we run this, starting with 4 in the state cupboard, we get back the
>> result (4) at the end of the line, while the state cupboard now contains
>> 5 (a value that depended on a previous effect, which was not possible
>> with idioms). So what's up with these "arr" and tuples and
>> first/seconds/fst/snd parts in the normal (non-arrow) notation? I like
>> to think of it as flow control for the assembly line. Like tags being
>> put on the boxes to indicate which co-worker they are meant for. Simple
>> robotic parts of the line (arr snd) just throw out boxes that aren't
>> needed anymore so they don't have to travel all the way to the end of
>> the line.
>>
>> So from this example it's clear that arrows have some extra power over
>> idioms, without sacrificing the clarity of the entire factory-flow.
>> All static optimizations that are possible with idioms should still work
>> with arrows, so basically I think they are just plain better from all
>> technical points of view. But syntactically I cannot stand them :)
>> Shuffling tuples around constructing, deconstructing them everywhere
>> just doesn't lead to readable code and I'm not 100% sure that the
>> compiler can fully optimize them away. Arrow syntax helps a lot, but
>> compared to an elegant idiom (especially if you have idiom brackets
>> available like in idris or using SHE) it's just ugly.
>>
>> So how about making dynamic choices based on box contents?
>> This is possible using ArrowChoice. The existence of this separate class
>> probably implies that ArrowChoice cannot always be implemented for every
>> Arrow, but it might just be that the designers of the Arrow classes
>> wanted to keep things as modular as possible.
>>
>> I'm not going into the technical details of ArrowChoice (it's a bunch of
>> box labeling tricks once again) but in factory-visualization there is a
>> big difference between the if-then-else within Monad and the
>> if-then-else in Arrow. Remember, for Monad, after making the choice, the
>> rest of the factory had to be reorganized and connected before we could
>> continue. We, the programmers knew there were only 2 possible outcomes,
>> but at runtine everything was handled as if any random new factory setup
>> should be possible.
>> With Arrows, we can nicely see (before starting) that a certain part of
>> the assembly line will make a choice. It has 2 lines flowing from it so
>> it's clear that at runtime the worker will have to place the boxes on 1
>> of these continuation lines. We can reason about both situations and see
>> the remaining layout of the factory and reason about that too. At
>> runtime it remains static. No moving heavy machinery around.
>>
>> I think that in 99% of all situations, this solution is way more elegant
>> than the monad solution. The full-dynamism that monads add really sounds
>> like overkill. Looking at most code, the possible code-paths *are* known
>> beforehand (to programmers), so it's a shame that knowledge gets
>> destroyed by monads by using a function (a -> m b) to "bind" the parts.
>>
>> However, in haskell, there are many nice libraries that provide monadic
>> interfaces and not a lot that have Arrow+ArrowChoice. Even when they
>> would be perfectly suitable and the dynamics of monad aren't needed.
>> So because of this, if you need a few of these libraries for your
>> application, you stick to monads, because you don't want to end up with
>> many different syntaxes everywhere.
>>
>>
>> Ok, nearing the end. This got a bit bigger than I planned =)
>>
>>
>> Yet another view at the arrow -> monad difference:
>>
>> class Arrow a => ArrowApply a where
>>     app :: a (a b c, b) c
>>
>> ArrowApply is "the last step". If your arrow can implement ArrowApply
>> you basically are a monad and you've lost the nice static properties
>> that idiom and arrow gave. It's quite clear from the signature of 'app'
>> why this is. In this representation it's not a worker himself that
>> starts to reorganize the entire factory when he receives his input. In
>> this case he just receives a rather big box containing an entire new
>> assembly line to be placed in the next part of the factory, and a small
>> box to put into that new line. See? The same dynamism from an even more
>> extreme point of view :)
>>
>>
>> Another thing I want to point out, because it's closely related:
>> Alternative/ArrowPlus/MonadPlus
>> These provide the assembly lines with another form of
>> choice/combination. Of course you should note that not every
>> idiom(Applicative) is an Alternative, and the same is true for Arrow and
>> Monad. They all work when the effect has some notion of emptiness and
>> there is some way to combine stuff (Monoid). For Maybe, empty is Nothing
>> and when we have something (Just) we feel no need to combine. For lists,
>> [] is empty and combining is just concatenation.
>> So why do I mention this at all? Because it can act like a kind of
>> choice (if/then/else) or as a way to traverse multiple codepaths, which
>> is especially useful for idioms, as we've just seen these have no
>> native ways to do this. Of course you have to remember that this isn't
>> really a dynamic choice "inside". But it's not completely steered from
>> outside of the factory either. It's somewhat nicely halfway and of
>> course limited to "is it empty? / did it succeed?" type of choices only,
>> but in many cases (parsing for example) it can just give idioms that
>> extra boost it misses, without having to move to arrows/monads.
>> I haven't bothered thinking of a factory-visualization analogy for these
>> yet, because I'm afraid nobody wants to work there anymore if they have
>> to worry of Monoids sneaking around.
>>
>>
>>
>> Lastly: what about these static optimizations I keep mentioning?
>> It is explained in http://www.cse.chalmers.se/~rjmh/Papers/arrows.pdf
>> chapter 3.
>> Another nice example, which is more about reasoning about code:
>> http://blog.downstairspeople.org/2010/06/14/a-brutal-introduction-to-arrows
>>
>> Both examples build up static information about a computation/assembly
>> line without starting it yet. This information can then be used to
>> optimize certain parts (not run an expensive computation if we already
>> know the outcome), combine parts (do 2 things at once if we know they
>> are closely related) or to refuse to run at all unless certain
>> conditions (performance/security) aren't met.
>>
>>
>> But while having worked with dependently typed languages for some time
>> now, both these examples feel redundant in a way.
>> They both just combine a piece of static data with some dynamic data
>> (function). Then on startup, they collapse the static stuff, act upon
>> what they've learned(optimize,report back) and leave the dynamic part as
>> a result, to run. So in a way they are all about an ordinary function,
>> with some fancy extra knowledge about it that needs to be stored
>> somewhere, and a phase where this knowledge is used to deliver an
>> optimized runtime thingy. Sounds an awful lot like what compilers do,
>> right?  Now, when these cases were worked out, haskell's type system was
>> not sufficient to store the static knowledge and to apply it, but
>> currently, with all modern extensions it's getting awfully close, if
>> it's not there already.
>>
>> So perhaps in the near future, we can just supply Monad with advanced
>> static knowledge+reasoning to give it all the nice properties that arrow
>> and idiom have.
>>
>> Have a nice weekend,
>> Mathijs
>>
>>
>> > _______________________________________________
>> > Haskell-Cafe mailing list
>> > Haskell-Cafe at haskell.org
>> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>




More information about the Haskell-Cafe mailing list