{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} #if __GLASGOW_HASKELL__ >= 706 {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE PolyKinds #-} #endif {-# OPTIONS_GHC -fno-warn-deprecations #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-| Exports orphan instances that mimic instances available in later versions of @base@. To use them, simply @import Data.Orphans ()@. -} module Data.Orphans () where #if MIN_VERSION_base(4,2,0) && !(MIN_VERSION_base(4,3,0)) import Data.Unique # endif #if MIN_VERSION_base(4,4,0) && __GLASGOW_HASKELL__ < 710 import GHC.Event import GHC.Fingerprint import GHC.IO.Encoding.Failure #endif #if __GLASGOW_HASKELL__ >= 702 && __GLASGOW_HASKELL__ < 710 import GHC.Generics as Generics # endif #if MIN_VERSION_base(4,5,0) && __GLASGOW_HASKELL__ < 710 import GHC.Stack import GHC.Stats #endif #if MIN_VERSION_base(4,6,0) && __GLASGOW_HASKELL__ < 710 import Data.Bits import Data.Ord import GHC.TypeLits #endif #if MIN_VERSION_base(4,7,0) && __GLASGOW_HASKELL__ < 710 import Control.Concurrent.QSem import Text.Read.Lex (Number) # endif #if __GLASGOW_HASKELL__ >= 708 && __GLASGOW_HASKELL__ < 710 import Control.Arrow import Control.Category hiding ((.)) import Control.Monad import Control.Monad.Fix import Control.Monad.Zip import Data.Fixed import Data.Ix import Data.Type.Coercion import Data.Type.Equality import GHC.Exts import GHC.IO.BufferedIO import GHC.IP import Text.Printf #endif #if !(MIN_VERSION_base(4,8,0)) import Data.Complex (Complex(..), realPart) import Data.Version import Foreign.Ptr (castPtr) import GHC.Real (Ratio(..), (%)) #endif #if __GLASGOW_HASKELL__ < 710 import Control.Applicative import Control.Exception import Control.Monad.ST.Lazy import Data.Char import Data.Data as Data import Data.Foldable import Data.Monoid as Monoid import Data.Traversable import Foreign.C.Error import Foreign.C.Types import Foreign.Marshal.Pool import Foreign.Storable import GHC.Conc import GHC.IO.Buffer import GHC.IO.Device import GHC.IO.Encoding import System.Console.GetOpt import System.IO import System.IO.Error import Text.ParserCombinators.ReadP import Text.ParserCombinators.ReadPrec as ReadPrec import Text.Read #endif ------------------------------------------------------------------------------- -- These instances are only valid if Bits isn't a subclass of Num (as Bool is -- not a Num instance), which is only true as of base-4.6.0.0 and later. #if MIN_VERSION_base(4,6,0) && !(MIN_VERSION_base(4,7,0)) instance Bits Bool where (.&.) = (&&) (.|.) = (||) xor = (/=) complement = not shift x 0 = x shift _ _ = False rotate x _ = x bit 0 = True bit _ = False testBit x 0 = x testBit _ _ = False bitSize _ = 1 isSigned _ = False popCount False = 0 popCount True = 1 deriving instance Read a => Read (Down a) deriving instance Show a => Show (Down a) #endif #if !(MIN_VERSION_base(4,7,0)) instance Foldable ((,) a) where foldMap f (_, y) = f y foldr f z (_, y) = f y z instance Traversable ((,) a) where traverse f (x, y) = (,) x <$> f y instance Foldable (Const m) where foldMap _ _ = mempty instance Monoid a => Monoid (Const a b) where mempty = Const mempty mappend (Const a) (Const b) = Const (mappend a b) instance Traversable (Const m) where traverse _ (Const m) = pure $ Const m instance Foldable (Either a) where foldMap _ (Left _) = mempty foldMap f (Right y) = f y foldr _ z (Left _) = z foldr f z (Right y) = f y z instance Traversable (Either a) where traverse _ (Left x) = pure (Left x) traverse f (Right y) = Right <$> f y deriving instance Eq ErrorCall deriving instance Ord ErrorCall deriving instance Num a => Num (Sum a) deriving instance Num a => Num (Product a) deriving instance Data Version -- GHC Trac #8218 instance Monad m => Monad (WrappedMonad m) where return = WrapMonad . return a >>= f = WrapMonad (unwrapMonad a >>= unwrapMonad . f) deriving instance Eq a => Eq (ZipList a) deriving instance Ord a => Ord (ZipList a) deriving instance Read a => Read (ZipList a) deriving instance Show a => Show (ZipList a) instance Functor ArgOrder where fmap _ RequireOrder = RequireOrder fmap _ Permute = Permute fmap f (ReturnInOrder g) = ReturnInOrder (f . g) instance Functor OptDescr where fmap f (Option a b argDescr c) = Option a b (fmap f argDescr) c instance Functor ArgDescr where fmap f (NoArg a) = NoArg (f a) fmap f (ReqArg g s) = ReqArg (f . g) s fmap f (OptArg g s) = OptArg (f . g) s #endif #if __GLASGOW_HASKELL__ >= 702 && !(MIN_VERSION_base(4,7,0)) -- Although DeriveGeneric has been around since GHC 7.2, various bugs cause -- the standalone-derived code below to fail to compile unless a fairly -- recent version of GHC is used. # if __GLASGOW_HASKELL__ >= 706 deriving instance Generic All deriving instance Generic Any deriving instance Generic (Const a b) deriving instance Generic (Dual a) deriving instance Generic (Endo a) deriving instance Generic (First a) deriving instance Generic (Last a) deriving instance Generic (Product a) deriving instance Generic (Sum a) deriving instance Generic (WrappedArrow a b c) deriving instance Generic (WrappedMonad m a) deriving instance Generic (ZipList a) deriving instance Generic1 (Const a) deriving instance Generic1 Dual deriving instance Generic1 First deriving instance Generic1 Last deriving instance Generic1 Product deriving instance Generic1 Sum deriving instance Generic1 (WrappedArrow a b) deriving instance Generic1 (WrappedMonad m) deriving instance Generic1 ZipList deriving instance Generic (U1 p) deriving instance Generic (Par1 p) deriving instance Generic (Rec1 f p) deriving instance Generic (K1 i c p) deriving instance Generic (M1 i c f p) deriving instance Generic ((f :+: g) p) deriving instance Generic ((f :*: g) p) deriving instance Generic ((f :.: g) p) # endif deriving instance Eq (U1 p) deriving instance Ord (U1 p) deriving instance Read (U1 p) deriving instance Show (U1 p) deriving instance Eq p => Eq (Par1 p) deriving instance Ord p => Ord (Par1 p) deriving instance Read p => Read (Par1 p) deriving instance Show p => Show (Par1 p) deriving instance Eq (f p) => Eq (Rec1 f p) deriving instance Ord (f p) => Ord (Rec1 f p) deriving instance Read (f p) => Read (Rec1 f p) deriving instance Show (f p) => Show (Rec1 f p) deriving instance Eq c => Eq (K1 i c p) deriving instance Ord c => Ord (K1 i c p) deriving instance Read c => Read (K1 i c p) deriving instance Show c => Show (K1 i c p) deriving instance Eq (f p) => Eq (M1 i c f p) deriving instance Ord (f p) => Ord (M1 i c f p) deriving instance Read (f p) => Read (M1 i c f p) deriving instance Show (f p) => Show (M1 i c f p) deriving instance (Eq (f p), Eq (g p)) => Eq ((f :+: g) p) deriving instance (Ord (f p), Ord (g p)) => Ord ((f :+: g) p) deriving instance (Read (f p), Read (g p)) => Read ((f :+: g) p) deriving instance (Show (f p), Show (g p)) => Show ((f :+: g) p) deriving instance (Eq (f p), Eq (g p)) => Eq ((f :*: g) p) deriving instance (Ord (f p), Ord (g p)) => Ord ((f :*: g) p) -- Due to a GHC bug (https://ghc.haskell.org/trac/ghc/ticket/9830), the derived -- Read and Show instances for infix data constructors will use the wrong -- precedence (prior to GHC 7.10). -- We'll manually derive Read :*: and Show :*: instances to avoid this. instance (Read (f p), Read (g p)) => Read ((f :*: g) p) where readPrec = parens . ReadPrec.prec 6 $ do fp <- ReadPrec.step readPrec Symbol ":*:" <- lexP gp <- ReadPrec.step readPrec return $ fp :*: gp readListPrec = readListPrecDefault instance (Show (f p), Show (g p)) => Show ((f :*: g) p) where showsPrec p (l :*: r) = showParen (p > sixPrec) $ showsPrec (sixPrec + 1) l . showString " :*: " . showsPrec (sixPrec + 1) r where sixPrec = 6 deriving instance Eq (f (g p)) => Eq ((f :.: g) p) deriving instance Ord (f (g p)) => Ord ((f :.: g) p) deriving instance Read (f (g p)) => Read ((f :.: g) p) deriving instance Show (f (g p)) => Show ((f :.: g) p) #endif #if MIN_VERSION_base(4,7,0) && !(MIN_VERSION_base(4,8,0)) -- | Construct tag-less 'Version' -- -- /Since: 4.8.0.0/ makeVersion :: [Int] -> Version makeVersion b = Version b [] -- | /Since: 4.8.0.0/ instance IsList Version where type (Item Version) = Int fromList = makeVersion toList = versionBranch #endif #if !(MIN_VERSION_base(4,8,0)) deriving instance Eq a => Eq (Const a b) deriving instance Ord a => Ord (Const a b) instance Read a => Read (Const a b) where readsPrec d = readParen (d > 10) $ \r -> [(Const x,t) | ("Const", s) <- lex r, (x, t) <- readsPrec 11 s] instance Show a => Show (Const a b) where showsPrec d (Const x) = showParen (d > 10) $ showString "Const " . showsPrec 11 x -- The actual constraint in base-4.8.0.0 doesn't include RealFloat a, but it -- is needed in previous versions of base due to Complex having lots of -- RealFloat constraints in its functions' type signatures. instance (Storable a, RealFloat a) => Storable (Complex a) where sizeOf a = 2 * sizeOf (realPart a) alignment a = alignment (realPart a) peek p = do q <- return $ castPtr p r <- peek q i <- peekElemOff q 1 return (r :+ i) poke p (r :+ i) = do q <-return $ (castPtr p) poke q r pokeElemOff q 1 i instance (Storable a, Integral a) => Storable (Ratio a) where sizeOf (n :% _) = 2 * sizeOf n alignment (n :% _) = alignment n peek p = do q <- return $ castPtr p r <- peek q i <- peekElemOff q 1 return (r % i) poke p (r :% i) = do q <-return $ (castPtr p) poke q r pokeElemOff q 1 i #endif #if __GLASGOW_HASKELL__ < 710 deriving instance Typeable All deriving instance Typeable1 ArgDescr deriving instance Typeable1 ArgOrder deriving instance Typeable Monoid.Any deriving instance Typeable BlockReason deriving instance Typeable1 Buffer deriving instance Typeable3 BufferCodec deriving instance Typeable BufferMode deriving instance Typeable BufferState deriving instance Typeable CFile deriving instance Typeable CFpos deriving instance Typeable CJmpBuf deriving instance Typeable2 Const deriving instance Typeable Constr deriving instance Typeable ConstrRep deriving instance Typeable DataRep deriving instance Typeable DataType deriving instance Typeable1 Dual deriving instance Typeable1 Endo deriving instance Typeable Errno deriving instance Typeable1 First deriving instance Typeable Data.Fixity deriving instance Typeable GeneralCategory deriving instance Typeable HandlePosn deriving instance Typeable1 Handler deriving instance Typeable IODeviceType deriving instance Typeable IOErrorType deriving instance Typeable IOMode deriving instance Typeable1 Last deriving instance Typeable Lexeme deriving instance Typeable Newline deriving instance Typeable NewlineMode deriving instance Typeable1 OptDescr deriving instance Typeable Pool deriving instance Typeable1 Product deriving instance Typeable1 ReadP deriving instance Typeable1 ReadPrec deriving instance Typeable SeekMode deriving instance Typeable2 ST deriving instance Typeable1 Sum deriving instance Typeable TextEncoding deriving instance Typeable ThreadStatus deriving instance Typeable1 ZipList #if MIN_VERSION_base(4,2,0) && !(MIN_VERSION_base(4,3,0)) deriving instance Typeable Unique # endif # if MIN_VERSION_base(4,3,0) deriving instance Typeable MaskingState # endif # if MIN_VERSION_base(4,4,0) deriving instance Typeable CodingFailureMode deriving instance Typeable CodingProgress deriving instance Typeable Event deriving instance Typeable EventManager deriving instance Typeable FdKey deriving instance Typeable Fingerprint deriving instance Typeable TimeoutKey # endif # if __GLASGOW_HASKELL__ >= 702 deriving instance Typeable Arity deriving instance Typeable Associativity deriving instance Typeable C deriving instance Typeable D deriving instance Typeable Generics.Fixity deriving instance Typeable3 K1 deriving instance Typeable NoSelector deriving instance Typeable P deriving instance Typeable1 Par1 deriving instance Typeable R deriving instance Typeable S deriving instance Typeable1 U1 deriving instance Typeable1 V1 # endif # if MIN_VERSION_base(4,5,0) deriving instance Typeable CostCentre deriving instance Typeable CostCentreStack deriving instance Typeable GCStats # endif # if MIN_VERSION_base(4,6,0) deriving instance Typeable1 Down deriving instance Typeable Nat deriving instance Typeable Symbol # endif # if MIN_VERSION_base(4,7,0) deriving instance Typeable FieldFormat deriving instance Typeable FormatAdjustment deriving instance Typeable FormatParse deriving instance Typeable FormatSign deriving instance Typeable Number deriving instance Typeable SomeNat deriving instance Typeable SomeSymbol deriving instance Typeable QSem -- This instance seems to have been removed -- (accidentally?) in base-4.7.0.0 # endif # if __GLASGOW_HASKELL__ >= 708 -- Data types which have more than seven type arguments deriving instance Typeable (,,,,,,,) deriving instance Typeable (,,,,,,,,) deriving instance Typeable (,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) deriving instance Typeable (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) -- Data types which require PolyKinds deriving instance Typeable (:+:) deriving instance Typeable (:*:) deriving instance Typeable (:.:) deriving instance Typeable ArrowMonad deriving instance Typeable Kleisli deriving instance Typeable M1 deriving instance Typeable Rec1 deriving instance Typeable WrappedArrow deriving instance Typeable WrappedMonad -- Typeclasses deriving instance Typeable Arrow deriving instance Typeable ArrowApply deriving instance Typeable ArrowChoice deriving instance Typeable ArrowLoop deriving instance Typeable ArrowZero deriving instance Typeable Bits deriving instance Typeable Bounded deriving instance Typeable BufferedIO deriving instance Typeable Category deriving instance Typeable Coercible deriving instance Typeable Constructor deriving instance Typeable Data deriving instance Typeable Datatype deriving instance Typeable Enum deriving instance Typeable Exception deriving instance Typeable Eq deriving instance Typeable FiniteBits deriving instance Typeable Floating deriving instance Typeable Foldable deriving instance Typeable Fractional deriving instance Typeable Functor deriving instance Typeable Generic deriving instance Typeable Generic1 deriving instance Typeable HasResolution deriving instance Typeable HPrintfType deriving instance Typeable Integral deriving instance Typeable IODevice deriving instance Typeable IP deriving instance Typeable IsChar deriving instance Typeable IsList deriving instance Typeable IsString deriving instance Typeable Ix deriving instance Typeable KnownNat deriving instance Typeable KnownSymbol deriving instance Typeable Monad deriving instance Typeable MonadFix deriving instance Typeable MonadPlus deriving instance Typeable MonadZip deriving instance Typeable Num deriving instance Typeable Ord deriving instance Typeable PrintfArg deriving instance Typeable PrintfType deriving instance Typeable RawIO deriving instance Typeable Read deriving instance Typeable Real deriving instance Typeable RealFloat deriving instance Typeable RealFrac deriving instance Typeable Selector deriving instance Typeable Show deriving instance Typeable Storable deriving instance Typeable TestCoercion deriving instance Typeable TestEquality deriving instance Typeable Traversable deriving instance Typeable Typeable # endif #endif