transformers-compat-0.6.4: A small compatibility shim for the transformers library

Copyright(C) 2015-2016 Edward Kmett Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
StabilityProvisional
PortabilityGHC
Safe HaskellNone
LanguageHaskell98

Data.Functor.Classes.Generic.Internal

Contents

Description

Internal functionality for Data.Functor.Classes.Generic.

This is an internal module and, as such, the API is not guaranteed to remain the same between any given release.

Synopsis

Options

newtype Options Source #

Options that further configure how the functions in Data.Functor.Classes.Generic should behave.

Constructors

Options 

Fields

defaultOptions :: Options Source #

Options that match the behavior of the installed version of GHC.

latestGHCOptions :: Options Source #

Options that match the behavior of the most recent GHC release.

Eq1

liftEqDefault :: (GEq1 NonV4 (Rep1 f), Generic1 f) => (a -> b -> Bool) -> f a -> f b -> Bool Source #

A sensible default liftEq implementation for Generic1 instances.

liftEqOptions :: (GEq1 NonV4 (Rep1 f), Generic1 f) => Options -> (a -> b -> Bool) -> f a -> f b -> Bool Source #

Like liftEqDefault, but with configurable Options. Currently, the Options have no effect (but this may change in the future).

class GEq1 v t where Source #

Class of generic representation types that can be checked for equality.

Methods

gliftEq :: Eq1Args v a b -> t a -> t b -> Bool Source #

Instances
GEq1 NonV4 Par1 Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args NonV4 a b -> Par1 a -> Par1 b -> Bool Source #

GEq1 v (UWord :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args v a b -> UWord a -> UWord b -> Bool Source #

GEq1 v (UInt :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args v a b -> UInt a -> UInt b -> Bool Source #

GEq1 v (UFloat :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args v a b -> UFloat a -> UFloat b -> Bool Source #

GEq1 v (UDouble :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args v a b -> UDouble a -> UDouble b -> Bool Source #

GEq1 v (UChar :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args v a b -> UChar a -> UChar b -> Bool Source #

GEq1 v (UAddr :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args v a b -> UAddr a -> UAddr b -> Bool Source #

GEq1 v (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args v a b -> V1 a -> V1 b -> Bool Source #

GEq1 v (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args v a b -> U1 a -> U1 b -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args NonV4 a b -> Rec1 f a -> Rec1 f b -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args v a b -> (f :+: g) a -> (f :+: g) b -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args v a b -> (f :*: g) a -> (f :*: g) b -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args v a b -> K1 i c a -> K1 i c b -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args v a b -> M1 i c f a -> M1 i c f b -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args NonV4 a b -> (f :.: g) a -> (f :.: g) b -> Bool Source #

data Eq1Args v a b where Source #

An Eq1Args value either stores an Eq a dictionary (for the transformers-0.4 version of Eq1), or it stores the function argument that checks the equality of occurrences of the type parameter (for the non-transformers-0.4 version of Eq1).

Constructors

V4Eq1Args :: Eq a => Eq1Args V4 a a 
NonV4Eq1Args :: (a -> b -> Bool) -> Eq1Args NonV4 a b 

Ord1

liftCompareDefault :: (GOrd1 NonV4 (Rep1 f), Generic1 f) => (a -> b -> Ordering) -> f a -> f b -> Ordering Source #

A sensible default liftCompare implementation for Generic1 instances.

liftCompareOptions :: (GOrd1 NonV4 (Rep1 f), Generic1 f) => Options -> (a -> b -> Ordering) -> f a -> f b -> Ordering Source #

Like liftCompareDefault, but with configurable Options. Currently, the Options have no effect (but this may change in the future).

class GEq1 v t => GOrd1 v t where Source #

Class of generic representation types that can be totally ordered.

Methods

gliftCompare :: Ord1Args v a b -> t a -> t b -> Ordering Source #

Instances
GOrd1 NonV4 Par1 Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args NonV4 a b -> Par1 a -> Par1 b -> Ordering Source #

GOrd1 v (UWord :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args v a b -> UWord a -> UWord b -> Ordering Source #

GOrd1 v (UInt :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args v a b -> UInt a -> UInt b -> Ordering Source #

GOrd1 v (UFloat :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args v a b -> UFloat a -> UFloat b -> Ordering Source #

GOrd1 v (UDouble :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args v a b -> UDouble a -> UDouble b -> Ordering Source #

GOrd1 v (UChar :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args v a b -> UChar a -> UChar b -> Ordering Source #

GOrd1 v (UAddr :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args v a b -> UAddr a -> UAddr b -> Ordering Source #

GOrd1 v (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args v a b -> V1 a -> V1 b -> Ordering Source #

GOrd1 v (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args v a b -> U1 a -> U1 b -> Ordering Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args NonV4 a b -> Rec1 f a -> Rec1 f b -> Ordering Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args v a b -> (f :+: g) a -> (f :+: g) b -> Ordering Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args v a b -> (f :*: g) a -> (f :*: g) b -> Ordering Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args v a b -> K1 i c a -> K1 i c b -> Ordering Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args v a b -> M1 i c f a -> M1 i c f b -> Ordering Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args NonV4 a b -> (f :.: g) a -> (f :.: g) b -> Ordering Source #

data Ord1Args v a b where Source #

An Ord1Args value either stores an Ord a dictionary (for the transformers-0.4 version of Ord1), or it stores the function argument that compares occurrences of the type parameter (for the non-transformers-0.4 version of Ord1).

Constructors

V4Ord1Args :: Ord a => Ord1Args V4 a a 
NonV4Ord1Args :: (a -> b -> Ordering) -> Ord1Args NonV4 a b 

Read1

liftReadsPrecDefault :: (GRead1 NonV4 (Rep1 f), Generic1 f) => (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a) Source #

A sensible default liftReadsPrec implementation for Generic1 instances.

liftReadsPrecOptions :: (GRead1 NonV4 (Rep1 f), Generic1 f) => Options -> (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a) Source #

Like liftReadsPrecDefault, but with configurable Options. Currently, the Options have no effect (but this may change in the future).

class GRead1 v f where Source #

Class of generic representation types that can be parsed from a String.

Methods

gliftReadPrec :: Read1Args v a -> ReadPrec (f a) Source #

Instances
GRead1 v (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftReadPrec :: Read1Args v a -> ReadPrec (V1 a) Source #

(Constructor c, GRead1Con v f, IsNullary f) => GRead1 v (C1 c f) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftReadPrec :: Read1Args v a -> ReadPrec (C1 c f a) Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftReadPrec :: Read1Args v a -> ReadPrec ((f :+: g) a) Source #

GRead1 v f => GRead1 v (D1 d f) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftReadPrec :: Read1Args v a -> ReadPrec (D1 d f a) Source #

class GRead1Con v f where Source #

Class of generic representation types that can be parsed from a String, and for which the ConType has been determined.

Instances
GRead1Con NonV4 Par1 Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

GRead1Con v (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

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

Defined in Data.Functor.Classes.Generic.Internal

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftReadPrecCon :: ConType -> Read1Args v a -> ReadPrec ((f :*: g) a) Source #

(Selector s, GRead1Con v f) => GRead1Con v (S1 s f) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftReadPrecCon :: ConType -> Read1Args v a -> ReadPrec (S1 s f a) Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftReadPrecCon :: ConType -> Read1Args v a -> ReadPrec (K1 i c a) Source #

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

Defined in Data.Functor.Classes.Generic.Internal

data Read1Args v a where Source #

A Read1Args value either stores a Read a dictionary (for the transformers-0.4 version of Read1), or it stores the two function arguments that parse occurrences of the type parameter (for the non-transformers-0.4 version of Read1).

Constructors

V4Read1Args :: Read a => Read1Args V4 a 
NonV4Read1Args :: ReadPrec a -> ReadPrec [a] -> Read1Args NonV4 a 

Show1

liftShowsPrecDefault :: (GShow1 NonV4 (Rep1 f), Generic1 f) => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS Source #

A sensible default liftShowsPrec implementation for Generic1 instances.

liftShowsPrecOptions :: (GShow1 NonV4 (Rep1 f), Generic1 f) => Options -> (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS Source #

Like liftShowsPrecDefault, but with configurable Options.

class GShow1 v f where Source #

Class of generic representation types that can be converted to a String.

Methods

gliftShowsPrec :: Options -> Show1Args v a -> Int -> f a -> ShowS Source #

Instances
GShow1 v (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftShowsPrec :: Options -> Show1Args v a -> Int -> V1 a -> ShowS Source #

(Constructor c, GShow1Con v f, IsNullary f) => GShow1 v (C1 c f) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftShowsPrec :: Options -> Show1Args v a -> Int -> C1 c f a -> ShowS Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftShowsPrec :: Options -> Show1Args v a -> Int -> (f :+: g) a -> ShowS Source #

GShow1 v f => GShow1 v (D1 d f) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftShowsPrec :: Options -> Show1Args v a -> Int -> D1 d f a -> ShowS Source #

class GShow1Con v f where Source #

Class of generic representation types that can be converted to a String, and for which the ConType has been determined.

Methods

gliftShowsPrecCon :: Options -> ConType -> Show1Args v a -> Int -> f a -> ShowS Source #

Instances
GShow1Con NonV4 Par1 Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

GShow1Con v (UWord :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

GShow1Con v (UInt :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

GShow1Con v (UFloat :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

GShow1Con v (UDouble :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

GShow1Con v (UChar :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

GShow1Con v (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftShowsPrecCon :: Options -> ConType -> Show1Args v a -> Int -> U1 a -> ShowS Source #

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

Defined in Data.Functor.Classes.Generic.Internal

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftShowsPrecCon :: Options -> ConType -> Show1Args v a -> Int -> (f :*: g) a -> ShowS Source #

(Selector s, GShow1Con v f) => GShow1Con v (S1 s f) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftShowsPrecCon :: Options -> ConType -> Show1Args v a -> Int -> S1 s f a -> ShowS Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftShowsPrecCon :: Options -> ConType -> Show1Args v a -> Int -> K1 i c a -> ShowS Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftShowsPrecCon :: Options -> ConType -> Show1Args NonV4 a -> Int -> (f :.: g) a -> ShowS Source #

data Show1Args v a where Source #

A Show1Args value either stores a Show a dictionary (for the transformers-0.4 version of Show1), or it stores the two function arguments that show occurrences of the type parameter (for the non-transformers-0.4 version of Show1).

Constructors

V4Show1Args :: Show a => Show1Args V4 a 
NonV4Show1Args :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Show1Args NonV4 a 

Miscellaneous types

data V4 Source #

A type-level indicator that the transformers-0.4 version of a class method is being derived generically.

data NonV4 Source #

A type-level indicator that the non-transformers-0.4 version of a class method is being derived generically.

Instances
GShow1Con NonV4 Par1 Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

GRead1Con NonV4 Par1 Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

GOrd1 NonV4 Par1 Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args NonV4 a b -> Par1 a -> Par1 b -> Ordering Source #

GEq1 NonV4 Par1 Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args NonV4 a b -> Par1 a -> Par1 b -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

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

Defined in Data.Functor.Classes.Generic.Internal

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args NonV4 a b -> Rec1 f a -> Rec1 f b -> Ordering Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args NonV4 a b -> Rec1 f a -> Rec1 f b -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftShowsPrecCon :: Options -> ConType -> Show1Args NonV4 a -> Int -> (f :.: g) a -> ShowS Source #

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

Defined in Data.Functor.Classes.Generic.Internal

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftCompare :: Ord1Args NonV4 a b -> (f :.: g) a -> (f :.: g) b -> Ordering Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

gliftEq :: Eq1Args NonV4 a b -> (f :.: g) a -> (f :.: g) b -> Bool Source #

data ConType Source #

Whether a constructor is a record (Rec), a tuple (Tup), is prefix (Pref), or infix (Inf).

Constructors

Rec 
Tup 
Pref 
Inf String 

class IsNullary f where Source #

Class of generic representation types that represent a constructor with zero or more fields.

Methods

isNullary :: f a -> Bool Source #

Instances
IsNullary Par1 Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

isNullary :: Par1 a -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

isNullary :: U1 a -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

isNullary :: UChar a -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

isNullary :: UDouble a -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

isNullary :: UFloat a -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

isNullary :: UInt a -> Bool Source #

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

Defined in Data.Functor.Classes.Generic.Internal

Methods

isNullary :: UWord a -> Bool Source #

IsNullary (Rec1 f) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

isNullary :: Rec1 f a -> Bool Source #

IsNullary (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

isNullary :: K1 i c a -> Bool Source #

IsNullary (f :*: g) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

isNullary :: (f :*: g) a -> Bool Source #

IsNullary f => IsNullary (S1 s f) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

isNullary :: S1 s f a -> Bool Source #

IsNullary (f :.: g) Source # 
Instance details

Defined in Data.Functor.Classes.Generic.Internal

Methods

isNullary :: (f :.: g) a -> Bool Source #