#ifdef MIN_VERSION_base
#define MINVER_base_411 MIN_VERSION_base(4,11,0)
#define MINVER_base_48 MIN_VERSION_base(4,8,0)
#define MINVER_base_47 MIN_VERSION_base(4,7,0)
#else
#define MINVER_base_411 (__GLASGOW_HASKELL__ >= 804)
#define MINVER_base_48 (__GLASGOW_HASKELL__ >= 710)
#define MINVER_base_47 (__GLASGOW_HASKELL__ >= 708)
#endif
module Distribution.Compat.Prelude (
module BasePrelude,
#if !MINVER_base_48
Applicative(..), (<$), (<$>),
Monoid(..),
#endif
Semigroup (..),
gmappend, gmempty,
Typeable, TypeRep, typeRep,
Data,
Generic,
NFData (..), genericRnf,
Binary (..),
Structured,
Alternative (..),
MonadPlus (..),
IsString (..),
Map,
Set,
NonEmptySet,
Identity (..),
Proxy (..),
Const (..),
Void,
partitionEithers,
catMaybes, mapMaybe,
fromMaybe,
maybeToList, listToMaybe,
isNothing, isJust,
unfoldr,
isPrefixOf, isSuffixOf,
intercalate, intersperse,
sort, sortBy,
nub, nubBy,
partition,
NonEmpty((:|)), foldl1, foldr1,
head, tail, last, init,
Foldable, foldMap, foldr,
null, length,
find, foldl',
traverse_, for_,
any, all,
toList,
Traversable, traverse, sequenceA,
for,
on,
comparing,
first,
liftM, liftM2,
unless, when,
ap, void,
foldM, filterM,
join, guard,
catch, throwIO, evaluate,
Exception (..), IOException, SomeException (..),
#if !MINVER_base_48
displayException,
#endif
tryIO, catchIO, catchExit,
deepseq, force,
isSpace, isDigit, isUpper, isAlpha, isAlphaNum,
chr, ord,
toLower, toUpper,
absurd, vacuous,
Word,
Word8, Word16, Word32, Word64,
Int8, Int16, Int32, Int64,
(<<>>), (Disp.<+>),
ExitCode (..),
exitWith, exitSuccess, exitFailure,
readMaybe,
trace, traceShow, traceShowId,
) where
import Prelude as BasePrelude hiding
( mapM, mapM_, sequence, null, length, foldr, any, all, head, tail, last, init
, read
, foldr1, foldl1
#if MINVER_base_411
, Semigroup(..)
#endif
#if MINVER_base_48
, Word
, Traversable, traverse, sequenceA
, Foldable, foldMap
#endif
)
#if !MINVER_base_48
import Control.Applicative (Applicative (..), (<$), (<$>))
import Data.Foldable (toList)
import Distribution.Compat.Semigroup (Monoid (..))
#else
import Data.Foldable (Foldable (toList), length, null)
#endif
import Data.Foldable (Foldable (foldMap, foldr), all, any, find, foldl', for_, traverse_)
import Data.Traversable (Traversable (sequenceA, traverse), for)
import qualified Data.Foldable
import Control.Applicative (Alternative (..))
import Control.Applicative (Const (..))
import Control.Arrow (first)
import Control.DeepSeq (NFData (..), deepseq, force)
import Control.Exception (Exception (..), IOException, SomeException (..), catch, evaluate, throwIO)
import Control.Monad (MonadPlus (..), ap, filterM, foldM, guard, join, liftM, liftM2, unless, void, when)
import Data.Char (chr, isAlpha, isAlphaNum, isDigit, isSpace, isUpper, ord, toLower, toUpper)
import Data.Data (Data)
import Data.Either (partitionEithers)
import Data.Function (on)
import Data.Functor.Identity (Identity (..))
import Data.Int (Int16, Int32, Int64, Int8)
import Data.List (intercalate, intersperse, isPrefixOf, isSuffixOf, nub, nubBy, partition, sort, sortBy, unfoldr)
import Data.List.NonEmpty (NonEmpty ((:|)), head, init, last, tail)
import Data.Map (Map)
import Data.Maybe (catMaybes, fromMaybe, isJust, isNothing, listToMaybe, mapMaybe, maybeToList)
import Data.Ord (comparing)
import Data.Proxy (Proxy (..))
import Data.Set (Set)
import Data.String (IsString (..))
import Data.Void (Void, absurd, vacuous)
import Data.Word (Word, Word16, Word32, Word64, Word8)
import Distribution.Compat.Binary (Binary (..))
import Distribution.Compat.Semigroup (Semigroup (..), gmappend, gmempty)
import Distribution.Compat.Typeable (TypeRep, Typeable, typeRep)
import GHC.Generics ((:*:) ((:*:)), (:+:) (L1, R1), Generic, K1 (unK1), M1 (unM1), Rep (..), U1 (U1), V1)
import System.Exit (ExitCode (..), exitFailure, exitSuccess, exitWith)
import Text.Read (readMaybe)
import qualified Text.PrettyPrint as Disp
import Distribution.Compat.Exception
import Distribution.Compat.NonEmptySet (NonEmptySet)
import Distribution.Utils.Structured (Structured)
import qualified Debug.Trace
(<<>>) :: Disp.Doc -> Disp.Doc -> Disp.Doc
(<<>>) = (Disp.<>)
#if !MINVER_base_48
null :: Foldable t => t a -> Bool
null = foldr (\_ _ -> False) True
length :: Foldable t => t a -> Int
length = foldl' (\c _ -> c+1) 0
#endif
genericRnf :: (Generic a, GNFData (Rep a)) => a -> ()
genericRnf = grnf . from
class GNFData f where
grnf :: f a -> ()
instance GNFData V1 where
grnf = error "Control.DeepSeq.rnf: uninhabited type"
instance GNFData U1 where
grnf U1 = ()
instance NFData a => GNFData (K1 i a) where
grnf = rnf . unK1
instance GNFData a => GNFData (M1 i c a) where
grnf = grnf . unM1
instance (GNFData a, GNFData b) => GNFData (a :*: b) where
grnf (x :*: y) = grnf x `seq` grnf y
instance (GNFData a, GNFData b) => GNFData (a :+: b) where
grnf (L1 x) = grnf x
grnf (R1 x) = grnf x
foldr1 :: (a -> a -> a) -> NonEmpty a -> a
foldr1 = Data.Foldable.foldr1
foldl1 :: (a -> a -> a) -> NonEmpty a -> a
foldl1 = Data.Foldable.foldl1
trace :: String -> a -> a
trace = Debug.Trace.trace
traceShowId :: Show a => a -> a
traceShowId x = Debug.Trace.traceShow x x
traceShow :: Show a => a -> b -> b
traceShow = Debug.Trace.traceShow