pandoc/prelude/Prelude.hs
John MacFarlane 82b3e0ab97 Use custom Prelude to avoid compiler warnings.
- The (non-exported) prelude is in prelude/Prelude.hs.
- It exports Monoid and Applicative, like base 4.8 prelude,
  but works with older base versions.
- It exports (<>) for mappend.
- It hides 'catch' on older base versions.

This allows us to remove many imports of Data.Monoid
and Control.Applicative, and remove Text.Pandoc.Compat.Monoid.

It should allow us to use -Wall again for ghc 7.10.
2015-10-14 09:09:10 -07:00

39 lines
629 B
Haskell

{-# LANGUAGE PackageImports #-}
{-# LANGUAGE CPP #-}
module Prelude
(
module P
, Monoid(..)
, Applicative(..)
#if MIN_VERSION_base(4,8,0)
#else
, (<$>)
, (<$)
#endif
, (<>)
)
where
#if MIN_VERSION_base(4,8,0)
import "base" Prelude as P
import Data.Monoid ((<>))
#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
#if MIN_VERSION_base(4,5,0)
#else
infixr 6 <>
-- | An infix synonym for 'mappend'.
(<>) :: Monoid m => m -> m -> m
(<>) = mappend
{-# INLINE (<>) #-}
#endif