[HN Gopher] Upcoming/proposed breaking changes to Haskell
       ___________________________________________________________________
        
       Upcoming/proposed breaking changes to Haskell
        
       Author : todsacerdoti
       Score  : 108 points
       Date   : 2021-11-17 08:53 UTC (14 hours ago)
        
 (HTM) web link (github.com)
 (TXT) w3m dump (github.com)
        
       | throwaway81523 wrote:
       | Wow, some of these changes are pretty bold (eliminating ListT),
       | and I would have off the top of my head guessed higher breakage
       | levels than their estimate in some cases. E.g. does removing * as
       | "type" break basically every GADT-syntax type definition
       | everywhere?
       | 
       | It would be great if the entries in the list each included a very
       | brief rationale for the change. Yes I can see there is a linked
       | document for each one, but that is a lot more reading, when in
       | many cases a one-liner is probably enough.
        
       | masklinn wrote:
       | Still no removal of head and friends eh? Sad.
       | 
       | I think elm has shown that it's ok to avoid functions being
       | partial out of the box, even you're nowhere near a total language
       | and you certainly allow the user to create partial functions or
       | panic / throw errors.
        
         | dllthomas wrote:
         | I mostly agree, but will note that I find "head and friends"
         | unobjectionable and sometimes convenient at the ghci prompt.
         | 
         | I think the right solution ultimately might be different
         | preludes geared to different things, though doing the right
         | dance around making the right things available in the right
         | places (and unavailable in the wrong ones) while also making it
         | easy to understand (and remember) which context you're working
         | in and also not splitting the community is going to be...
         | delicate.
        
           | sullyj3 wrote:
           | It could be interesting to have an `Unsafe` convenience
           | module that is imported by default in the repl, but not in
           | source files. Maybe that would be too confusing for beginners
           | though.
        
       | jpe90 wrote:
       | I remember wondering why "return" is in the Monad class when you
       | can just use "pure" from Applicative, and why (<>) and "mapped"
       | both exist, so it's cool to read the historical explanations
       | here.
       | 
       | They are all logical, but will unfortunately add to the burden of
       | new learners who read books and guides that contain obsolete
       | references. I know a lot of the material I learned with will be
       | confusing when examples start spitting out compile errors. I
       | didn't see if there are efforts to account for this with some
       | custom error messages that notify you why the obsolete code no
       | longer works and suggests how to fix it, but I think that would
       | be helpful.
       | 
       | Edit: It looks like that concern was already raised and
       | addressed, glad to see it.
        
         | mdm12 wrote:
         | The return/pure distinction is due to history, I believe. The
         | Monad typeclass was defined before the Applicative typeclass.
         | 
         | Part of the fun of being a research language is that you don't
         | know everything up-front!
        
           | quchen wrote:
           | Monad and Functor were first, if I remember correctly
           | Applicative made its debut when Parsec became popular. For a
           | long time, the hierarchy was >>Functor ===> Applicative,
           | Monad is independent<<.
           | 
           | We made Applicative a superclass of Monad around 2015, and
           | since then return has been a historical artifact (with a
           | dangerously misleading name).
        
             | 1-more wrote:
             | ty for this history! I write haskell at work but with an
             | honestly middling understanding of the category theory that
             | goes into what typeclasses are supersets of other
             | typeclasses. Mostly because we use an overly verbose
             | version of Prelude. So it's wild to me that these mathy
             | bits were not always set in stone!
        
         | nerdponx wrote:
         | If you are interested in "Haskell, but with a nicer standard
         | library", Idris 2 might actually be an interesting choice. The
         | Idris 2 prelude very much feels like a cleaned-up version of
         | the Haskell prelude, and all the fancy dependent and
         | quantitative type stuff is mostly "opt-in".
         | 
         | For example, in Idris 2, the `[ foo | x <- bar ]` syntax is not
         | just a "list comprehension", but a "monad comprehension", and
         | `map` is not specialized for lists but it is actually what
         | `fmap` is in Haskell. There is also other interesting shorthand
         | syntax like `!foo` which is equivalent to something like `do x
         | <- foo ; x`.
         | 
         | The fact that it compiles to Chez Scheme and has a fairly easy-
         | to-use FFI is even nicer.
         | 
         | Would I deploy it in production yet? No. But the language is
         | trying to be fundamentally practical and user-friendly while
         | still being dependently- and quantitatively-typed. And in my
         | opinion, it's succeeding so far! It also has a language server,
         | so you can get advanced interactive editing features in pretty
         | much any code editor that supports LSP.
         | 
         | Oh, and there's no `return` in Idris 2, only `pure` :)
        
           | kaba0 wrote:
           | Isn't haskell's list comprehension can be used for monad
           | comprehensions as well with a language extension? I remember
           | using that once.
        
           | throwaway81523 wrote:
           | GHC has monad comprehensions with an extension, {-# LANGUAGE:
           | MonadComprehensions #-}
           | 
           | GHC has an enormous amount of machinery to infer types and
           | check equality automatically. I wonder if Idris has anywhere
           | near that much. Automatic inference is why Haskell resisted
           | dependent types until quite recently, though there were
           | already some cases that it couldn't do automatically.
           | 
           | As for pure vs return, that's because the typeclass system
           | was rearranged pretty recently. Before that, Monad instances
           | weren't necessarily also Applicative. "return" was kind of
           | cool in that you could write what looked like imperative
           | subroutines that returned values.
           | 
           | !foo in Idris sounds like foo >>= whatever or whatever =<<
           | foo in Haskell.
        
             | nerdponx wrote:
             | > GHC has an enormous amount of machinery to infer types
             | 
             | Idris 2 has more or less no type inference at all. I think
             | maybe type inference for dependent types isn't decidable,
             | or something like that?
             | 
             | But I know that they are interested in adding inference to
             | Idris 2 in certain cases that can be proven to work
             | correctly.
             | 
             | It's definitely a deficiency in the Idris user experience
             | vs the Haskell user experience.
             | 
             | > !foo in Idris sounds like foo >>= whatever or whatever
             | =<< foo in Haskell.
             | 
             | Idris has >>= as well. But see here for a nice demo of !
             | and other "do"-related syntax: https://idris2.readthedocs.i
             | o/en/latest/tutorial/interfaces....
        
               | sullyj3 wrote:
               | Yep, type checking clearly can't be decidable, since the
               | type system is turing complete.
               | 
               | Imo inference is a bit overrated anyway. I find
               | annotations to be very useful.
               | 
               | There's a series of steps here:
               | 
               | - "Static type annotations are too verbose, dynamic
               | languages allow you to avoid the ceremony." - "But
               | Hindler Milner type systems can infer the types, so you
               | usually don't have to write the type annotations!" -
               | "Writing type annotations is useful anyway, because it
               | serves as valuable documentation, makes reasoning about
               | the program easier, and results in more useful type
               | errors."
               | 
               | Thinking about it more now, there's another step: - "If
               | you have good type inference, you can use editor tooling
               | (eg the LSP) to automatically insert the type signatures
               | for you!"
        
               | throwaway81523 wrote:
               | Top level type annotations in Haskell are very helpful,
               | but with no type inference, you would also have to
               | annotate every intermediate term in the program, which
               | would be intolerable. Remember that the programs are
               | essentially typed lambda calculus, so every term must
               | have a type. Normally you let the compiler figure out all
               | or almost all of the types.
               | 
               | Part of the usefulness of top level annotations in
               | Haskell is that if your program has a type error,
               | inference can fail in multiple ways. I.e. the unification
               | algorithm might assign type T to your function F and chug
               | along happily until it runs into a conflict in some
               | unrelated part of the program, then throw an unhelpful
               | error message in the case where T wasn't the type that
               | you intended for F. By annotating F with the type you
               | really want, you get an error message that does a better
               | job pinpointing the problem.
               | 
               | This is less of an issue in ML, since ML's type system is
               | less general than Haskell's, so the inference algorithm
               | can't go as crazy, and you usually get good error
               | messages even without annotations.
        
           | wk_end wrote:
           | I want to like Idris - as a language it does so much right -
           | but I still feel a little burnt. A few years ago were
           | exciting times; Idris 1 had hit 1.0 and was humming along
           | nicely, there was excellent tooling available, & Type-Driven
           | Development with Idris had been published - a real printed
           | book about practical coding with dependent types! Could
           | reliable software be far behind? Would I maybe get to develop
           | somewhere that took software engineering seriously in my
           | lifetime?
           | 
           | And then, with the possibility of success on the horizon, the
           | Idris folk(s) got distracted by the QTT hype and decided to
           | abandon ship so they could start on Idris 2. And, like, don't
           | get me wrong - the QTT stuff is cool, and I'm a Rust fan in
           | part because getting to encode linearity in your types is a
           | real superpower - but it's so depressing that the world of
           | practical dependent types feels just as far away now as it
           | did ten years ago, after getting so excited about it five
           | years ago. And it underscores what might be a bigger problem:
           | at the end of the day - and by the Idris FAQ's own admission
           | - Idris is a research project into practical dependent types,
           | and Edwin Brady is an academic. Which means that when he gets
           | interested in some other area of research, he's free to
           | just...do that instead, or start over on Idris n+1, and leave
           | Idris 1, 2, 3 ... n to wither.
        
           | mdm12 wrote:
           | Your description of a monad comprehension in Idris reminds me
           | of computation expressions in F#[1]. Looks like I have one
           | more programming language to dive into!
           | 
           | [1] https://docs.microsoft.com/en-us/dotnet/fsharp/language-
           | refe...
        
             | sullyj3 wrote:
             | A closer analogue is probably do-notation, which
             | comprehensions are syntactic sugar for. Comprehensions can
             | be terser for simple expressions, but for anything longer,
             | do notation is generally more readable.
        
           | sullyj3 wrote:
           | There are many things I like about Idris 2. I think I'll be
           | more inclined to take it seriously as a practical language
           | once it has the equivalent of Hackage, hoogle, and cabal.
           | Right now I can't even read the standard library docs, I have
           | to browse the github source. And I have no idea how I'd go
           | about depending on a package. I'm sure I could figure it out,
           | but I assume at this stage it's fairly tedious.
        
       | WJW wrote:
       | What I like about Haskell is that it is unashamedly a language
       | for programming language research, by programming language
       | researchers. "This change needs to happens because otherwise the
       | mathematics don't work out" would never fly in golang or Ruby if
       | it broke backwards compatibility, but happens regularly in
       | Haskell.
       | 
       | This has a couple of effects:
       | 
       | - It does make it harder to maintain code for businesses, since
       | keeping up with language updates means that you will have to do
       | relatively more maintenance work to keep up with these breaking
       | changes.
       | 
       | - It slowly makes the core libraries more and more elegant over
       | time and this paves the way for new advances in eg type systems
       | and whatnot. Linear types would have been way harder to add if
       | the existing system had been (even more) a giant mess of hacks to
       | maintain backwards compatibility 20 years back.
       | 
       | - The ease of writing GHC extensions makes it so that it is
       | relatively easy to extend the base language in some way and back
       | out if it doesn't turn out to work. This makes experimentation
       | way cheaper than if every core language change has to be
       | "permanent".
       | 
       | These changes combined mean that Haskell itself will probably
       | never be a mainstream language for business applications, and
       | that is fine. Because many (most?) programming language
       | implementors have had some exposure to Haskell in university and
       | because they all speak to one another on conferences etc, many of
       | the ideas first explored by Haskell (and its predecessors in
       | academia) are "leaking out" if they are good (like list
       | comprehensions in Python or type classes in Rust) and they don't
       | get taken over if they turn out to have been mistakes (like lazy
       | I/O). The true value of Haskell is having a language in which to
       | experiment with new concepts, so they can be proven useful (or
       | not) before they make their way into the wild.
        
         | bradrn wrote:
         | > What I like about Haskell is that it is unashamedly a
         | language for programming language research, by programming
         | language researchers
         | 
         | Wait, what? This runs completely counter to my experience of
         | Haskell. I use it whenever I can, and I'm pretty sure I'm not a
         | PL researcher. Lots of other programmers write actual, real-
         | world programs in Haskell as well. Much of the discussion I see
         | in Haskell communities concerns areas such as performance,
         | toolchains and libraries -- areas which PL researches are
         | famous for ignoring. I will admit that we often talk about GHC
         | extensions and type theory and whatnot, but the discourse
         | around those areas is not all that mathematical; it tends
         | towards 'how is this useful for writing programs?'. In other
         | words, exactly like every other real-world programming language
         | out there.
         | 
         | (That being said, maths _is_ fun, and I regularly see people
         | defining weird and wonderful abstractions. But this rarely gets
         | in the way of writing programs. If anything, every now and then
         | someone comes up with an abstraction which turns out to be
         | incredibly useful in practice: lenses, free monads,
         | applicatives, HKTs...)
        
           | WJW wrote:
           | I didn't mean to imply that nobody else but PL researchers
           | _can_ use Haskell, clearly a lot of people do. What my post
           | intended to convey was that the _focus_ of the language seems
           | a lot more focused on research than (say) Ruby or Javascript.
           | This is not strange, given its history as a designed-by-
           | committee language  "to serve as a basis for future research
           | in functional-language design". (see https://en.wikipedia.org
           | /wiki/Haskell_(programming_language)... )
           | 
           | The point in your last sentence that "every now and then
           | someone comes up with an abstraction which turns out to be
           | incredibly useful in practice" is exactly what I meant in the
           | OP: these abstractions seem to be developed way more often in
           | Haskell first and then they leak to other programming
           | languages later than the other way around.
        
         | valenterry wrote:
         | Very well summarised.
         | 
         | I like that Haskell has inspired Scala, my main language. While
         | it lacks some of the elegance of Haskell, it is a nice
         | compromise between an advanced and Haskell-inspired type-system
         | and stability for business, plus having the whole JVM ecosystem
         | is awesome.
         | 
         | Therefore, hopefully Haskell keeps advancing and bringing
         | innovations and having them trickle into more mainstream
         | languages.
        
           | rkrzr wrote:
           | Having written both Haskell and Scala professionally, I
           | actually see Scala's dependence on the JVM as its biggest
           | flaw.
           | 
           | If it weren't for the JVM Scala could make do without an Any
           | type and without having to deal with null values. I hope that
           | alternative runtimes like Scala Native will become more
           | popular, since Scala could evolve away from its JVM roots
           | then.
           | 
           | I'm also not a fan of JVM performance optimization, since
           | there are too many knobs to turn, and the knobs often have
           | (undocumented) side-effects on other knobs. This is a lot
           | simpler with the Haskell runtime (in my experience) since you
           | mainly need to tweak the GC settings there.
        
             | kaba0 wrote:
             | You really should never tweak anything in case of the JVM
             | other than perhaps max heap size and rarely target pause
             | time (for G1, so you can either prefer throughput or
             | latency). Anything else you find online is likely already
             | outdated and very specific for a given code. Instead just
             | use a recent JDK and profile your code.
             | 
             | As for scala, missing the java ecosystem would pretty much
             | decimate the language, no matter how cool it is.
        
         | cptwunderlich wrote:
         | That's not really true. There was a huge outcry against the
         | removal of (/=). There are still lots of warts in Prelude and
         | base (head being partial, foldl is in prelude but not foldl').
         | So yeah, language evolution is still a hard problem
        
           | WJW wrote:
           | You are right that it's not "really" true, but I do think
           | that at least it's not wholly untrue. Foldable/Traversable
           | got through, and so did Monad Of No Return, the Functor-
           | Applicative-Monad Proposal and several more that I can't name
           | off the top of my head. It does happen, even if we both would
           | like progress to be quicker and more drastic :)
           | 
           | IMO, the existence of the Haskell Report and the inability of
           | the community to update it in a reasonably timely manner is
           | the biggest cause of the persistence of the biggest warts
           | like partial head and foldl. I don't think anyone wants to
           | keep those but "The Haskell Report specifies that they are in
           | the prelude and with the exact implementation they have"
           | tends to kill any discussion. Let's hope the HF makes some
           | progress on that soon!
        
         | fbn79 wrote:
         | Breaking changes happen regularly in many commercial and
         | business adopted languages. Es. PHP 5 vs 7, Python 2 vs 3,
         | Typescript ecc. Even Java added some keywords over time.
        
           | kaba0 wrote:
           | That's breaking forward compatibility though, not backwards.
           | The former is pretty cool but unrealistic and not as useful.
        
           | Cthulhu_ wrote:
           | Nit: Adding a keyword is not a breaking change, removing them
           | is.
           | 
           | With PHP, you could argue that they were needed because it
           | developed organically, instead of through a process by
           | experienced language designers. I'm not sure about Python
           | though.
           | 
           | Counter-example, Go hasn't had backwards-incompatible changes
           | yet, and at the moment there's no compelling reasons to make
           | a breaking 2.0 version - and any plans for a 2.0 version so
           | far have minimal changes, so going to 2.0 should be a smooth
           | and quick process.
        
             | [deleted]
        
             | masklinn wrote:
             | > Nit: Adding a keyword is not a breaking change, removing
             | them is.
             | 
             | Langages generally try to add contextual / soft keywords
             | these days but otherwise it's absolutely a breaking change:
             | any variable named the same will trigger a parse error.
             | That is why languages try to either not add keywords, or
             | find ways to make them opt-in somehow.
        
             | knome wrote:
             | >Nit: Adding a keyword is not a breaking change, removing
             | them is.
             | 
             | Of course adding a keyword is a breaking change. It will
             | invalidate all uses of that keyword where used as a
             | variable. Perhaps PHP is unaffected, as it has sigils on
             | its variables, but most languages, including haskell, do
             | not.
        
               | masklinn wrote:
               | > Perhaps PHP is unaffected, as it has sigils on its
               | variables
               | 
               | Locals are prefixed but functions, constants, and classes
               | are not.
               | 
               | Also barewords but that horror was removed in php 8.
        
           | jesboat wrote:
           | To be fair, almost all of the keyword-ish things Java's added
           | have been done such that they _rarely_ can change the meaning
           | of any existing programs. Assuming I didn 't miss any, all
           | the keyword-ish things which have been added, ever:
           | Java 1.4, 2002: assert       Java 1.5, 2004: enum       Java
           | 10, 2018: var       Java 14, 2020: yield       Java 16, 2021:
           | record       Java 17, 2021: permits, sealed
           | 
           | Almost all were added in such a way that the extent of the
           | breakage would be that a program which previously worked
           | would now fail to compile (i.e. fail safely.)
           | 
           | (The only exceptions I can see are for `assert` and `var`,
           | and even then only when some parts of a program are compiled
           | with older versions of the compiler, and even then only when
           | various other conditions are met.)
        
           | tzs wrote:
           | A breaking change is only a breaking change to you if you
           | switch to the updated language. If your business does not
           | actually need anything the updated language offers you can
           | often just stick with the old version.
           | 
           | There are plenty of sites still on PHP 5 for example.
           | 
           | If you are doing something where you rely on third party
           | libraries, and you have to keep those third party libraries
           | up to date (e.g., a third party library that uses a remote
           | service and that remote service keeps changing their API),
           | then you may be forced to update to the new version of the
           | language because the library switches to the new version.
           | 
           | For a language that isn't really mainstream for business use,
           | I'd expect that there aren't a lot of third party business
           | libraries that you'd be using and so the "library made me do
           | it" language update would not be necessary. That should allow
           | staying on the old version as long as an OS upgrade doesn't
           | kill the ability to run the compiler or interpreter.
        
         | marcosdumay wrote:
         | > It does make it harder to maintain code for businesses, since
         | keeping up with language updates means that you will have to do
         | relatively more maintenance work to keep up with these breaking
         | changes.
         | 
         | That is so incredibly slow, that this point is moot, unless you
         | are comparing it to C++.
         | 
         | You will have much more work keeping up with change on the
         | Haskell library ecosystem, will have more work keeping up the
         | changes on the core of most mainstream languages, and will have
         | orders of magnitude more work keeping up with the ecosystem of
         | any other language.
        
         | yakshaving_jgt wrote:
         | > It does make it harder to maintain code for businesses, since
         | keeping up with language updates means that you will have to do
         | relatively more maintenance work to keep up with these breaking
         | changes.
         | 
         | To be honest -- I think even in my 90KLOC Haskell codebase --
         | handling these breaking changes are a cheap and easy change
         | because of the compiler.
        
           | SkyMarshal wrote:
           | Yeah, refactoring the whole codebase in a language like
           | Haskell is, maybe not trivial, but something the language
           | lets you lean into, systematize, and make SOP.
        
         | moss2 wrote:
         | Let's hope Haskell never becomes commercially successful then
         | :-)
        
           | jpe90 wrote:
           | I recall reading historical threads and being surprised at
           | animosity towards FPComplete and some of the efforts they
           | were making to standardize changes to make Haskell more
           | commercially viable. At the time I thought being upset by
           | that was absurd, but over time I guess I sort of understood
           | the sentiment.
        
       | mseepgood wrote:
       | After witnessing a country sever its legs with Brexit, we now see
       | a programming language commit suicide via breaking changes.
       | 'Avoid success' at all costs.
        
         | kadoban wrote:
         | Haskell does these type of breaking changes pretty much all the
         | time. Nothing in the article looks out of the norm.
        
         | tromp wrote:
         | The motto is rather: Avoid `success at all costs'.
        
           | throwamon wrote:
           | The precedence of the words depends on what compiler version
           | you're using.
        
             | tromp wrote:
             | infixl 0 `avoid`
             | 
             | infixr 1 `at_all`
        
         | tejohnso wrote:
         | That's some impressive context conflation.
        
         | kreetx wrote:
         | What are you talking about?
        
       | kreetx wrote:
       | For those not in the know, a redundant method (/=) is removed
       | from the Eq class and added as a regular function, and,
       | apparently, this is making a few people very angry. (Not sure why
       | though)
        
         | retrac wrote:
         | I find it delightful, really.                   a /= b = not (a
         | == b)
         | 
         | is the kind of thing that makes Haskell beautiful. Slowly
         | ascending to purity. Didn't break anything of mine, though.
        
           | jez wrote:
           | That is already how it's defined in the `base` package right
           | now though:                   class  Eq a  where
           | (==), (/=)           :: a -> a -> Bool             x /= y
           | = not (x == y)             x == y               = not (x /=
           | y)
           | 
           | https://www.stackage.org/haddock/lts-18.17/ghc-
           | prim-0.6.1/sr...
           | 
           | The way this works is that when you implement the `Eq`
           | typeclass for a type, you can provide more specific
           | implementations. A minimal complete implementation is to
           | implement either == or /= for your type, and the other
           | definition will apply.
           | 
           | The way this breaks existing code (iiuc) is that as a top-
           | level function, if you have imported the `Eq` type class but
           | haven't imported the `Prelude` module implicitly (on by
           | default but can be turned off), you will not have `/=` in
           | scope anymore.
           | 
           | I think people are upset by this less because of how hard it
           | would be to fix, but more because of how it acts as a sort of
           | signaling change ("they're willing to break my code for this,
           | which I didn't want, but not for X which I did"). The most
           | common value of X I've seen is removing or reworking the
           | partial functions in the Prelude (e.g., head / tail on `[a]`
           | raising an exception instead of returning `Maybe a`).
        
       | lngnmn2 wrote:
       | Applicative is actually an artificial concept, much more awkward.
       | 
       | Anyway, making a hierarchy more consistent with mathematical
       | tradition is a good thing.
       | 
       | As for usefulness, without redundant esoteric abstractions Monoid
       | is all we need, and the abstract Monad type-class, of course (for
       | building abstraction barriers at a type level).
       | 
       | The problem with Haskell is whole Himalayas of bullshit under
       | which its clarity and principles has been buried.
       | 
       | Haskell became _the way of "virtue" signalling_ for narcissistic
       | snowflakes, second only to the Category Theory, which is, buy the
       | way, is "empty" outside of monoidian composition and the notion
       | of an abstract functor.
        
       ___________________________________________________________________
       (page generated 2021-11-17 23:02 UTC)