Towards a prevalent alternative prelude?

What would happen to packages that import base like base == 4.*? I am grepping index-00 and I see lots of hits (some quite popular too — like hspec).

There seems to be a lot of confusion about the relationship between Prelude and the dual roles of base library. Let me try to lay out the land.

  1. Starting from the lowest level, there is base-of-GHC-primitives, a collection of low-level modules that are provided by GHC and cannot be implemented anywhere else.

  2. Then there is base-the-kitchen-sink, which is a collection of modules that you get as part of library called base, guaranteed to always be available without fiddling with Cabal or Stack.

  3. Finally there’s Prelude, a special module that is always implicitly imported.

The current situation is that base-the-kitchen-sink includes both Prelude (as one of its exposed modules) and base-of-GHC-primitives (as a subset of all its modules). This however need not be the case. GHC installation can come with more than one primitive library, and base-the-kitchen-sink doesn’t need to expose everything from every primitive library.

The better way to think about this from user’s point of view is:

  1. There is a small set of standard types and values that are in scope by default, with no need to import them. This is Prelude.
  2. There is a wider set of relatively well-known types and values that are always available with any GHC installation, but one has to import a module before using them. The import of these modules does not depend on a package manger, and there’s no question of which version of a module one gets.
  3. Finally there’s a universe of Haskell modules that come from packages, and you gotta use a package manager before you can import one.

Note I didn’t mention base in the second item, because it’s irrelevant where these modules come from. The only thing that matters is that they are available by default, at least until you want to define your own package and need to specify the dependency bounds.

4 Likes

I’ve seen this sentiment pop up a few times in this thread. I feel like this is already the case with the “wired in” packages that GHC provides. Am I missing something?

For example if you install GHC 8.10.4 then you can rely on these packages being available, which includes many of the usual suspects: bytestring, containers, process, text, transformers, and so on.

And with respect to base and Prelude, my two cents are: Alternative preludes work great for applications but suck for libraries. As a library author I want my software to be approachable and usable. Unfortunately that means sticking with the lowest common denominator, which is base. Depending on wired in packages is fine, but on Hackage it’s still visually cluttered to depend on mtl, transformers, text, and bytestring even though they’re all provided “for free”.

2 Likes

What would happen to packages that import base like base == 4.*? I am grepping index-00 and I see lots of hits (some quite popular too — like hspec).

They’ll update.

3 Likes

No on is saying “Nah let’s keep foldl around, it’s fine.”

Unfortunately it’s not as simple as that (to my surprise).

1 Like

I don’t think you’re missing anything and I’m not sentimental about it. I’m just trying to explain, apparently not very well, that the discussion of the base package is not terribly relevant. To a beginner there is no distinction between base and text, because they are both available out of the box and one can import Data.List and Data.Text with exactly the same effort.

The trouble usually begins when you have to use a package manager to obtain and use a module outside the default set that comes with GHC. At least that’s my impression from Reddit; I don’t recall many questions about how to import a function from an already-available module. Merging text into base would not help with this problem at all.

3 Likes

To a beginner there is no distinction between base and text, because they are both available out of the box and one can import Data.List and Data.Text with exactly the same effort

One can import a later version of text than shipped with one’s GHC (and possibly even an earlier one!). Can one import a later version of base?

The first three words you quoted matter. If you’re talking about experts, then yes, expanding base would bring more problems to them and it wouldn’t help beginners either. Is this what you’re driving at?

Yes, if the beginner never needs a later version of text than was shipped with her GHC then you are correct that there is not much distinction between text and base.

I am, well, surprised that people would want to create yet another base library, to put it politely. We have so many of them, and another one is certainly one too many. None has been widely successful although many of them are, purely as a library, better than base.

An alternative base will not be successful.

Too few people would care about it, the ecosystem will simply not move there. (The obligatory XKCD has already been posted: https://xkcd.com/927/) What really needs to be adressed is the actual problem:

The development model of base is not good.

Important changes are not made, claiming backwards compatibility as a reason. But similar to what Michael Snoyman and other have pointed out, the Haskell ecosystem is ready to accept a certain amount of breaking changes, since GHC itself causes some breakage. If you want to freeze code, you freeze the GHC version, and thus the base version. Thus:

base does not need to be backwards compatible forever.

No library ever can reasonably be expected to be backwards compatible forever, and still be expected to be pleasant to work with after a few decades. And we really need to offer a pleasant base!

base is the standard library and it needs to be good!

The success of Haskell is to some non-negligible portion tied to a good standard library. Beginners use it, advanced folk stay with it for a long time. It’s the default starting place. So it needs to be kept in a good state. Once you accept that, it’s not the question anymore whether we clean up messes like head, String and foldl, but how fast we do it.

My opinion: Three versions back are sufficient. Mark historic warts as deprecated in one version, and remove them in a later version. Packages will update, or come out of fashion, and in the latter case, rightly so since they probably won’t run with newer GHCs anyways. Summary:

Slowly, but determinedly, clean up the existing base instead of making yet another one.

Split it up in base-ghc and base-prelude-and-kitchen-sink, fine, but work with it and make it good! There are enough people who will contribute the relevant code, it’s purely a coordination issue.

24 Likes

I don’t necessarily have much stock in what mentality is used in designing the new base, but I do definitely support decoupling it from GHC. More than just the release schedule, though, I’d argue for no hard dependency on its blessed implementations either; base should be a core library for whatever compiler is being used. Yes, GHC is currently the only player in town, but I’d speculate that part of that is because everything depends on base, and base exposes a lot of the internals. In order for an alternate compiler to be viable, it essentially has to replicate all of GHC —which is a rather prohibitive task— or advertise that it provides modules that it really doesn’t —and risk breaking things that do depend on what is (silently!) unimplemented.

Instead, I’d like to see a division into at least base and base-ghc or whatever other name is chosen, so that a toy- or a research compiler could be built to provide the (probably minimal) base and at least be used for simple packages, while any performance-sensitive projects can additionally depend on base-ghc for lower-level control of the in-memory representation (or whatever it is that people use the GHC modules for).

I don’t know exactly how that would be implemented, but I’d probably be initially looking at Backpack. If that means enshrining package managers, then so be it. (More likely, base may still wind up being special-cased by compilers, even if they don’t otherwise implement Backpack, but at least it would have a general target scope.) I’d still prefer that to locking in a “GHC” ecosystem vs a “XHC” ecosystem.

3 Likes

There are some established practices across other communities. If something is about to get removed, first it’s marked as deprecated, use xxx instead. So that people see it, aware about it and can plan changes in advance. And in next release it’s relatively safe to remove it with minimal broken code.

4 Likes

Today we released the 1.0.0.0 version of relude and it addresses one particular point, mentioned in this thread several times:

That being said, my largest reservation about relude’s particular approach is that it introduces its own abstractions and hides a good amount of functionality of the libraries on which it is based.

It (relude) also exposes the Text type, but it seems like I still have to register the text dependency to use the value.

Now relude reexports the main API of text, bytestring, containers and unordered-containers. So, reexporting the functionality from other libraries entirely without the need to add them to .cabal is something that is already possible in Haskell (not as convenient as I wanted, but still something). And it is just a matter of some time, devoted to this feature implementation.

12 Likes

Three cheers! Let’s make it happen!

I’d agree it’s mostly a coordination issue, but we also need to navigate cultural hurdles (why hasn’t this cleanup already happened?). We also have some strong egos to work with.

1 Like

The first issue situations like Data.Int -> GHC.Int, where the interface is standard enough but the implementation is GHC-specific. But we can now use backpack to save us from that.

The second issue is orphans. It’s really hard to not write orphans in base without adding lots off “extra” dependencies linearizing thing. I started on https://gitlab.haskell.org/ghc/ghc/-/wikis/Rehabilitating-Orphans-with-Order-theory to make orphans permissable, as described in my post in the original thread.

With those two things, I believe we will be able to decouple base from GHC very satisfactorily.

3 Likes

The orphans proposal doesn’t spell out the exact method of declaring an orphan module or package, but I imagine at the top level it would be some new syntax in the Cabal package, like

 name: containers-lens-orphans
 orphan-meet: containers, lens
 ...

Cabal could ensure that there is no more than one orphan-meet for any two packages in the package set, that part is easy. I don’t quite see how this trickles down to the compiler, though.

@blamario No worries, it hasn’t been exactly worked out yet.

  1. One would additionally need to specify the exact modules, say Data.Map and Control.Lens.At, and the module in the current library that is the meet. All that information is then handed off to GHC when it is compiling modules.
  2. When checking say Ord k => At (Map k a) in the third module, it can see that this instance uses items from the two modules, At, and Map. Furthermore, the only possible instance head that would overlap is the At v, which would have to go in Control.Lens.At if it exists. So GHC can approve of Ord k => At (Map k a) knowing that any other overlapping instance would either violate the lattice rules, or be in a module that’s already imported and thus caught when Ord k => At (Map k a)` is defined. Together, GHC can be sure is no other way to have two overlapping orphan instances that are both valid in isolation.

Thank you for your contributions on that! I only follow half, but I can understand the general problem and how that increases resistance to improving/changing this. It seems like now is a good time to get attention on your proposals/work in an effort to see them thru and keep momentum going on this.

1 Like

Deprecate partial functions from the Prelude, giving them new quarantined homes · Issue #70 · haskell/core-libraries-committee · GitHub :


andreasabel:


Gabriella439:


Gabriella439:

  • head :: a -> [a] -> a
    head d []     = d
    head _ (x:xs) = x
    
    tail :: a -> [a] -> a
    tail d []     = d
    tail _ (_:xs) = xs
    
    init :: a -> [a] -> [a]
    init d []     = d
    init _ [_]    = []
    init d (x:xs) = xs : init d xs
    
    last :: a -> [a] -> [a]
    last d []     = d
    last _ [x]    = x
    last _ (_:xs) = last d xs
    

soupi:

  • module Tutorial_Prelude where
    import Prelude hiding (
        head, tail, init, last, ...
    )
    

emilypi:


I just want to chime in and echo the the haskell standard library should be good and the base should be modular sentiments.

3 Likes