Monadic Code In Haskell

When you’re dealing with monadic (straight IO, ReaderT IO, mtl, effect systems, free monads) code in Haskell, what are the various styles for handling them, and what are the tradeoffs between them?

For instance, I see that some users like to pretend Haskell is Cobol or Python, using a very imperative and accessible dialect:

main :: IO ()
main = program

program :: IO ()
program = do
    let a = 3
    let b = 4
    print (a + b)

Others might prefer a more functional seeming dialect, going straight to monadic binds when viable, essentially being a form of monadic pipelining or point-free.

main :: IO ()
main = program

program :: IO ()
program = getLine >>= putStrLn

There are, I think, other approaches, which hybridize the pure bind and do approaches


import Network.HTTP.Conduit (simpleHttp)
import System.IO (hFlush, stdout)
import Data.ByteString.Lazy qualified as LBS

main :: IO ()
main = program

program :: IO ()
program = do
    putStrLn "Enter the website you'd like to access."
    putStr "Website: "
    hFlush stdout

    site <- getLine >>= simpleHttp

    LBS.putStr site
    putStrLn ""

There is also the where-intensive approach:


import Network.HTTP.Conduit (simpleHttp)
import System.IO (hFlush, stdout)
import Data.ByteString.Lazy qualified as LBS

main :: IO ()
main = program

program :: IO ()
program = getText
      >>= getSite
      >>= showSite
  where
    getText :: IO String
    getText = do
        putStrLn "Enter the website you'd like to access."
        putStr "Website: "
        hFlush stdout

        getLine

    getSite :: String -> IO ByteString
    getSite = simpleHttp

    showSite :: ByteString -> IO ()
    showSite = (>> putStrLn "") . LBS.putStr

Are there any other ways to style Haskell monadic code that bear mentioning? What are the tradeoffs of each approach, in terms of readability, concision, flexibility, and modularity?


Edit: I’ll just put out my working hypothesis.

  1. The ultra-imperative method is a waste, but is acceptable when people are looking for maximum onboarding potential, or are dealing with learners.

  2. The pure bind approach obviously fails when you are reusing a value for multiple operations, but it also loses readability when the chain gets too large, at around 4-6 elements (human working memory averages 4, SD 1).

    Monadic then also gets clumsy when you have more than 2 monadic values.

  3. The hybrid approach can get eclipsed by the pure bind approach when the elements are small enough, or when it’s monadic / applicative then. It also allows breaking up terms that a pure bind approach has more trouble doing, or has to relegate itself to where.

  4. Where doesn’t have to be where, because the functions could be top-level and reusable. The main benefit of where-like approaches might be in helping to provide an outline of your program, and encouraging monadic actions to be more composable.

    On the other hand, it has the trade-off of introducing more terms than is strictly necessary, which can make code harder to comprehend.

    There is a further potential for unidiomatic Haskell code, as well, which is double-edged. Aggressively using where potentially allows you to have a 0% pure Haskell program, at least on the top-level, which I’d consider bad, but it also is potentially helpful for learners to understand how to handle purity.

I have strong feelings about this and I’m sure not everyone will agree with me but here is my take:

Go for the first approach whenever possible.

There is nothing more or less “imperative” about this style than the others and writing out the bind calls just obscures what you’re doing.
Readability is much more important than writing code in a cute pipeline and giving intermediate results names is a great way to achieve that.

(>>=) can be useful if it helps readability – for example, I quite like using expr >>= \case as the monadic equivalent of a standard case expression – but most of the time it just makes things more opaque.

There are times where trying to be clever is fine, but basic monadic function application and sequencing is not one of them.

11 Likes

Strongly agreed, as those who saw my answer to Jose Valim’s challenge will probably guess.

4 Likes

…along with all the other “linglyphics” associated with effect-centric code in Haskell e.g. from Applicative, et al.


Agreed: one person’s moment of cuteness or cleverness can often look like “write-only code” to others - we cannot assume that everyone who uses Haskell these days have the years or decades of experience that those of us who were there “in the early days” have now accumulated.

So as ugly as Haskell’s “two-tone” syntax (for regular and imperative Haskell) is, for now using do-notation is the least ugliest (it lessens the need for those linglyphics).

2 Likes

Another cost of mixed styles is more frequent “switching” between:

  • “expression-style” contexts, (which use (>>=), (>>) and the rest),

  • and “statement-style” ones (using do and <-);

…in order to understand the resulting code - not only is this an acquired skill for most, but the need to remember which context is being used is still an expense to be avoided, no matter what the magnitude of Haskell experience.

But this should not be thought of as an endorsement by me of do-notation: if I could go back to 1996, we would all be writing something more like:

program :: IO ()
program = do () | let a = 3,
                  let b = 4,
                  print (a + b)

i.e. do-blocks would have the syntax of list comprehensions, but without the brackets (those being reserved only for actual list comprehensions).

1 Like

To specify, I think this is an important problem because for a lot of applications (but not all, or even most), Haskell naturally ends up with a lot of monadic code and relatively little pure code (not imperative shell, functional core, but imperative bones, functional flesh).

When it comes to #1, the problem comes down to simply not being good enough.

Yes, Haskell has a notion of effect, but the way I describe do-notation is as “somewhat more verbose Python”, and even though Python is widely regarded as the most readable of all imperative languages, I’d expect that Haskell can do better.

That is why I’m interested in #2, #3, and #4; i.e, if a lot of Haskell code is going to be monadic, it’d better be a very pleasant monadic experience, otherwise the only thing you have to offer is having an explicit notion of effects.


As far as going for #2, #3, and #4, over #1, yes, I’m aware both of Do Notation Considered Harmful, as well as, I believe, Chris Allen mentioning that many Haskell learners go through a “**** do notation” phase.

And I agree with the last statement; i.e, avoiding do notation entirely is a phase people go through on their Haskell journey (I’m at least a year past this), but being purist on “imitation Cobol/Python”, is something I have to question too.

Sorry if I missed it, but I don’t think you explained this. You said 1 is “a waste” and “simply not good enough” but I don’t understand why you think that.

3 Likes

When it comes to #1, the problem comes down to simply not being good enough.

It absolutely is good enough. Results are always produced on the left and every line describes a single step. It can be split or combined to the level of granularity wanted and it’s pleasantly uniform.

Using anything else to spice up the control flow immediately kills this simplicity and the resulting code is guaranteed to be harder to both read and alter.

the way I describe do-notation is as “somewhat more verbose Python”

Are you sure this is on the do-notation and not on the fact that virtually everything you do in Haskell is more verbose? You’ll need a mountain of sugar to compete in shortness with that.

2 Likes

Frankly, “do notation considered harmful” is at best misleading and at worst completely wrong. Again, there is nothing more imperative about do notation than about any other use of Monads.

If you don’t want to use monads, that’s fine I guess but don’t fool yourself into thinking that writing out obtuse operators for simple monadic code makes you any more “pure” than others.

Well, yes, that is exactly what monads are. (>>=) is literally the monadic equivalent of a let binding.

4 Likes

@tomjaguarpaw

#1 is a strawman, and I didn’t think this was going to be the approach everyone preferred. If I did, I’d have spent more time writing it.

The reason I think #1 is a waste, is because of the superfluous bindings, when it could have been written simply as print (3 + 4) or print 7.

Of course, making intermediate steps explicit is always useful when you’re dealing with a long function chain, but in the example given, it’s simply not useful.


As far as being “not good enough”, Haskell has a reputation for extremely elegant code. I see this quite often in the pure space, where the algorithm is extremely explicit and boilerplate-free, thanks to higher-order functions, recursion, and function composition.

When you get to do-notation, on the other hand, it’s hard to make the same apply.


At others:

The point is more, I’m trying to explore what is a strong way to write monadic code in such a way that readability and concision, if not necessarily accessibility, is better than Python.

I think Haskell can actually do this, but not via an apples-to-apples comparison.

The trick comes because in Haskell, it is, at least in some corners of the community, idiomatic to use >>=, <$>, liftA2 / <*>, before a do-notation bind (bar ← foo).

This is equivalent to using function pipelines or method chaining in more traditional languages, and that’s either controversial or smelly in traditional / imperative programming.

The whole monadic/applicative/factorial smorgasbord makes explicit what you’re doing, and even if it’s less concise or ends with weird operators, the explicitness cuts away the smell.


Here’s two programs, translated back and forth between Python and Haskell, which do the same thing. No, the exception control is horrible, but these are just samples showing what’s possible.

def main():
    file1_file_path = input()
    file2_file_path = input()
#
    file1 = open(file1_file_path).readlines()
    file2 = open(file2_file_path).readlines()
#
    if file1 == file2:
        print('Success!')
    else:
        print('Failure!')
import System.IO (readFile')

main :: IO ()
main = do
    file1FilePath <- getLine
    file2FilePath <- getLine

    file1 <- readFile' file1FilePath
    file2 <- readFile' file2FilePath

    if file1 == file2
        then putStrLn "Success!"
        else putStrLn "Failure!"

Okay, so that’s version one. Let’s see the same semantics, but ordered a bit differently:

import System.IO (readFile')
import Data.Bool (bool)

main :: IO ()
main =  liftA2 (==) (getLine >>= readFile') (getLine >>= readFile')
    >>= putStrLn . bool "Failure!" "Success!"
def main():
    print('success' if open(input()).readlines() == open(input()).readlines() else 'failure')

Okay, so in both versions, the Python version wins out in terms of concision. But when you’re looking at the 2nd Haskell version, it’s more concise than the 1st Python version, I’d say it’s more readable, and it’s idiomatic, at least among some Haskellers.

The 2nd Python version, on the other hand, I’d think is generally smelly because it doesn’t clearly indicate an order of effect, and will get you screamed at by the Python style purity brigade.

Wait for that angry code review! :stuck_out_tongue:

Generally speaking I think with Haskell you can make good use of horizontal space, but let us not forget code is written once and read many times. I prefer version #1, what is happening is immediately clear you can sprinkle traceM later if needed, etc.

The more the function gets larger, the more I prefer unambiguous, simple code. if it gets too long, you can always move stuff to where; adding signatures helps too!

6 Likes

Unfortunately, that’s usually the case with most larger forms of syntactic sugar: they don’t provide a way to use certain “granules” as that would lead to syntax errors. An example is the use of <-, which some have thought was an Haskell operator that can somehow extract the result of any monadic expression (it isn’t and it doesn’t).


Considering that:

I think we can assume that the inspiration for Python’s procedural syntax was in large part the functional syntax in Miranda(R) and Haskell - if I understand you correctly, you are now attempting to find a way to make Haskell’s procedural (do-notation) syntax as neat as Python’s. If so, then by way of “syntactic transitivity”, it seems you’re wanting a more functional syntax for monadic expressions, beyond either do-notation or regular Haskell expression/function syntax involving the various monadic operators - you’re taking on quite a challenge there!

Before you proceed any further:

To add:

In summary:

  • at the time, do-notation was considered to be the most-palatable form of syntactic sugar.

  • while it started out as the work of a few individuals, it entered standard Haskell by way of group approval.

1 Like

Well that is an interesting example because I absolutely disagree that the second Haskell version is more readable.
It just unnecessarily obscures the order of effects and I don’t think I’m in the minority with this opinion. In fact, you got it wrong yourself! ^^

These two versions aren’t actually quite equivalent.

The order of effects in the first one is (obviously because you can clearly read it off the order of statements) getLine -> getLine -> readFile' -> readFile'.

But your second version actually performs effects in the order getLine -> readFile' -> getLine -> readFile', which manifests itself if the first file is not found.

I also find the claim that this is “idiomatic” somewhat objectionable. Just as one data point from someone who definitely knows what she’s doing, the pipes tutorial (which is amazing btw) only uses the first stlye.

4 Likes

From this example:

…it seems you prefer the “point-free” style - at the time, so did John Backus:

Can Programming Be Liberated from the von Neumann Style? … (1978)

1 Like

@prophet

Here’s another point I’ve gotten wrong. The Haskell version, if you ignore the usual “10 lines of extensions, 25 lines of imports” stuff Haskell code often incorporates (and here to a very tiny degree), is actually very slightly smaller than the Python version.

@atravers

To clarify, I prefer restricted point-free, i.e, I think point-free can easily become unreadable when the chain gets too long, but when used in moderation it’s beneficial.

If, say, the problem is “get two file names on the input prompt, try to compare the files represented, and return success if they’re the same and failure if not”, my actual preference would be:

import System.IO (readFile')

main :: IO ()
main = do
    file1 <- getLine >>= readFile'
    file2 <- getLine >>= readFile'

    putStrLn
        $ if file1 == file2
            then "Success"
            else "Failure"

This is a blend of the readability of #1 and the concision of #2.

As a limit of where I think point-free starts falling apart:

apiGet :: IO ()
apiGet = do
    res <- getChar 
    	>>= parseRequest . \case
            '1' -> urls !! 0
            ___ -> urls !! 1
        >>= httpLBS

    traverse_ putStrLn $ responseBodyBlock res
  where
    urls =
      [ "https://jsonplaceholder.typicode.com/todos/1"
      , "https://api.example.com/data"
      ]

    responseBodyBlock resource =
      [ "Response body:"
      , unpack $ getResponseBody resource
      , "OK1"
      ]

Just a snippet, a refactor of someone else’s code. Someone suggested me to take out do entirely, and turn it into a purely monadic pipeline.

But for me, it’s obvious that, even if I’m point-freeing to avoid some unnecessary bindings, the “get data” and “print data” are two separate steps, and just directly pipelining the traverse would make it significantly harder for me to read.

If this were to be turned into a pure pipeline, it’d follow the #4 model, where the steps are clearly delineated on the top-level, then have their implementation specified in the where clause.

And I’m already uncomfortable with the pipeline; it is at the maximum level I can tolerate. Anything more, I’d stuff a name on it and push it down to the where clause.


To summarize, then, I like, but do not push for, a semi-point-free style often mediated by do-notation.

I think I now understand your perspective on this matter: Haskell is labelled as being a functional language, but more often or not you find yourself looking at vast expanses of rather-procedural code.

The first nonstrict functional language I learned about was Miranda(R). So the transition to Haskell, and the already-widespread use of do-notation, was a slow one (it being more the result of necessity rather than preference). But I remained dissatisfied with Haskell’s imperative style for working with effects - over the last twenty years or so, I’ve learned to tolerate it, but not accept it (if many of the quotes, articles and references I’ve placed here and elsewhere didn’t already make that obvious ;-).

This remark:

…seems “about right” on this matter: these days, it seems most new Haskellers are far more interested in just “getting up and going”, which that simple “ultra-imperative” style allows them to do more quickly, particularly if they have prior exposure to imperativity. So for now, we need to write code that they can easily understand, even if we aren’t entirely satisfied with it.

1 Like

Yeah, but the point of this thread was to ask a question about how people style their monadic code, i.e, what kinds of best practices people had arrived at.

I’m just really disappointed that the most common answer was #1, that is to say, people seem to be seeking an imperativeness which is greater than that of Javascript, Python, F#, Elixir, and OCaml.

In the two mainstream languages, mild use of method chaining has become mainstream, and method chaining is somewhat similar to direct monadic bind in terms of style.

In the impure functional languages, pipeline operators are both used and abused, and there’s effectively experience around when pipelining is bad, as opposed to just trying to ban direct monadic bind altogether.

Imperative Haskell code isn’t the same as imperative JS, Rust, Go, etc. The fact that it’s first class and has Monad etc instances means you can metaprogram Haskell imperative code very nicely. That’s where it shines imo.

2 Likes

That’s where it shines […]

…like the proverbial “gilded cage” where I/O is concerned:

I also think this blended or hybrid approach is preferable. To me, semi-point-free code absolutely can improve readability because it emphasizes certain concepts by assigning them names.

When you have a little pipeline whose intermediate state should be irrelevant to the context, assigning a name to that state is clutter. Extracting the little pipeline to a named top-level form is the alternative, but now you need to name that pipeline and that might be more confusing for a reader than letting them just see the familiar pieces it is composed from.

4 Likes