generic-deriving-1.14.5: Generic programming library for generalised deriving.
Safe HaskellTrustworthy
LanguageHaskell2010

Generics.Deriving.Enum

Synopsis

Generic enum class

class GEnum a where Source #

Minimal complete definition

Nothing

Methods

genum :: [a] Source #

default genum :: (Generic a, Enum' (Rep a)) => [a] Source #

Instances

Instances details
GEnum All Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [All] Source #

GEnum Any Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Any] Source #

GEnum CBool Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CBool] Source #

GEnum CChar Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CChar] Source #

GEnum CClock Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CClock] Source #

GEnum CDouble Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CDouble] Source #

GEnum CFloat Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CFloat] Source #

GEnum CInt Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CInt] Source #

GEnum CIntMax Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CIntMax] Source #

GEnum CIntPtr Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CIntPtr] Source #

GEnum CLLong Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CLLong] Source #

GEnum CLong Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CLong] Source #

GEnum CPtrdiff Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CPtrdiff] Source #

GEnum CSChar Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CSChar] Source #

GEnum CSUSeconds Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CSUSeconds] Source #

GEnum CShort Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CShort] Source #

GEnum CSigAtomic Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CSigAtomic] Source #

GEnum CSize Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CSize] Source #

GEnum CTime Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CTime] Source #

GEnum CUChar Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CUChar] Source #

GEnum CUInt Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CUInt] Source #

GEnum CUIntMax Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CUIntMax] Source #

GEnum CUIntPtr Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CUIntPtr] Source #

GEnum CULLong Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CULLong] Source #

GEnum CULong Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CULong] Source #

GEnum CUSeconds Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CUSeconds] Source #

GEnum CUShort Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CUShort] Source #

GEnum CWchar Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CWchar] Source #

GEnum IntPtr Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [IntPtr] Source #

GEnum WordPtr Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [WordPtr] Source #

GEnum Associativity Source # 
Instance details

Defined in Generics.Deriving.Enum

GEnum Fixity Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Fixity] Source #

GEnum ExitCode Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [ExitCode] Source #

GEnum Int16 Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Int16] Source #

GEnum Int32 Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Int32] Source #

GEnum Int64 Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Int64] Source #

GEnum Int8 Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Int8] Source #

GEnum Word16 Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Word16] Source #

GEnum Word32 Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Word32] Source #

GEnum Word64 Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Word64] Source #

GEnum Word8 Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Word8] Source #

GEnum CBlkCnt Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CBlkCnt] Source #

GEnum CBlkSize Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CBlkSize] Source #

GEnum CCc Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CCc] Source #

GEnum CClockId Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CClockId] Source #

GEnum CDev Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CDev] Source #

GEnum CFsBlkCnt Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CFsBlkCnt] Source #

GEnum CFsFilCnt Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CFsFilCnt] Source #

GEnum CGid Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CGid] Source #

GEnum CId Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CId] Source #

GEnum CIno Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CIno] Source #

GEnum CKey Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CKey] Source #

GEnum CMode Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CMode] Source #

GEnum CNlink Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CNlink] Source #

GEnum COff Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [COff] Source #

GEnum CPid Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CPid] Source #

GEnum CRLim Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CRLim] Source #

GEnum CSpeed Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CSpeed] Source #

GEnum CSsize Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CSsize] Source #

GEnum CTcflag Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CTcflag] Source #

GEnum CUid Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [CUid] Source #

GEnum Fd Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Fd] Source #

GEnum Ordering Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Ordering] Source #

GEnum Integer Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Integer] Source #

GEnum Natural Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Natural] Source #

GEnum () Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [()] Source #

GEnum Bool Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Bool] Source #

GEnum Double Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Double] Source #

GEnum Float Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Float] Source #

GEnum Int Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Int] Source #

GEnum Word Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Word] Source #

GEnum a => GEnum (ZipList a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [ZipList a] Source #

GEnum a => GEnum (Complex a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Complex a] Source #

GEnum a => GEnum (Identity a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Identity a] Source #

GEnum a => GEnum (First a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [First a] Source #

GEnum a => GEnum (Last a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Last a] Source #

GEnum a => GEnum (First a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [First a] Source #

GEnum a => GEnum (Last a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Last a] Source #

GEnum a => GEnum (Max a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Max a] Source #

GEnum a => GEnum (Min a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Min a] Source #

GEnum m => GEnum (WrappedMonoid m) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [WrappedMonoid m] Source #

GEnum a => GEnum (Dual a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Dual a] Source #

GEnum a => GEnum (Product a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Product a] Source #

GEnum a => GEnum (Sum a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Sum a] Source #

GEnum p => GEnum (Par1 p) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Par1 p] Source #

(Generic a, GEq a, Enum' (Rep a)) => GEnum (Default a) Source #

The Enum class in base is slightly different; it comprises toEnum and fromEnum. Generics.Deriving.Enum provides functions toEnumDefault and fromEnumDefault.

Instance details

Defined in Generics.Deriving.Default

Methods

genum :: [Default a] Source #

GEnum a => GEnum (NonEmpty a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [NonEmpty a] Source #

GEnum a => GEnum (Maybe a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Maybe a] Source #

GEnum a => GEnum [a] Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [[a]] Source #

(GEnum a, GEnum b) => GEnum (Either a b) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Either a b] Source #

GEnum (Proxy s) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Proxy s] Source #

(GEnum a, GEnum b) => GEnum (Arg a b) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Arg a b] Source #

GEnum (U1 p) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [U1 p] Source #

(GEnum a, GEnum b) => GEnum (a, b) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [(a, b)] Source #

GEnum a => GEnum (Const a b) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Const a b] Source #

GEnum (f a) => GEnum (Alt f a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Alt f a] Source #

GEnum (f p) => GEnum (Rec1 f p) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [Rec1 f p] Source #

(GEnum a, GEnum b, GEnum c) => GEnum (a, b, c) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [(a, b, c)] Source #

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

Defined in Generics.Deriving.Enum

Methods

genum :: [(f :*: g) p] Source #

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

Defined in Generics.Deriving.Enum

Methods

genum :: [(f :+: g) p] Source #

GEnum c => GEnum (K1 i c p) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [K1 i c p] Source #

(GEnum a, GEnum b, GEnum c, GEnum d) => GEnum (a, b, c, d) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [(a, b, c, d)] Source #

GEnum (f (g p)) => GEnum ((f :.: g) p) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [(f :.: g) p] Source #

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

Defined in Generics.Deriving.Enum

Methods

genum :: [M1 i c f p] Source #

(GEnum a, GEnum b, GEnum c, GEnum d, GEnum e) => GEnum (a, b, c, d, e) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [(a, b, c, d, e)] Source #

(GEnum a, GEnum b, GEnum c, GEnum d, GEnum e, GEnum f) => GEnum (a, b, c, d, e, f) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [(a, b, c, d, e, f)] Source #

(GEnum a, GEnum b, GEnum c, GEnum d, GEnum e, GEnum f, GEnum g) => GEnum (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

genum :: [(a, b, c, d, e, f, g)] Source #

Default definitions for GEnum

genumDefault :: (Generic a, Enum' (Rep a)) => [a] Source #

toEnumDefault :: (Generic a, Enum' (Rep a)) => Int -> a Source #

fromEnumDefault :: (GEq a, Generic a, Enum' (Rep a)) => a -> Int Source #

Internal enum class

class Enum' f where Source #

Methods

enum' :: [f a] Source #

Instances

Instances details
Enum' (U1 :: k -> Type) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

enum' :: forall (a :: k0). [U1 a] Source #

(Enum' f, Enum' g) => Enum' (f :*: g :: k -> Type) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

enum' :: forall (a :: k0). [(f :*: g) a] Source #

(Enum' f, Enum' g) => Enum' (f :+: g :: k -> Type) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

enum' :: forall (a :: k0). [(f :+: g) a] Source #

GEnum c => Enum' (K1 i c :: k -> Type) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

enum' :: forall (a :: k0). [K1 i c a] Source #

Enum' f => Enum' (M1 i c f :: k -> Type) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

enum' :: forall (a :: k0). [M1 i c f a] Source #

Generic Ix class

class Ord a => GIx a where Source #

Minimal complete definition

Nothing

Methods

range :: (a, a) -> [a] Source #

The list of values in the subrange defined by a bounding pair.

default range :: (GEq a, Generic a, Enum' (Rep a)) => (a, a) -> [a] Source #

index :: (a, a) -> a -> Int Source #

The position of a subscript in the subrange.

default index :: (GEq a, Generic a, Enum' (Rep a)) => (a, a) -> a -> Int Source #

inRange :: (a, a) -> a -> Bool Source #

Returns True the given subscript lies in the range defined the bounding pair.

default inRange :: (GEq a, Generic a, Enum' (Rep a)) => (a, a) -> a -> Bool Source #

Instances

Instances details
GIx All Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (All, All) -> [All] Source #

index :: (All, All) -> All -> Int Source #

inRange :: (All, All) -> All -> Bool Source #

GIx Any Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Any, Any) -> [Any] Source #

index :: (Any, Any) -> Any -> Int Source #

inRange :: (Any, Any) -> Any -> Bool Source #

GIx CBool Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CChar Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CInt Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (CInt, CInt) -> [CInt] Source #

index :: (CInt, CInt) -> CInt -> Int Source #

inRange :: (CInt, CInt) -> CInt -> Bool Source #

GIx CIntMax Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CIntPtr Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CLLong Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CLong Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CPtrdiff Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CSChar Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CShort Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CSigAtomic Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CSize Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CUChar Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CUInt Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CUIntMax Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CUIntPtr Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CULLong Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CULong Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CUShort Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CWchar Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx IntPtr Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx WordPtr Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx Associativity Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx Fixity Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx ExitCode Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx Int16 Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx Int32 Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx Int64 Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx Int8 Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Int8, Int8) -> [Int8] Source #

index :: (Int8, Int8) -> Int8 -> Int Source #

inRange :: (Int8, Int8) -> Int8 -> Bool Source #

GIx Word16 Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx Word32 Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx Word64 Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx Word8 Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CBlkCnt Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CBlkSize Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CClockId Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CFsBlkCnt Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CFsFilCnt Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CGid Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (CGid, CGid) -> [CGid] Source #

index :: (CGid, CGid) -> CGid -> Int Source #

inRange :: (CGid, CGid) -> CGid -> Bool Source #

GIx CId Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (CId, CId) -> [CId] Source #

index :: (CId, CId) -> CId -> Int Source #

inRange :: (CId, CId) -> CId -> Bool Source #

GIx CIno Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (CIno, CIno) -> [CIno] Source #

index :: (CIno, CIno) -> CIno -> Int Source #

inRange :: (CIno, CIno) -> CIno -> Bool Source #

GIx CKey Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (CKey, CKey) -> [CKey] Source #

index :: (CKey, CKey) -> CKey -> Int Source #

inRange :: (CKey, CKey) -> CKey -> Bool Source #

GIx CMode Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CNlink Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx COff Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (COff, COff) -> [COff] Source #

index :: (COff, COff) -> COff -> Int Source #

inRange :: (COff, COff) -> COff -> Bool Source #

GIx CPid Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (CPid, CPid) -> [CPid] Source #

index :: (CPid, CPid) -> CPid -> Int Source #

inRange :: (CPid, CPid) -> CPid -> Bool Source #

GIx CRLim Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CSsize Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CTcflag Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx CUid Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (CUid, CUid) -> [CUid] Source #

index :: (CUid, CUid) -> CUid -> Int Source #

inRange :: (CUid, CUid) -> CUid -> Bool Source #

GIx Fd Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Fd, Fd) -> [Fd] Source #

index :: (Fd, Fd) -> Fd -> Int Source #

inRange :: (Fd, Fd) -> Fd -> Bool Source #

GIx Ordering Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx Integer Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx Natural Source # 
Instance details

Defined in Generics.Deriving.Enum

GIx () Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: ((), ()) -> [()] Source #

index :: ((), ()) -> () -> Int Source #

inRange :: ((), ()) -> () -> Bool Source #

GIx Bool Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Bool, Bool) -> [Bool] Source #

index :: (Bool, Bool) -> Bool -> Int Source #

inRange :: (Bool, Bool) -> Bool -> Bool Source #

GIx Int Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Int, Int) -> [Int] Source #

index :: (Int, Int) -> Int -> Int Source #

inRange :: (Int, Int) -> Int -> Bool Source #

GIx Word Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Word, Word) -> [Word] Source #

index :: (Word, Word) -> Word -> Int Source #

inRange :: (Word, Word) -> Word -> Bool Source #

(GEq a, GEnum a, GIx a) => GIx (Identity a) Source # 
Instance details

Defined in Generics.Deriving.Enum

(GEq a, GEnum a, GIx a) => GIx (First a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (First a, First a) -> [First a] Source #

index :: (First a, First a) -> First a -> Int Source #

inRange :: (First a, First a) -> First a -> Bool Source #

(GEq a, GEnum a, GIx a) => GIx (Last a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Last a, Last a) -> [Last a] Source #

index :: (Last a, Last a) -> Last a -> Int Source #

inRange :: (Last a, Last a) -> Last a -> Bool Source #

(GEq a, GEnum a, GIx a) => GIx (First a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (First a, First a) -> [First a] Source #

index :: (First a, First a) -> First a -> Int Source #

inRange :: (First a, First a) -> First a -> Bool Source #

(GEq a, GEnum a, GIx a) => GIx (Last a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Last a, Last a) -> [Last a] Source #

index :: (Last a, Last a) -> Last a -> Int Source #

inRange :: (Last a, Last a) -> Last a -> Bool Source #

(GEq a, GEnum a, GIx a) => GIx (Max a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Max a, Max a) -> [Max a] Source #

index :: (Max a, Max a) -> Max a -> Int Source #

inRange :: (Max a, Max a) -> Max a -> Bool Source #

(GEq a, GEnum a, GIx a) => GIx (Min a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Min a, Min a) -> [Min a] Source #

index :: (Min a, Min a) -> Min a -> Int Source #

inRange :: (Min a, Min a) -> Min a -> Bool Source #

(GEq m, GEnum m, GIx m) => GIx (WrappedMonoid m) Source # 
Instance details

Defined in Generics.Deriving.Enum

(GEq a, GEnum a, GIx a) => GIx (Dual a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Dual a, Dual a) -> [Dual a] Source #

index :: (Dual a, Dual a) -> Dual a -> Int Source #

inRange :: (Dual a, Dual a) -> Dual a -> Bool Source #

(GEq a, GEnum a, GIx a) => GIx (Product a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Product a, Product a) -> [Product a] Source #

index :: (Product a, Product a) -> Product a -> Int Source #

inRange :: (Product a, Product a) -> Product a -> Bool Source #

(GEq a, GEnum a, GIx a) => GIx (Sum a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Sum a, Sum a) -> [Sum a] Source #

index :: (Sum a, Sum a) -> Sum a -> Int Source #

inRange :: (Sum a, Sum a) -> Sum a -> Bool Source #

(GEq a, GEnum a, GIx a) => GIx (NonEmpty a) Source # 
Instance details

Defined in Generics.Deriving.Enum

(GEq a, GEnum a, GIx a) => GIx (Maybe a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Maybe a, Maybe a) -> [Maybe a] Source #

index :: (Maybe a, Maybe a) -> Maybe a -> Int Source #

inRange :: (Maybe a, Maybe a) -> Maybe a -> Bool Source #

(GEq a, GEnum a, GIx a) => GIx [a] Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: ([a], [a]) -> [[a]] Source #

index :: ([a], [a]) -> [a] -> Int Source #

inRange :: ([a], [a]) -> [a] -> Bool Source #

(GEq a, GEnum a, GIx a, GEq b, GEnum b, GIx b) => GIx (Either a b) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Either a b, Either a b) -> [Either a b] Source #

index :: (Either a b, Either a b) -> Either a b -> Int Source #

inRange :: (Either a b, Either a b) -> Either a b -> Bool Source #

GIx (Proxy s) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] Source #

index :: (Proxy s, Proxy s) -> Proxy s -> Int Source #

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool Source #

(GEq a, GEnum a, GIx a, GEnum b) => GIx (Arg a b) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Arg a b, Arg a b) -> [Arg a b] Source #

index :: (Arg a b, Arg a b) -> Arg a b -> Int Source #

inRange :: (Arg a b, Arg a b) -> Arg a b -> Bool Source #

(GEq a, GEnum a, GIx a, GEq b, GEnum b, GIx b) => GIx (a, b) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: ((a, b), (a, b)) -> [(a, b)] Source #

index :: ((a, b), (a, b)) -> (a, b) -> Int Source #

inRange :: ((a, b), (a, b)) -> (a, b) -> Bool Source #

(GEq (f a), GEnum (f a), GIx (f a)) => GIx (Alt f a) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: (Alt f a, Alt f a) -> [Alt f a] Source #

index :: (Alt f a, Alt f a) -> Alt f a -> Int Source #

inRange :: (Alt f a, Alt f a) -> Alt f a -> Bool Source #

(GEq a, GEnum a, GIx a, GEq b, GEnum b, GIx b, GEq c, GEnum c, GIx c) => GIx (a, b, c) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: ((a, b, c), (a, b, c)) -> [(a, b, c)] Source #

index :: ((a, b, c), (a, b, c)) -> (a, b, c) -> Int Source #

inRange :: ((a, b, c), (a, b, c)) -> (a, b, c) -> Bool Source #

(GEq a, GEnum a, GIx a, GEq b, GEnum b, GIx b, GEq c, GEnum c, GIx c, GEq d, GEnum d, GIx d) => GIx (a, b, c, d) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: ((a, b, c, d), (a, b, c, d)) -> [(a, b, c, d)] Source #

index :: ((a, b, c, d), (a, b, c, d)) -> (a, b, c, d) -> Int Source #

inRange :: ((a, b, c, d), (a, b, c, d)) -> (a, b, c, d) -> Bool Source #

(GEq a, GEnum a, GIx a, GEq b, GEnum b, GIx b, GEq c, GEnum c, GIx c, GEq d, GEnum d, GIx d, GEq e, GEnum e, GIx e) => GIx (a, b, c, d, e) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: ((a, b, c, d, e), (a, b, c, d, e)) -> [(a, b, c, d, e)] Source #

index :: ((a, b, c, d, e), (a, b, c, d, e)) -> (a, b, c, d, e) -> Int Source #

inRange :: ((a, b, c, d, e), (a, b, c, d, e)) -> (a, b, c, d, e) -> Bool Source #

(GEq a, GEnum a, GIx a, GEq b, GEnum b, GIx b, GEq c, GEnum c, GIx c, GEq d, GEnum d, GIx d, GEq e, GEnum e, GIx e, GEq f, GEnum f, GIx f) => GIx (a, b, c, d, e, f) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> [(a, b, c, d, e, f)] Source #

index :: ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> (a, b, c, d, e, f) -> Int Source #

inRange :: ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> (a, b, c, d, e, f) -> Bool Source #

(GEq a, GEnum a, GIx a, GEq b, GEnum b, GIx b, GEq c, GEnum c, GIx c, GEq d, GEnum d, GIx d, GEq e, GEnum e, GIx e, GEq f, GEnum f, GIx f, GEq g, GEnum g, GIx g) => GIx (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Generics.Deriving.Enum

Methods

range :: ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> [(a, b, c, d, e, f, g)] Source #

index :: ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> (a, b, c, d, e, f, g) -> Int Source #

inRange :: ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> (a, b, c, d, e, f, g) -> Bool Source #

Default definitions for GIx

rangeDefault :: (GEq a, Generic a, Enum' (Rep a)) => (a, a) -> [a] Source #

indexDefault :: (GEq a, Generic a, Enum' (Rep a)) => (a, a) -> a -> Int Source #

inRangeDefault :: (GEq a, Generic a, Enum' (Rep a)) => (a, a) -> a -> Bool Source #