Copyright | (c) 2013-2023 Brendan Hay |
---|---|
License | Mozilla Public License, v. 2.0. |
Maintainer | Brendan Hay <brendan.g.hay+amazonka@gmail.com> |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
An intentionally limited set of prelude exports to control backward compatibility and simplify code generation.
Please consider long and hard before adding any addtional types exports to this module - they should either be in pervasive use throughout the project or have zero ambiguity. If you ever are forced to disambiguate at any point, it's a bad export.
Try and avoid any value, operator, or symbol exports, if possible. Most of the ones here exist to ease legacy code-migration.
Synopsis
- (++) :: [a] -> [a] -> [a]
- seq :: forall {r :: RuntimeRep} a (b :: TYPE r). a -> b -> b
- filter :: (a -> Bool) -> [a] -> [a]
- zip :: [a] -> [b] -> [(a, b)]
- print :: Show a => a -> IO ()
- fst :: (a, b) -> a
- snd :: (a, b) -> b
- otherwise :: Bool
- map :: (a -> b) -> [a] -> [b]
- ($) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b
- coerce :: forall {k :: RuntimeRep} (a :: TYPE k) (b :: TYPE k). Coercible a b => a -> b
- fromIntegral :: (Integral a, Num b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- guard :: Alternative f => Bool -> f ()
- class IsList l where
- join :: Monad m => m (m a) -> m a
- 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]
- class Eq a where
- class Fractional a => Floating a where
- class Num a => Fractional a where
- (/) :: a -> a -> a
- recip :: a -> a
- fromRational :: Rational -> a
- class (Real a, Enum a) => Integral a where
- class Applicative m => Monad (m :: Type -> Type) where
- class Functor (f :: Type -> Type) where
- class Num a where
- class Eq a => Ord a where
- class Read a where
- class (Num a, Ord a) => Real a where
- toRational :: a -> Rational
- class (RealFrac a, Floating a) => RealFloat a where
- floatRadix :: a -> Integer
- floatDigits :: a -> Int
- floatRange :: a -> (Int, Int)
- decodeFloat :: a -> (Integer, Int)
- encodeFloat :: Integer -> Int -> a
- exponent :: a -> Int
- significand :: a -> a
- scaleFloat :: Int -> a -> a
- isNaN :: a -> Bool
- isInfinite :: a -> Bool
- isDenormalized :: a -> Bool
- isNegativeZero :: a -> Bool
- isIEEE :: a -> Bool
- atan2 :: a -> a -> a
- class (Real a, Fractional a) => RealFrac a where
- class Show a where
- class Monad m => MonadFail (m :: Type -> Type) where
- class IsString a where
- fromString :: String -> a
- class Functor f => Applicative (f :: Type -> Type) where
- class Foldable (t :: TYPE LiftedRep -> Type) where
- foldMap :: Monoid m => (a -> m) -> t a -> m
- foldr :: (a -> b -> b) -> b -> t a -> b
- foldl :: (b -> a -> b) -> b -> t a -> b
- foldr1 :: (a -> a -> a) -> t a -> a
- foldl1 :: (a -> a -> a) -> t a -> a
- null :: t a -> Bool
- length :: t a -> Int
- elem :: Eq a => a -> t a -> Bool
- maximum :: Ord a => t a -> a
- minimum :: Ord a => t a -> a
- sum :: Num a => t a -> a
- product :: Num a => t a -> a
- class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- sequenceA :: Applicative f => t (f a) -> f (t a)
- mapM :: Monad m => (a -> m b) -> t a -> m (t b)
- sequence :: Monad m => t (m a) -> m (t a)
- class Generic a
- class KnownNat (n :: Nat)
- class KnownSymbol (n :: Symbol)
- class Semigroup a where
- (<>) :: a -> a -> a
- class Semigroup a => Monoid a where
- data Bool
- type String = [Char]
- data Char
- data Double
- data Float
- data Int
- data Int8
- data Int16
- data Int32
- data Int64
- data Integer
- data Natural
- data Maybe a
- data Ordering
- type Rational = Ratio Integer
- data IO a
- data Word
- data Word8
- data Word16
- data Word32
- data Word64
- data Either a b
- data NonEmpty a = a :| [a]
- type Type = TYPE LiftedRep
- class a ~R# b => Coercible (a :: k) (b :: k)
- data Symbol
- liftM :: Monad m => (a1 -> r) -> m a1 -> m r
- id :: a -> a
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- data Scientific
- class Eq a => Hashable a where
- hashWithSalt :: Int -> a -> Int
- hash :: a -> Int
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- const :: a -> b -> a
- (.) :: (b -> c) -> (a -> b) -> a -> c
- data UTCTime
- data ByteString
- data Text
- data HashMap k v
- class Bifunctor (p :: Type -> Type -> Type) where
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- read :: Read a => String -> a
- class Applicative f => Alternative (f :: Type -> Type) where
- (<|>) :: f a -> f a -> f a
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
- data Void
- type family Item l
- class (Bifunctor t, Bifoldable t) => Bitraversable (t :: Type -> Type -> Type) where
- bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> t a b -> f (t c d)
- bisequenceA :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b)
- bisequence :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b)
- bimapM :: (Bitraversable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d)
- bimapDefault :: Bitraversable t => (a -> b) -> (c -> d) -> t a c -> t b d
- bimapAccumR :: Bitraversable t => (a -> b -> (a, c)) -> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e)
- bimapAccumL :: Bitraversable t => (a -> b -> (a, c)) -> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e)
- biforM :: (Bitraversable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d)
- bifor :: (Bitraversable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d)
- bifoldMapDefault :: (Bitraversable t, Monoid m) => (a -> m) -> (b -> m) -> t a b -> m
- class Bifoldable (p :: TYPE LiftedRep -> TYPE LiftedRep -> Type) where
- bitraverse_ :: (Bifoldable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f ()
- bisum :: (Bifoldable t, Num a) => t a a -> a
- bisequence_ :: (Bifoldable t, Applicative f) => t (f a) (f b) -> f ()
- bisequenceA_ :: (Bifoldable t, Applicative f) => t (f a) (f b) -> f ()
- biproduct :: (Bifoldable t, Num a) => t a a -> a
- bior :: Bifoldable t => t Bool Bool -> Bool
- binull :: Bifoldable t => t a b -> Bool
- binotElem :: (Bifoldable t, Eq a) => a -> t a a -> Bool
- bimsum :: (Bifoldable t, Alternative f) => t (f a) (f a) -> f a
- biminimumBy :: Bifoldable t => (a -> a -> Ordering) -> t a a -> a
- biminimum :: (Bifoldable t, Ord a) => t a a -> a
- bimaximumBy :: Bifoldable t => (a -> a -> Ordering) -> t a a -> a
- bimaximum :: (Bifoldable t, Ord a) => t a a -> a
- bimapM_ :: (Bifoldable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f ()
- bilength :: Bifoldable t => t a b -> Int
- bifor_ :: (Bifoldable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f ()
- biforM_ :: (Bifoldable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f ()
- bifoldrM :: (Bifoldable t, Monad m) => (a -> c -> m c) -> (b -> c -> m c) -> c -> t a b -> m c
- bifoldr1 :: Bifoldable t => (a -> a -> a) -> t a a -> a
- bifoldr' :: Bifoldable t => (a -> c -> c) -> (b -> c -> c) -> c -> t a b -> c
- bifoldlM :: (Bifoldable t, Monad m) => (a -> b -> m a) -> (a -> c -> m a) -> a -> t b c -> m a
- bifoldl1 :: Bifoldable t => (a -> a -> a) -> t a a -> a
- bifoldl' :: Bifoldable t => (a -> b -> a) -> (a -> c -> a) -> a -> t b c -> a
- bifind :: Bifoldable t => (a -> Bool) -> t a a -> Maybe a
- bielem :: (Bifoldable t, Eq a) => a -> t a a -> Bool
- biconcatMap :: Bifoldable t => (a -> [c]) -> (b -> [c]) -> t a b -> [c]
- biconcat :: Bifoldable t => t [a] [a] -> [a]
- biasum :: (Bifoldable t, Alternative f) => t (f a) (f a) -> f a
- biany :: Bifoldable t => (a -> Bool) -> (b -> Bool) -> t a b -> Bool
- biand :: Bifoldable t => t Bool Bool -> Bool
- biall :: Bifoldable t => (a -> Bool) -> (b -> Bool) -> t a b -> Bool
- biList :: Bifoldable t => t a a -> [a]
- class Monad m => MonadIO (m :: Type -> Type) where
- zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m ()
- zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c]
- unless :: Applicative f => Bool -> f () -> f ()
- replicateM_ :: Applicative m => Int -> m a -> m ()
- replicateM :: Applicative m => Int -> m a -> m [a]
- mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a
- mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c])
- forever :: Applicative f => f a -> f b
- foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m ()
- foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a]
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
- (<$!>) :: Monad m => (a -> b) -> m a -> m b
- forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- newtype Identity a = Identity {
- runIdentity :: a
- writeFile :: FilePath -> String -> IO ()
- readLn :: Read a => IO a
- readIO :: Read a => String -> IO a
- readFile :: FilePath -> IO String
- putStrLn :: String -> IO ()
- putStr :: String -> IO ()
- putChar :: Char -> IO ()
- interact :: (String -> String) -> IO ()
- getLine :: IO String
- getContents :: IO String
- getChar :: IO Char
- appendFile :: FilePath -> String -> IO ()
- ioError :: IOError -> IO a
- type FilePath = String
- type IOError = IOException
- userError :: String -> IOError
- class (Typeable e, Show e) => Exception e
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- or :: Foldable t => t Bool -> Bool
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- concat :: Foldable t => t [a] -> [a]
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- and :: Foldable t => t Bool -> Bool
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- words :: String -> [String]
- unwords :: [String] -> String
- unlines :: [String] -> String
- lines :: String -> [String]
- data First a
- type Nat = Natural
- reads :: Read a => ReadS a
- data Proxy (t :: k) = Proxy
- readParen :: Bool -> ReadS a -> ReadS a
- lex :: ReadS String
- type ReadS a = String -> [(a, String)]
- odd :: Integral a => a -> Bool
- lcm :: Integral a => a -> a -> a
- gcd :: Integral a => a -> a -> a
- even :: Integral a => a -> Bool
- (^^) :: (Fractional a, Integral b) => a -> b -> a
- (^) :: (Num a, Integral b) => a -> b -> a
- type ShowS = String -> String
- shows :: Show a => a -> ShowS
- showString :: String -> ShowS
- showParen :: Bool -> ShowS -> ShowS
- showChar :: Char -> ShowS
- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- unzip :: [(a, b)] -> ([a], [b])
- takeWhile :: (a -> Bool) -> [a] -> [a]
- take :: Int -> [a] -> [a]
- tail :: [a] -> [a]
- splitAt :: Int -> [a] -> ([a], [a])
- span :: (a -> Bool) -> [a] -> ([a], [a])
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanl :: (b -> a -> b) -> b -> [a] -> [b]
- reverse :: [a] -> [a]
- replicate :: Int -> a -> [a]
- repeat :: a -> [a]
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- last :: [a] -> a
- iterate :: (a -> a) -> a -> [a]
- init :: [a] -> [a]
- head :: [a] -> a
- dropWhile :: (a -> Bool) -> [a] -> [a]
- drop :: Int -> [a] -> [a]
- cycle :: [a] -> [a]
- break :: (a -> Bool) -> [a] -> ([a], [a])
- (!!) :: [a] -> Int -> a
- maybeToList :: Maybe a -> [a]
- maybe :: b -> (a -> b) -> Maybe a -> b
- mapMaybe :: (a -> Maybe b) -> [a] -> [b]
- listToMaybe :: [a] -> Maybe a
- isNothing :: Maybe a -> Bool
- isJust :: Maybe a -> Bool
- fromMaybe :: a -> Maybe a -> a
- fromJust :: HasCallStack => Maybe a -> a
- catMaybes :: [Maybe a] -> [a]
- (&) :: a -> (a -> b) -> b
- void :: Functor f => f a -> f ()
- (<&>) :: Functor f => f a -> (a -> b) -> f b
- uncurry :: (a -> b -> c) -> (a, b) -> c
- curry :: ((a, b) -> c) -> a -> b -> c
- subtract :: Num a => a -> a -> a
- when :: Applicative f => Bool -> f () -> f ()
- until :: (a -> Bool) -> (a -> a) -> a -> a
- liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
- liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
- liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
- liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
- flip :: (a -> b -> c) -> b -> a -> c
- asTypeOf :: a -> a -> a
- ap :: Monad m => m (a -> b) -> m a -> m b
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- ($!) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b
- undefined :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => a
- errorWithoutStackTrace :: forall (r :: RuntimeRep) (a :: TYPE r). [Char] -> a
- error :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => [Char] -> a
- data SomeException
- (&&) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- data CI s
- class MonadIO m => MonadResource (m :: Type -> Type)
- class MonadTrans (t :: (Type -> Type) -> Type -> Type) where
- data DiffTime
- class NFData a where
- rnf :: a -> ()
- data HashSet a
- type Lens' s a = Lens s s a a
- type Traversal' s a = Traversal s s a a
- type Setter' s a = Setter s s a a
- type Iso' s a = Iso s s a a
- type Prism' s a = Prism s s a a
- data NominalDiffTime
- data Day
- type TextLazy = Text
- type TextBuilder = Builder
- type ByteStringLazy = ByteString
- type ByteStringBuilder = Builder
Documentation
(++) :: [a] -> [a] -> [a] infixr 5 #
Append two lists, i.e.,
[x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
If the first list is not finite, the result is the first list.
seq :: forall {r :: RuntimeRep} a (b :: TYPE r). a -> b -> b infixr 0 #
The value of seq a b
is bottom if a
is bottom, and
otherwise equal to b
. In other words, it evaluates the first
argument a
to weak head normal form (WHNF). seq
is usually
introduced to improve performance by avoiding unneeded laziness.
A note on evaluation order: the expression seq a b
does
not guarantee that a
will be evaluated before b
.
The only guarantee given by seq
is that the both a
and b
will be evaluated before seq
returns a value.
In particular, this means that b
may be evaluated before
a
. If you need to guarantee a specific order of evaluation,
you must use the function pseq
from the "parallel" package.
filter :: (a -> Bool) -> [a] -> [a] #
\(\mathcal{O}(n)\). filter
, applied to a predicate and a list, returns
the list of those elements that satisfy the predicate; i.e.,
filter p xs = [ x | x <- xs, p x]
>>>
filter odd [1, 2, 3]
[1,3]
zip :: [a] -> [b] -> [(a, b)] #
\(\mathcal{O}(\min(m,n))\). zip
takes two lists and returns a list of
corresponding pairs.
>>>
zip [1, 2] ['a', 'b']
[(1,'a'),(2,'b')]
If one input list is shorter than the other, excess elements of the longer list are discarded, even if one of the lists is infinite:
>>>
zip [1] ['a', 'b']
[(1,'a')]>>>
zip [1, 2] ['a']
[(1,'a')]>>>
zip [] [1..]
[]>>>
zip [1..] []
[]
zip
is right-lazy:
>>>
zip [] undefined
[]>>>
zip undefined []
*** Exception: Prelude.undefined ...
zip
is capable of list fusion, but it is restricted to its
first list argument and its resulting list.
print :: Show a => a -> IO () #
The print
function outputs a value of any printable type to the
standard output device.
Printable types are those that are instances of class Show
; print
converts values to strings for output using the show
operation and
adds a newline.
For example, a program to print the first 20 integers and their powers of 2 could be written as:
main = print ([(n, 2^n) | n <- [0..19]])
map :: (a -> b) -> [a] -> [b] #
\(\mathcal{O}(n)\). map
f xs
is the list obtained by applying f
to
each element of xs
, i.e.,
map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] map f [x1, x2, ...] == [f x1, f x2, ...]
>>>
map (+1) [1, 2, 3]
[2,3,4]
($) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b infixr 0 #
Application operator. This operator is redundant, since ordinary
application (f x)
means the same as (f
. However, $
x)$
has
low, right-associative binding precedence, so it sometimes allows
parentheses to be omitted; for example:
f $ g $ h x = f (g (h x))
It is also useful in higher-order situations, such as
,
or map
($
0) xs
.zipWith
($
) fs xs
Note that (
is levity-polymorphic in its result type, so that
$
)foo
where $
Truefoo :: Bool -> Int#
is well-typed.
coerce :: forall {k :: RuntimeRep} (a :: TYPE k) (b :: TYPE k). Coercible a b => a -> b #
The function coerce
allows you to safely convert between values of
types that have the same representation with no run-time overhead. In the
simplest case you can use it instead of a newtype constructor, to go from
the newtype's concrete type to the abstract type. But it also works in
more complicated settings, e.g. converting a list of newtypes to a list of
concrete types.
This function is runtime-representation polymorphic, but the
RuntimeRep
type argument is marked as Inferred
, meaning
that it is not available for visible type application. This means
the typechecker will accept coerce @Int @Age 42
.
fromIntegral :: (Integral a, Num b) => a -> b #
general coercion from integral types
realToFrac :: (Real a, Fractional b) => a -> b #
general coercion to fractional types
guard :: Alternative f => Bool -> f () #
Conditional failure of Alternative
computations. Defined by
guard True =pure
() guard False =empty
Examples
Common uses of guard
include conditionally signaling an error in
an error monad and conditionally rejecting the current choice in an
Alternative
-based parser.
As an example of signaling an error in the error monad Maybe
,
consider a safe division function safeDiv x y
that returns
Nothing
when the denominator y
is zero and
otherwise. For example:Just
(x `div`
y)
>>>
safeDiv 4 0
Nothing
>>>
safeDiv 4 2
Just 2
A definition of safeDiv
using guards, but not guard
:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y | y /= 0 = Just (x `div` y) | otherwise = Nothing
A definition of safeDiv
using guard
and Monad
do
-notation:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y = do guard (y /= 0) return (x `div` y)
The IsList
class and its methods are intended to be used in
conjunction with the OverloadedLists extension.
Since: base-4.7.0.0
The fromList
function constructs the structure l
from the given
list of Item l
fromListN :: Int -> [Item l] -> l #
The fromListN
function takes the input list's length and potentially
uses it to construct the structure l
more efficiently compared to
fromList
. If the given number does not equal to the input list's length
the behaviour of fromListN
is not specified.
fromListN (length xs) xs == fromList xs
The toList
function extracts a list of Item l
from the structure l
.
It should satisfy fromList . toList = id.
Instances
join :: Monad m => m (m a) -> m a #
The join
function is the conventional monad join operator. It
is used to remove one level of monadic structure, projecting its
bound argument into the outer level.
'
' can be understood as the join
bssdo
expression
do bs <- bss bs
Examples
A common use of join
is to run an IO
computation returned from
an STM
transaction, since STM
transactions
can't perform IO
directly. Recall that
atomically
:: STM a -> IO a
is used to run STM
transactions atomically. So, by
specializing the types of atomically
and join
to
atomically
:: STM (IO b) -> IO (IO b)join
:: IO (IO b) -> IO b
we can compose them as
join
.atomically
:: STM (IO b) -> IO b
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
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
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] #
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] #
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] #
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
The Eq
class defines equality (==
) and inequality (/=
).
All the basic datatypes exported by the Prelude are instances of Eq
,
and Eq
may be derived for any datatype whose constituents are also
instances of Eq
.
The Haskell Report defines no laws for Eq
. However, instances are
encouraged to follow these properties: