Haskell vs Rust from FPBlock

I found this article, and while I find some of it useful, I found several points completely disingenuous:

From the article:

config <- loadConfig
config' <- validateConfig config
config'' <- mergeDefaults config'

I would never write that, and I would push back in a code review. I would much rather see:

config <- mergeDefaults =<< validateConfig =<< loadConfig

Rust eliminates this class of errors by design:

enum Person {
    Student { name: String, university: String },
    Worker { name: String, company: String },
}

fn get_company(person: &Person) -> Option<&str> {
    match person {
        Person::Worker { company, .. } => Some(company),
        Person::Student { .. } => None,
    }
}

That looks suspiciously like a haskell case statement. Add {-# LANGUAGE NoFieldSelectors #-} if you don’t want field selectors.

The error handling section is disingenuous as well. You can always turn a possibly error throwing function into an Either with try, or an Either into an exception with either <throw function> id.

Unit tests as part of source code

Haskell supports this, and HLS will re-evaluate examples on the fly. Maybe the author didn’t know, but it seems incredibly lazy to not have checked. You can set up a doctest to verify that the examples continue to match.

I find the section on formatting kind of petty. Pick a formatting tool and possibly a config file for you organization/project and then stick with it. If a team is bikeshedding, that sounds like a team problem instead of a haskell problem.

I don’t get the problem with Linked Lists. Hey, this language that was initially built to study lazy functional programming special-cases linked lists. They’re slow. OK, then don’t use them. Maybe there’s a valid gripe that the default is bad if you’re both new to haskell and have a poor semantic mismatch about what [1, 2, 3] means?

I think the gripe about a cabal file being its own syntax is completely unwarranted. If you want a standard format, then use hpack.

There’s a bunch in the article that I think is spot on. I believe that the production issues described were real. I know that the cross compilation story is worse for ghc and is being worked on. I think those correct points would hit with more force if the things that were just plain false were removed, along with the points that were really trivial.

9 Likes

Re: Compilation times, one problem Rust has that GHC doesn’t is that Rust doesn’t support separate compilation. So every time you compile a different rust tool, you recompile all of its dependencies. That may not matter in a given project, but it’s certainly worth mentioning when comparing compilation speeds.

2 Likes

Looks like:

{-# LANGUAGE DuplicateRecordFields, RecordWildCards #-}

module Person where

data Person
  = Student { name:: String, university:: String }
  | Worker { name:: String, company:: String }

get_company person =
  case person of
      Person.Worker { company, .. } -> Just company
      Person.Student { .. } -> Nothing

Wildcards not needed:

data Person
  = Student { name :: String, university :: String }
  | Worker { name :: String, company :: String }

get_company person =
  case person of
      Worker { company } -> Just company
      Student { } -> Nothing

And the Result<T, E> pattern is
 the result pattern, maybe something like this:

readFile2 path = do
  r <- liftIO (try (readFile path))
  case r of
    Left ex -> throwError (ConfigReadError (show ex))
    Right content -> return content

parseJSON2 str = do
  case parseJSON str of
    Left err -> throwError (ConfigParseError err)
    Right config -> return config

parseConfig :: FilePath -> ExceptT ConfigError IO Config
parseConfig path = do
    content <- readFile2 path
    config <- parseJSON2 content
    return config

So yeah, mostly nitpicks and a matter of taste, but it’s true Rust has better tooling.

3 Likes

The article is linked from last week’s weekly news.

Yeah, I saw several bits of Haskell code and thought I wouldn’t do it that way.

As a profession, haven’t we rather got over ‘language wars’(?) Is it a case of Haskell versus Rust or rather different tools for different jobs? (If you’re comparing hammer vs wrench, there’s something you don’t understand.)

1 Like

As a profession, haven’t we rather got over ‘language wars’(?) Is it a case of Haskell versus Rust or rather different tools for different jobs?

I didn’t mean versus as in “Two languages enter, one language leaves”, but as in “compared against”.

Programming languages are tools with a lot of overlap between their applicable niches.
I find value in accurate pros and cons comparing different tools and their strengths and weaknesses in various niches. I was annoyed at the clearly slapdash manner in which it was written. I actually thought it detracted from the useful points that the article actually contained.

2 Likes

Then I suspect “disingenuous” is not the word to be using. It carries a connotation that O.P. is being consciously misleading/deceptively partisan. Whereas it looks more like they’re merely not very experienced with Haskell/haven’t learnt appropriate idioms/perhaps are working in a shop that has a coding style better suited to OOP. (Their naĂŻvetĂ© is not a pose.)

Case in point would be your “looks suspiciously like a haskell case statement”. I agree field selectors and .style are over-used/not appropriate for partial fields. (The article actually comments “Safe approach requires pattern matching”, with the appropriate code. d’uh)

It does seem naïve for the article to talk about GHCi as a REPL and then complain about lack of support for unit tests, when they’ve also talked about HLS. Do they not know HLS’s capabilities?/perhaps they’ve only used a very old version?

I see from wikip Rust supports OOP style, including allowing mutable variables. (Is that what’s going on with the multiple let config = ...s? [**]) I’d have liked to see some reflection on how mutability influences coding style in a language claiming support for “multiple programming paradigms”. (I tend to treat such a claim as both scarey and probably marketing fluff.)

[**] And Haskell does support shadowing the same-named var in a do block. What’s going on with that config is it’s passing/mutating the var from one statement to the next; whereas Haskell sees the config on RHS and wants it to be a recursive def’n.


On the “different tools for different jobs” 
 Imagine you’re about to build a new application. Suppose Haskell or Rust skills and infrastructure are equally available. Would you be in two minds as to which tool to use? Or would the nature of the application make for an easy choice?

1 Like

I don’t know. The OP has contacts at FP complete, and could have run the article past one or more of them before posting. At what point does willful ignorance become significant enough to reach “deceptively partisan”.

To me, at least, not recognizing that Haskell’s case is available to destructure records is an example of this.

But this isn’t about language wars and us vs them. It’s about being informed before you post something. I can find half of an article to be uninformed propaganda and the other half useful comparisons.

While the author’s naĂŻvetĂ© is apparent to most of us on Haskell Discourse, it won’t be obvious to someone who is familiar with Rust, but not Haskell. Someone that wanted a useful dialogue would have done a better job to make sure the Haskell side was more accurately represented.

That would very much depend on the application. For most, I prefer Haskell. There are some on the boundary, where I could be swayed either way. There are some applications where rust would be much better.

1 Like

I see where you’re coming from. The article does seem to prefer Rust in most circumstances, and its arguments against Haskell seem a little outdated. To claim shady behavior, however, is disapponting. I would like to see us be more welcoming to somebody who’s having the opportunity to get back into Haskell.

Shadowing

Then I think you’ve missed the point, which is that OP actually wants to use variable name shadowing. In Haskell it’s discouraged or impossible, and OP prefers Rust’s style of encouraging it. I would disagree with him, but I wouldn’t be mad about it.

Partial field accessors

Do you really think OP doesn’t know how to do case statements in Haskell? Is that the point he’s making here?

I do agree this is a great opportunity to talk about all the cool stuff that’s improved with Haskell records recently, though!

Tests next to code

I’m sorry, what? This works? How? :smiley: Can I run it with cabal test? I had no idea, and I use Haskell all the time. I was under the impression that doctests are rather poorly supported by Cabal. Regardless, I’d hate to actually write all of my tests as doctests, wouldn’t you? And how many actual Haskell codebases out there do it in the Rust style?

Other

I disagree with you on whether or not formatting is a trivial issue — just a couple weeks ago I had to spend quite a bit of time convincing a newcomer to spend less time on it, but it was too late: they had already spent hours of their life comparing and contrasting Haskell formatting options. I never think about it anymore, but that’s only because I’ve already wasted the hours and hours of my life building up the muscle memory. I think it’s a perfectly valid place to say, “Rust does better.”

Finally, you say OP has “contacts at FP Complete”, perhaps unaware that they are FP Complete. (To be fair, it looks like a rebranding recently happened. But come on, it’s right in the footer of the blog post.) Sibi was the person who did the handoff of Stackage to me at the HF, and he still checks in from time to time. I’m basically writing this whole opus because I’m bummed you would accuse him of trying to spread FUD about Haskell. Can we please assume good faith, perhaps of someone who’s a bit out of the loop of the latest Haskell? A lot’s happened the last few years! I’m glad he’s getting the opportunity to get back into it!

8 Likes

I actually found O.P.'s Rust style easier to read. (And the version with multiple =<< not so much. [**]) Because we’re inside a do block, we can think of consecutive <- statements as performing some Monad action and chaining a result through them. (Why hang on to a merely loaded config after we’ve successfully validated then merged it?) As I mentioned above, shadowing is possible in Haskell, provided the bound-to name doesn’t appear on RHS. But in this case (which might be atypical), it’s precisely the name getting shadowed that we want to chain.

  • Are there use-cases where we’d want a recursive config <- blahConfig config?
  • Does a <- have to follow the same logic as let xs = 1:xs in ...?
  • (What’s going on inside a Monad with an infinite tail?)

[**] Also what if I want to emit a progress message at each step?

I think this would work, which gets a little way towards it:

config  <- loadConfig
putStrLn   "config Loaded"
config' <- validateConfig config
putStrLn   "config Validated"
config  <- mergeDefaults config'        -- shadow the loaded config

(This re-use is obviously fragile/vulnerable to abuse. I do not endorse this product.)

Me neither. And I’ve half a feeling I’ve seen similar request around the traps.

I’m really not trying to impugn motives. I’ve always been more interested in the strength of the arguments. I found several of them wanting and felt it distracted from the parts I felt hit home.

It certainly read that way to me, that the author didn’t see that there was a Haskell equivalent of case destructuring a record and its fields. If the specific point was just against the automatic generation of partial-function accessors, I definitely missed it.

Edit: I did miss it. Sorry. The pattern matching example uses positional rather than named arguments, so it was harder to see. I hope Sibi will be happy to find out about NoFieldSelectors, RecordWildCards, and NamedFieldPuns.

I’m sorry, what? This works? How? Can I run it with cabal test?

It works. There are several packages that support it. Cabal integration is not as good as you would hope. It’s an option in haskell-ci and several packages use it, including Cabal.

The HLS integration is really slick though, with hls-eval-plugin.

I’d hate to actually write all of my tests as doctests, wouldn’t you?

Yes, but having the option to write some of them inline is nice.

Can we please assume good faith, perhaps of someone who’s a bit out of the loop of the latest Haskell? A lot’s happened the last few years! I’m glad he’s getting the opportunity to get back into it!

I’m sorry. I really am. My purpose in posting this was that I found some of the criticism useful and other parts misinformed or outdated. I was hopeful that I would get a fair comparison with pros and cons, and from my perspective that wasn’t what I got.

2 Likes

Not sure if this is rhetorical question, but in case it isn’t: Reflex is a prominent user of RecursiveDo.

The Reflex documentation has a section which links to explainers for MonadFix and RecursiveDo: Resources — Reflex 0.5 documentation

It’s fascinating how Haskell is old enough for the culture to change over the years. For example, previously NondecreasingIndentation was a neat hack, a way to bail out while avoiding an additional level of indentation. And so, I’d wager that it was added to Alex without much judgment. But today, I don’t know of a single Haskeller that finds it tasteful. And so we have modern proposals like Borrow some Applicative/Monad syntax from Idris.

The snippet from Alex was brought to my attention recently in a MicroHS bug report. You can see how it uses both shadowing and NondecreasingIndentation, now both frowned upon:

main = do
  b <- readLn
  if b then return () else do
  b <- readLn
  if b then return () else do
  return ()

My point is that shadowing used to be more popular.

1 Like

No that wasn’t a rhetorical question, but it was about the specific IO code from the article, which is inside vanilla do, not mdo or rec. How/why would you want recursive config <- blahConfig config, where blahConfig does IO?

So when the article says:

In Haskell, you would typically need different names:

config <- loadConfig
config' <- validateConfig config
config'' <- mergeDefaults config'

You actually wouldn’t need different names; rather that’s a difference in taste/styleguide. And Sibi could write it with bare config throughout as per the preferred Rust, and it would work the same way as the version with config''. (Subject to FP’s house style, I guess. So this is a nitpick with the programming shop, not with Haskell-the-language.)

When the article says

Rust’s ability to shadow variables seamlessly is something I came to appreciate.

That’s not a difference compared to Haskell. You can shadow just as seamlessly in Haskell, merely programmers prefer not to.

1 Like

For what it’s worth, I’ve recently (last month or so) worked with Sibi on a Haskell project! I read this article without realising it was from him initially, but reviewing this thread and seeing it mention Sibi, I’m re-reviewing it.

I do think there’s something to be said about the defaults for Haskell allowing records and enums to be such footguns/needless conflicts. I think a lot of the contents of the post we can fairly say “yeah, that is a little annoying” - such as the disparate error handling methods and tooling support.

I’ll also say that despite ostensibly being able to use more modern extensions and such, often people just won’t reach for them because either the company style doesn’t include them or they don’t use them personally.

As usual, of course, we can look at some of these differences and aspire to be more supportive in those ways, whether that’s by advocating for a better set of defaults (to remove record field footguns for example) or by building better tooling.

1 Like