aboutsummaryrefslogtreecommitdiff
path: root/prelude
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2018-03-18 09:20:21 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2018-03-18 09:20:21 -0700
commitdd53545154c5149dc720cc34c9990b92aec78c1a (patch)
treec3193d8ee86a9f8cde7cd127f0166e9d25d27848 /prelude
parent09a32de173f2aa343d724925b2d1c976c68ddeec (diff)
downloadpandoc-dd53545154c5149dc720cc34c9990b92aec78c1a.tar.gz
New approach to custom Prelude.
We use no custom Prelude with the latest ghc version (8.4.1), so we don't have problems with ghci. See https://ghc.haskell.org/trac/ghc/ticket/10920 https://www.reddit.com/r/haskell/comments/3ryf2p/how_can_you_use_a_custom_prelude_with_ghci/ This may help with #4464.
Diffstat (limited to 'prelude')
-rw-r--r--prelude/Prelude.hs14
1 files changed, 7 insertions, 7 deletions
diff --git a/prelude/Prelude.hs b/prelude/Prelude.hs
index 9c8ac9363..5ea523433 100644
--- a/prelude/Prelude.hs
+++ b/prelude/Prelude.hs
@@ -1,17 +1,17 @@
+{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE CPP #-}
+-- The intent is that this Prelude provide the API of
+-- the base 4.11 Prelude in a way that is portable for
+-- all base versions.
+
module Prelude
(
- module P
-, Monoid(..)
+ module Prelude.Compat
, Semigroup(..)
-, Applicative(..)
)
where
-import "base" Prelude as P
+import Prelude.Compat
import Data.Semigroup (Semigroup(..)) -- includes (<>)
-#if MIN_VERSION_base(4,11,0)
-import Data.Monoid (Monoid(..))
-#endif