{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeOperators #-}
#ifdef MIN_VERSION_base
#define MINVER_base_411 MIN_VERSION_base(4,11,0)
#else
#define MINVER_base_411 (__GLASGOW_HASKELL__ >= 804)
#endif
module Distribution.Compat.Prelude (
module BasePrelude,
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,
dropWhileEnd,
NonEmpty((:|)), 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 (..),
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
, Word
, Traversable, traverse, sequenceA
, Foldable, foldMap
)
import Data.Foldable
( Foldable(toList),
length,
null,
Foldable(foldMap, foldr),
all,
any,
find,
foldl',
for_,
traverse_ )
import Data.Traversable (Traversable (sequenceA, traverse), for)
import qualified Data.Foldable
import Control.Applicative (Alternative (..), 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 (dropWhileEnd, intercalate, intersperse, isPrefixOf, isSuffixOf, nub, nubBy, partition, sort, sortBy, unfoldr)
import Data.List.NonEmpty (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
<<>> :: Doc -> Doc -> Doc
(<<>>) = Doc -> Doc -> Doc
(Disp.<>)
genericRnf :: (Generic a, GNFData (Rep a)) => a -> ()
genericRnf :: forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf = Rep a Any -> ()
forall a. Rep a a -> ()
forall (f :: * -> *) a. GNFData f => f a -> ()
grnf (Rep a Any -> ()) -> (a -> Rep a Any) -> a -> ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rep a Any
forall x. a -> Rep a x
forall a x. Generic a => a -> Rep a x
from
class GNFData f where
grnf :: f a -> ()
instance GNFData V1 where
grnf :: forall a. V1 a -> ()
grnf = [Char] -> V1 a -> ()
forall a. HasCallStack => [Char] -> a
error [Char]
"Control.DeepSeq.rnf: uninhabited type"
instance GNFData U1 where
grnf :: forall a. U1 a -> ()
grnf U1 a
U1 = ()
instance NFData a => GNFData (K1 i a) where
grnf :: forall a. K1 i a a -> ()
grnf = a -> ()
forall a. NFData a => a -> ()
rnf (a -> ()) -> (K1 i a a -> a) -> K1 i a a -> ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. K1 i a a -> a
forall k i c (p :: k). K1 i c p -> c
unK1
{-# INLINEABLE grnf #-}
instance GNFData a => GNFData (M1 i c a) where
grnf :: forall a. M1 i c a a -> ()
grnf = a a -> ()
forall a. a a -> ()
forall (f :: * -> *) a. GNFData f => f a -> ()
grnf (a a -> ()) -> (M1 i c a a -> a a) -> M1 i c a a -> ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. M1 i c a a -> a a
forall k i (c :: Meta) (f :: k -> *) (p :: k). M1 i c f p -> f p
unM1
{-# INLINEABLE grnf #-}
instance (GNFData a, GNFData b) => GNFData (a :*: b) where
grnf :: forall a. (:*:) a b a -> ()
grnf (a a
x :*: b a
y) = a a -> ()
forall a. a a -> ()
forall (f :: * -> *) a. GNFData f => f a -> ()
grnf a a
x () -> () -> ()
forall a b. a -> b -> b
`seq` b a -> ()
forall a. b a -> ()
forall (f :: * -> *) a. GNFData f => f a -> ()
grnf b a
y
{-# INLINEABLE grnf #-}
instance (GNFData a, GNFData b) => GNFData (a :+: b) where
grnf :: forall a. (:+:) a b a -> ()
grnf (L1 a a
x) = a a -> ()
forall a. a a -> ()
forall (f :: * -> *) a. GNFData f => f a -> ()
grnf a a
x
grnf (R1 b a
x) = b a -> ()
forall a. b a -> ()
forall (f :: * -> *) a. GNFData f => f a -> ()
grnf b a
x
{-# INLINEABLE grnf #-}
{-# INLINE foldr1 #-}
foldr1 :: (a -> a -> a) -> NonEmpty a -> a
foldr1 :: forall a. (a -> a -> a) -> NonEmpty a -> a
foldr1 = (a -> a -> a) -> NonEmpty a -> a
forall a. (a -> a -> a) -> NonEmpty a -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
Data.Foldable.foldr1
{-# INLINE foldl1 #-}
foldl1 :: (a -> a -> a) -> NonEmpty a -> a
foldl1 :: forall a. (a -> a -> a) -> NonEmpty a -> a
foldl1 = (a -> a -> a) -> NonEmpty a -> a
forall a. (a -> a -> a) -> NonEmpty a -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
Data.Foldable.foldl1
trace :: String -> a -> a
trace :: forall a. [Char] -> a -> a
trace = [Char] -> a -> a
forall a. [Char] -> a -> a
Debug.Trace.trace
{-# DEPRECATED trace "Don't leave me in the code" #-}
traceShowId :: Show a => a -> a
traceShowId :: forall a. Show a => a -> a
traceShowId a
x = a -> a -> a
forall a b. Show a => a -> b -> b
Debug.Trace.traceShow a
x a
x
{-# DEPRECATED traceShowId "Don't leave me in the code" #-}
traceShow :: Show a => a -> b -> b
traceShow :: forall a b. Show a => a -> b -> b
traceShow = a -> b -> b
forall a b. Show a => a -> b -> b
Debug.Trace.traceShow
{-# DEPRECATED traceShow "Don't leave me in the code" #-}