
Hello fellow Haskellers, I'd like to discuss an interesting topic. My experience is that there are two worlds in Haskell, which are quite separate: the pure, algorithmic world, where you use idiomatic pure Haskell, and the IO-driven world of state, change, threads and execution, where you use idiomatic concurrent Haskell. If you understand these two concepts well, then you are usually a good Haskell programmer. Interestingly this doesn't mean that you get applications done faster or done at all. Most languages today provide a certain "glue" to bring everything together. I think that term originates from "Why Functional Programming Matters" by John Hughes. Haskell provides a lot of low level glue like laziness, currying and other very helpful language features. But what is different in Haskell is that it doesn't seem to provide any high level glue like other languages do, especially when it comes to the IO world. There is a somewhat powerful module system, but nothing to bring modules and the objects they define together in a consistent way. In my opinion this is both a disadvantage and an advantage. It's bad because there is no standard way of gluing, nothing everybody learns and uses. On the other hand it's good, because you can make your own glue. This has proven very useful for me. My usual way is writing monad transformers and sticking them together, often together with concurrent programming. The problem with that approach is: This makes my code harder to understand for beginners. Usually they can tell /what/ my code is doing, because it's written in natural language as much as possible, but they couldn't reproduce it. And when they try to learn it, they give up fast, because you need quite some background for that. Also sometimes when I write Haskell, my friend sits beside me and watches. When he asks (as a PHP programmer with some C background), say, about my types, I can't give a brief explanation like I could in other languages. Yesterday I was writing a toy texture handler for OpenGL (for loading and selecting textures). He asked about my TextureT type. I couldn't explain it, because you couldn't even express such a thing in PHP or C. type TextureT = StateT Config -- Note that this is MonadLib. -- BaseM m IO corresponds to MonadIO m. selectTexture :: BaseM m IO => B.ByteString -> TextureT m () I fear that my code is already too difficult to understand for beginners, and it's getting worse. But then I ask myself: I've got a powerful language, so why shouldn't I use that power? After all I haven't learnt Haskell to write C code with it. And a new Haskell programmer doesn't read my code to learn Haskell. They first learn Haskell and /then/ read my code. Is this a real problem or am I just exaggerating? What do you think? Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

Ertugrul Soeylemez
I fear that my code is already too difficult to understand for beginners, and it's getting worse. But then I ask myself: I've got a powerful language, so why shouldn't I use that power? After all I haven't learnt Haskell to write C code with it. And a new Haskell programmer doesn't read my code to learn Haskell. They first learn Haskell and /then/ read my code.
Is this a real problem or am I just exaggerating? What do you think?
I think that code should be written in as clear a manner as possible without affecting performance or functionality. That is, don't write the code complicated just for the sake of it, but don't be afraid to use extensions or advanced techniques if you think it's worth it. That said, whilst the problem might be more pronounced in Haskell, do all Java programmers instantly understand Factory patterns, etc.? This isn't a Haskell-specific pattern... -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Hello Ertugrul, Saturday, July 3, 2010, 4:25:22 PM, you wrote:
This has proven very useful for me. My usual way is writing monad transformers and sticking them together, often together with concurrent programming.
... /what/ my code is doing, because it's written in natural language as much as possible
can we see such code? i always thought that monad transformers are hard to use since you need to lift operations from inner monads on every use -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin
Saturday, July 3, 2010, 4:25:22 PM, you wrote:
This has proven very useful for me. My usual way is writing monad transformers and sticking them together, often together with concurrent programming.
... /what/ my code is doing, because it's written in natural language as much as possible
can we see such code? i always thought that monad transformers are hard to use since you need to lift operations from inner monads on every use
This may appear like a disadvantage, but as your monad gets more complicated, this becomes a virtue, because it gives you great type safety. In general, you can write specialized lifting functions for specialized monads. Here is an example monad: type CounterT = StateT runCounterT :: (Functor m, Num c) => CounterT c m a -> m a runCounterT c = fst <$> runStateT 0 c increment :: (Monad m, Num c) => CounterT c m () increment = sets_ (+1) decrement :: (Monad m, Num c) => CounterT c m () decrement = sets_ (subtract 1) printCounter :: (BaseM m IO, Show c) => CounterT c m () printCounter = get >>= inBase . print Let's build a custom monad using CounterT somewhere in the middle: type MyMonad = IdT (IdT (CounterT Integer (IdT IO))) Now let's write the specialized lifting functions: myMonadIO :: IO a -> MyMonad a myMonadIO = inBase myMonadInnerId :: IdT IO a -> MyMonad a myMonadInnerId = lift . lift . lift myMonadCtr :: CounterT Integer (IdT IO) a -> MyMonad a myMonadCtr = lift . lift myMonadOuterId :: IdT (CounterT Integer (IdT IO)) a -> MyMonad a myMonadOuterId = lift As you can see this can get quite ugly and tiresome. There is a much easier approach, inspired by monadLib's 'inBase' function: class (Monad m, Monad n) => CounterM m n | m -> n where inCtr :: n a -> m a instance Monad m => CounterM (CounterT c m) (CounterT c m) where inCtr = id instance CounterM m n => CounterM (IdT m) n where inCtr = lift . inCtr This requires a bunch of type system extensions, though, most notably the UndecidableInstances extension. But it's safe to use here. Now you can get along without custom lifting functions entirely: testComp :: MyMonad () testComp = do x <- inCtr $ increment >> increment >> get inBase $ print x y <- inCtr $ decrement >> decrement >> get inBase $ print y The type system calculates the proper number of lifts for you here and provides them through the 'inCtr' function. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Sun, 4 Jul 2010 15:47:21 +0200, Ertugrul Soeylemez
This requires a bunch of type system extensions, though, most notably the UndecidableInstances extension. But it's safe to use here.
Probably a bit off topic, but whats wrong with UndecidableInstances? Where is it safe to use, when would you avoid it and what can go wrong here?

Nils Schweinsberg
On Sun, 4 Jul 2010 15:47:21 +0200, Ertugrul Soeylemez
wrote: This requires a bunch of type system extensions, though, most notably the UndecidableInstances extension. But it's safe to use here.
Probably a bit off topic, but whats wrong with UndecidableInstances? Where is it safe to use, when would you avoid it and what can go wrong here?
I've been told that it's safe to use; enabling it just tells GHC that you're sure that the instance constraints are OK (as they might be too complicated for GHC's type checker; e.g. I have to use it when doing a whole bunch of associated type constraints as GHC doens't like having such a large set of constraints on the instance definition). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Nils Schweinsberg
This requires a bunch of type system extensions, though, most notably the UndecidableInstances extension. But it's safe to use here.
Probably a bit off topic, but whats wrong with UndecidableInstances? Where is it safe to use, when would you avoid it and what can go wrong here?
Essentially UndecidableInstances turns the type system into a Turing-complete programming language. One direct consequence is that type checking may not terminate and, because of the halting problem, the type system is unable to tell when that happens. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Sat, Jul 3, 2010 at 9:25 AM, Ertugrul Soeylemez
Haskell provides a lot of low level glue like laziness, currying and other very helpful language features. But what is different in Haskell is that it doesn't seem to provide any high level glue like other languages do, especially when it comes to the IO world. There is a somewhat powerful module system, but nothing to bring modules and the objects they define together in a consistent way.
When I first read this paragraph, I thought: "STM to the rescue!". STM is one of the best concurrent world glues, IMHO.
In my opinion this is both a disadvantage and an advantage. It's bad because there is no standard way of gluing, nothing everybody learns and uses. On the other hand it's good, because you can make your own glue. This has proven very useful for me. My usual way is writing monad transformers and sticking them together, often together with concurrent programming.
Oh, so it is about monad transformers. =) If you want, you may use Haskell just as you as PHP or C: just put everything in IO. Your code will get uglier and the type system won't catch many bugs, but that's what we get when doing C or PHP, right?
The problem with that approach is: This makes my code harder to understand for beginners. Usually they can tell /what/ my code is doing, because it's written in natural language as much as possible, but they couldn't reproduce it. And when they try to learn it, they give up fast, because you need quite some background for that. Also sometimes when I write Haskell, my friend sits beside me and watches. When he asks (as a PHP programmer with some C background), say, about my types, I can't give a brief explanation like I could in other languages.
I agree that it gets harder to reason about the code. In fact, sometimes I stack monad transformers in the wrong order. However, as Ivan says, if the feature is useful for you, don't be afraid of using it. Beginners may have a hard time grasping the concepts for the first time, but that's only until they "get it". About monad transformers, I don't really like to use them because they can get hairy in some cases, and because they have poor performance in other cases. Yet the decision of using transformers or not should be made depending on your particular needs.
Yesterday I was writing a toy texture handler for OpenGL (for loading and selecting textures). He asked about my TextureT type. I couldn't explain it, because you couldn't even express such a thing in PHP or C.
type TextureT = StateT Config
-- Note that this is MonadLib. -- BaseM m IO corresponds to MonadIO m. selectTexture :: BaseM m IO => B.ByteString -> TextureT m ()
"It is the type of functions that may access and modify a state of type Config." Cheers, -- Felipe.

Felipe Lessa wrote:
Oh, so it is about monad transformers. =)
I agree that it gets harder to reason about the code. In fact, sometimes I stack monad transformers in the wrong order.
About monad transformers, I don't really like to use them because they can get hairy in some cases, and because they have poor performance in other cases. Yet the decision of using transformers or not should be made depending on your particular needs.
In my experience, using more than one monad transformer at once makes code utterly incomprehensible. (!) In my humble opinion, this is the principle weakness of monads; they allow you to do lots of cool stuff, but it's intractibly hard to mix several of them together. (See, for example, the combinatorial explosion of class instances in the MTL package.) On the few occasions I've attempted to use monad transformers, I've often wasted hours staring at a single function call, desperately trying to make it type-check. I almost which there was some kind of automated tool to tell you which magic combination of library functions generates an expression of the correct type. (But there isn't. Hoogle will tell you if any existing function vaguely matches what you want, but it's no help in suggesting how to combine a dozen functions together to get the right type.) Tangentally, it seems to me that all monads can be described as doing zero or more of: - Invisibly pass state around (and possibly modify it). - Perform unusual flow control. - I/O (or some restricted subset of it). Can anybody think of a monad that does something that doesn't fall under one of these categories? (For example, a parser monad carries around invisible state - the current source location, the input being parsed, etc. It also usually implements choice - in other words, unusual flow control. And some like Parsec allow you to do I/O as well.)
type TextureT = StateT Config
-- Note that this is MonadLib. -- BaseM m IO corresponds to MonadIO m. selectTexture :: BaseM m IO => B.ByteString -> TextureT m ()
"It is the type of functions that may access and modify a state of type Config."
Damn, *I* didn't manage to figure that out, never mind PHP n00bs...

* Andrew Coppin
In my experience, using more than one monad transformer at once makes code utterly incomprehensible.
See X monad (xmonad) for an counterexample. -- | The X monad, 'ReaderT' and 'StateT' transformers over 'IO' -- encapsulating the window manager configuration and state, -- respectively. -- -- Dynamic components may be retrieved with 'get', static components -- with 'ask'. With newtype deriving we get readers and state monads -- instantiated on 'XConf' and 'XState' automatically. -- newtype X a = X (ReaderT XConf (StateT XState IO) a) -- Roman I. Cheplyaka :: http://ro-che.info/ "Don't let school get in the way of your education." - Mark Twain

Roman Cheplyaka wrote:
* Andrew Coppin
[2010-07-03 14:20:14+0100] In my experience, using more than one monad transformer at once makes code utterly incomprehensible.
See X monad (xmonad) for an counterexample.
-- | The X monad, 'ReaderT' and 'StateT' transformers over 'IO' -- encapsulating the window manager configuration and state, -- respectively. -- -- Dynamic components may be retrieved with 'get', static components -- with 'ask'. With newtype deriving we get readers and state monads -- instantiated on 'XConf' and 'XState' automatically. -- newtype X a = X (ReaderT XConf (StateT XState IO) a)
In my experience, defining a type representing several stacked monad transformers is the easy part. The hard part is figuring out how in the name of God to run the resulting computation, or how to access functions burried at various levels of the stack. From what I've seen, it usually ends up being faster and easier to just define a custom monad that does exactly what you want, and then use that.

* Andrew Coppin
Roman Cheplyaka wrote:
* Andrew Coppin
[2010-07-03 14:20:14+0100] In my experience, using more than one monad transformer at once makes code utterly incomprehensible.
See X monad (xmonad) for an counterexample.
-- | The X monad, 'ReaderT' and 'StateT' transformers over 'IO' -- encapsulating the window manager configuration and state, -- respectively. -- -- Dynamic components may be retrieved with 'get', static components -- with 'ask'. With newtype deriving we get readers and state monads -- instantiated on 'XConf' and 'XState' automatically. -- newtype X a = X (ReaderT XConf (StateT XState IO) a)
In my experience, defining a type representing several stacked monad transformers is the easy part.
Of course it is. It wasn't my intention just to show you how easy it is to define a newtype in Haskell :) I just showed you a monad stack which is successfully used in xmonad -- and you really need to read the code a bit to get the taste of it.
The hard part is figuring out how in the name of God to run the resulting computation
It is run just in the one place, so you don't need to think about it each time you do some changes.
or how to access functions burried at various levels of the stack.
See above: -- Dynamic components may be retrieved with 'get', static components -- with 'ask'. So you use ask to get some configuration variable (reader monad is used for configuration in xmonad) and get/put/modify to deal with dynamic state of application. You use liftIO (abbreviated to 'io') to run IO computations.
From what I've seen, it usually ends up being faster and easier to just define a custom monad that does exactly what you want, and then use that.
In which way is it faster and easier? Can you show faster and easier implementation of the X monad shown above? -- Roman I. Cheplyaka :: http://ro-che.info/ "Don't let school get in the way of your education." - Mark Twain

Roman Cheplyaka wrote:
* Andrew Coppin
[2010-07-03 15:07:17+0100] In my experience, defining a type representing several stacked monad transformers is the easy part.
Of course it is. It wasn't my intention just to show you how easy it is to define a newtype in Haskell :)
I just showed you a monad stack which is successfully used in xmonad -- and you really need to read the code a bit to get the taste of it.
OK, fair enough then.
The hard part is figuring out how in the name of God to run the resulting computation
It is run just in the one place, so you don't need to think about it each time you do some changes.
As I say, every time I've tried to do this, I end up writing a function to "run this stuff", and it typically takes a few hours to reach the point where it type-checks.
or how to access functions burried at various levels of the stack.
See above: -- Dynamic components may be retrieved with 'get', static components -- with 'ask'.
So you use ask to get some configuration variable (reader monad is used for configuration in xmonad) and get/put/modify to deal with dynamic state of application. You use liftIO (abbreviated to 'io') to run IO computations.
In other words, somebody has written a combinatorial explosion of class instances to automate some of the lifting.
From what I've seen, it usually ends up being faster and easier to just define a custom monad that does exactly what you want, and then use that.
In which way is it faster and easier?
It's faster and easier to write the code because I don't have to spend multiple hours trying to work out how to make it type-check. Whether it's any faster at run-time, I have no idea...

As I say, every time I've tried to do this, I end up writing a function to "run this stuff", and it typically takes a few hours to reach the point where it type-checks.
It took me a while the first time, but then I just learned the pattern and I do it that way every time. Here's my pattern: type SomethingStack m = Monad1T Args (Monad2T Args (Monad3T Args m)) newtype SomethingT m a = SomethingT (SomethingStack m a) deriving (Functor, Monad, MonadIO, MonadError MyError, KitchenSink) run_something_t (SomethingT m) = m run :: (Monad m) => SomethingT m a -> m (a, MonadCrap, MonadCrap, ...) run = Monad3T.run args . Monad2T.run args . Monad1T.run args . run_something_t Or if you don't need the polymorphism, just stick a 'Identity.runIdentity' before Monad3T.run and make a type Something = SomethingT Identity The tricky bit is that you run them inside-out so the composition looks like the stack backwards. And sometimes mtl's 'run' functions have an inconvenient arg order (e.g. StateT), so you have to flip them.

begin Andrew Coppin quotation:
Roman Cheplyaka wrote:
See above: -- Dynamic components may be retrieved with 'get', static components -- with 'ask'.
So you use ask to get some configuration variable (reader monad is used for configuration in xmonad) and get/put/modify to deal with dynamic state of application. You use liftIO (abbreviated to 'io') to run IO computations.
In other words, somebody has written a combinatorial explosion of class instances to automate some of the lifting.
Well then you need to automate writing the instances too :) The GeneralizedNewtypeDeriving extension can be used to get instances for Monad, MonadReader XConf, MonadState XState, and MonadIO automatically for a newtype like X that should suffice in most cases. -md

On 3 July 2010 14:20, Andrew Coppin
Tangentally, it seems to me that all monads can be described as doing zero or more of: - Invisibly pass state around (and possibly modify it). - Perform unusual flow control. - I/O (or some restricted subset of it). Can anybody think of a monad that does something that doesn't fall under one of these categories?
The Identity monad of course. You did ask...

Stephen Tetley
On 3 July 2010 14:20, Andrew Coppin
wrote: Tangentally, it seems to me that all monads can be described as doing zero or more of: - Invisibly pass state around (and possibly modify it). - Perform unusual flow control.
What do you consider "unusual"? -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Ivan Lazar Miljenovic wrote:
Stephen Tetley
writes: On 3 July 2010 14:20, Andrew Coppin
wrote: Tangentally, it seems to me that all monads can be described as doing zero or more of: - Invisibly pass state around (and possibly modify it). - Perform unusual flow control.
What do you consider "unusual"?
Not the usual flow control that you'd implement by simply chaining vanilla functions together. Maybe and similar error monads implement early exit. List and similar containers implement multiple execution in some order or other. There are monads that implement choice. Cont implements... uh, everything? Even STM, which is largely about state mutation, implements [very] unusual flow control - the flow is controlled by other concurrent threads!

Stephen Tetley wrote:
On 3 July 2010 14:20, Andrew Coppin
wrote: Tangentally, it seems to me that all monads can be described as doing zero or more of: - Invisibly pass state around (and possibly modify it). - Perform unusual flow control. - I/O (or some restricted subset of it). Can anybody think of a monad that does something that doesn't fall under one of these categories?
The Identity monad of course.
You did ask...
I said "does something that doesn't fall under one of these". The identity monad, by contrast, does nothing that does fall under these. :-P (It falls under zero of these.)

On 3 July 2010 15:04, Andrew Coppin
I said "does something that doesn't fall under one of these". The identity monad, by contrast, does nothing that does fall under these. :-P (It falls under zero of these.)
Okay, how about: The probability monad The powerset monad The monad of locales http://www.cs.bham.ac.uk/~mhe/papers/pinjective.pdf The filter monad http://www.cs.bham.ac.uk/~mhe/papers/filtersnorthbay2.pdf Once you move into the mathematically territory I couldn't tell you want the monads actually do, but on the surface they don't seem very "effectful".

Felipe Lessa
On Sat, Jul 3, 2010 at 9:25 AM, Ertugrul Soeylemez
wrote: Haskell provides a lot of low level glue like laziness, currying and other very helpful language features. But what is different in Haskell is that it doesn't seem to provide any high level glue like other languages do, especially when it comes to the IO world. There is a somewhat powerful module system, but nothing to bring modules and the objects they define together in a consistent way.
When I first read this paragraph, I thought: "STM to the rescue!". STM is one of the best concurrent world glues, IMHO.
I found that I get along with the basic concurrency constructs. STM may be handy in a few applications, but in none that I write.
If you want, you may use Haskell just as you as PHP or C: just put everything in IO. Your code will get uglier and the type system won't catch many bugs, but that's what we get when doing C or PHP, right?
Not really. Even when programming in such a style, Haskell is much safer than PHP with its braindead type system, and still somewhat safer than C.
The problem with that approach is: This makes my code harder to understand for beginners. Usually they can tell /what/ my code is doing, because it's written in natural language as much as possible, but they couldn't reproduce it. And when they try to learn it, they give up fast, because you need quite some background for that. Also sometimes when I write Haskell, my friend sits beside me and watches. When he asks (as a PHP programmer with some C background), say, about my types, I can't give a brief explanation like I could in other languages.
I agree that it gets harder to reason about the code. In fact, sometimes I stack monad transformers in the wrong order. However, as Ivan says, if the feature is useful for you, don't be afraid of using it. Beginners may have a hard time grasping the concepts for the first time, but that's only until they "get it".
I find monad transformers easy to reason about, and in most cases the stacking order doesn't make a difference at all. Just remember to change the running function, too. The problem with them is that beginners learn them very late.
Yesterday I was writing a toy texture handler for OpenGL (for loading and selecting textures). He asked about my TextureT type. I couldn't explain it, because you couldn't even express such a thing in PHP or C.
type TextureT = StateT Config
-- Note that this is MonadLib. -- BaseM m IO corresponds to MonadIO m. selectTexture :: BaseM m IO => B.ByteString -> TextureT m ()
"It is the type of functions that may access and modify a state of type Config."
Then you need to explain "type of functions" and this explicitly implicit "state" and why you have to do it that way in Haskell. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Mon, Jul 5, 2010 at 6:12 AM, Ertugrul Soeylemez
Felipe Lessa
wrote: On Sat, Jul 3, 2010 at 9:25 AM, Ertugrul Soeylemez
wrote: Haskell provides a lot of low level glue like laziness, currying and other very helpful language features. But what is different in Haskell is that it doesn't seem to provide any high level glue like other languages do, especially when it comes to the IO world. There is a somewhat powerful module system, but nothing to bring modules and the objects they define together in a consistent way.
When I first read this paragraph, I thought: "STM to the rescue!". STM is one of the best concurrent world glues, IMHO.
I found that I get along with the basic concurrency constructs. STM may be handy in a few applications, but in none that I write.
STM has the same basic concurrency constructs, but they are safe to use. MVars and everything derived from them have tricky semantics that can fail in catastrofic ways. Neil Mitchell was recently trying to find a subtle bug in his code because of MVars and Chans. Cheers! -- Felipe.

Felipe Lessa
On Mon, Jul 5, 2010 at 6:12 AM, Ertugrul Soeylemez
wrote: Felipe Lessa
wrote: On Sat, Jul 3, 2010 at 9:25 AM, Ertugrul Soeylemez
wrote: Haskell provides a lot of low level glue like laziness, currying and other very helpful language features. But what is different in Haskell is that it doesn't seem to provide any high level glue like other languages do, especially when it comes to the IO world. There is a somewhat powerful module system, but nothing to bring modules and the objects they define together in a consistent way.
When I first read this paragraph, I thought: "STM to the rescue!". STM is one of the best concurrent world glues, IMHO.
I found that I get along with the basic concurrency constructs. STM may be handy in a few applications, but in none that I write.
STM has the same basic concurrency constructs, but they are safe to use. MVars and everything derived from them have tricky semantics that can fail in catastrofic ways. Neil Mitchell was recently trying to find a subtle bug in his code because of MVars and Chans.
It happened once to me that I forgot that MVars don't have a queue. A database thread would take values out of the MVar as commands and execute them, but I used the same thread to put a command into the MVar (for later execution). It worked most of the time, unless another thread put a command concurrently, right after the last command was executed and before the database thread put another command ⇒ deadlock. I fixed this by replacing the MVar by a Chan. Could STM have helped here? And as a related question, how fast does STM perform in average? Is it suitable for high traffic applications (not network/file traffic, but MVar/Chan traffic)? Usually in a non-SMP setting I can easily pass hundreds of thousands of values per second through MVars between tens of thousands of threads. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Mon, Jul 5, 2010 at 10:29 AM, Ertugrul Soeylemez
It happened once to me that I forgot that MVars don't have a queue. A database thread would take values out of the MVar as commands and execute them, but I used the same thread to put a command into the MVar (for later execution). It worked most of the time, unless another thread put a command concurrently, right after the last command was executed and before the database thread put another command ⇒ deadlock.
I fixed this by replacing the MVar by a Chan. Could STM have helped here?
Probably only if both "puts" were in the same transaction, I guess. Even with STM the solution is a channel, i.e. TChan.
And as a related question, how fast does STM perform in average? Is it suitable for high traffic applications (not network/file traffic, but MVar/Chan traffic)? Usually in a non-SMP setting I can easily pass hundreds of thousands of values per second through MVars between tens of thousands of threads.
As always, I guess you should benchmark :). There is some overhead, indeed, however for most applications I guess it should be fine. Specially because that overhead comes to save you from a lot of headaches. Cheers, -- Felipe.

On 5 July 2010 10:39, Yves Parès
Then what is your alternative? How do you replace monad transformers?
Possibly more a case of doing without rather than replacing them with something else, you would amalgamate all the monadic effects you want into one monad. E.g. State and Environment (reader) and partiality (Maybe) newtype Amalgamated s e a = Amalgamated { getAmalgamated :: e -> s -> (Maybe a,st) } instance Monad (Amalgamated s e) where return a = Amalgamated $ \e s -> return (Just a, st) m >>= k = Amalgamated $ \e s -- TODO (after the first coffee of the morning...)

Stephen Tetley
On 5 July 2010 10:39, Yves Parès
wrote: Then what is your alternative? How do you replace monad transformers?
Possibly more a case of doing without rather than replacing them with something else, you would amalgamate all the monadic effects you want into one monad.
E.g. State and Environment (reader) and partiality (Maybe)
newtype Amalgamated s e a = Amalgamated { getAmalgamated :: e -> s -> (Maybe a,st) }
instance Monad (Amalgamated s e) where return a = Amalgamated $ \e s -> return (Just a, st) m >>= k = Amalgamated $ \e s -- TODO (after the first coffee of the morning...)
That's what monad transformers are good for. Why reinvent the wheel? type Amalgamated s e m = MaybeT (StateT s (ReaderT e m)) This is all you need to create your own monad with the specified functionality. testComp :: Amalgamated Int Bool IO () testComp = do x <- return (Just 3) y <- ask z0 <- get when y $ sets_ (+1) z1 <- get inBase $ print (x, y, z0, z1) However, MaybeT as defined in the 'MaybeT' package will probably not work here. But this is not a transformer-related problem, just compatibility. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On 5 July 2010 11:30, Ertugrul Soeylemez
That's what monad transformers are good for. Why reinvent the wheel?
Hi Ertugrul The post was chiming in with Felipe Lessa's comment upthread that avoiding transfomers can have performance benefits. Whether the formulation I gave is particulary efficient is moot - I'd have to give consideration to the strictness of the state at least - but I was answering Yves Parès about "how" you would do it, rather than "why". Given the status of MTL, I nowadays avoid transformers for pragmatic reasons rather than performance ones. If I have substantial code I'll rely on Iavor S. Diatchki's very nice MonadLib, but for small projects I'll just roll an amalgamated monad.

Stephen Tetley
On 5 July 2010 11:30, Ertugrul Soeylemez
wrote: That's what monad transformers are good for. Why reinvent the wheel?
The post was chiming in with Felipe Lessa's comment upthread that avoiding transfomers can have performance benefits.
Whether the formulation I gave is particulary efficient is moot - I'd have to give consideration to the strictness of the state at least - but I was answering Yves Parès about "how" you would do it, rather than "why".
Yes, there is some performance loss because of wrapping/unwrapping, but I think this loss is neglible for most applications. And I'd ask anyway. This is a discussion thread after all. =)
Given the status of MTL, I nowadays avoid transformers for pragmatic reasons rather than performance ones. If I have substantial code I'll rely on Iavor S. Diatchki's very nice MonadLib, but for small projects I'll just roll an amalgamated monad.
Almost all of my projects, including one published one, depend on monadLib. I find the MTL comparatively inconvenient. And especially for small projects I don't see why I should roll my own monad. I prefer to stick some transformers together. For larger applications my criterion is speed, but I've yet to see an application, where transformers are too slow. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Mon, Jul 5, 2010 at 2:41 PM, Ertugrul Soeylemez
Yes, there is some performance loss because of wrapping/unwrapping, but I think this loss is neglible for most applications. And I'd ask anyway. This is a discussion thread after all. =)
Pretty much all monad transformers are implemented as newtypes, so the wrapping and unwrapping operations themselves should get compiled into nothing, I think. It may be that the extra type faff makes inlining or other arcane optimisations less straightforward, but I see no reason to assume that monad transformers are necessarily even slightly slower than explicitly-constructed amalgamations. In my experience, something like ReaderT Params (StateT SessionData IO) a may *look* scary, but in all your code you just use ask and put and get anyway and they all work like magic - the difficult bits are generally speaking hidden in your type synonyms and run function. But then, my largest haskell projects have never been more than a thousand or so lines, so perhaps it's just an issue of scale.

Most languages today provide a certain "glue" to bring everything together.
Most languages today provide several kinds of glue and, while some of those kinds are not recommended, Haskell unfortunately doesn't provide all useful kinds of glue. Especially the module system is a weak point: in SML, you'd have parameterized modules, in Java, you'd have dependency injection (of course, being Java, they do everything the hard way, via XML and reflection; but they are already on their way back, with things like Spring, annotations, and aspect-oriented programming, pushing full reflection under the hood, permitting to compose plain-old Java objects, and reducing the role of XML configuration files), in Haskell, we have ?? (yes, extended type-classes are equivalent to SML modules in theory, but not in hackage practice, nor are first-class modules modelled via extensible records).
The problem with that approach is: This makes my code harder to understand for beginners. Usually they can tell /what/ my code is doing, because it's written in natural language as much as possible, but they couldn't reproduce it. And when they try to learn it, they give up fast, because you need quite some background for that.
What kind of beginner? What kind of background? Since you are talking to a PHP developer, you will first have to repeat the common parts of both languages, pointing out all the headaches that disappear when moving from PHP to even imperative Haskell (static scoping and IO typing means no accidental global variables or accidental side-effects, much less manual-reading to figure out which parts of some library API are functional, which have side-effects, etc.). Then your friend has to start trusting the compiler (those unit tests that only make sure that we don't break scoping disappear; those defensively programmed runtime type checks and comment annotations disappear in favour of real statically checked types; etc) and libraries (much less worrying about whether some library routine will modify its parameters in place; callbacks are no big deal or new feature; many design patterns can actually be encoded in libraries, rather than pre-processors; which means that small-scale design patterns are worth a library; etc.). Once that happens, a whole lot of thinking capacity is freed for worrying about higher-level details, and you two will have an easier time walking through high-level abstractions. Do not try to lead your friends through higher-order abstractions in Haskell when they are still worrying about small stuff like scoping or type safety - that would be frightening.
Also sometimes when I write Haskell, my friend sits beside me and watches. When he asks (as a PHP programmer with some C background), say, about my types, I can't give a brief explanation like I could in other languages.
When looking through job adverts, I get the impression that nobody is working in plain programming languages anymore: it is Java plus Spring plus persistence framework plus web framework plus .., and for PHP especially, it is some framework or content-management system that just happens to be programmed and extended in PHP, but otherwise has its own language conventions and configuration languages. If you think of monad transformers and the like as mini-frameworks, implemented *without* changing the language conventions, should they not be easier to explain than a PHP framework or preprocessor that comes with its own syntax/semantics?
Yesterday I was writing a toy texture handler for OpenGL (for loading and selecting textures). He asked about my TextureT type. I couldn't explain it, because you couldn't even express such a thing in PHP or C.
type TextureT = StateT Config
-- Note that this is MonadLib. -- BaseM m IO corresponds to MonadIO m. selectTexture :: BaseM m IO => B.ByteString -> TextureT m ()
State monads are the ones that translate most directly to an OOP pattern from the Smalltalk days: method chaining (each method returns its object, so you can build chains of method calls just as you can chain monad operations. The state is held in the object (which is similar to holding a record in a State monad instead of nesting State transformers, but inheritance could be likened to nesting). Of course, in imperative OOP languages, only programmer discipline keeps you from modifying other objects as well, while in Haskell, the type system sets safety boundaries (not in the "there is something wonderful you can't do" sense but in the "you'd hurt someone if you'd do that" sense).
I fear that my code is already too difficult to understand for beginners, and it's getting worse. But then I ask myself: I've got a powerful language, so why shouldn't I use that power? After all I haven't learnt Haskell to write C code with it. And a new Haskell programmer doesn't read my code to learn Haskell. They first learn Haskell and /then/ read my code.
It is necessary to understand enough of Haskell that one gets comfortable not thinking about less important details. After that the adventure can begin. That doesn't mean that any complexity is justified (watch out for examples from "evolution of a Haskell programmer" in your code base;-), also tool support would be great (when I first encountered Programatica code I was frequently at a loss to figure out which part of their monad stack some piece of code was actually running in; figuring that out meant being side-tracked from what one was thinking about at the time).
Is this a real problem or am I just exaggerating? What do you think?
There's a real danger in there, but it need not become a problem once you are aware of it. Claus -- Secret of Haskell programmers: you don't need to be more intelligent to solve more complex applications, just as long as you don't have to waste your limited intelligence on the wrong kind of problems.
participants (13)
-
Andrew Coppin
-
Ben Millwood
-
Bulat Ziganshin
-
Claus Reinke
-
Ertugrul Soeylemez
-
Evan Laforge
-
Felipe Lessa
-
Ivan Lazar Miljenovic
-
Mike Dillon
-
Nils Schweinsberg
-
Roman Cheplyaka
-
Stephen Tetley
-
Yves Parès