base-orphans-0.9.3: Backwards-compatible orphan instances for base
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Orphans

Description

Exports orphan instances that mimic instances available in later versions of base. To use them, simply import Data.Orphans ().

Orphan instances

Eq1 Par1 Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> Par1 a -> Par1 b -> Bool #

Ord1 Par1 Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> Par1 a -> Par1 b -> Ordering #

Read1 Par1 Source # 
Instance details

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Par1 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Par1 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Par1 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Par1 a] #

Show1 Par1 Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Par1 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Par1 a] -> ShowS #

Monoid a => MonadFix ((,) a) Source # 
Instance details

Methods

mfix :: (a0 -> (a, a0)) -> (a, a0) #

Eq1 (U1 :: Type -> Type) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> U1 a -> U1 b -> Bool #

Eq1 (UAddr :: Type -> Type) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> UAddr a -> UAddr b -> Bool #

Eq1 (UChar :: Type -> Type) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> UChar a -> UChar b -> Bool #

Eq1 (UDouble :: Type -> Type) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> UDouble a -> UDouble b -> Bool #

Eq1 (UFloat :: Type -> Type) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> UFloat a -> UFloat b -> Bool #

Eq1 (UInt :: Type -> Type) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> UInt a -> UInt b -> Bool #

Eq1 (UWord :: Type -> Type) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> UWord a -> UWord b -> Bool #

Eq1 (V1 :: Type -> Type) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> V1 a -> V1 b -> Bool #

Ord1 (U1 :: Type -> Type) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> U1 a -> U1 b -> Ordering #

Ord1 (UAddr :: Type -> Type) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> UAddr a -> UAddr b -> Ordering #

Ord1 (UChar :: Type -> Type) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> UChar a -> UChar b -> Ordering #

Ord1 (UDouble :: Type -> Type) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> UDouble a -> UDouble b -> Ordering #

Ord1 (UFloat :: Type -> Type) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> UFloat a -> UFloat b -> Ordering #

Ord1 (UInt :: Type -> Type) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> UInt a -> UInt b -> Ordering #

Ord1 (UWord :: Type -> Type) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> UWord a -> UWord b -> Ordering #

Ord1 (V1 :: Type -> Type) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> V1 a -> V1 b -> Ordering #

Read1 (U1 :: Type -> Type) Source # 
Instance details

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (U1 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [U1 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (U1 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [U1 a] #

Read1 (V1 :: Type -> Type) Source # 
Instance details

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V1 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V1 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V1 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V1 a] #

Show1 (U1 :: Type -> Type) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> U1 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [U1 a] -> ShowS #

Show1 (UAddr :: Type -> Type) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UAddr a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UAddr a] -> ShowS #

Show1 (UChar :: Type -> Type) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UChar a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UChar a] -> ShowS #

Show1 (UDouble :: Type -> Type) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UDouble a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UDouble a] -> ShowS #

Show1 (UFloat :: Type -> Type) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UFloat a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UFloat a] -> ShowS #

Show1 (UInt :: Type -> Type) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UInt a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UInt a] -> ShowS #

Show1 (UWord :: Type -> Type) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UWord a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UWord a] -> ShowS #

Show1 (V1 :: Type -> Type) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V1 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V1 a] -> ShowS #

Eq (SChar c) Source # 
Instance details

Methods

(==) :: SChar c -> SChar c -> Bool #

(/=) :: SChar c -> SChar c -> Bool #

Eq (SSymbol s) Source # 
Instance details

Methods

(==) :: SSymbol s -> SSymbol s -> Bool #

(/=) :: SSymbol s -> SSymbol s -> Bool #

Eq (SNat n) Source # 
Instance details

Methods

(==) :: SNat n -> SNat n -> Bool #

(/=) :: SNat n -> SNat n -> Bool #

Ord (SChar c) Source # 
Instance details

Methods

compare :: SChar c -> SChar c -> Ordering #

(<) :: SChar c -> SChar c -> Bool #

(<=) :: SChar c -> SChar c -> Bool #

(>) :: SChar c -> SChar c -> Bool #

(>=) :: SChar c -> SChar c -> Bool #

max :: SChar c -> SChar c -> SChar c #

min :: SChar c -> SChar c -> SChar c #

Ord (SSymbol s) Source # 
Instance details

Methods

compare :: SSymbol s -> SSymbol s -> Ordering #

(<) :: SSymbol s -> SSymbol s -> Bool #

(<=) :: SSymbol s -> SSymbol s -> Bool #

(>) :: SSymbol s -> SSymbol s -> Bool #

(>=) :: SSymbol s -> SSymbol s -> Bool #

max :: SSymbol s -> SSymbol s -> SSymbol s #

min :: SSymbol s -> SSymbol s -> SSymbol s #

Ord (SNat n) Source # 
Instance details

Methods

compare :: SNat n -> SNat n -> Ordering #

(<) :: SNat n -> SNat n -> Bool #

(<=) :: SNat n -> SNat n -> Bool #

(>) :: SNat n -> SNat n -> Bool #

(>=) :: SNat n -> SNat n -> Bool #

max :: SNat n -> SNat n -> SNat n #

min :: SNat n -> SNat n -> SNat n #

Eq1 f => Eq1 (Rec1 f) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> Rec1 f a -> Rec1 f b -> Bool #

Ord1 f => Ord1 (Rec1 f) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> Rec1 f a -> Rec1 f b -> Ordering #

Read1 f => Read1 (Rec1 f) Source # 
Instance details

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Rec1 f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Rec1 f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Rec1 f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Rec1 f a] #

Show1 f => Show1 (Rec1 f) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Rec1 f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Rec1 f a] -> ShowS #

Show (UAddr p) Source # 
Instance details

Methods

showsPrec :: Int -> UAddr p -> ShowS #

show :: UAddr p -> String #

showList :: [UAddr p] -> ShowS #

(Eq1 f, Eq1 g) => Eq1 (f :*: g) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> (f :*: g) a -> (f :*: g) b -> Bool #

(Eq1 f, Eq1 g) => Eq1 (f :+: g) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> (f :+: g) a -> (f :+: g) b -> Bool #

Eq c => Eq1 (K1 i c :: Type -> Type) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> K1 i c a -> K1 i c b -> Bool #

(Ord1 f, Ord1 g) => Ord1 (f :*: g) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> (f :*: g) a -> (f :*: g) b -> Ordering #

(Ord1 f, Ord1 g) => Ord1 (f :+: g) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> (f :+: g) a -> (f :+: g) b -> Ordering #

Ord c => Ord1 (K1 i c :: Type -> Type) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> K1 i c a -> K1 i c b -> Ordering #

(Read1 f, Read1 g) => Read1 (f :*: g) Source # 
Instance details

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :*: g) a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :*: g) a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :*: g) a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :*: g) a] #

(Read1 f, Read1 g) => Read1 (f :+: g) Source # 
Instance details

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :+: g) a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :+: g) a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :+: g) a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :+: g) a] #

Read c => Read1 (K1 i c :: Type -> Type) Source # 
Instance details

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (K1 i c a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [K1 i c a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (K1 i c a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [K1 i c a] #

(Show1 f, Show1 g) => Show1 (f :*: g) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (f :*: g) a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [(f :*: g) a] -> ShowS #

(Show1 f, Show1 g) => Show1 (f :+: g) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (f :+: g) a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [(f :+: g) a] -> ShowS #

Show c => Show1 (K1 i c :: Type -> Type) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> K1 i c a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [K1 i c a] -> ShowS #

(Eq1 f, Eq1 g) => Eq1 (f :.: g) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> (f :.: g) a -> (f :.: g) b -> Bool #

Eq1 f => Eq1 (M1 i c f) Source # 
Instance details

Methods

liftEq :: (a -> b -> Bool) -> M1 i c f a -> M1 i c f b -> Bool #

(Ord1 f, Ord1 g) => Ord1 (f :.: g) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> (f :.: g) a -> (f :.: g) b -> Ordering #

Ord1 f => Ord1 (M1 i c f) Source # 
Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> M1 i c f a -> M1 i c f b -> Ordering #

(Read1 f, Read1 g) => Read1 (f :.: g) Source # 
Instance details

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :.: g) a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :.: g) a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :.: g) a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :.: g) a] #

Read1 f => Read1 (M1 i c f) Source # 
Instance details

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (M1 i c f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [M1 i c f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (M1 i c f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [M1 i c f a] #

(Show1 f, Show1 g) => Show1 (f :.: g) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (f :.: g) a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [(f :.: g) a] -> ShowS #

Show1 f => Show1 (M1 i c f) Source # 
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> M1 i c f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [M1 i c f a] -> ShowS #

Bounded (f (g a)) => Bounded (Compose f g a) Source # 
Instance details

Methods

minBound :: Compose f g a #

maxBound :: Compose f g a #

Enum (f (g a)) => Enum (Compose f g a) Source # 
Instance details

Methods

succ :: Compose f g a -> Compose f g a #

pred :: Compose f g a -> Compose f g a #

toEnum :: Int -> Compose f g a #

fromEnum :: Compose f g a -> Int #

enumFrom :: Compose f g a -> [Compose f g a] #

enumFromThen :: Compose f g a -> Compose f g a -> [Compose f g a] #

enumFromTo :: Compose f g a -> Compose f g a -> [Compose f g a] #

enumFromThenTo :: Compose f g a -> Compose f g a -> Compose f g a -> [Compose f g a] #

Floating (f (g a)) => Floating (Compose f g a) Source # 
Instance details

Methods

pi :: Compose f g a #

exp :: Compose f g a -> Compose f g a #

log :: Compose f g a -> Compose f g a #

sqrt :: Compose f g a -> Compose f g a #

(**) :: Compose f g a -> Compose f g a -> Compose f g a #

logBase :: Compose f g a -> Compose f g a -> Compose f g a #

sin :: Compose f g a -> Compose f g a #

cos :: Compose f g a -> Compose f g a #

tan :: Compose f g a -> Compose f g a #

asin :: Compose f g a -> Compose f g a #

acos :: Compose f g a -> Compose f g a #

atan :: Compose f g a -> Compose f g a #

sinh :: Compose f g a -> Compose f g a #

cosh :: Compose f g a -> Compose f g a #

tanh :: Compose f g a -> Compose f g a #

asinh :: Compose f g a -> Compose f g a #

acosh :: Compose f g a -> Compose f g a #

atanh :: Compose f g a -> Compose f g a #

log1p :: Compose f g a -> Compose f g a #

expm1 :: Compose f g a -> Compose f g a #

log1pexp :: Compose f g a -> Compose f g a #

log1mexp :: Compose f g a -> Compose f g a #

RealFloat (f (g a)) => RealFloat (Compose f g a) Source # 
Instance details

Methods

floatRadix :: Compose f g a -> Integer #

floatDigits :: Compose f g a -> Int #

floatRange :: Compose f g a -> (Int, Int) #

decodeFloat :: Compose f g a -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Compose f g a #

exponent :: Compose f g a -> Int #

significand :: Compose f g a -> Compose f g a #

scaleFloat :: Int -> Compose f g a -> Compose f g a #

isNaN :: Compose f g a -> Bool #

isInfinite :: Compose f g a -> Bool #

isDenormalized :: Compose f g a -> Bool #

isNegativeZero :: Compose f g a -> Bool #

isIEEE :: Compose f g a -> Bool #

atan2 :: Compose f g a -> Compose f g a -> Compose f g a #

Num (f (g a)) => Num (Compose f g a) Source # 
Instance details

Methods

(+) :: Compose f g a -> Compose f g a -> Compose f g a #

(-) :: Compose f g a -> Compose f g a -> Compose f g a #

(*) :: Compose f g a -> Compose f g a -> Compose f g a #

negate :: Compose f g a -> Compose f g a #

abs :: Compose f g a -> Compose f g a #

signum :: Compose f g a -> Compose f g a #

fromInteger :: Integer -> Compose f g a #

Fractional (f (g a)) => Fractional (Compose f g a) Source # 
Instance details

Methods

(/) :: Compose f g a -> Compose f g a -> Compose f g a #

recip :: Compose f g a -> Compose f g a #

fromRational :: Rational -> Compose f g a #

Integral (f (g a)) => Integral (Compose f g a) Source # 
Instance details

Methods

quot :: Compose f g a -> Compose f g a -> Compose f g a #

rem :: Compose f g a -> Compose f g a -> Compose f g a #

div :: Compose f g a -> Compose f g a -> Compose f g a #

mod :: Compose f g a -> Compose f g a -> Compose f g a #

quotRem :: Compose f g a -> Compose f g a -> (Compose f g a, Compose f g a) #

divMod :: Compose f g a -> Compose f g a -> (Compose f g a, Compose f g a) #

toInteger :: Compose f g a -> Integer #

Real (f (g a)) => Real (Compose f g a) Source # 
Instance details

Methods

toRational :: Compose f g a -> Rational #

RealFrac (f (g a)) => RealFrac (Compose f g a) Source # 
Instance details

Methods

properFraction :: Integral b => Compose f g a -> (b, Compose f g a) #

truncate :: Integral b => Compose f g a -> b #

round :: Integral b => Compose f g a -> b #

ceiling :: Integral b => Compose f g a -> b #

floor :: Integral b => Compose f g a -> b #