pandoc/prelude/Prelude.hs
John MacFarlane c1e474f005 Restored Text.Pandoc.Compat.Monoid.
Don't use custom prelude for latest ghc.

This is a better approach to making 'stack ghci' and 'cabal repl'
work.  Instead of using NoImplicitPrelude, we only use the custom
prelude for older ghc versions.  The custom prelude presents a
uniform API that matches the current base version's prelude.
So, when developing (presumably with latest ghc), we don't
use a custom prelude at all and hence have no trouble with ghci.

The custom prelude no longer exports (<>):  we now want to
match the base 4.8 prelude behavior.
2015-11-09 11:19:25 -08:00

30 lines
511 B
Haskell

{-# LANGUAGE PackageImports #-}
{-# LANGUAGE CPP #-}
-- This custom Prelude emulates the API of the prelude
-- with base 4.8.
module Prelude
(
module P
#if MIN_VERSION_base(4,8,0)
#else
, Monoid(..)
, Applicative(..)
, (<$>)
, (<$)
#endif
)
where
#if MIN_VERSION_base(4,8,0)
import "base" Prelude as P
#elif MIN_VERSION_base(4,6,0)
import "base" Prelude as P
import Control.Applicative
import Data.Monoid
#else
import "base" Prelude as P hiding (catch)
import Control.Applicative
import Data.Monoid
#endif