Copyright | (c) The University of Glasgow 1992-2002 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | cvs-ghc@haskell.org |
Stability | internal |
Portability | non-portable (GHC extensions) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
GHC.Enum
Synopsis
- class Bounded a where
- class Enum a where
- succ :: a -> a
- pred :: a -> a
- toEnum :: Int -> a
- fromEnum :: a -> Int
- enumFrom :: a -> [a]
- enumFromThen :: a -> a -> [a]
- enumFromTo :: a -> a -> [a]
- enumFromThenTo :: a -> a -> a -> [a]
- boundedEnumFrom :: (Enum a, Bounded a) => a -> [a]
- boundedEnumFromThen :: (Enum a, Bounded a) => a -> a -> [a]
- toEnumError :: Show a => String -> Int -> (a, a) -> b
- fromEnumError :: Show a => String -> a -> b
- succError :: String -> a
- predError :: String -> a
Documentation
class Bounded a where Source #
The Bounded
class is used to name the upper and lower limits of a
type. Ord
is not a superclass of Bounded
since types that are not
totally ordered may also have upper and lower bounds.
The Bounded
class may be derived for any enumeration type;
minBound
is the first constructor listed in the data
declaration
and maxBound
is the last.
Bounded
may also be derived for single-constructor datatypes whose
constituent types are in Bounded
.
Instances
Instances details
Instance details
Defined in GHC.Unicode
Instance details
Defined in Foreign.C.Types
Instance details
Defined in GHC.Generics
Instance details
Defined in GHC.Generics
Instance details
Defined in GHC.Generics
Instance details
Defined in GHC.Generics
Instance details
Defined in Data.Semigroup
Since: 2.1
Since: 2.1
Since: 2.1
Since: 2.1
Since: 2.1
Since: 2.1
Since: 2.1
Since: 2.1
Since: 2.1
Since: 2.1
Class Enum
defines operations on sequentially ordered types.
The enumFrom
... methods are used in Haskell's translation of
arithmetic sequences.
Instances of Enum
may be derived for any enumeration type (types
whose constructors have no fields). The nullary constructors are
assumed to be numbered left-to-right by fromEnum
from 0
through n-1
.
See Chapter 10 of the Haskell Report for more details.
For any type that is an instance of class Bounded
as well as Enum
,
the following should hold:
- The calls
andsucc
maxBound
should result in a runtime error.pred
minBound
fromEnum
andtoEnum
should give a runtime error if the result value is not representable in the result type. For example,
is an error.toEnum
7 ::Bool
enumFrom
andenumFromThen
should be defined with an implicit bound, thus:
enumFrom x = enumFromTo x maxBound enumFromThen x y = enumFromThenTo x y bound where bound | fromEnum y >= fromEnum x = maxBound | otherwise = minBound
Methods
the successor of a value. For numeric types, succ
adds 1.
the predecessor of a value. For numeric types, pred
subtracts 1.
Convert from an Int
.
Convert to an Int
.
It is implementation-dependent what fromEnum
returns when
applied to a value that is too large to fit in an Int
.
Used in Haskell's translation of [n..]
with [n..] = enumFrom n
,
a possible implementation being enumFrom n = n : enumFrom (succ n)
.
For example:
enumFrom 4 :: [Integer] = [4,5,6,7,...]
enumFrom 6 :: [Int] = [6,7,8,9,...,maxBound :: Int]
enumFromThen :: a -> a -> [a] Source #
Used in Haskell's translation of [n,n'..]
with [n,n'..] = enumFromThen n n'
, a possible implementation being
enumFromThen n n' = n : n' : worker (f x) (f x n')
,
worker s v = v : worker s (s v)
, x = fromEnum n' - fromEnum n
and
f n y
| n > 0 = f (n - 1) (succ y)
| n < 0 = f (n + 1) (pred y)
| otherwise = y
For example:
enumFromThen 4 6 :: [Integer] = [4,6,8,10...]
enumFromThen 6 2 :: [Int] = [6,2,-2,-6,...,minBound :: Int]
enumFromTo :: a -> a -> [a] Source #
Used in Haskell's translation of [n..m]
with
[n..m] = enumFromTo n m
, a possible implementation being
enumFromTo n m
| n <= m = n : enumFromTo (succ n) m
| otherwise = []
.
For example:
enumFromTo 6 10 :: [Int] = [6,7,8,9,10]
enumFromTo 42 1 :: [Integer] = []
enumFromThenTo :: a -> a -> a -> [a] Source #
Used in Haskell's translation of [n,n'..m]
with
[n,n'..m] = enumFromThenTo n n' m
, a possible implementation
being enumFromThenTo n n' m = worker (f x) (c x) n m
,
x = fromEnum n' - fromEnum n
, c x = bool (>=) ((x 0)
f n y
| n > 0 = f (n - 1) (succ y)
| n < 0 = f (n + 1) (pred y)
| otherwise = y
and
worker s c v m
| c v m = v : worker s c (s v) m
| otherwise = []
For example:
enumFromThenTo 4 2 -6 :: [Integer] = [4,2,0,-2,-4,-6]
enumFromThenTo 6 8 2 :: [Int] = []
Instances
Instances details
Instance details
Defined in GHC.Float
Methods
succ :: Double -> Double Source #
pred :: Double -> Double Source #
toEnum :: Int -> Double Source #
fromEnum :: Double -> Int Source #
enumFrom :: Double -> [Double] Source #
enumFromThen :: Double -> Double -> [Double] Source #
enumFromTo :: Double -> Double -> [Double] Source #
enumFromThenTo :: Double -> Double -> Double -> [Double] Source #
Instance details
Defined in GHC.Float
Methods
succ :: Float -> Float Source #
pred :: Float -> Float Source #
toEnum :: Int -> Float Source #
fromEnum :: Float -> Int Source #
enumFrom :: Float -> [Float] Source #
enumFromThen :: Float -> Float -> [Float] Source #
enumFromTo :: Float -> Float -> [Float] Source #
enumFromThenTo :: Float -> Float -> Float -> [Float] Source #
Instance details
Defined in GHC.Int
Methods
succ :: Int16 -> Int16 Source #
pred :: Int16 -> Int16 Source #
toEnum :: Int -> Int16 Source #
fromEnum :: Int16 -> Int Source #
enumFrom :: Int16 -> [Int16] Source #
enumFromThen :: Int16 -> Int16 -> [Int16] Source #
enumFromTo :: Int16 -> Int16 -> [Int16] Source #
enumFromThenTo :: Int16 -> Int16 -> Int16 -> [Int16] Source #
Instance details
Defined in GHC.Int
Methods
succ :: Int32 -> Int32 Source #
pred :: Int32 -> Int32 Source #
toEnum :: Int -> Int32 Source #
fromEnum :: Int32 -> Int Source #
enumFrom :: Int32 -> [Int32] Source #
enumFromThen :: Int32 -> Int32 -> [Int32] Source #
enumFromTo :: Int32 -> Int32 -> [Int32] Source #
enumFromThenTo :: Int32 -> Int32 -> Int32 -> [Int32] Source #
Instance details
Defined in GHC.Int
Methods
succ :: Int64 -> Int64 Source #
pred :: Int64 -> Int64 Source #
toEnum :: Int -> Int64 Source #
fromEnum :: Int64 -> Int Source #
enumFrom :: Int64 -> [Int64] Source #
enumFromThen :: Int64 -> Int64 -> [Int64] Source #
enumFromTo :: Int64 -> Int64 -> [Int64] Source #
enumFromThenTo :: Int64 -> Int64 -> Int64 -> [Int64] Source #
Instance details
Defined in GHC.Enum
Methods
succ :: Integer -> Integer Source #
pred :: Integer -> Integer Source #
toEnum :: Int -> Integer Source #
fromEnum :: Integer -> Int Source #
enumFrom :: Integer -> [Integer] Source #
enumFromThen :: Integer -> Integer -> [Integer] Source #
enumFromTo :: Integer -> Integer -> [Integer] Source #
enumFromThenTo :: Integer -> Integer -> Integer -> [Integer] Source #
Instance details
Defined in GHC.Enum
Methods
succ :: Natural -> Natural Source #
pred :: Natural -> Natural Source #
toEnum :: Int -> Natural Source #
fromEnum :: Natural -> Int Source #
enumFrom :: Natural -> [Natural] Source #
enumFromThen :: Natural -> Natural -> [Natural] Source #
enumFromTo :: Natural -> Natural -> [Natural] Source #
enumFromThenTo :: Natural -> Natural -> Natural -> [Natural] Source #
Instance details
Defined in GHC.Enum
Methods
succ :: Ordering -> Ordering Source #
pred :: Ordering -> Ordering Source #
toEnum :: Int -> Ordering Source #
fromEnum :: Ordering -> Int Source #
enumFrom :: Ordering -> [Ordering] Source #
enumFromThen :: Ordering -> Ordering -> [Ordering] Source #
enumFromTo :: Ordering -> Ordering -> [Ordering] Source #
enumFromThenTo :: Ordering -> Ordering -> Ordering -> [Ordering] Source #
Instance details
Defined in GHC.Word
Methods
succ :: Word8 -> Word8 Source #
pred :: Word8 -> Word8 Source #
toEnum :: Int -> Word8 Source #
fromEnum :: Word8 -> Int Source #
enumFrom :: Word8 -> [Word8] Source #
enumFromThen :: Word8 -> Word8 -> [Word8] Source #
enumFromTo :: Word8 -> Word8 -> [Word8] Source #
enumFromThenTo :: Word8 -> Word8 -> Word8 -> [Word8] Source #
Instance details
Defined in GHC.Word
Methods
succ :: Word16 -> Word16 Source #
pred :: Word16 -> Word16 Source #
toEnum :: Int -> Word16 Source #
fromEnum :: Word16 -> Int Source #
enumFrom :: Word16 -> [Word16] Source #
enumFromThen :: Word16 -> Word16 -> [Word16] Source #
enumFromTo :: Word16 -> Word16 -> [Word16] Source #
enumFromThenTo :: Word16 -> Word16 -> Word16 -> [Word16] Source #
Instance details
Defined in GHC.Word
Methods
succ :: Word32 -> Word32 Source #
pred :: Word32 -> Word32 Source #
toEnum :: Int -> Word32 Source #
fromEnum :: Word32 -> Int Source #
enumFrom :: Word32 -> [Word32] Source #
enumFromThen :: Word32 -> Word32 -> [Word32] Source #
enumFromTo :: Word32 -> Word32 -> [Word32] Source #
enumFromThenTo :: Word32 -> Word32 -> Word32 -> [Word32] Source #
Instance details
Defined in GHC.Word
Methods
succ :: Word64 -> Word64 Source #
pred :: Word64 -> Word64 Source #
toEnum :: Int -> Word64 Source #
fromEnum :: Word64 -> Int Source #
enumFrom :: Word64 -> [Word64] Source #
enumFromThen :: Word64 -> Word64 -> [Word64] Source #
enumFromTo :: Word64 -> Word64 -> [Word64] Source #
enumFromThenTo :: Word64 -> Word64 -> Word64 -> [Word64] Source #
Instance details
Defined in GHC.Enum
Methods
succ :: VecCount -> VecCount Source #
pred :: VecCount -> VecCount Source #
toEnum :: Int -> VecCount Source #
fromEnum :: VecCount -> Int Source #
enumFrom :: VecCount -> [VecCount] Source #
enumFromThen :: VecCount -> VecCount -> [VecCount] Source #
enumFromTo :: VecCount -> VecCount -> [VecCount] Source #
enumFromThenTo :: VecCount -> VecCount -> VecCount -> [VecCount] Source #
Instance details
Defined in GHC.Enum
Methods
succ :: VecElem -> VecElem Source #
pred :: VecElem -> VecElem Source #
toEnum :: Int -> VecElem Source #
fromEnum :: VecElem -> Int Source #
enumFrom :: VecElem -> [VecElem] Source #
enumFromThen :: VecElem -> VecElem -> [VecElem] Source #
enumFromTo :: VecElem -> VecElem -> [VecElem] Source #
enumFromThenTo :: VecElem -> VecElem -> VecElem -> [VecElem] Source #
Instance details
Defined in GHC.Enum
Instance details
Defined in GHC.Unicode
Methods
succ :: GeneralCategory -> GeneralCategory Source #
pred :: GeneralCategory -> GeneralCategory Source #
toEnum :: Int -> GeneralCategory Source #
fromEnum :: GeneralCategory -> Int Source #
enumFrom :: GeneralCategory -> [GeneralCategory] Source #
enumFromThen :: GeneralCategory -> GeneralCategory -> [GeneralCategory] Source #
enumFromTo :: GeneralCategory -> GeneralCategory -> [GeneralCategory] Source #
enumFromThenTo :: GeneralCategory -> GeneralCategory -> GeneralCategory -> [GeneralCategory] Source #
Instance details
Defined in GHC.IO.IOMode
Methods
succ :: IOMode -> IOMode Source #
pred :: IOMode -> IOMode Source #
toEnum :: Int -> IOMode Source #
fromEnum :: IOMode -> Int Source #
enumFrom :: IOMode -> [IOMode] Source #
enumFromThen :: IOMode -> IOMode -> [IOMode] Source #
enumFromTo :: IOMode -> IOMode -> [IOMode] Source #
enumFromThenTo :: IOMode -> IOMode -> IOMode -> [IOMode] Source #
Instance details
Defined in Foreign.Ptr
Methods
succ :: IntPtr -> IntPtr Source #
pred :: IntPtr -> IntPtr Source #
toEnum :: Int -> IntPtr Source #
fromEnum :: IntPtr -> Int Source #
enumFrom :: IntPtr -> [IntPtr] Source #
enumFromThen :: IntPtr -> IntPtr -> [IntPtr] Source #
enumFromTo :: IntPtr -> IntPtr -> [IntPtr] Source #
enumFromThenTo :: IntPtr -> IntPtr -> IntPtr -> [IntPtr] Source #
Instance details
Defined in Foreign.Ptr
Methods
succ :: WordPtr -> WordPtr Source #
pred :: WordPtr -> WordPtr Source #
toEnum :: Int -> WordPtr Source #
fromEnum :: WordPtr -> Int Source #
enumFrom :: WordPtr -> [WordPtr] Source #
enumFromThen :: WordPtr -> WordPtr -> [WordPtr] Source #
enumFromTo :: WordPtr -> WordPtr -> [WordPtr] Source #
enumFromThenTo :: WordPtr -> WordPtr -> WordPtr -> [WordPtr] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CUIntMax -> CUIntMax Source #
pred :: CUIntMax -> CUIntMax Source #
toEnum :: Int -> CUIntMax Source #
fromEnum :: CUIntMax -> Int Source #
enumFrom :: CUIntMax -> [CUIntMax] Source #
enumFromThen :: CUIntMax -> CUIntMax -> [CUIntMax] Source #
enumFromTo :: CUIntMax -> CUIntMax -> [CUIntMax] Source #
enumFromThenTo :: CUIntMax -> CUIntMax -> CUIntMax -> [CUIntMax] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CIntMax -> CIntMax Source #
pred :: CIntMax -> CIntMax Source #
toEnum :: Int -> CIntMax Source #
fromEnum :: CIntMax -> Int Source #
enumFrom :: CIntMax -> [CIntMax] Source #
enumFromThen :: CIntMax -> CIntMax -> [CIntMax] Source #
enumFromTo :: CIntMax -> CIntMax -> [CIntMax] Source #
enumFromThenTo :: CIntMax -> CIntMax -> CIntMax -> [CIntMax] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CUIntPtr -> CUIntPtr Source #
pred :: CUIntPtr -> CUIntPtr Source #
toEnum :: Int -> CUIntPtr Source #
fromEnum :: CUIntPtr -> Int Source #
enumFrom :: CUIntPtr -> [CUIntPtr] Source #
enumFromThen :: CUIntPtr -> CUIntPtr -> [CUIntPtr] Source #
enumFromTo :: CUIntPtr -> CUIntPtr -> [CUIntPtr] Source #
enumFromThenTo :: CUIntPtr -> CUIntPtr -> CUIntPtr -> [CUIntPtr] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CIntPtr -> CIntPtr Source #
pred :: CIntPtr -> CIntPtr Source #
toEnum :: Int -> CIntPtr Source #
fromEnum :: CIntPtr -> Int Source #
enumFrom :: CIntPtr -> [CIntPtr] Source #
enumFromThen :: CIntPtr -> CIntPtr -> [CIntPtr] Source #
enumFromTo :: CIntPtr -> CIntPtr -> [CIntPtr] Source #
enumFromThenTo :: CIntPtr -> CIntPtr -> CIntPtr -> [CIntPtr] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CSUSeconds -> CSUSeconds Source #
pred :: CSUSeconds -> CSUSeconds Source #
toEnum :: Int -> CSUSeconds Source #
fromEnum :: CSUSeconds -> Int Source #
enumFrom :: CSUSeconds -> [CSUSeconds] Source #
enumFromThen :: CSUSeconds -> CSUSeconds -> [CSUSeconds] Source #
enumFromTo :: CSUSeconds -> CSUSeconds -> [CSUSeconds] Source #
enumFromThenTo :: CSUSeconds -> CSUSeconds -> CSUSeconds -> [CSUSeconds] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CUSeconds -> CUSeconds Source #
pred :: CUSeconds -> CUSeconds Source #
toEnum :: Int -> CUSeconds Source #
fromEnum :: CUSeconds -> Int Source #
enumFrom :: CUSeconds -> [CUSeconds] Source #
enumFromThen :: CUSeconds -> CUSeconds -> [CUSeconds] Source #
enumFromTo :: CUSeconds -> CUSeconds -> [CUSeconds] Source #
enumFromThenTo :: CUSeconds -> CUSeconds -> CUSeconds -> [CUSeconds] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CTime -> CTime Source #
pred :: CTime -> CTime Source #
toEnum :: Int -> CTime Source #
fromEnum :: CTime -> Int Source #
enumFrom :: CTime -> [CTime] Source #
enumFromThen :: CTime -> CTime -> [CTime] Source #
enumFromTo :: CTime -> CTime -> [CTime] Source #
enumFromThenTo :: CTime -> CTime -> CTime -> [CTime] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CClock -> CClock Source #
pred :: CClock -> CClock Source #
toEnum :: Int -> CClock Source #
fromEnum :: CClock -> Int Source #
enumFrom :: CClock -> [CClock] Source #
enumFromThen :: CClock -> CClock -> [CClock] Source #
enumFromTo :: CClock -> CClock -> [CClock] Source #
enumFromThenTo :: CClock -> CClock -> CClock -> [CClock] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CSigAtomic -> CSigAtomic Source #
pred :: CSigAtomic -> CSigAtomic Source #
toEnum :: Int -> CSigAtomic Source #
fromEnum :: CSigAtomic -> Int Source #
enumFrom :: CSigAtomic -> [CSigAtomic] Source #
enumFromThen :: CSigAtomic -> CSigAtomic -> [CSigAtomic] Source #
enumFromTo :: CSigAtomic -> CSigAtomic -> [CSigAtomic] Source #
enumFromThenTo :: CSigAtomic -> CSigAtomic -> CSigAtomic -> [CSigAtomic] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CWchar -> CWchar Source #
pred :: CWchar -> CWchar Source #
toEnum :: Int -> CWchar Source #
fromEnum :: CWchar -> Int Source #
enumFrom :: CWchar -> [CWchar] Source #
enumFromThen :: CWchar -> CWchar -> [CWchar] Source #
enumFromTo :: CWchar -> CWchar -> [CWchar] Source #
enumFromThenTo :: CWchar -> CWchar -> CWchar -> [CWchar] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CSize -> CSize Source #
pred :: CSize -> CSize Source #
toEnum :: Int -> CSize Source #
fromEnum :: CSize -> Int Source #
enumFrom :: CSize -> [CSize] Source #
enumFromThen :: CSize -> CSize -> [CSize] Source #
enumFromTo :: CSize -> CSize -> [CSize] Source #
enumFromThenTo :: CSize -> CSize -> CSize -> [CSize] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CPtrdiff -> CPtrdiff Source #
pred :: CPtrdiff -> CPtrdiff Source #
toEnum :: Int -> CPtrdiff Source #
fromEnum :: CPtrdiff -> Int Source #
enumFrom :: CPtrdiff -> [CPtrdiff] Source #
enumFromThen :: CPtrdiff -> CPtrdiff -> [CPtrdiff] Source #
enumFromTo :: CPtrdiff -> CPtrdiff -> [CPtrdiff] Source #
enumFromThenTo :: CPtrdiff -> CPtrdiff -> CPtrdiff -> [CPtrdiff] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CDouble -> CDouble Source #
pred :: CDouble -> CDouble Source #
toEnum :: Int -> CDouble Source #
fromEnum :: CDouble -> Int Source #
enumFrom :: CDouble -> [CDouble] Source #
enumFromThen :: CDouble -> CDouble -> [CDouble] Source #
enumFromTo :: CDouble -> CDouble -> [CDouble] Source #
enumFromThenTo :: CDouble -> CDouble -> CDouble -> [CDouble] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CFloat -> CFloat Source #
pred :: CFloat -> CFloat Source #
toEnum :: Int -> CFloat Source #
fromEnum :: CFloat -> Int Source #
enumFrom :: CFloat -> [CFloat] Source #
enumFromThen :: CFloat -> CFloat -> [CFloat] Source #
enumFromTo :: CFloat -> CFloat -> [CFloat] Source #
enumFromThenTo :: CFloat -> CFloat -> CFloat -> [CFloat] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CBool -> CBool Source #
pred :: CBool -> CBool Source #
toEnum :: Int -> CBool Source #
fromEnum :: CBool -> Int Source #
enumFrom :: CBool -> [CBool] Source #
enumFromThen :: CBool -> CBool -> [CBool] Source #
enumFromTo :: CBool -> CBool -> [CBool] Source #
enumFromThenTo :: CBool -> CBool -> CBool -> [CBool] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CULLong -> CULLong Source #
pred :: CULLong -> CULLong Source #
toEnum :: Int -> CULLong Source #
fromEnum :: CULLong -> Int Source #
enumFrom :: CULLong -> [CULLong] Source #
enumFromThen :: CULLong -> CULLong -> [CULLong] Source #
enumFromTo :: CULLong -> CULLong -> [CULLong] Source #
enumFromThenTo :: CULLong -> CULLong -> CULLong -> [CULLong] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CLLong -> CLLong Source #
pred :: CLLong -> CLLong Source #
toEnum :: Int -> CLLong Source #
fromEnum :: CLLong -> Int Source #
enumFrom :: CLLong -> [CLLong] Source #
enumFromThen :: CLLong -> CLLong -> [CLLong] Source #
enumFromTo :: CLLong -> CLLong -> [CLLong] Source #
enumFromThenTo :: CLLong -> CLLong -> CLLong -> [CLLong] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CULong -> CULong Source #
pred :: CULong -> CULong Source #
toEnum :: Int -> CULong Source #
fromEnum :: CULong -> Int Source #
enumFrom :: CULong -> [CULong] Source #
enumFromThen :: CULong -> CULong -> [CULong] Source #
enumFromTo :: CULong -> CULong -> [CULong] Source #
enumFromThenTo :: CULong -> CULong -> CULong -> [CULong] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CLong -> CLong Source #
pred :: CLong -> CLong Source #
toEnum :: Int -> CLong Source #
fromEnum :: CLong -> Int Source #
enumFrom :: CLong -> [CLong] Source #
enumFromThen :: CLong -> CLong -> [CLong] Source #
enumFromTo :: CLong -> CLong -> [CLong] Source #
enumFromThenTo :: CLong -> CLong -> CLong -> [CLong] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CUInt -> CUInt Source #
pred :: CUInt -> CUInt Source #
toEnum :: Int -> CUInt Source #
fromEnum :: CUInt -> Int Source #
enumFrom :: CUInt -> [CUInt] Source #
enumFromThen :: CUInt -> CUInt -> [CUInt] Source #
enumFromTo :: CUInt -> CUInt -> [CUInt] Source #
enumFromThenTo :: CUInt -> CUInt -> CUInt -> [CUInt] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CUShort -> CUShort Source #
pred :: CUShort -> CUShort Source #
toEnum :: Int -> CUShort Source #
fromEnum :: CUShort -> Int Source #
enumFrom :: CUShort -> [CUShort] Source #
enumFromThen :: CUShort -> CUShort -> [CUShort] Source #
enumFromTo :: CUShort -> CUShort -> [CUShort] Source #
enumFromThenTo :: CUShort -> CUShort -> CUShort -> [CUShort] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CShort -> CShort Source #
pred :: CShort -> CShort Source #
toEnum :: Int -> CShort Source #
fromEnum :: CShort -> Int Source #
enumFrom :: CShort -> [CShort] Source #
enumFromThen :: CShort -> CShort -> [CShort] Source #
enumFromTo :: CShort -> CShort -> [CShort] Source #
enumFromThenTo :: CShort -> CShort -> CShort -> [CShort] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CUChar -> CUChar Source #
pred :: CUChar -> CUChar Source #
toEnum :: Int -> CUChar Source #
fromEnum :: CUChar -> Int Source #
enumFrom :: CUChar -> [CUChar] Source #
enumFromThen :: CUChar -> CUChar -> [CUChar] Source #
enumFromTo :: CUChar -> CUChar -> [CUChar] Source #
enumFromThenTo :: CUChar -> CUChar -> CUChar -> [CUChar] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CSChar -> CSChar Source #
pred :: CSChar -> CSChar Source #
toEnum :: Int -> CSChar Source #
fromEnum :: CSChar -> Int Source #
enumFrom :: CSChar -> [CSChar] Source #
enumFromThen :: CSChar -> CSChar -> [CSChar] Source #
enumFromTo :: CSChar -> CSChar -> [CSChar] Source #
enumFromThenTo :: CSChar -> CSChar -> CSChar -> [CSChar] Source #
Instance details
Defined in Foreign.C.Types
Methods
succ :: CChar -> CChar Source #
pred :: CChar -> CChar Source #
toEnum :: Int -> CChar Source #
fromEnum :: CChar -> Int Source #
enumFrom :: CChar -> [CChar] Source #
enumFromThen :: CChar -> CChar -> [CChar] Source #
enumFromTo :: CChar -> CChar -> [CChar] Source #
enumFromThenTo :: CChar -> CChar -> CChar -> [CChar] Source #
Instance details
Defined in GHC.Generics
Methods
succ :: DecidedStrictness -> DecidedStrictness Source #
pred :: DecidedStrictness -> DecidedStrictness Source #
toEnum :: Int -> DecidedStrictness Source #
fromEnum :: DecidedStrictness -> Int Source #
enumFrom :: DecidedStrictness -> [DecidedStrictness] Source #
enumFromThen :: DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] Source #
enumFromTo :: DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] Source #
enumFromThenTo :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] Source #
Instance details
Defined in GHC.Generics
Methods
succ :: SourceStrictness -> SourceStrictness Source #
pred :: SourceStrictness -> SourceStrictness Source #
toEnum :: Int -> SourceStrictness Source #
fromEnum :: SourceStrictness -> Int Source #
enumFrom :: SourceStrictness -> [SourceStrictness] Source #
enumFromThen :: SourceStrictness -> SourceStrictness -> [SourceStrictness] Source #
enumFromTo :: SourceStrictness -> SourceStrictness -> [SourceStrictness] Source #
enumFromThenTo :: SourceStrictness -> SourceStrictness -> SourceStrictness -> [SourceStrictness] Source #
Instance details
Defined in GHC.Generics
Methods
succ :: SourceUnpackedness -> SourceUnpackedness Source #
pred :: SourceUnpackedness -> SourceUnpackedness Source #
toEnum :: Int -> SourceUnpackedness Source #
fromEnum :: SourceUnpackedness -> Int Source #
enumFrom :: SourceUnpackedness -> [SourceUnpackedness] Source #
enumFromThen :: SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] Source #
enumFromTo :: SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] Source #
enumFromThenTo :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] Source #
Instance details
Defined in GHC.Generics
Methods
succ :: Associativity -> Associativity Source #
pred :: Associativity -> Associativity Source #
toEnum :: Int -> Associativity Source #
fromEnum :: Associativity -> Int Source #
enumFrom :: Associativity -> [Associativity] Source #
enumFromThen :: Associativity -> Associativity -> [Associativity] Source #
enumFromTo :: Associativity -> Associativity -> [Associativity] Source #
enumFromThenTo :: Associativity -> Associativity -> Associativity -> [Associativity] Source #
Instance details
Defined in GHC.IO.Device
Methods
succ :: SeekMode -> SeekMode Source #
pred :: SeekMode -> SeekMode Source #
toEnum :: Int -> SeekMode Source #
fromEnum :: SeekMode -> Int Source #
enumFrom :: SeekMode -> [SeekMode] Source #
enumFromThen :: SeekMode -> SeekMode -> [SeekMode] Source #
enumFromTo :: SeekMode -> SeekMode -> [SeekMode] Source #
enumFromThenTo :: SeekMode -> SeekMode -> SeekMode -> [SeekMode] Source #
Instance details
Defined in System.Posix.Types
Instance details
Defined in System.Posix.Types
Methods
succ :: CFsFilCnt -> CFsFilCnt Source #
pred :: CFsFilCnt -> CFsFilCnt Source #
toEnum :: Int -> CFsFilCnt Source #
fromEnum :: CFsFilCnt -> Int Source #
enumFrom :: CFsFilCnt -> [CFsFilCnt] Source #
enumFromThen :: CFsFilCnt -> CFsFilCnt -> [CFsFilCnt] Source #
enumFromTo :: CFsFilCnt -> CFsFilCnt -> [CFsFilCnt] Source #
enumFromThenTo :: CFsFilCnt -> CFsFilCnt -> CFsFilCnt -> [CFsFilCnt] Source #
Instance details
Defined in System.Posix.Types
Methods
succ :: CFsBlkCnt -> CFsBlkCnt Source #
pred :: CFsBlkCnt -> CFsBlkCnt Source #
toEnum :: Int -> CFsBlkCnt Source #
fromEnum :: CFsBlkCnt -> Int Source #
enumFrom :: CFsBlkCnt -> [CFsBlkCnt] Source #
enumFromThen :: CFsBlkCnt -> CFsBlkCnt -> [CFsBlkCnt] Source #
enumFromTo :: CFsBlkCnt -> CFsBlkCnt -> [CFsBlkCnt] Source #
enumFromThenTo :: CFsBlkCnt -> CFsBlkCnt -> CFsBlkCnt -> [CFsBlkCnt] Source #
Instance details
Defined in System.Posix.Types
Methods
succ :: CClockId -> CClockId Source #
pred :: CClockId -> CClockId Source #
toEnum :: Int -> CClockId Source #
fromEnum :: CClockId -> Int Source #
enumFrom :: CClockId -> [CClockId] Source #
enumFromThen :: CClockId -> CClockId -> [CClockId] Source #
enumFromTo :: CClockId -> CClockId -> [CClockId] Source #
enumFromThenTo :: CClockId -> CClockId -> CClockId -> [CClockId] Source #
Instance details
Defined in System.Posix.Types
Methods
succ :: CBlkCnt -> CBlkCnt Source #
pred :: CBlkCnt -> CBlkCnt Source #
toEnum :: Int -> CBlkCnt Source #
fromEnum :: CBlkCnt -> Int Source #
enumFrom :: CBlkCnt -> [CBlkCnt] Source #
enumFromThen :: CBlkCnt -> CBlkCnt -> [CBlkCnt] Source #
enumFromTo :: CBlkCnt -> CBlkCnt -> [CBlkCnt] Source #
enumFromThenTo :: CBlkCnt -> CBlkCnt -> CBlkCnt -> [CBlkCnt] Source #
Instance details
Defined in System.Posix.Types
Methods
succ :: CBlkSize -> CBlkSize Source #
pred :: CBlkSize -> CBlkSize Source #
toEnum :: Int -> CBlkSize Source #
fromEnum :: CBlkSize -> Int Source #
enumFrom :: CBlkSize -> [CBlkSize] Source #
enumFromThen :: CBlkSize -> CBlkSize -> [CBlkSize] Source #
enumFromTo :: CBlkSize -> CBlkSize -> [CBlkSize] Source #
enumFromThenTo :: CBlkSize -> CBlkSize -> CBlkSize -> [CBlkSize] Source #
Instance details
Defined in System.Posix.Types
Methods
succ :: CRLim -> CRLim Source #
pred :: CRLim -> CRLim Source #
toEnum :: Int -> CRLim Source #
fromEnum :: CRLim -> Int Source #
enumFrom :: CRLim -> [CRLim] Source #
enumFromThen :: CRLim -> CRLim -> [CRLim] Source #
enumFromTo :: CRLim -> CRLim -> [CRLim] Source #
enumFromThenTo :: CRLim -> CRLim -> CRLim -> [CRLim] Source #
Instance details
Defined in System.Posix.Types
Methods
succ :: CTcflag -> CTcflag Source #
pred :: CTcflag -> CTcflag Source #
toEnum :: Int -> CTcflag Source #
fromEnum :: CTcflag -> Int Source #
enumFrom :: CTcflag -> [CTcflag] Source #
enumFromThen :: CTcflag -> CTcflag -> [CTcflag] Source #
enumFromTo :: CTcflag -> CTcflag -> [CTcflag] Source #
enumFromThenTo :: CTcflag -> CTcflag -> CTcflag -> [CTcflag] Source #
Instance details
Defined in System.Posix.Types
Methods
succ :: CSpeed -> CSpeed Source #
pred :: CSpeed -> CSpeed Source #
toEnum :: Int -> CSpeed Source #
fromEnum :: CSpeed -> Int Source #
enumFrom :: CSpeed -> [CSpeed] Source #
enumFromThen :: CSpeed -> CSpeed -> [CSpeed] Source #
enumFromTo :: CSpeed -> CSpeed -> [CSpeed] Source #
enumFromThenTo :: CSpeed -> CSpeed -> CSpeed -> [CSpeed] Source #
Instance details
Defined in System.Posix.Types
Methods
succ :: CNlink -> CNlink Source #
pred :: CNlink -> CNlink Source #
toEnum :: Int -> CNlink Source #
fromEnum :: CNlink -> Int Source #
enumFrom :: CNlink -> [CNlink] Source #
enumFromThen :: CNlink -> CNlink -> [CNlink] Source #
enumFromTo :: CNlink -> CNlink -> [CNlink] Source #
enumFromThenTo :: CNlink -> CNlink -> CNlink -> [CNlink] Source #
Instance details
Defined in System.Posix.Types
Methods
succ :: CSsize -> CSsize Source #
pred :: CSsize -> CSsize Source #
toEnum :: Int -> CSsize Source #
fromEnum :: CSsize -> Int Source #
enumFrom :: CSsize -> [CSsize] Source #
enumFromThen :: CSsize -> CSsize -> [CSsize] Source #
enumFromTo :: CSsize -> CSsize -> [CSsize] Source #
enumFromThenTo :: CSsize -> CSsize -> CSsize -> [CSsize] Source #
Instance details
Defined in System.Posix.Types
Methods
succ :: CMode -> CMode Source #
pred :: CMode -> CMode Source #
toEnum :: Int -> CMode Source #
fromEnum :: CMode -> Int Source #
enumFrom :: CMode -> [CMode] Source #
enumFromThen :: CMode -> CMode -> [CMode] Source #
enumFromTo :: CMode -> CMode -> [CMode] Source #
enumFromThenTo :: CMode -> CMode -> CMode -> [CMode] Source #
Instance details
Defined in GHC.ByteOrder
Methods
succ :: ByteOrder -> ByteOrder Source #
pred :: ByteOrder -> ByteOrder Source #
toEnum :: Int -> ByteOrder Source #
fromEnum :: ByteOrder -> Int Source #
enumFrom :: ByteOrder -> [ByteOrder] Source #
enumFromThen :: ByteOrder -> ByteOrder -> [ByteOrder] Source #
enumFromTo :: ByteOrder -> ByteOrder -> [ByteOrder] Source #
enumFromThenTo :: ByteOrder -> ByteOrder -> ByteOrder -> [ByteOrder] Source #
Instance details
Defined in GHC.RTS.Flags
Methods
succ :: DoTrace -> DoTrace Source #
pred :: DoTrace -> DoTrace Source #
toEnum :: Int -> DoTrace Source #
fromEnum :: DoTrace -> Int Source #
enumFrom :: DoTrace -> [DoTrace] Source #
enumFromThen :: DoTrace -> DoTrace -> [DoTrace] Source #
enumFromTo :: DoTrace -> DoTrace -> [DoTrace] Source #
enumFromThenTo :: DoTrace -> DoTrace -> DoTrace -> [DoTrace] Source #
Instance details
Defined in GHC.RTS.Flags
Methods
succ :: DoHeapProfile -> DoHeapProfile Source #
pred :: DoHeapProfile -> DoHeapProfile Source #
toEnum :: Int -> DoHeapProfile Source #
fromEnum :: DoHeapProfile -> Int Source #
enumFrom :: DoHeapProfile -> [DoHeapProfile] Source #
enumFromThen :: DoHeapProfile -> DoHeapProfile -> [DoHeapProfile] Source #
enumFromTo :: DoHeapProfile -> DoHeapProfile -> [DoHeapProfile] Source #
enumFromThenTo :: DoHeapProfile -> DoHeapProfile -> DoHeapProfile -> [DoHeapProfile] Source #
Instance details
Defined in GHC.RTS.Flags
Methods
succ :: DoCostCentres -> DoCostCentres Source #
pred :: DoCostCentres -> DoCostCentres Source #
toEnum :: Int -> DoCostCentres Source #
fromEnum :: DoCostCentres -> Int Source #
enumFrom :: DoCostCentres -> [DoCostCentres] Source #
enumFromThen :: DoCostCentres -> DoCostCentres -> [DoCostCentres] Source #
enumFromTo :: DoCostCentres -> DoCostCentres -> [DoCostCentres] Source #
enumFromThenTo :: DoCostCentres -> DoCostCentres -> DoCostCentres -> [DoCostCentres] Source #
Instance details
Defined in GHC.RTS.Flags
Methods
succ :: GiveGCStats -> GiveGCStats Source #
pred :: GiveGCStats -> GiveGCStats Source #
toEnum :: Int -> GiveGCStats Source #
fromEnum :: GiveGCStats -> Int Source #
enumFrom :: GiveGCStats -> [GiveGCStats] Source #
enumFromThen :: GiveGCStats -> GiveGCStats -> [GiveGCStats] Source #
enumFromTo :: GiveGCStats -> GiveGCStats -> [GiveGCStats] Source #
enumFromThenTo :: GiveGCStats -> GiveGCStats -> GiveGCStats -> [GiveGCStats] Source #
Instance details
Defined in GHC.Real
Methods
succ :: Ratio a -> Ratio a Source #
pred :: Ratio a -> Ratio a Source #
toEnum :: Int -> Ratio a Source #
fromEnum :: Ratio a -> Int Source #
enumFrom :: Ratio a -> [Ratio a] Source #
enumFromThen :: Ratio a -> Ratio a -> [Ratio a] Source #
enumFromTo :: Ratio a -> Ratio a -> [Ratio a] Source #
enumFromThenTo :: Ratio a -> Ratio a -> Ratio a -> [Ratio a] Source #
Instance details
Defined in Data.Functor.Identity
Methods
succ :: Identity a -> Identity a Source #
pred :: Identity a -> Identity a Source #
toEnum :: Int -> Identity a Source #
fromEnum :: Identity a -> Int Source #
enumFrom :: Identity a -> [Identity a] Source #
enumFromThen :: Identity a -> Identity a -> [Identity a] Source #
enumFromTo :: Identity a -> Identity a -> [Identity a] Source #
enumFromThenTo :: Identity a -> Identity a -> Identity a -> [Identity a] Source #
Instance details
Defined in Data.Semigroup
Methods
succ :: WrappedMonoid a -> WrappedMonoid a Source #
pred :: WrappedMonoid a -> WrappedMonoid a Source #
toEnum :: Int -> WrappedMonoid a Source #
fromEnum :: WrappedMonoid a -> Int Source #
enumFrom :: WrappedMonoid a -> [WrappedMonoid a] Source #
enumFromThen :: WrappedMonoid a -> WrappedMonoid a -> [WrappedMonoid a] Source #
enumFromTo :: WrappedMonoid a -> WrappedMonoid a -> [WrappedMonoid a] Source #
enumFromThenTo :: WrappedMonoid a -> WrappedMonoid a -> WrappedMonoid a -> [WrappedMonoid a] Source #
Instance details
Defined in Data.Semigroup
Methods
succ :: Last a -> Last a Source #
pred :: Last a -> Last a Source #
toEnum :: Int -> Last a Source #
fromEnum :: Last a -> Int Source #
enumFrom :: Last a -> [Last a] Source #
enumFromThen :: Last a -> Last a -> [Last a] Source #
enumFromTo :: Last a -> Last a -> [Last a] Source #
enumFromThenTo :: Last a -> Last a -> Last a -> [Last a] Source #
Instance details
Defined in Data.Semigroup
Methods
succ :: First a -> First a Source #
pred :: First a -> First a Source #
toEnum :: Int -> First a Source #
fromEnum :: First a -> Int Source #
enumFrom :: First a -> [First a] Source #
enumFromThen :: First a -> First a -> [First a] Source #
enumFromTo :: First a -> First a -> [First a] Source #
enumFromThenTo :: First a -> First a -> First a -> [First a] Source #
Instance details
Defined in Data.Semigroup
Methods
succ :: Max a -> Max a Source #
pred :: Max a -> Max a Source #
toEnum :: Int -> Max a Source #
fromEnum :: Max a -> Int Source #
enumFrom :: Max a -> [Max a] Source #
enumFromThen :: Max a -> Max a -> [Max a] Source #
enumFromTo :: Max a -> Max a -> [Max a] Source #
enumFromThenTo :: Max a -> Max a -> Max a -> [Max a] Source #
Instance details
Defined in Data.Semigroup
Methods
succ :: Min a -> Min a Source #
pred :: Min a -> Min a Source #
toEnum :: Int -> Min a Source #
fromEnum :: Min a -> Int Source #
enumFrom :: Min a -> [Min a] Source #
enumFromThen :: Min a -> Min a -> [Min a] Source #
enumFromTo :: Min a -> Min a -> [Min a] Source #
enumFromThenTo :: Min a -> Min a -> Min a -> [Min a] Source #
Instance details
Defined in Data.Fixed
Methods
succ :: Fixed a -> Fixed a Source #
pred :: Fixed a -> Fixed a Source #
toEnum :: Int -> Fixed a Source #
fromEnum :: Fixed a -> Int Source #
enumFrom :: Fixed a -> [Fixed a] Source #
enumFromThen :: Fixed a -> Fixed a -> [Fixed a] Source #
enumFromTo :: Fixed a -> Fixed a -> [Fixed a] Source #
enumFromThenTo :: Fixed a -> Fixed a -> Fixed a -> [Fixed a] Source #
Instance details
Defined in Data.Proxy
Methods
succ :: Proxy s -> Proxy s Source #
pred :: Proxy s -> Proxy s Source #
toEnum :: Int -> Proxy s Source #
fromEnum :: Proxy s -> Int Source #
enumFrom :: Proxy s -> [Proxy s] Source #
enumFromThen :: Proxy s -> Proxy s -> [Proxy s] Source #
enumFromTo :: Proxy s -> Proxy s -> [Proxy s] Source #
enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] Source #
Instance details
Defined in Data.Type.Equality
Methods
succ :: (a :~: b) -> a :~: b Source #
pred :: (a :~: b) -> a :~: b Source #
toEnum :: Int -> a :~: b Source #
fromEnum :: (a :~: b) -> Int Source #
enumFrom :: (a :~: b) -> [a :~: b] Source #
enumFromThen :: (a :~: b) -> (a :~: b) -> [a :~: b] Source #
enumFromTo :: (a :~: b) -> (a :~: b) -> [a :~: b] Source #
enumFromThenTo :: (a :~: b) -> (a :~: b) -> (a :~: b) -> [a :~: b] Source #
Instance details
Defined in Data.Type.Coercion
Methods
succ :: Coercion a b -> Coercion a b Source #
pred :: Coercion a b -> Coercion a b Source #
toEnum :: Int -> Coercion a b Source #
fromEnum :: Coercion a b -> Int Source #
enumFrom :: Coercion a b -> [Coercion a b] Source #
enumFromThen :: Coercion a b -> Coercion a b -> [Coercion a b] Source #
enumFromTo :: Coercion a b -> Coercion a b -> [Coercion a b] Source #
enumFromThenTo :: Coercion a b -> Coercion a b -> Coercion a b -> [Coercion a b] Source #
Instance details
Defined in Data.Semigroup.Internal
Methods
succ :: Alt f a -> Alt f a Source #
pred :: Alt f a -> Alt f a Source #
toEnum :: Int -> Alt f a Source #
fromEnum :: Alt f a -> Int Source #
enumFrom :: Alt f a -> [Alt f a] Source #
enumFromThen :: Alt f a -> Alt f a -> [Alt f a] Source #
enumFromTo :: Alt f a -> Alt f a -> [Alt f a] Source #
enumFromThenTo :: Alt f a -> Alt f a -> Alt f a -> [Alt f a] Source #
Instance details
Defined in Data.Monoid
Methods
succ :: Ap f a -> Ap f a Source #
pred :: Ap f a -> Ap f a Source #
toEnum :: Int -> Ap f a Source #
fromEnum :: Ap f a -> Int Source #
enumFrom :: Ap f a -> [Ap f a] Source #
enumFromThen :: Ap f a -> Ap f a -> [Ap f a] Source #
enumFromTo :: Ap f a -> Ap f a -> [Ap f a] Source #
enumFromThenTo :: Ap f a -> Ap f a -> Ap f a -> [Ap f a] Source #
Instance details
Defined in Data.Functor.Const
Methods
succ :: Const a b -> Const a b Source #
pred :: Const a b -> Const a b Source #
toEnum :: Int -> Const a b Source #
fromEnum :: Const a b -> Int Source #
enumFrom :: Const a b -> [Const a b] Source #
enumFromThen :: Const a b -> Const a b -> [Const a b] Source #
enumFromTo :: Const a b -> Const a b -> [Const a b] Source #
enumFromThenTo :: Const a b -> Const a b -> Const a b -> [Const a b] Source #
Instance details
Defined in Data.Type.Equality
Methods
succ :: (a :~~: b) -> a :~~: b Source #
pred :: (a :~~: b) -> a :~~: b Source #
toEnum :: Int -> a :~~: b Source #
fromEnum :: (a :~~: b) -> Int Source #
enumFrom :: (a :~~: b) -> [a :~~: b] Source #
enumFromThen :: (a :~~: b) -> (a :~~: b) -> [a :~~: b] Source #
enumFromTo :: (a :~~: b) -> (a :~~: b) -> [a :~~: b] Source #
enumFromThenTo :: (a :~~: b) -> (a :~~: b) -> (a :~~: b) -> [a :~~: b] Source #
boundedEnumFrom :: (Enum a, Bounded a) => a -> [a] Source #
boundedEnumFromThen :: (Enum a, Bounded a) => a -> a -> [a] Source #
fromEnumError :: Show a => String -> a -> b Source #