| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Generic.Enum
- class (Num (EnumNumT a), Integral (EnumIntegralT a)) => Enum a where
- type EnumNumT a
- type EnumIntegralT a
- class DefaultEnum a b where
- type family Element a
- class Enum (Element a) => EnumFromTo a where
- class Enum (Element a) => EnumFrom a where
Documentation
class (Num (EnumNumT a), Integral (EnumIntegralT a)) => Enum a where Source #
The generic Enum class. Firstly, this class just deals with fromEnum, toEnum type functions,
not the list generating functions like enumFrom and enumFromTo
the normal Enum has.
This class has a number of defaults for making defining both existing Prelude style Enum classes and ordinary Numeric classes quick and painless.
Firstly, for existing Enums:
instance Enum Blah
Will completely define Blah as an Enum if Blah is already a Prelude style Enum, just forwarding
calls to the functions in the Prelude's Enum.
Secondly, for integral datatypes (i.e. in class Integral)
instance Enum Blah type EnumNumT Blah = Blah
will defined Blah to be an Enum, with it's Enum type itself.
For example,
instance Enum Integer type EnumNumT Integer = Integer
is an Enum with fromEnum and toEnum simply id.
Note that with this approach, toEnum . fromEnum == id, instead of going through Int
and possibly overflowing.
Note also that operations like succ and pred don't bounds check like the Prelude versions often do.
For types that don't fit one of the above two categories (i.e. don't have a satisfactory Prelude Enum instance or aren't Integral) you'll have to define the individual functions as discussed with their documentation.
Note that the following function, whilst valid with Prelude style enums, is not valid with the Enum class in this module:
convertEnum :: (Enum a, Enum b) => a -> b convertEnum = toEnum . fromEnum
because now, Enum's can have different "enum types". That is. fromEnum is not always an Int, and toEnum does
not always take an Int.
Though it is debatable if the above function is sensible though anyway.
I have attempted to define instances of Enum for all types in GHCs included libraries, tell me
if I've missed any though.
Associated Types
This is the "enum" type. It just needs to be in the class Num.
type EnumIntegralT a Source #
EnumIntegralT (default - EnumNumT): this is a type that represents the number of "steps"
between two enums, based on a stepsize. Whilst EnumNumT must only be a Num, EnumIntegralT
needs to be Integral. If EnumNumT is already Integral it's almost certainly a good choice.
Methods
toEnum :: EnumNumT a -> a Source #
toEnum :: DefaultEnum a (EnumNumT a) => EnumNumT a -> a Source #
fromEnum :: a -> EnumNumT a Source #
fromEnum :: DefaultEnum a (EnumNumT a) => a -> EnumNumT a Source #
numStepsBetween :: a -> a -> EnumNumT a -> EnumIntegralT a Source #
numStepsBetween: This takes three arguments, firstly, two of type t for some Enum t ("start" and "end",
and also "step" of EnumNumT t, i.e. the "enum" type of t.
The result should be the length of the following list:
[start, (start + step) .. end]
and also of type EnumIntegralT t. It should not be less than 0.
For example:
numStepsBetween 'a' 'e' 2
should be 3.
numStepsBetween :: (e ~ EnumNumT a, e ~ EnumIntegralT a) => a -> a -> e -> e Source #
numStepsBetween: This takes three arguments, firstly, two of type t for some Enum t ("start" and "end",
and also "step" of EnumNumT t, i.e. the "enum" type of t.
The result should be the length of the following list:
[start, (start + step) .. end]
and also of type EnumIntegralT t. It should not be less than 0.
For example:
numStepsBetween 'a' 'e' 2
should be 3.
Instances
class DefaultEnum a b where Source #
A little trick for defining the two default cases mentioned in the documentation for Enum.
Minimal complete definition
Instances
| DefaultEnum Int Int Source # | |
| DefaultEnum a a Source # | |
| Enum a => DefaultEnum a Int Source # | |
type family Element a Source #
This specifies the type of elements of an instance of a class of either EnumFromTo or EnumFrom.
For example, the definition for lists is:
type instance Element [a] = a
class Enum (Element a) => EnumFromTo a where Source #
The EnumFromTo class defines versions of the Prelude Enum functions
enumFromTo and enumFromThenTo, as well as other functions which
may sometimes be more convienient.
But more importantly, it can produce any structure you define an instance for, not just lists.
The only function that needs to be defined is enumFromStepCount,
default definitions will look after the rest.
Note that this class does not deal with the infinite list generating functions,
you'll need to look at the EnumFrom class for that.
I've attempted to define appropriate instances for any structures in the core GHC distribution, currently lists, arrays and bytestrings.
Minimal complete definition
Methods
enumFromTo :: Element a -> Element a -> a Source #
Much like enumFromTo from Prelude
enumFromThenTo :: Element a -> Element a -> Element a -> a Source #
Much like enumFromThenTo from Prelude
enumFromCount :: Element a -> EnumIntegralT (Element a) -> a Source #
This is like enumFromTo, but instead of a final stopping number, a count is given.
enumFromThenCount :: Element a -> Element a -> EnumIntegralT (Element a) -> a Source #
This is like enumFromThenTo, but instead of a final stopping number, a count is given.
enumFromStepTo :: Element a -> EnumNumT (Element a) -> Element a -> a Source #
This is like enumFromThenTo, but instead of giving the second element directly, a step size is passed.
enumFromStepCount :: Element a -> EnumNumT (Element a) -> EnumIntegralT (Element a) -> a Source #
This is a combination of the conviencience changes in enumFromThenCount and enumFromStepTo.
Instead of having to explicitly state the second element, a "stepsize" is passed, Also, instead of stating the last element, a "count" is passed.
I find this tends to be more useful more often.
Instances
| EnumFromTo ByteString Source # | |
| EnumFromTo ShortByteString Source # | |
| EnumFromTo ByteString Source # | |
| Enum a => EnumFromTo [a] Source # | |
| (Enum e, Ix i, Num i) => EnumFromTo (Array i e) Source # | |
class Enum (Element a) => EnumFrom a where Source #
Much like the EnumFromTO class, but defines the "infinite" Prelude Enum functions, namely
enumFrom and enumFromThen, as well as enumFromStep.
The only function that needs to be defined is enumFromStep,
default definitions will look after the rest.
Methods
enumFrom :: Element a -> a Source #
Much like enumFrom from Prelude
enumFromThen :: Element a -> Element a -> a Source #
Much like enumFromThen from Prelude
enumFromStep :: Element a -> EnumNumT (Element a) -> a Source #
Like enumFromThen, but with an explicit step size, not just the second element given.
enumFromStep :: (Bounded (EnumIntegralT (Element a)), EnumFromTo a) => Element a -> EnumNumT (Element a) -> a Source #
Like enumFromThen, but with an explicit step size, not just the second element given.