[Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-15 Thread Ertugrul Soeylemez
"Apfelmus, Heinrich"  wrote:

> [...] but this is very different from using a particular monad like
> the state monad and hoping that using it somehow gives an insight into
> the problem domain.

You're right, mostly.  However, there are a lot of problems, where you
cannot provide any useful abstraction, or the abstraction would destroy
the convenience and clarity of expressing the problem as something as
simple as a stateful computation.

The 'insight' into a problem often comes from expressing its solution,
not the problem itself.  Please consider that I'm talking about
real-world applications, so my problems are things like internal
database servers.  Of course, there may be better ways to model such a
thing, but a 'StateT (Map a b) IO' computation is the way to go for
someone, who wants to get the job done rather than doing research, and
in fact I think this is a very beautiful and elegant approach exploiting
Haskell's (or at least GHC's) great RTS features.


Greets,
Ertugrul.


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://blog.ertes.de/


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


[Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-15 Thread Apfelmus, Heinrich
Ertugrul Soeylemez wrote:
> [...]

Thank you for your reply, I think I can refine my thoughts. And make
them much longer... ;)


The elegance I have in mind comes from abstraction, that is when a type
takes a meaning on its own, independent of its implementation. Let's
take the example of vector graphics again

  data Graphic

  empty   :: Graphic
  polygon :: [Point] -> Graphic
  over:: Graphic -> Graphic -> Graphic

All primitives can be explained in terms of our intuition on pictures
alone; it is completely unnecessary to know that  Graphic  is implemented as

  type Graphics = Window -> IO ()

  empty  = \w -> return ()
  polygon (p:ps) = \w -> moveTo p w >> mapM_ (\p -> lineTo p w) ps
  over g1 g2 = \w -> g1 w >> g2 w

Furthermore, this independence is often exemplified by the existence of
many different implementations. For instance,  Graphics  can as well be
written as

  type Graphics = Pixel -> Color

  empty  = const Transparent
  polygon (p:ps) = foldr over empty $ zipWith line (p:ps) ps
  over g1 g2 = \p -> if g1 p == Transparent then g2 p else g1 p

Incidentally, this representation also makes a nice formalization of the
intuitive notion of pictures, making it possible to verify the
correctness of other implementations. Of course, taking it as definition
for  Graphic  would still fall short of the original goal of creating
meaning independent of any implementation. But this can be achieved by
stating the laws that relate the available operations. For instance, we have

 g = empty `over` g = g `over` empty  (identity element)
  g `over` (h `over` j) = (g `over` h) `over` j   (associativity)
 g `over` g = g   (idempotence)

The first two equations say that  Graphics  is a monoid. Abstraction and
equational laws are the cornerstones of functional programming. For
more, see also the following classics

  John Hughes. The Design of a Pretty-printing Library.
  http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.38.8777

  Philip Wadler. A prettier printer.
  http://homepages.inf.ed.ac.uk/wadler/topics/
language-design.html#prettier

  Richard Bird. A program to solve Sudoku
  Slides: http://icfp06.cs.uchicago.edu/bird-talk.pdf


(From this point of view, the feature of non-pure languages to allow
side effects in every function is useless and distracting. Why on earth
would I want  over  to potentially have side effects? That would just
invalidate the laws while offering nothing in return.)

> Often, the monadic solution _is_ the elegant solution.  Please don't
> confuse monads with impure operations.  I use the monadic properties of
> lists, often together with monad transformers, to find elegant
> solutions.  As long as you're not abusing monads to program
> imperatively, I think, they are an excellent and elegant structure.
>
> I do use state monads where there is no more elegant solution than passing
> state around.  It's simply that:  you have a structure, which you modify
> continuously in a complex fashion, such as a neural network or an
> automaton.  Monads are the way to go here, unless you want to do
> research and find a better way to express this.

In the light of the discussion above, the state monad for a particular
state is an implementation, not an abstraction. There is no independent
meaning in "stateful computation with an automaton as state", it is
defined by its sole implementation. Sure, it does reduce boilerplate and
simplifies the implementation, but it doesn't offer any insights.

In other words, "passing state" is not an abstraction and it's a good
idea to consciously exclude it from the design space when searching for
a good abstraction. Similar for the other monads, maybe except the
nondeterminism monad to some extend.

Of course, a good abstraction depends on the problem domain. For
automata, in particular finite state automata, I can imagine that the
operations on corresponding regular expressions like concatenation,
alternation and Kleene star are viable candidates. I have no clue about
neural networks.


On a side note, not every function that involves "state" does need the
state monad. For instance, an imperative language might accumulate a
value with a while-loop and updating a state variable, but in Haskell we
simply pass a parameter to the recursive call

   foldl f z [] = z
   foldl f z (x:xs) = foldl f (f z x) xs

Another example is "modifying" a value where a simple function of type
s -> s  like

   insert 1 'a' :: Map k v -> Map k v

will do the trick.

> Personally I prefer this:
> 
>   somethingWithRandomsM :: (Monad m, Random a) => m a -> Something a
> 
> over these:
> 
>   somethingWithRandoms1 :: [a] -> Something a
>   somethingWithRandoms2 :: RandomGen g => g -> Something a
>
>> Consciously excluding monads and restricting the design space to pure
>> functions is the basic tool of thought for finding such elegant
>> abstractions. [...]
> 
> You don't need to exclude monads

Re: [Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-13 Thread Duncan Coutts
On Tue, 2009-01-13 at 19:44 -0500, Dan Doel wrote:
> On Tuesday 13 January 2009 7:27:10 pm Luke Palmer wrote:
> > > When GHC starts optimizing (Writer Builder) as well as it optimizes PutM,
> > > then
> > > that will be a cogent argument. Until then, one might argue that it
> > > misses "the whole point of Put".
> >
> > Well it can still serve as an optimization over bytestrings using whatever
> > trickery it uses (I am assuming here -- I am not familiar with its
> > trickery), the same way DList is an optimization over List.  It's just that
> > its  monadiness is superfluous.
> >
> > Surely PutM and Writer Put have almost the same performance?!  (I am
> > worried if not -- if not, can you give an indication why?)
> 
> The underlying monoid is Builder. The point of PutM is to be a version of 
> Writer that's specialized to the Builder monoid for maximum performance. It 
> looks like:
> 
>   data PairS a = PairS a {-# UNPACK #-} !Builder
> 
>   newtype PutM a = Put { unPut :: PairS a }
> 
> I'm not sure why it's split up like that. Anyhow, the strict, unpacked 
> Builder 
> gets optimized better than Writer Builder.

Oops, I walked into this conversation without reading enough context.
Sorry, I see what you mean now.

Yes, it's specialised to get decent performance. As you say, the lifted
(,) in the Writer would get in the way otherwise.

There's an interesting project in optimising parametrised monads and
stacks of monad transformers.

Duncan

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


Re: [Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-13 Thread Ross Paterson
On Tue, Jan 13, 2009 at 07:44:17PM -0500, Dan Doel wrote:
> On Tuesday 13 January 2009 7:27:10 pm Luke Palmer wrote:
> > Surely PutM and Writer Put have almost the same performance?!  (I am
> > worried if not -- if not, can you give an indication why?)
> 
> The underlying monoid is Builder.  The point of PutM is to be
> a version of Writer that's specialized to the Builder monoid for
> maximum performance.  It looks like:
> 
>   data PairS a = PairS a {-# UNPACK #-} !Builder
> 
>   newtype PutM a = Put { unPut :: PairS a }
> 
> I'm not sure why it's split up like that.  Anyhow, the strict, unpacked
> Builder gets optimized better than Writer Builder.

But the only reason you want this monad optimized is so that you can
use it in do-notation.  Otherwise you'd just use Builder directly.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-13 Thread Duncan Coutts
On Tue, 2009-01-13 at 19:19 -0500, Dan Doel wrote:
> On Tuesday 13 January 2009 5:51:09 pm Luke Palmer wrote:
> > On Tue, Jan 13, 2009 at 11:21 AM, Tim Newsham  wrote:
> > > I have seen several libraries where all functions of a monad have the
> > >
> > >> monadic result (), e.g. Binary.Put and other writing functions. This is
> > >> a clear indicator, that the Monad instance is artificial and was only
> > >> chosen because of the 'do' notation.
> > >
> > > Maybe that was the initial reason, but I've actually found the
> > > Binary.Put.PutM (where Put = PutM ()) to be useful.  Sometimes
> > > your putter does need to propogate a result...
> >
> > But that's the whole point of Writer!  Take a monoid, make it into a monad.
> > Put as a monad is silly.
> 
> You mean it should be Writer instead?
> 
> When GHC starts optimizing (Writer Builder) as well as it optimizes PutM, 
> then 
> that will be a cogent argument.

In that case it's a cogent argument now. :-)

You may be interested to note that PutM really is implemented as a
writer monad over the Builder monoid:

-- | The PutM type. A Writer monad over the efficient Builder monoid.
newtype PutM a = Put { unPut :: PairS a }
data PairS a = PairS a {-# UNPACK #-}!Builder

-- | Put merely lifts Builder into a Writer monad, applied to ().
type Put = PutM ()


> Until then, one might argue that it misses "the whole point of Put".


Back when we were first writing the binary library, Ross converted our
original Put to be a monoid called Builder with Put left as a Writer.
GHC optimises it perfectly, we checked.

The reason we provide Put as well as Builder is purely for symmetry with
code written using Get. Also `mappend` is not so pretty. Another
argument for redefining (++) == mappend :-)

Get doesn't need to be a Monad either, it only needs to be an
applicative functor. Indeed the rules to eliminate adjacent bounds
checks only fire if it is used in this way (using >> also works).

Duncan

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


Re: [Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-13 Thread Dan Doel
On Tuesday 13 January 2009 7:27:10 pm Luke Palmer wrote:
> > When GHC starts optimizing (Writer Builder) as well as it optimizes PutM,
> > then
> > that will be a cogent argument. Until then, one might argue that it
> > misses "the whole point of Put".
>
> Well it can still serve as an optimization over bytestrings using whatever
> trickery it uses (I am assuming here -- I am not familiar with its
> trickery), the same way DList is an optimization over List.  It's just that
> its  monadiness is superfluous.
>
> Surely PutM and Writer Put have almost the same performance?!  (I am
> worried if not -- if not, can you give an indication why?)

The underlying monoid is Builder. The point of PutM is to be a version of 
Writer that's specialized to the Builder monoid for maximum performance. It 
looks like:

  data PairS a = PairS a {-# UNPACK #-} !Builder

  newtype PutM a = Put { unPut :: PairS a }

I'm not sure why it's split up like that. Anyhow, the strict, unpacked Builder 
gets optimized better than Writer Builder. Even if you change Writer to:

  data Writer w a = Writer a !w

it still won't match up, because polymorphic components don't get unpacked and 
such. That's, for instance, why Data.Sequence uses a specialized version of 
the finger tree type, instead of using the general version in Data.FingerTree.

Only exposing Put as a monoid is kind of redundant. You might as well work 
straight with Builder.

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


Re: [Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-13 Thread Luke Palmer
On Tue, Jan 13, 2009 at 5:19 PM, Dan Doel  wrote:

> On Tuesday 13 January 2009 5:51:09 pm Luke Palmer wrote:
> > On Tue, Jan 13, 2009 at 11:21 AM, Tim Newsham  wrote:
> > > I have seen several libraries where all functions of a monad have the
> > >
> > >> monadic result (), e.g. Binary.Put and other writing functions. This
> is
> > >> a clear indicator, that the Monad instance is artificial and was only
> > >> chosen because of the 'do' notation.
> > >
> > > Maybe that was the initial reason, but I've actually found the
> > > Binary.Put.PutM (where Put = PutM ()) to be useful.  Sometimes
> > > your putter does need to propogate a result...
> >
> > But that's the whole point of Writer!  Take a monoid, make it into a
> monad.
> > Put as a monad is silly.
>
> You mean it should be Writer instead?


Or rather, PutM should not exist (or be exposed), and Put should just be a
monoid.


> When GHC starts optimizing (Writer Builder) as well as it optimizes PutM,
> then
> that will be a cogent argument. Until then, one might argue that it misses
> "the whole point of Put".


Well it can still serve as an optimization over bytestrings using whatever
trickery it uses (I am assuming here -- I am not familiar with its
trickery), the same way DList is an optimization over List.  It's just that
its  monadiness is superfluous.

Surely PutM and Writer Put have almost the same performance?!  (I am worried
if not -- if not, can you give an indication why?)

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


Re: [Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-13 Thread Dan Doel
On Tuesday 13 January 2009 5:51:09 pm Luke Palmer wrote:
> On Tue, Jan 13, 2009 at 11:21 AM, Tim Newsham  wrote:
> > I have seen several libraries where all functions of a monad have the
> >
> >> monadic result (), e.g. Binary.Put and other writing functions. This is
> >> a clear indicator, that the Monad instance is artificial and was only
> >> chosen because of the 'do' notation.
> >
> > Maybe that was the initial reason, but I've actually found the
> > Binary.Put.PutM (where Put = PutM ()) to be useful.  Sometimes
> > your putter does need to propogate a result...
>
> But that's the whole point of Writer!  Take a monoid, make it into a monad.
> Put as a monad is silly.

You mean it should be Writer instead?

When GHC starts optimizing (Writer Builder) as well as it optimizes PutM, then 
that will be a cogent argument. Until then, one might argue that it misses 
"the whole point of Put".

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


Re: [Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-13 Thread Luke Palmer
On Tue, Jan 13, 2009 at 11:21 AM, Tim Newsham  wrote:

> I have seen several libraries where all functions of a monad have the
>> monadic result (), e.g. Binary.Put and other writing functions. This is
>> a clear indicator, that the Monad instance is artificial and was only
>> chosen because of the 'do' notation.
>>
>
> Maybe that was the initial reason, but I've actually found the
> Binary.Put.PutM (where Put = PutM ()) to be useful.  Sometimes
> your putter does need to propogate a result...


But that's the whole point of Writer!  Take a monoid, make it into a monad.
Put as a monad is silly.

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


Re: [Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-13 Thread Tim Newsham

I have seen several libraries where all functions of a monad have the
monadic result (), e.g. Binary.Put and other writing functions. This is
a clear indicator, that the Monad instance is artificial and was only
chosen because of the 'do' notation.


Maybe that was the initial reason, but I've actually found the
Binary.Put.PutM (where Put = PutM ()) to be useful.  Sometimes
your putter does need to propogate a result...

Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-13 Thread Ross Paterson
On Tue, Jan 13, 2009 at 10:16:32AM +, ChrisK wrote:
> Henning Thielemann wrote:
>> I have seen several libraries where all functions of a monad have the
>> monadic result (), e.g. Binary.Put and other writing functions. This is
>> a clear indicator, that the Monad instance is artificial and was only
>> chosen because of the 'do' notation.
>
> I completely disagree with that example.
> The Put monad is, mainly, a specialized State monad.
> The internal state being the current fixed-size bytestring memory buffer 
> that has been allocated and is being filled.
> The monad make the execution sequential so that there is only one memory 
> buffer being filled at a time.

No, Put is a specialized Writer monad.  The sequencing is imposed by
the mappend operation of the Builder monoid.  The monadic interface is
indeed there just to access do notation.  And Henning's general point
also holds: a monad that is always applied to () is just a monoid.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-13 Thread ChrisK

Henning Thielemann wrote:

I have seen several libraries where all functions of a monad have the
monadic result (), e.g. Binary.Put and other writing functions. This is
a clear indicator, that the Monad instance is artificial and was only
chosen because of the 'do' notation.


I completely disagree with that example.
The Put monad is, mainly, a specialized State monad.
The internal state being the current fixed-size bytestring memory buffer that 
has been allocated and is being filled.
The monad make the execution sequential so that there is only one memory buffer 
being filled at a time.
In Put, when one memory buffer has been filled it allocates the next one to 
create a Lazy Bytestring.


This is not to say that all M () are really monads, but just that Put () is.

--
Chris

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


Re: [Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-12 Thread Henning Thielemann
Ertugrul Soeylemez schrieb:
> "Apfelmus, Heinrich"  wrote:
> 
>> The insistence on avoiding monads by experienced Haskellers, in
>> particular on avoiding the IO monad, is motivated by the quest for
>> elegance.
>>
>> The IO and other monads make it easy to fall back to imperative
>> programming patterns to "get the job done".  [...]
> 
> Often, the monadic solution _is_ the elegant solution.  Please don't
> confuse monads with impure operations.  I use the monadic properties of
> lists, often together with monad transformers, to find elegant
> solutions.  As long as you're not abusing monads to program
> imperatively, I think, they are an excellent and elegant structure.

I have seen several libraries where all functions of a monad have the
monadic result (), e.g. Binary.Put and other writing functions. This is
a clear indicator, that the Monad instance is artificial and was only
chosen because of the 'do' notation.

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


[Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-11 Thread Ertugrul Soeylemez
Ertugrul Soeylemez  wrote:

> Personally I prefer this:
>
>   somethingWithRandomsM :: (Monad m, Random a) => m a -> Something a

Of course, there is something missing here:

  somethingWithRandomsM :: (Monad m, Random a) => m a -> m (Something a)

Sorry.


Greets,
Ertugrul.


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://blog.ertes.de/


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


[Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-11 Thread Ertugrul Soeylemez
"Apfelmus, Heinrich"  wrote:

> Ertugrul Soeylemez wrote:
>
> > Let me tell you that usually 90% of my code is monadic and there is
> > really nothing wrong with that.  I use especially State monads and
> > StateT transformers very often, because they are convenient and are
> > just a clean combinator frontend to what you would do manually
> > without them:  passing state.
>
> The insistence on avoiding monads by experienced Haskellers, in
> particular on avoiding the IO monad, is motivated by the quest for
> elegance.
>
> The IO and other monads make it easy to fall back to imperative
> programming patterns to "get the job done".  [...]

Often, the monadic solution _is_ the elegant solution.  Please don't
confuse monads with impure operations.  I use the monadic properties of
lists, often together with monad transformers, to find elegant
solutions.  As long as you're not abusing monads to program
imperatively, I think, they are an excellent and elegant structure.

I said that 90% of my code is monadic, not that 90% of it is in IO.  I
do use state monads where there is no more elegant solution than passing
state around.  It's simply that:  you have a structure, which you modify
continuously in a complex fashion, such as a neural network or an
automaton.  Monads are the way to go here, unless you want to do
research and find a better way to express this.

Personally I prefer this:

  somethingWithRandomsM :: (Monad m, Random a) => m a -> Something a

over these:

  somethingWithRandoms1 :: [a] -> Something a
  somethingWithRandoms2 :: RandomGen g => g -> Something a

Also I use monads a lot for displaying progress:

  lengthyComputation :: Monad m => (Progress -> m ()) -> m Result


> Consciously excluding monads and restricting the design space to pure
> functions is the basic tool of thought for finding such elegant
> abstractions. [...]

You don't need to exclude monads to restrict the design space to pure
functions.  Everything except IO and ST (and some related monads) is
pure.  As said, often monads _are_ the elegant solutions.  Just look at
parser monads.


Greets,
Ertugrul.


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://blog.ertes.de/


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