The NoImplicitPrelude
GHC extension is used to disable the prelude.For other ways to disable the prelNoImplicitPreludeude, see Disabling the prelude
GHC normally includes the Prelude
as an implicit import, both in GHCi and in compilation. This is sometimes what you want; it gives you access to a collection of types, typeclasses, and functions that you don’t usually want to write from scratch for each project.
This extension is primarily useful when
you are learning Haskell and want to re-implement many of the
Prelude
types and functions yourself, for learning purposes. This enables you to do so without name clashes.you have informed opinions about the set of things included in the Haskell
Prelude
and wish to use an alternative “prelude” that is better tailored to your tastes or project.
We give examples of each of these uses in this article.
This extension has been available since GHC 6.8.1 in 2007.GHC documentation for NoImplicitPrelude
It replaced the very old and now-deprecated -fno-implicit-prelude
flag, which had been around for (as far as we can tell) as long as GHC has existed.
Example
Let’s say we’re a Haskell beginner teaching ourselves Haskell by implementing a lot of the basic Haskell types and functions ourselves. So we might start a module off like this.
{-# LANGUAGE NoImplicitPrelude #-}
module Maybe where
data Maybe a = Nothing | Just a
class Eq a where
(==) :: a -> a -> Bool
(/=) :: a -> a -> Bool
If you then try to compile or run or load this into GHCi or what have you, you’ll see an error.
λ> :load
[1 of 1] Compiling Maybe
no-prelude.hs:12:21: error:
Not in scope: type constructor or class ‘Bool’
|
12 | (==) :: a -> a -> Bool
| ^^^^
Since you have disabled the entire Prelude
and you haven’t written a Bool
type yet, there is no type called Bool
in scope. You can handle this in one of two ways: write a Bool
type or import that type without importing the rest of the Prelude
that you don’t want. This example will cover the latter because there are certainly things you will want to do this for, such as IO
and some related things that would be relatively impossible to implement yourself.It’s probably worth pointing out that even if you have the whole Prelude
disabled, when you use GHCi it will still be able to “do I/O”, at least enough to print values to your screen.
The Bool
type is defined in the Data.Bool
module of the base
library. You can choose to import
- just the
Bool
type (without its constructors)
import Data.Bool (Bool)
- the
Bool
type with its constructors (True
andFalse
)
import Data.Bool (Bool (..))
- the entire module, but qualified so that you could still use some of the names in that module without clashing.
import qualified Data.Bool as B
There are some other choices you could make, such as importing the entire module unqualified. Maybe you’ve already learned all you can from implementing the Boolean functions in that module and want to be able to use them now (if you did that and you have your own Bool
module, you could also choose to import your own module), in which case a simple import Data.Bool
would suffice.
For most cases, we believe the second or third of those possibilities would be most useful. We’ll continue our example using the third possibility, to show you what that would look like.
{-# LANGUAGE NoImplicitPrelude #-}
module Maybe where
import qualified Data.Bool as B
data Maybe a = Nothing | Just a
class Eq a where
(==) :: a -> a -> B.Bool
(/=) :: a -> a -> B.Bool
instance Eq a => Eq (Maybe a) where
Nothing == Nothing = B.True
Nothing == Just y = B.False
Just x == Nothing = B.False
Just x == Just y | x == y = B.True
| B.otherwise = B.False
If you qualify your import like that, then it is very visible when you are using something you have not implemented yourself, and those visual reminders of where something came from can be useful – to you while you’re learning, to future you, and to anyone who reads your code.
Alternative preludes
As we mentioned earlier, sometimes you also want to disable the Prelude
in order to use an alternative prelude. As you might have noticed in the example above, you have to add that Data.Bool
import in order to use a couple of basic things, and as you can imagine, the list of imports will grow longer and longer as you go on. So, while that is useful occasionally, it can also become a pain. The oldest GHC documentation we can findDocumentation for GHC 0.29, circa 1995 playfully comments:
You are unlikely to get very far without a Prelude, but, hey, it’s a free country.
Enter the alternative preludes.
The base
module called Prelude
is somewhat controversial among Haskellers. For one thing, it has several notable partial functions in it. It is not controversial that those functions are fairly bad – isn’t Haskell about safety and compile-time rather than runtime errors? It is somewhat more controversial whether people who are new to Haskell should try using an alternative prelude in order, in part, to avoid those functions. Furthermore, there is a lot of debate about how best to structure a prelude for writing modern Haskell. Prelude
is quite old and dates from a time when Haskell wasn’t much used industrially.
And so the modern Haskell ecosystem is now home to several alternative preludes. Each has made different choices about what to include, although they mostly all share the goal of eliminating those partial functions. One of our personal favorites is the relude
package.The relude
package on Hackage. So let’s look at an example using that.
Changing the prelude in GHCi
If you’d like to open a GHCi session for experimentation with relude
instead of Prelude
, do this:
You may need to first install the
relude
package usingcabal install
,stack install
, or Nix.Open a GHCi session with the
-XNoImplicitPrelude
and-package
flags.
$ ghci -XNoImplicitPrelude -package relude
- Import the
Relude
module ofrelude
once it opens.
λ> import Relude
- Start looking around to see what has changed.
λ> :type head
head :: NonEmpty a -> a
Look! head
isn’t a partial function anymore!
In modules
For writing code in Haskell source files, there are, as usual, a few ways you can do this. One is to establish a project with a cabal
file or a similar setup and add relude
as a dependency. Another way to play around with it, if you have relude
installed, is to have a Haskell module that opens like this:
{-# LANGUAGE NoImplicitPrelude #-}
module Main where
import Relude
and load that module into GHCi, which will disable the normal Prelude
and use relude
instead. You will need to have some main
defined before you load it (even if it says undefined
).GHC and GHCi expect that a module named Main
will have a main
action defined within them. It is OK if you put main = undefined
or if you take off the module name; either way, the code should load into GHCi because for whatever reason, GHCi does not expect a main
defined in an unnamed module.
{-# LANGUAGE NoImplicitPrelude #-}
module Main where
import Relude
main :: IO ()
main = undefined
Let’s try loading this into GHCi.
$ ghci
GHCi, version 8.6.3: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/jmo/.ghc/ghci.conf
λ> :type head
head :: [a] -> a
λ> :load relude.hs
[1 of 1] Compiling Main ( relude.hs, interpreted )
relude.hs:8:8: warning: [-Wdeprecations]
In the use of ‘undefined’
(imported from Relude, but defined in Relude.Debug):
"'undefined' function remains in code"
|
8 | main = undefined
| ^^^^^^^^^
Ok, one module loaded.
λ> :type head
head :: NonEmpty a -> a
We wanted to show you two things with this.
Unlike normal
Prelude
or GHC,relude
gives you a warning when you have anundefined
in your code. It’s nice that it’s a warning, and not an error, so that the module can still be loaded, but also you can be alerted to the presence of (perhaps a forgotten)undefined
.As you can see, the type of
head
changes after we load therelude.hs
file, so the changes we expect given our use of theNoImplicitPrelude
extension andRelude
import have taken effect.
We’re going to add some things to this file that are intended to show off how relude
differs from Prelude
rather than to represent a realistic program. For example, let’s try this step above “hello, world”.
main :: IO ()
=
main do
<- getLine
name putStrLn ("hello " ++ name)
This compiles and works fine when we use the standard Prelude
. However, when we are using relude
instead, we get this error message.
relude.hs:11:27: error:
• Couldn't match expected type ‘[Char]’ with actual type ‘Text’
• In the second argument of ‘(++)’, namely ‘name’
As the documentation for relude
explains, they’ve opted to make many of the standard functions work with the Text
type instead of with String
. Using Text
or ByteString
instead of String
is considered best practices in Haskell for many, if not most, purposes; however, the Prelude
uses the String
type extensively mostly due to its age. So, relude
re-exports important types and functions from the text
and bytestring
packages – which means that to use the Text
type or associated functions, we don’t need to add a dependency or import from the text
library. But it also means that we do need to find a way in relude
to fix that error.
What the message seems to be telling us is that our use of (++)
expects two [Char]
arguments, but name
is a Text
argument. One way to fix this would be to find a conversion function to do that for us. There is a relude
module called Relude.String.Conversion
so we’re guessing that’s a good place to look.
It took a little bit of scrolling to find the ToString
typeclass with its one method, toString
, and it seems like that will work, so let’s try it.
main :: IO ()
=
main do
<- getLine
name putStrLn ("hello " ++ (toString name))
And, indeed, this does work. But it might seem like a step backwards to use String
instead of Text
so we can look for a more “relude-y” way to achieve the same purpose. Usually for Text
we use the semigroup operator (<>)
instead of (++)
so we can switch to that first of all.
We also notice, however, that putStrLn
expects a String
input.
λ> :type putStrLn
putStrLn :: MonadIO m => String -> m ()
A quick search of the Index for relude
gives us a bunch of other put
functions: putTextLn
is probably the one we want. So, now our main
looks like this:
main :: IO ()
=
main do
<- getLine
name "hello " <> name) putTextLn (
This still doesn’t quite work because, syntactically, "hello "
, is a String
. Those quotation marks are reserved syntax for lists of Char
, sorry! There are two options here.
We could enable the
OverloadedStrings
extension. This is not a bad option, and it’s what therelude
designers seem to prefer, as it takes this pain away throughout your file when enabled.We could manually “pack” that
String
into aText
representation. Just as we found theToString
class earlier, we see that there is a similarToText
class as well, with atoText
function. We’ll choose this route so that we can show you the new, working code without reprinting the entire file.
main :: IO ()
=
main do
<- getLine
name "hello ") <> name) putTextLn ((toText
This is the kind of adaptation you should expect when you switch off the standard Prelude
and onto one of the more modern or specialized preludes. We think that these adaptations are often worthwhile, especially when they can help you use better types.