Safe Haskell | None |
---|---|
Language | Haskell2010 |
Generic deriving for Enum
.
Synopsis
- gtoEnum :: forall a. (Generic a, GEnum StandardEnum (Rep a)) => Int -> a
- gfromEnum :: (Generic a, GEnum StandardEnum (Rep a)) => a -> Int
- genumFrom :: (Generic a, GEnum StandardEnum (Rep a)) => a -> [a]
- genumFromThen :: (Generic a, GEnum StandardEnum (Rep a)) => a -> a -> [a]
- genumFromTo :: (Generic a, GEnum StandardEnum (Rep a)) => a -> a -> [a]
- genumFromThenTo :: (Generic a, GEnum StandardEnum (Rep a)) => a -> a -> a -> [a]
- gtoFiniteEnum :: forall a. (Generic a, GEnum FiniteEnum (Rep a)) => Int -> a
- gfromFiniteEnum :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> Int
- gfiniteEnumFrom :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> [a]
- gfiniteEnumFromThen :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> a -> [a]
- gfiniteEnumFromTo :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> a -> [a]
- gfiniteEnumFromThenTo :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> a -> a -> [a]
- gtoEnumRaw' :: forall opts a. (Generic a, GEnum opts (Rep a)) => Int -> a
- gtoEnum' :: forall opts a. (Generic a, GEnum opts (Rep a)) => String -> Int -> a
- gfromEnum' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> Int
- genumMin :: Int
- genumMax :: forall opts a. (Generic a, GEnum opts (Rep a)) => Int
- genumFrom' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> [a]
- genumFromThen' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> a -> [a]
- genumFromTo' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> a -> [a]
- genumFromThenTo' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> a -> a -> [a]
- gminBound :: (Generic a, GBounded (Rep a)) => a
- gmaxBound :: (Generic a, GBounded (Rep a)) => a
- class GEnum opts f where
- data StandardEnum
- data FiniteEnum
- class GBounded f where
Documentation
gtoEnum :: forall a. (Generic a, GEnum StandardEnum (Rep a)) => Int -> a Source #
Generic toEnum
generated with the StandardEnum
option.
instanceEnum
MyType wheretoEnum
=gtoEnum
fromEnum
=gfromEnum
enumFrom
=genumFrom
enumFromThen
=genumFromThen
enumFromTo
=genumFromTo
enumFromThenTo
=genumFromThenTo
gfromEnum :: (Generic a, GEnum StandardEnum (Rep a)) => a -> Int Source #
Generic fromEnum
generated with the StandardEnum
option.
See also gtoEnum
.
genumFrom :: (Generic a, GEnum StandardEnum (Rep a)) => a -> [a] Source #
Generic enumFrom
generated with the StandardEnum
option.
See also gtoEnum
.
genumFromThen :: (Generic a, GEnum StandardEnum (Rep a)) => a -> a -> [a] Source #
Generic enumFromThen
generated with the StandardEnum
option.
See also gtoEnum
.
genumFromTo :: (Generic a, GEnum StandardEnum (Rep a)) => a -> a -> [a] Source #
Generic enumFromTo
generated with the StandardEnum
option.
See also gtoEnum
.
genumFromThenTo :: (Generic a, GEnum StandardEnum (Rep a)) => a -> a -> a -> [a] Source #
Generic enumFromThenTo
generated with the StandardEnum
option.
See also gtoEnum
.
gtoFiniteEnum :: forall a. (Generic a, GEnum FiniteEnum (Rep a)) => Int -> a Source #
Generic toEnum
generated with the FiniteEnum
option.
instanceEnum
MyType wheretoEnum
=gtoFiniteEnum
fromEnum
=gfromFiniteEnum
enumFrom
=gfiniteEnumFrom
enumFromThen
=gfiniteEnumFromThen
enumFromTo
=gfiniteEnumFromTo
enumFromThenTo
=gfiniteEnumFromThenTo
gfromFiniteEnum :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> Int Source #
Generic fromEnum
generated with the FiniteEnum
option.
See also gtoFiniteEnum
.
gfiniteEnumFrom :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> [a] Source #
Generic enumFrom
generated with the FiniteEnum
option.
See also gtoFiniteEnum
.
gfiniteEnumFromThen :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> a -> [a] Source #
Generic enumFromThen
generated with the FiniteEnum
option.
See also gtoFiniteEnum
.
gfiniteEnumFromTo :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> a -> [a] Source #
Generic enumFromTo
generated with the FiniteEnum
option.
See also gtoFiniteEnum
.
gfiniteEnumFromThenTo :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> a -> a -> [a] Source #
Generic enumFromThenTo
generated with the FiniteEnum
option.
See also gtoFiniteEnum
.
gtoEnumRaw' :: forall opts a. (Generic a, GEnum opts (Rep a)) => Int -> a Source #
Unsafe generic toEnum
. Does not check whether the argument is within
valid bounds. Use gtoEnum
or gtoFiniteEnum
instead.
gtoEnum' :: forall opts a. (Generic a, GEnum opts (Rep a)) => String -> Int -> a Source #
Generic toEnum
. Use gfromEnum
or gfromFiniteEnum
instead.
gfromEnum' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> Int Source #
Generic fromEnum
. Use gfromEnum
or gfromFiniteEnum
instead.
genumMax :: forall opts a. (Generic a, GEnum opts (Rep a)) => Int Source #
genumMax == gfromEnum gmaxBound
genumFrom' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> [a] Source #
Generic enumFrom
. Use genumFrom
or gfiniteEnumFrom
instead.
genumFromThen' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> a -> [a] Source #
Generic enumFromThen
. Use genumFromThen
or gfiniteEnumFromThen
instead.
genumFromTo' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> a -> [a] Source #
Generic enumFromTo
. Use genumFromTo
or gfiniteEnumFromTo
instead.
genumFromThenTo' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> a -> a -> [a] Source #
Generic enumFromThenTo
. Use genumFromThenTo
or gfiniteEnumFromThenTo
instead.
class GEnum opts f where Source #
Generic representation of Enum
types.
The opts
parameter is a type-level option to select different
implementations.
Instances
GEnum opts (U1 :: Type -> Type) Source # | |
(GEnum opts f, GEnum opts g) => GEnum opts (f :+: g) Source # | |
(Bounded c, Enum c) => GEnum FiniteEnum (K1 i c :: Type -> Type) Source # | |
(GEnum FiniteEnum f, GEnum FiniteEnum g) => GEnum FiniteEnum (f :*: g) Source # | |
GEnum opts f => GEnum opts (M1 i c f) Source # | |
data StandardEnum Source #
Standard option for GEnum
: derive Enum
for types with only nullary
constructors (the same restrictions as in the Haskell 2010
report).
data FiniteEnum Source #
Extends the StandardEnum
option for GEnum
to allow all constructors to
have arbitrary many fields. Each field type must be an instance of
both Enum
and Bounded
. Two restrictions require the user's caution:
- The
Enum
instances of the field types need to start enumerating from 0. ParticularlyInt
is an unfit field type, because the enumeration of the negative values starts before 0. - There can only be up to
values (because the implementation represents the cardinality explicitly as anmaxBound
::Int
Int
). This restriction makesWord
an invalid field type. Notably, it is insufficient for each individual field types to stay below this limit. Instead it applies to the generic type as a whole.
The resulting GEnum
instance starts enumerating from 0
up to
(cardinality - 1)
and respects the generic Ord
instance (defined by
gcompare
). The values from different constructors are enumerated
sequentially; they are not interleaved.
data Example = C0 Bool Bool | C1 Bool deriving (Eq
,Ord
,Show
,Generic
) cardinality = 6 -- 2 * 2 + 2 -- Bool * Bool | Bool enumeration = [ C0 False False , C0 False True , C0 True False , C0 True True , C1 False , C1 True ] enumeration == mapgtoFiniteEnum
[0 .. 5] [0 .. 5] == mapgfromFiniteEnum
enumeration
Instances
(Bounded c, Enum c) => GEnum FiniteEnum (K1 i c :: Type -> Type) Source # | |
(GEnum FiniteEnum f, GEnum FiniteEnum g) => GEnum FiniteEnum (f :*: g) Source # | |
class GBounded f where Source #
Generic representation of Bounded
types.