Copyright | (c) The University of Glasgow 1992-2002 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | ghc-devs@haskell.org |
Stability | internal |
Portability | non-portable (GHC extensions) |
Safe Haskell | Safe |
Language | Haskell2010 |
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
Bounded ByteOrder | @since base-4.11.0.0 |
Bounded All | @since base-2.01 |
Bounded Any | @since base-2.01 |
Bounded CBool | |
Bounded CChar | |
Bounded CInt | |
Bounded CIntMax | |
Bounded CIntPtr | |
Bounded CLLong | |
Bounded CLong | |
Bounded CPtrdiff | |
Bounded CSChar | |
Bounded CShort | |
Bounded CSigAtomic | |
Defined in GHC.Internal.Foreign.C.Types | |
Bounded CSize | |
Bounded CUChar | |
Bounded CUInt | |
Bounded CUIntMax | |
Bounded CUIntPtr | |
Bounded CULLong | |
Bounded CULong | |
Bounded CUShort | |
Bounded CWchar | |
Bounded IntPtr | |
Bounded WordPtr | |
Bounded Associativity | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics | |
Bounded DecidedStrictness | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics | |
Bounded SourceStrictness | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics | |
Bounded SourceUnpackedness | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics | |
Bounded Int16 | @since base-2.01 |
Bounded Int32 | @since base-2.01 |
Bounded Int64 | @since base-2.01 |
Bounded Int8 | @since base-2.01 |
Bounded CBlkCnt | |
Bounded CBlkSize | |
Bounded CClockId | |
Bounded CDev | |
Bounded CFsBlkCnt | |
Bounded CFsFilCnt | |
Bounded CGid | |
Bounded CId | |
Bounded CIno | |
Bounded CKey | |
Bounded CMode | |
Bounded CNfds | |
Bounded CNlink | |
Bounded COff | |
Bounded CPid | |
Bounded CRLim | |
Bounded CSocklen | |
Bounded CSsize | |
Bounded CTcflag | |
Bounded CUid | |
Bounded Fd | |
Bounded GeneralCategory | @since base-2.01 |
Defined in GHC.Internal.Unicode | |
Bounded Word16 | @since base-2.01 |
Bounded Word32 | @since base-2.01 |
Bounded Word64 | @since base-2.01 |
Bounded Word8 | @since base-2.01 |
Bounded Ordering | @since base-2.01 |
Bounded () | @since base-2.01 |
Bounded Bool | @since base-2.01 |
Bounded Char | @since base-2.01 |
Bounded Int | @since base-2.01 |
Bounded Levity | @since base-4.16.0.0 |
Bounded VecCount | @since base-4.10.0.0 |
Bounded VecElem | @since base-4.10.0.0 |
Bounded Word | @since base-2.01 |
Bounded a => Bounded (First a) Source # | Since: base-4.9.0.0 |
Bounded a => Bounded (Last a) Source # | Since: base-4.9.0.0 |
Bounded a => Bounded (Max a) Source # | Since: base-4.9.0.0 |
Bounded a => Bounded (Min a) Source # | Since: base-4.9.0.0 |
Bounded m => Bounded (WrappedMonoid m) Source # | Since: base-4.9.0.0 |
Defined in Data.Semigroup minBound :: WrappedMonoid m Source # maxBound :: WrappedMonoid m Source # | |
Bounded a => Bounded (And a) | @since base-4.16 |
Bounded a => Bounded (Iff a) | @since base-4.16 |
Bounded a => Bounded (Ior a) | @since base-4.16 |
Bounded a => Bounded (Xor a) | @since base-4.16 |
Bounded a => Bounded (Identity a) | @since base-4.9.0.0 |
Bounded a => Bounded (Down a) | Swaps @since base-4.14.0.0 |
Bounded a => Bounded (Dual a) | @since base-2.01 |
Bounded a => Bounded (Product a) | @since base-2.01 |
Bounded a => Bounded (Sum a) | @since base-2.01 |
Bounded a => Bounded (Solo a) | |
Bounded (Proxy t) | @since base-4.7.0.0 |
(Bounded a, Bounded b) => Bounded (a, b) | @since base-2.01 |
Bounded a => Bounded (Const a b) | @since base-4.9.0.0 |
(Applicative f, Bounded a) => Bounded (Ap f a) | @since base-4.12.0.0 |
Coercible a b => Bounded (Coercion a b) | @since base-4.7.0.0 |
a ~ b => Bounded (a :~: b) | @since base-4.7.0.0 |
(Bounded a, Bounded b, Bounded c) => Bounded (a, b, c) | @since base-2.01 |
a ~~ b => Bounded (a :~~: b) | @since base-4.10.0.0 |
(Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (a, b, c, d) | @since base-2.01 |
Bounded (f (g a)) => Bounded (Compose f g a) Source # | Since: base-4.19.0.0 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e) => Bounded (a, b, c, d, e) | @since base-2.01 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f) => Bounded (a, b, c, d, e, f) | @since base-2.01 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g) => Bounded (a, b, c, d, e, f, g) | @since base-2.01 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h) => Bounded (a, b, c, d, e, f, g, h) | @since base-2.01 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i) => Bounded (a, b, c, d, e, f, g, h, i) | @since base-2.01 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j) => Bounded (a, b, c, d, e, f, g, h, i, j) | @since base-2.01 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k) => Bounded (a, b, c, d, e, f, g, h, i, j, k) | @since base-2.01 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l) | @since base-2.01 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m) | @since base-2.01 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | @since base-2.01 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n, Bounded o) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | @since base-2.01 |
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
Successor of a value. For numeric types, succ
adds 1.
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)
.
Examples
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
Examples
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 = []
Examples
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 = []
Examples
enumFromThenTo 4 2 -6 :: [Integer] = [4,2,0,-2,-4,-6]
enumFromThenTo 6 8 2 :: [Int] = []
Instances
boundedEnumFrom :: (Enum a, Bounded a) => a -> [a] Source #
boundedEnumFromThen :: (Enum a, Bounded a) => a -> a -> [a] Source #
fromEnumError :: Show a => String -> a -> b Source #