generic-enum-0.1.0.0: An Enum class that fixes some deficiences with Prelude's Enum

Safe HaskellNone
LanguageHaskell2010

Data.Generic.Enum

Synopsis

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.

Methods

succ :: a -> a Source #

pred :: a -> a Source #

toEnum :: EnumNumT a -> a Source #

Just like Prelude's toEnum, but with EnumNumT t instead of Int

toEnum :: DefaultEnum a (EnumNumT a) => EnumNumT a -> a Source #

Just like Prelude's toEnum, but with EnumNumT t instead of Int

fromEnum :: a -> EnumNumT a Source #

Just like Prelude's fromEnum, but with EnumNumT t instead of Int

fromEnum :: DefaultEnum a (EnumNumT a) => a -> EnumNumT a Source #

Just like Prelude's fromEnum, but with EnumNumT t instead of Int

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

Enum Bool Source # 

Associated Types

type EnumNumT Bool :: *

type EnumIntegralT Bool :: *

Methods

succ :: Bool -> Bool Source #

pred :: Bool -> Bool Source #

toEnum :: EnumNumT Bool -> Bool Source #

fromEnum :: Bool -> EnumNumT Bool Source #

numStepsBetween :: Bool -> Bool -> EnumNumT Bool -> EnumIntegralT Bool Source #

Enum Char Source # 

Associated Types

type EnumNumT Char :: *

type EnumIntegralT Char :: *

Methods

succ :: Char -> Char Source #

pred :: Char -> Char Source #

toEnum :: EnumNumT Char -> Char Source #

fromEnum :: Char -> EnumNumT Char Source #

numStepsBetween :: Char -> Char -> EnumNumT Char -> EnumIntegralT Char Source #

Enum Int Source # 

Associated Types

type EnumNumT Int :: *

type EnumIntegralT Int :: *

Methods

succ :: Int -> Int Source #

pred :: Int -> Int Source #

toEnum :: EnumNumT Int -> Int Source #

fromEnum :: Int -> EnumNumT Int Source #

numStepsBetween :: Int -> Int -> EnumNumT Int -> EnumIntegralT Int Source #

Enum Int8 Source # 

Associated Types

type EnumNumT Int8 :: *

type EnumIntegralT Int8 :: *

Methods

succ :: Int8 -> Int8 Source #

pred :: Int8 -> Int8 Source #

toEnum :: EnumNumT Int8 -> Int8 Source #

fromEnum :: Int8 -> EnumNumT Int8 Source #

numStepsBetween :: Int8 -> Int8 -> EnumNumT Int8 -> EnumIntegralT Int8 Source #

Enum Int16 Source # 

Associated Types

type EnumNumT Int16 :: *

type EnumIntegralT Int16 :: *

Methods

succ :: Int16 -> Int16 Source #

pred :: Int16 -> Int16 Source #

toEnum :: EnumNumT Int16 -> Int16 Source #

fromEnum :: Int16 -> EnumNumT Int16 Source #

numStepsBetween :: Int16 -> Int16 -> EnumNumT Int16 -> EnumIntegralT Int16 Source #

Enum Int32 Source # 

Associated Types

type EnumNumT Int32 :: *

type EnumIntegralT Int32 :: *

Methods

succ :: Int32 -> Int32 Source #

pred :: Int32 -> Int32 Source #

toEnum :: EnumNumT Int32 -> Int32 Source #

fromEnum :: Int32 -> EnumNumT Int32 Source #

numStepsBetween :: Int32 -> Int32 -> EnumNumT Int32 -> EnumIntegralT Int32 Source #

Enum Int64 Source # 

Associated Types

type EnumNumT Int64 :: *

type EnumIntegralT Int64 :: *

Methods

succ :: Int64 -> Int64 Source #

pred :: Int64 -> Int64 Source #

toEnum :: EnumNumT Int64 -> Int64 Source #

fromEnum :: Int64 -> EnumNumT Int64 Source #

numStepsBetween :: Int64 -> Int64 -> EnumNumT Int64 -> EnumIntegralT Int64 Source #

Enum Integer Source # 

Associated Types

type EnumNumT Integer :: *

type EnumIntegralT Integer :: *

Methods

succ :: Integer -> Integer Source #

pred :: Integer -> Integer Source #

toEnum :: EnumNumT Integer -> Integer Source #

fromEnum :: Integer -> EnumNumT Integer Source #

numStepsBetween :: Integer -> Integer -> EnumNumT Integer -> EnumIntegralT Integer Source #

Enum Ordering Source # 

Associated Types

type EnumNumT Ordering :: *

type EnumIntegralT Ordering :: *

Enum Word8 Source # 

Associated Types

type EnumNumT Word8 :: *

type EnumIntegralT Word8 :: *

Methods

succ :: Word8 -> Word8 Source #

pred :: Word8 -> Word8 Source #

toEnum :: EnumNumT Word8 -> Word8 Source #

fromEnum :: Word8 -> EnumNumT Word8 Source #

numStepsBetween :: Word8 -> Word8 -> EnumNumT Word8 -> EnumIntegralT Word8 Source #

Enum Word16 Source # 

Associated Types

type EnumNumT Word16 :: *

type EnumIntegralT Word16 :: *

Methods

succ :: Word16 -> Word16 Source #

pred :: Word16 -> Word16 Source #

toEnum :: EnumNumT Word16 -> Word16 Source #

fromEnum :: Word16 -> EnumNumT Word16 Source #

numStepsBetween :: Word16 -> Word16 -> EnumNumT Word16 -> EnumIntegralT Word16 Source #

Enum Word32 Source # 

Associated Types

type EnumNumT Word32 :: *

type EnumIntegralT Word32 :: *

Methods

succ :: Word32 -> Word32 Source #

pred :: Word32 -> Word32 Source #

toEnum :: EnumNumT Word32 -> Word32 Source #

fromEnum :: Word32 -> EnumNumT Word32 Source #

numStepsBetween :: Word32 -> Word32 -> EnumNumT Word32 -> EnumIntegralT Word32 Source #

Enum Word64 Source # 

Associated Types

type EnumNumT Word64 :: *

type EnumIntegralT Word64 :: *

Methods

succ :: Word64 -> Word64 Source #

pred :: Word64 -> Word64 Source #

toEnum :: EnumNumT Word64 -> Word64 Source #

fromEnum :: Word64 -> EnumNumT Word64 Source #

numStepsBetween :: Word64 -> Word64 -> EnumNumT Word64 -> EnumIntegralT Word64 Source #

Enum () Source # 

Associated Types

type EnumNumT () :: *

type EnumIntegralT () :: *

Methods

succ :: () -> () Source #

pred :: () -> () Source #

toEnum :: EnumNumT () -> () Source #

fromEnum :: () -> EnumNumT () Source #

numStepsBetween :: () -> () -> EnumNumT () -> EnumIntegralT () Source #

Enum GiveGCStats Source # 

Associated Types

type EnumNumT GiveGCStats :: *

type EnumIntegralT GiveGCStats :: *

Enum DoCostCentres Source # 
Enum DoHeapProfile Source # 
Enum DoTrace Source # 

Associated Types

type EnumNumT DoTrace :: *

type EnumIntegralT DoTrace :: *

Methods

succ :: DoTrace -> DoTrace Source #

pred :: DoTrace -> DoTrace Source #

toEnum :: EnumNumT DoTrace -> DoTrace Source #

fromEnum :: DoTrace -> EnumNumT DoTrace Source #

numStepsBetween :: DoTrace -> DoTrace -> EnumNumT DoTrace -> EnumIntegralT DoTrace Source #

Enum Natural Source # 

Associated Types

type EnumNumT Natural :: *

type EnumIntegralT Natural :: *

Methods

succ :: Natural -> Natural Source #

pred :: Natural -> Natural Source #

toEnum :: EnumNumT Natural -> Natural Source #

fromEnum :: Natural -> EnumNumT Natural Source #

numStepsBetween :: Natural -> Natural -> EnumNumT Natural -> EnumIntegralT Natural Source #

Enum CDev Source # 

Associated Types

type EnumNumT CDev :: *

type EnumIntegralT CDev :: *

Methods

succ :: CDev -> CDev Source #

pred :: CDev -> CDev Source #

toEnum :: EnumNumT CDev -> CDev Source #

fromEnum :: CDev -> EnumNumT CDev Source #

numStepsBetween :: CDev -> CDev -> EnumNumT CDev -> EnumIntegralT CDev Source #

Enum CIno Source # 

Associated Types

type EnumNumT CIno :: *

type EnumIntegralT CIno :: *

Methods

succ :: CIno -> CIno Source #

pred :: CIno -> CIno Source #

toEnum :: EnumNumT CIno -> CIno Source #

fromEnum :: CIno -> EnumNumT CIno Source #

numStepsBetween :: CIno -> CIno -> EnumNumT CIno -> EnumIntegralT CIno Source #

Enum CMode Source # 

Associated Types

type EnumNumT CMode :: *

type EnumIntegralT CMode :: *

Methods

succ :: CMode -> CMode Source #

pred :: CMode -> CMode Source #

toEnum :: EnumNumT CMode -> CMode Source #

fromEnum :: CMode -> EnumNumT CMode Source #

numStepsBetween :: CMode -> CMode -> EnumNumT CMode -> EnumIntegralT CMode Source #

Enum COff Source # 

Associated Types

type EnumNumT COff :: *

type EnumIntegralT COff :: *

Methods

succ :: COff -> COff Source #

pred :: COff -> COff Source #

toEnum :: EnumNumT COff -> COff Source #

fromEnum :: COff -> EnumNumT COff Source #

numStepsBetween :: COff -> COff -> EnumNumT COff -> EnumIntegralT COff Source #

Enum CPid Source # 

Associated Types

type EnumNumT CPid :: *

type EnumIntegralT CPid :: *

Methods

succ :: CPid -> CPid Source #

pred :: CPid -> CPid Source #

toEnum :: EnumNumT CPid -> CPid Source #

fromEnum :: CPid -> EnumNumT CPid Source #

numStepsBetween :: CPid -> CPid -> EnumNumT CPid -> EnumIntegralT CPid Source #

Enum CSsize Source # 

Associated Types

type EnumNumT CSsize :: *

type EnumIntegralT CSsize :: *

Methods

succ :: CSsize -> CSsize Source #

pred :: CSsize -> CSsize Source #

toEnum :: EnumNumT CSsize -> CSsize Source #

fromEnum :: CSsize -> EnumNumT CSsize Source #

numStepsBetween :: CSsize -> CSsize -> EnumNumT CSsize -> EnumIntegralT CSsize Source #

Enum CGid Source # 

Associated Types

type EnumNumT CGid :: *

type EnumIntegralT CGid :: *

Methods

succ :: CGid -> CGid Source #

pred :: CGid -> CGid Source #

toEnum :: EnumNumT CGid -> CGid Source #

fromEnum :: CGid -> EnumNumT CGid Source #

numStepsBetween :: CGid -> CGid -> EnumNumT CGid -> EnumIntegralT CGid Source #

Enum CNlink Source # 

Associated Types

type EnumNumT CNlink :: *

type EnumIntegralT CNlink :: *

Methods

succ :: CNlink -> CNlink Source #

pred :: CNlink -> CNlink Source #

toEnum :: EnumNumT CNlink -> CNlink Source #

fromEnum :: CNlink -> EnumNumT CNlink Source #

numStepsBetween :: CNlink -> CNlink -> EnumNumT CNlink -> EnumIntegralT CNlink Source #

Enum CUid Source # 

Associated Types

type EnumNumT CUid :: *

type EnumIntegralT CUid :: *

Methods

succ :: CUid -> CUid Source #

pred :: CUid -> CUid Source #

toEnum :: EnumNumT CUid -> CUid Source #

fromEnum :: CUid -> EnumNumT CUid Source #

numStepsBetween :: CUid -> CUid -> EnumNumT CUid -> EnumIntegralT CUid Source #

Enum CCc Source # 

Associated Types

type EnumNumT CCc :: *

type EnumIntegralT CCc :: *

Methods

succ :: CCc -> CCc Source #

pred :: CCc -> CCc Source #

toEnum :: EnumNumT CCc -> CCc Source #

fromEnum :: CCc -> EnumNumT CCc Source #

numStepsBetween :: CCc -> CCc -> EnumNumT CCc -> EnumIntegralT CCc Source #

Enum CSpeed Source # 

Associated Types

type EnumNumT CSpeed :: *

type EnumIntegralT CSpeed :: *

Methods

succ :: CSpeed -> CSpeed Source #

pred :: CSpeed -> CSpeed Source #

toEnum :: EnumNumT CSpeed -> CSpeed Source #

fromEnum :: CSpeed -> EnumNumT CSpeed Source #

numStepsBetween :: CSpeed -> CSpeed -> EnumNumT CSpeed -> EnumIntegralT CSpeed Source #

Enum CTcflag Source # 

Associated Types

type EnumNumT CTcflag :: *

type EnumIntegralT CTcflag :: *

Methods

succ :: CTcflag -> CTcflag Source #

pred :: CTcflag -> CTcflag Source #

toEnum :: EnumNumT CTcflag -> CTcflag Source #

fromEnum :: CTcflag -> EnumNumT CTcflag Source #

numStepsBetween :: CTcflag -> CTcflag -> EnumNumT CTcflag -> EnumIntegralT CTcflag Source #

Enum CRLim Source # 

Associated Types

type EnumNumT CRLim :: *

type EnumIntegralT CRLim :: *

Methods

succ :: CRLim -> CRLim Source #

pred :: CRLim -> CRLim Source #

toEnum :: EnumNumT CRLim -> CRLim Source #

fromEnum :: CRLim -> EnumNumT CRLim Source #

numStepsBetween :: CRLim -> CRLim -> EnumNumT CRLim -> EnumIntegralT CRLim Source #

Enum Fd Source # 

Associated Types

type EnumNumT Fd :: *

type EnumIntegralT Fd :: *

Methods

succ :: Fd -> Fd Source #

pred :: Fd -> Fd Source #

toEnum :: EnumNumT Fd -> Fd Source #

fromEnum :: Fd -> EnumNumT Fd Source #

numStepsBetween :: Fd -> Fd -> EnumNumT Fd -> EnumIntegralT Fd Source #

Enum WordPtr Source # 

Associated Types

type EnumNumT WordPtr :: *

type EnumIntegralT WordPtr :: *

Methods

succ :: WordPtr -> WordPtr Source #

pred :: WordPtr -> WordPtr Source #

toEnum :: EnumNumT WordPtr -> WordPtr Source #

fromEnum :: WordPtr -> EnumNumT WordPtr Source #

numStepsBetween :: WordPtr -> WordPtr -> EnumNumT WordPtr -> EnumIntegralT WordPtr Source #

Enum IntPtr Source # 

Associated Types

type EnumNumT IntPtr :: *

type EnumIntegralT IntPtr :: *

Methods

succ :: IntPtr -> IntPtr Source #

pred :: IntPtr -> IntPtr Source #

toEnum :: EnumNumT IntPtr -> IntPtr Source #

fromEnum :: IntPtr -> EnumNumT IntPtr Source #

numStepsBetween :: IntPtr -> IntPtr -> EnumNumT IntPtr -> EnumIntegralT IntPtr Source #

Enum CChar Source # 

Associated Types

type EnumNumT CChar :: *

type EnumIntegralT CChar :: *

Methods

succ :: CChar -> CChar Source #

pred :: CChar -> CChar Source #

toEnum :: EnumNumT CChar -> CChar Source #

fromEnum :: CChar -> EnumNumT CChar Source #

numStepsBetween :: CChar -> CChar -> EnumNumT CChar -> EnumIntegralT CChar Source #

Enum CSChar Source # 

Associated Types

type EnumNumT CSChar :: *

type EnumIntegralT CSChar :: *

Methods

succ :: CSChar -> CSChar Source #

pred :: CSChar -> CSChar Source #

toEnum :: EnumNumT CSChar -> CSChar Source #

fromEnum :: CSChar -> EnumNumT CSChar Source #

numStepsBetween :: CSChar -> CSChar -> EnumNumT CSChar -> EnumIntegralT CSChar Source #

Enum CUChar Source # 

Associated Types

type EnumNumT CUChar :: *

type EnumIntegralT CUChar :: *

Methods

succ :: CUChar -> CUChar Source #

pred :: CUChar -> CUChar Source #

toEnum :: EnumNumT CUChar -> CUChar Source #

fromEnum :: CUChar -> EnumNumT CUChar Source #

numStepsBetween :: CUChar -> CUChar -> EnumNumT CUChar -> EnumIntegralT CUChar Source #

Enum CShort Source # 

Associated Types

type EnumNumT CShort :: *

type EnumIntegralT CShort :: *

Methods

succ :: CShort -> CShort Source #

pred :: CShort -> CShort Source #

toEnum :: EnumNumT CShort -> CShort Source #

fromEnum :: CShort -> EnumNumT CShort Source #

numStepsBetween :: CShort -> CShort -> EnumNumT CShort -> EnumIntegralT CShort Source #

Enum CUShort Source # 

Associated Types

type EnumNumT CUShort :: *

type EnumIntegralT CUShort :: *

Methods

succ :: CUShort -> CUShort Source #

pred :: CUShort -> CUShort Source #

toEnum :: EnumNumT CUShort -> CUShort Source #

fromEnum :: CUShort -> EnumNumT CUShort Source #

numStepsBetween :: CUShort -> CUShort -> EnumNumT CUShort -> EnumIntegralT CUShort Source #

Enum CInt Source # 

Associated Types

type EnumNumT CInt :: *

type EnumIntegralT CInt :: *

Methods

succ :: CInt -> CInt Source #

pred :: CInt -> CInt Source #

toEnum :: EnumNumT CInt -> CInt Source #

fromEnum :: CInt -> EnumNumT CInt Source #

numStepsBetween :: CInt -> CInt -> EnumNumT CInt -> EnumIntegralT CInt Source #

Enum CUInt Source # 

Associated Types

type EnumNumT CUInt :: *

type EnumIntegralT CUInt :: *

Methods

succ :: CUInt -> CUInt Source #

pred :: CUInt -> CUInt Source #

toEnum :: EnumNumT CUInt -> CUInt Source #

fromEnum :: CUInt -> EnumNumT CUInt Source #

numStepsBetween :: CUInt -> CUInt -> EnumNumT CUInt -> EnumIntegralT CUInt Source #

Enum CLong Source # 

Associated Types

type EnumNumT CLong :: *

type EnumIntegralT CLong :: *

Methods

succ :: CLong -> CLong Source #

pred :: CLong -> CLong Source #

toEnum :: EnumNumT CLong -> CLong Source #

fromEnum :: CLong -> EnumNumT CLong Source #

numStepsBetween :: CLong -> CLong -> EnumNumT CLong -> EnumIntegralT CLong Source #

Enum CULong Source # 

Associated Types

type EnumNumT CULong :: *

type EnumIntegralT CULong :: *

Methods

succ :: CULong -> CULong Source #

pred :: CULong -> CULong Source #

toEnum :: EnumNumT CULong -> CULong Source #

fromEnum :: CULong -> EnumNumT CULong Source #

numStepsBetween :: CULong -> CULong -> EnumNumT CULong -> EnumIntegralT CULong Source #

Enum CLLong Source # 

Associated Types

type EnumNumT CLLong :: *

type EnumIntegralT CLLong :: *

Methods

succ :: CLLong -> CLLong Source #

pred :: CLLong -> CLLong Source #

toEnum :: EnumNumT CLLong -> CLLong Source #

fromEnum :: CLLong -> EnumNumT CLLong Source #

numStepsBetween :: CLLong -> CLLong -> EnumNumT CLLong -> EnumIntegralT CLLong Source #

Enum CULLong Source # 

Associated Types

type EnumNumT CULLong :: *

type EnumIntegralT CULLong :: *

Methods

succ :: CULLong -> CULLong Source #

pred :: CULLong -> CULLong Source #

toEnum :: EnumNumT CULLong -> CULLong Source #

fromEnum :: CULLong -> EnumNumT CULLong Source #

numStepsBetween :: CULLong -> CULLong -> EnumNumT CULLong -> EnumIntegralT CULLong Source #

Enum CFloat Source # 

Associated Types

type EnumNumT CFloat :: *

type EnumIntegralT CFloat :: *

Methods

succ :: CFloat -> CFloat Source #

pred :: CFloat -> CFloat Source #

toEnum :: EnumNumT CFloat -> CFloat Source #

fromEnum :: CFloat -> EnumNumT CFloat Source #

numStepsBetween :: CFloat -> CFloat -> EnumNumT CFloat -> EnumIntegralT CFloat Source #

Enum CDouble Source # 

Associated Types

type EnumNumT CDouble :: *

type EnumIntegralT CDouble :: *

Methods

succ :: CDouble -> CDouble Source #

pred :: CDouble -> CDouble Source #

toEnum :: EnumNumT CDouble -> CDouble Source #

fromEnum :: CDouble -> EnumNumT CDouble Source #

numStepsBetween :: CDouble -> CDouble -> EnumNumT CDouble -> EnumIntegralT CDouble Source #

Enum CPtrdiff Source # 

Associated Types

type EnumNumT CPtrdiff :: *

type EnumIntegralT CPtrdiff :: *

Enum CSize Source # 

Associated Types

type EnumNumT CSize :: *

type EnumIntegralT CSize :: *

Methods

succ :: CSize -> CSize Source #

pred :: CSize -> CSize Source #

toEnum :: EnumNumT CSize -> CSize Source #

fromEnum :: CSize -> EnumNumT CSize Source #

numStepsBetween :: CSize -> CSize -> EnumNumT CSize -> EnumIntegralT CSize Source #

Enum CWchar Source # 

Associated Types

type EnumNumT CWchar :: *

type EnumIntegralT CWchar :: *

Methods

succ :: CWchar -> CWchar Source #

pred :: CWchar -> CWchar Source #

toEnum :: EnumNumT CWchar -> CWchar Source #

fromEnum :: CWchar -> EnumNumT CWchar Source #

numStepsBetween :: CWchar -> CWchar -> EnumNumT CWchar -> EnumIntegralT CWchar Source #

Enum CSigAtomic Source # 

Associated Types

type EnumNumT CSigAtomic :: *

type EnumIntegralT CSigAtomic :: *

Enum CClock Source # 

Associated Types

type EnumNumT CClock :: *

type EnumIntegralT CClock :: *

Methods

succ :: CClock -> CClock Source #

pred :: CClock -> CClock Source #

toEnum :: EnumNumT CClock -> CClock Source #

fromEnum :: CClock -> EnumNumT CClock Source #

numStepsBetween :: CClock -> CClock -> EnumNumT CClock -> EnumIntegralT CClock Source #

Enum CTime Source # 

Associated Types

type EnumNumT CTime :: *

type EnumIntegralT CTime :: *

Methods

succ :: CTime -> CTime Source #

pred :: CTime -> CTime Source #

toEnum :: EnumNumT CTime -> CTime Source #

fromEnum :: CTime -> EnumNumT CTime Source #

numStepsBetween :: CTime -> CTime -> EnumNumT CTime -> EnumIntegralT CTime Source #

Enum CUSeconds Source # 

Associated Types

type EnumNumT CUSeconds :: *

type EnumIntegralT CUSeconds :: *

Enum CSUSeconds Source # 

Associated Types

type EnumNumT CSUSeconds :: *

type EnumIntegralT CSUSeconds :: *

Enum CIntPtr Source # 

Associated Types

type EnumNumT CIntPtr :: *

type EnumIntegralT CIntPtr :: *

Methods

succ :: CIntPtr -> CIntPtr Source #

pred :: CIntPtr -> CIntPtr Source #

toEnum :: EnumNumT CIntPtr -> CIntPtr Source #

fromEnum :: CIntPtr -> EnumNumT CIntPtr Source #

numStepsBetween :: CIntPtr -> CIntPtr -> EnumNumT CIntPtr -> EnumIntegralT CIntPtr Source #

Enum CUIntPtr Source # 

Associated Types

type EnumNumT CUIntPtr :: *

type EnumIntegralT CUIntPtr :: *

Enum CIntMax Source # 

Associated Types

type EnumNumT CIntMax :: *

type EnumIntegralT CIntMax :: *

Methods

succ :: CIntMax -> CIntMax Source #

pred :: CIntMax -> CIntMax Source #

toEnum :: EnumNumT CIntMax -> CIntMax Source #

fromEnum :: CIntMax -> EnumNumT CIntMax Source #

numStepsBetween :: CIntMax -> CIntMax -> EnumNumT CIntMax -> EnumIntegralT CIntMax Source #

Enum CUIntMax Source # 

Associated Types

type EnumNumT CUIntMax :: *

type EnumIntegralT CUIntMax :: *

Enum SeekMode Source # 

Associated Types

type EnumNumT SeekMode :: *

type EnumIntegralT SeekMode :: *

Enum Associativity Source # 
Enum SourceUnpackedness Source # 
Enum SourceStrictness Source # 
Enum DecidedStrictness Source # 
Enum IOMode Source # 

Associated Types

type EnumNumT IOMode :: *

type EnumIntegralT IOMode :: *

Methods

succ :: IOMode -> IOMode Source #

pred :: IOMode -> IOMode Source #

toEnum :: EnumNumT IOMode -> IOMode Source #

fromEnum :: IOMode -> EnumNumT IOMode Source #

numStepsBetween :: IOMode -> IOMode -> EnumNumT IOMode -> EnumIntegralT IOMode Source #

Enum GeneralCategory Source # 
Integral a => Enum (Ratio a) Source # 

Associated Types

type EnumNumT (Ratio a) :: *

type EnumIntegralT (Ratio a) :: *

Methods

succ :: Ratio a -> Ratio a Source #

pred :: Ratio a -> Ratio a Source #

toEnum :: EnumNumT (Ratio a) -> Ratio a Source #

fromEnum :: Ratio a -> EnumNumT (Ratio a) Source #

numStepsBetween :: Ratio a -> Ratio a -> EnumNumT (Ratio a) -> EnumIntegralT (Ratio a) Source #

Enum a => Enum (Identity a) Source # 

Associated Types

type EnumNumT (Identity a) :: *

type EnumIntegralT (Identity a) :: *

Methods

succ :: Identity a -> Identity a Source #

pred :: Identity a -> Identity a Source #

toEnum :: EnumNumT (Identity a) -> Identity a Source #

fromEnum :: Identity a -> EnumNumT (Identity a) Source #

numStepsBetween :: Identity a -> Identity a -> EnumNumT (Identity a) -> EnumIntegralT (Identity a) Source #

Enum a => Enum (Min a) Source # 

Associated Types

type EnumNumT (Min a) :: *

type EnumIntegralT (Min a) :: *

Methods

succ :: Min a -> Min a Source #

pred :: Min a -> Min a Source #

toEnum :: EnumNumT (Min a) -> Min a Source #

fromEnum :: Min a -> EnumNumT (Min a) Source #

numStepsBetween :: Min a -> Min a -> EnumNumT (Min a) -> EnumIntegralT (Min a) Source #

Enum a => Enum (Max a) Source # 

Associated Types

type EnumNumT (Max a) :: *

type EnumIntegralT (Max a) :: *

Methods

succ :: Max a -> Max a Source #

pred :: Max a -> Max a Source #

toEnum :: EnumNumT (Max a) -> Max a Source #

fromEnum :: Max a -> EnumNumT (Max a) Source #

numStepsBetween :: Max a -> Max a -> EnumNumT (Max a) -> EnumIntegralT (Max a) Source #

Enum a => Enum (First a) Source # 

Associated Types

type EnumNumT (First a) :: *

type EnumIntegralT (First a) :: *

Methods

succ :: First a -> First a Source #

pred :: First a -> First a Source #

toEnum :: EnumNumT (First a) -> First a Source #

fromEnum :: First a -> EnumNumT (First a) Source #

numStepsBetween :: First a -> First a -> EnumNumT (First a) -> EnumIntegralT (First a) Source #

Enum a => Enum (Last a) Source # 

Associated Types

type EnumNumT (Last a) :: *

type EnumIntegralT (Last a) :: *

Methods

succ :: Last a -> Last a Source #

pred :: Last a -> Last a Source #

toEnum :: EnumNumT (Last a) -> Last a Source #

fromEnum :: Last a -> EnumNumT (Last a) Source #

numStepsBetween :: Last a -> Last a -> EnumNumT (Last a) -> EnumIntegralT (Last a) Source #

Enum a => Enum (WrappedMonoid a) Source # 

Associated Types

type EnumNumT (WrappedMonoid a) :: *

type EnumIntegralT (WrappedMonoid a) :: *

HasResolution a => Enum (Fixed a) Source # 

Associated Types

type EnumNumT (Fixed a) :: *

type EnumIntegralT (Fixed a) :: *

Methods

succ :: Fixed a -> Fixed a Source #

pred :: Fixed a -> Fixed a Source #

toEnum :: EnumNumT (Fixed a) -> Fixed a Source #

fromEnum :: Fixed a -> EnumNumT (Fixed a) Source #

numStepsBetween :: Fixed a -> Fixed a -> EnumNumT (Fixed a) -> EnumIntegralT (Fixed a) Source #

Enum (Proxy * s) Source # 

Associated Types

type EnumNumT (Proxy * s) :: *

type EnumIntegralT (Proxy * s) :: *

Methods

succ :: Proxy * s -> Proxy * s Source #

pred :: Proxy * s -> Proxy * s Source #

toEnum :: EnumNumT (Proxy * s) -> Proxy * s Source #

fromEnum :: Proxy * s -> EnumNumT (Proxy * s) Source #

numStepsBetween :: Proxy * s -> Proxy * s -> EnumNumT (Proxy * s) -> EnumIntegralT (Proxy * s) Source #

Enum a => Enum (Const * a b) Source # 

Associated Types

type EnumNumT (Const * a b) :: *

type EnumIntegralT (Const * a b) :: *

Methods

succ :: Const * a b -> Const * a b Source #

pred :: Const * a b -> Const * a b Source #

toEnum :: EnumNumT (Const * a b) -> Const * a b Source #

fromEnum :: Const * a b -> EnumNumT (Const * a b) Source #

numStepsBetween :: Const * a b -> Const * a b -> EnumNumT (Const * a b) -> EnumIntegralT (Const * a b) Source #

Enum (f a) => Enum (Alt * f a) Source # 

Associated Types

type EnumNumT (Alt * f a) :: *

type EnumIntegralT (Alt * f a) :: *

Methods

succ :: Alt * f a -> Alt * f a Source #

pred :: Alt * f a -> Alt * f a Source #

toEnum :: EnumNumT (Alt * f a) -> Alt * f a Source #

fromEnum :: Alt * f a -> EnumNumT (Alt * f a) Source #

numStepsBetween :: Alt * f a -> Alt * f a -> EnumNumT (Alt * f a) -> EnumIntegralT (Alt * f a) Source #

Coercible * a b => Enum (Coercion * a b) Source # 

Associated Types

type EnumNumT (Coercion * a b) :: *

type EnumIntegralT (Coercion * a b) :: *

Methods

succ :: Coercion * a b -> Coercion * a b Source #

pred :: Coercion * a b -> Coercion * a b Source #

toEnum :: EnumNumT (Coercion * a b) -> Coercion * a b Source #

fromEnum :: Coercion * a b -> EnumNumT (Coercion * a b) Source #

numStepsBetween :: Coercion * a b -> Coercion * a b -> EnumNumT (Coercion * a b) -> EnumIntegralT (Coercion * a b) Source #

(~) * a b => Enum ((:~:) * a b) Source # 

Associated Types

type EnumNumT ((:~:) * a b) :: *

type EnumIntegralT ((:~:) * a b) :: *

Methods

succ :: (* :~: a) b -> (* :~: a) b Source #

pred :: (* :~: a) b -> (* :~: a) b Source #

toEnum :: EnumNumT ((* :~: a) b) -> (* :~: a) b Source #

fromEnum :: (* :~: a) b -> EnumNumT ((* :~: a) b) Source #

numStepsBetween :: (* :~: a) b -> (* :~: a) b -> EnumNumT ((* :~: a) b) -> EnumIntegralT ((* :~: a) b) Source #

class DefaultEnum a b where Source #

A little trick for defining the two default cases mentioned in the documentation for Enum.

Minimal complete definition

defaultFromEnum, defaultToEnum

Methods

defaultFromEnum :: a -> b Source #

defaultToEnum :: b -> a 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

enumFromStepCount

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 # 

Methods

enumFromTo :: Element [a] -> Element [a] -> [a] Source #

enumFromThenTo :: Element [a] -> Element [a] -> Element [a] -> [a] Source #

enumFromCount :: Element [a] -> EnumIntegralT (Element [a]) -> [a] Source #

enumFromThenCount :: Element [a] -> Element [a] -> EnumIntegralT (Element [a]) -> [a] Source #

enumFromStepTo :: Element [a] -> EnumNumT (Element [a]) -> Element [a] -> [a] Source #

enumFromStepCount :: Element [a] -> EnumNumT (Element [a]) -> EnumIntegralT (Element [a]) -> [a] Source #

(Enum e, Ix i, Num i) => EnumFromTo (Array i e) Source # 

Methods

enumFromTo :: Element (Array i e) -> Element (Array i e) -> Array i e Source #

enumFromThenTo :: Element (Array i e) -> Element (Array i e) -> Element (Array i e) -> Array i e Source #

enumFromCount :: Element (Array i e) -> EnumIntegralT (Element (Array i e)) -> Array i e Source #

enumFromThenCount :: Element (Array i e) -> Element (Array i e) -> EnumIntegralT (Element (Array i e)) -> Array i e Source #

enumFromStepTo :: Element (Array i e) -> EnumNumT (Element (Array i e)) -> Element (Array i e) -> Array i e Source #

enumFromStepCount :: Element (Array i e) -> EnumNumT (Element (Array i e)) -> EnumIntegralT (Element (Array i e)) -> 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.

Instances

Enum a => EnumFrom [a] Source # 

Methods

enumFrom :: Element [a] -> [a] Source #

enumFromThen :: Element [a] -> Element [a] -> [a] Source #

enumFromStep :: Element [a] -> EnumNumT (Element [a]) -> [a] Source #