Fixing the `Prelude` problem

For a long time, the community has been spilling ink over these particular problems:

  1. Which functions should a brand-new Haskell programmer have at their disposal that best showcase the language’s features, patterns, and idioms?

  2. How can I easily create a project that a priori requires the use of a large or DSL-like package, like lens or optics, and use their types and operators implicitly?

  3. Qualified imports have to happen within the user’s module, and can’t be done through re-exports. Can we fix this without breaking the universe?

Point (1) has led to the proliferation of “alternative Preludes”/“standard libraries” that provide different combinations of functions and type classes for different purposes. To name a fraction:

Many of those with fewer Hackage downloads, omitted from this list, focused on either combining one or more of the above with other common libraries, which brings me to point (2). It is clearly desirable to have

  • a single source of reference per project, with
  • names, possibly qualified, from common dependency imports, that
  • encompass the referents in the local environment at the start of every module in the project,
  • while still allowing modules to import further modules, whether local or from dependencies.

One way to do this while also facilitating (3) is to introduce a new Cabal stanza. For example,

local-implicit-imports:
  , import Data.Text (Text)
  , import qualified Data.Map as Map
  , import Data.IntSet (insert)
  , import Data.IntSet qualified as IntSet (empty)

would tell your project’s build system to include the following declarations in each local module:

import Data.Text (Text)
import qualified Data.Map as Map
import Data.IntSet (insert)
import Data.IntSet qualified as IntSet (empty)

so that

-- Main.hs
module Main where

import System.IO (print)

main :: IO ()
main = do
  print (Map.empty :: Map.Map Text Text)
  print (insert 1 IntSet.empty)

compiles and runs. The Cabal-stanza-to-splice approach will also fail to compile if dependencies or language extensions are missing, and continue to warn when a name is ambiguous.

We’ve just solved (2) and (3). Users of popular libraries can simply share their build-depends and local-implicit-imports to create “standard namespaces” for projects using them. Actually, since it forces all project modules to have the same qualified imports, managing names this way can lead to better code comprehension and onboarding speeds.

But does this approach solve (1)? Can we really foist it upon a brand-new Haskell user to wield cabal when they’ve hardly touched ghci? I think we can. With the help of ghcup and the amazing language server team, going from zero to “new Haskell project using recent GHC version with language server support” is a matter of minutes on many systems. Pushing proper project setup techniques to newcomers will only increase the number of well-structured projects, familiarize useful libraries early, and reduce the barrier to contribution to many open-source projects.

Personally, I find the lack of qualified re-exports the most disappointing. Qualified imports of datatype modules make the most sense when they exactly match the name of the type they are defining, as we can use the module name to “look like” we’re using a method of the type name, rather than a field of a value:

import Data.Map (Map)
-- ideally there would be a warning/lint to reduce duplicate imports
import Data.Map qualified as Map

Map.insert :: (Ord k) => k -> v -> Map k v -> Map k v

-- as opposed to
--
-- instance (Ord k) => HasField "insert" (Map k v) (k -> v -> Map k v) where
--   getField _ m = \k v -> Map.insert k v m
--
-- (.insert) :: (Ord k) => Map k v -> (k -> v -> Map k v)

Set-and-forget project-wide (qualified) imports would promote namespace hygiene, be easily introduced into existing projects, and hopefully free the Haskell ecosystem from the shackles of the “one true Prelude”. Implicit imports become a configuration option, the default corresponding to the existing Prelude in base; we then give users an extensible solution as well as an easier way to opt out of specific changes between “import list” versions.

3 Likes

One way to do this while also facilitating (3) is to introduce a new Cabal stanza.

I don’t have a particular opinion but to me:

import Prelude ()
import Prelude.Compat

as someone new to a project (maybe I want to fix a bug, maybe I want to check a particular behaviour) is very useful. Those two lines tell me immediately that someone opted out standard Prelude and if I see head I need not to make assumptions regarding signatures.

4 Likes

This idea looks really good to me. Let’s see what cabal contributors have to say :slight_smile:

1 Like

Thanks for raising this topic! Two links two existing approaches/prior art in this space:

  1. There is a compiler plugin which emulates your local-implicit-imports feature: GitHub - utdemir/qualified-imports-plugin

  2. The (dormant) “Local Modules” proposal would allow for native qualified re-exports: ghc-proposals/0000-local-modules.rst at local-modules · goldfirere/ghc-proposals · GitHub

4 Likes