Safe Haskell | None |
---|---|
Language | Haskell2010 |
- ($) :: (a -> b) -> a -> b
- ($!) :: (a -> b) -> a -> b
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- (.) :: Category k cat => forall b c a. cat b c -> cat a b -> cat a c
- not :: Bool -> Bool
- otherwise :: Bool
- fst :: (a, b) -> a
- snd :: (a, b) -> b
- id :: Category k cat => forall a. cat a a
- maybe :: b -> (a -> b) -> Maybe a -> b
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- flip :: (a -> b -> c) -> b -> a -> c
- const :: a -> b -> a
- error :: HasCallStack => [Char] -> a
- putStr :: MonadIO m => Text -> m ()
- putStrLn :: MonadIO m => Text -> m ()
- print :: (MonadIO m, Show a) => a -> m ()
- getArgs :: MonadIO m => m [Text]
- terror :: HasCallStack => Text -> a
- odd :: Integral a => a -> Bool
- even :: Integral a => a -> Bool
- uncurry :: (a -> b -> c) -> (a, b) -> c
- curry :: ((a, b) -> c) -> a -> b -> c
- swap :: (a, b) -> (b, a)
- until :: (a -> Bool) -> (a -> a) -> a -> a
- asTypeOf :: a -> a -> a
- undefined :: HasCallStack => a
- seq :: a -> b -> b
- class Eq a => Ord a where
- class Eq a where
- class Bounded a where
- class Enum a where
- class Show a
- class Read a
- class Functor f where
- class Applicative m => Monad m where
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- class IsString a where
- class Num a where
- class (Num a, Ord a) => Real a where
- class (Real a, Enum a) => Integral a where
- class Num a => Fractional a where
- class Fractional a => Floating a where
- class (Real a, Fractional a) => RealFrac a where
- class (RealFrac a, Floating a) => RealFloat a where
- data Maybe a :: * -> *
- data Ordering :: *
- data Bool :: *
- data Char :: *
- data IO a :: * -> *
- data Either a b :: * -> * -> *
- data ByteString :: *
- type LByteString = ByteString
- data Text :: *
- type LText = Text
- data Map k a :: * -> * -> *
- data HashMap k v :: * -> * -> *
- data IntMap a :: * -> *
- data Set a :: * -> *
- data HashSet a :: * -> *
- data IntSet :: *
- data Seq a :: * -> *
- data Vector a :: * -> *
- type UVector = Vector
- class (Vector Vector a, MVector MVector a) => Unbox a
- type SVector = Vector
- class Storable a
- class Hashable a where
- data Word :: *
- data Word8 :: *
- data Word32 :: *
- data Word64 :: *
- data Int :: *
- data Int32 :: *
- data Int64 :: *
- data Integer :: *
- type Rational = Ratio Integer
- data Float :: *
- data Double :: *
- (^) :: (Num a, Integral b) => a -> b -> a
- (^^) :: (Fractional a, Integral b) => a -> b -> a
- subtract :: Num a => a -> a -> a
- fromIntegral :: (Integral a, Num b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- class Monoid a where
- (<>) :: Monoid m => m -> m -> m
- class Foldable t
- asum :: (Foldable t, Alternative f) => t (f a) -> f a
- class (Functor t, Foldable t) => Traversable t
- first :: Arrow a => forall b c d. a b c -> a (b, d) (c, d)
- second :: Arrow a => forall b c d. a b c -> a (d, b) (d, c)
- (***) :: Arrow a => forall b c b' c'. a b c -> a b' c' -> a (b, b') (c, c')
- (&&&) :: Arrow a => forall b c c'. a b c -> a b c' -> a b (c, c')
- bool :: a -> a -> Bool -> a
- mapMaybe :: (a -> Maybe b) -> [a] -> [b]
- catMaybes :: [Maybe a] -> [a]
- fromMaybe :: a -> Maybe a -> a
- isJust :: Maybe a -> Bool
- isNothing :: Maybe a -> Bool
- listToMaybe :: [a] -> Maybe a
- maybeToList :: Maybe a -> [a]
- partitionEithers :: [Either a b] -> ([a], [b])
- lefts :: [Either a b] -> [a]
- rights :: [Either a b] -> [b]
- on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
- comparing :: Ord a => (b -> a) -> b -> b -> Ordering
- equating :: Eq a => (b -> a) -> b -> b -> Bool
- newtype Down a :: * -> * = Down a
- class Functor f => Applicative f where
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<|>) :: Alternative f => forall a. f a -> f a -> f a
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- lift :: MonadTrans t => forall m a. Monad m => m a -> t m a
- class Monad m => MonadIO m where
- liftIO :: MonadIO m => forall a. IO a -> m a
- class (Typeable * e, Show e) => Exception e where
- class Typeable k a
- data SomeException :: *
- data IOException :: *
- module System.IO.Error
- type FilePath = String
- (</>) :: FilePath -> FilePath -> FilePath
- (<.>) :: FilePath -> String -> FilePath
- type String = [Char]
- hash :: Hashable a => a -> Int
- hashWithSalt :: Hashable a => Int -> a -> Int
Standard
Operators
($) :: (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
($!) :: (a -> b) -> a -> b infixr 0 #
Strict (call-by-value) application operator. It takes a function and an argument, evaluates the argument to weak head normal form (WHNF), then calls the function with that value.
Functions
maybe :: b -> (a -> b) -> Maybe a -> b #
The maybe
function takes a default value, a function, and a Maybe
value. If the Maybe
value is Nothing
, the function returns the
default value. Otherwise, it applies the function to the value inside
the Just
and returns the result.
Examples
Basic usage:
>>>
maybe False odd (Just 3)
True
>>>
maybe False odd Nothing
False
Read an integer from a string using readMaybe
. If we succeed,
return twice the integer; that is, apply (*2)
to it. If instead
we fail to parse an integer, return 0
by default:
>>>
import Text.Read ( readMaybe )
>>>
maybe 0 (*2) (readMaybe "5")
10>>>
maybe 0 (*2) (readMaybe "")
0
Apply show
to a Maybe Int
. If we have Just n
, we want to show
the underlying Int
n
. But if we have Nothing
, we return the
empty string instead of (for example) "Nothing":
>>>
maybe "" show (Just 5)
"5">>>
maybe "" show Nothing
""
either :: (a -> c) -> (b -> c) -> Either a b -> c #
Case analysis for the Either
type.
If the value is
, apply the first function to Left
aa
;
if it is
, apply the second function to Right
bb
.
Examples
We create two values of type
, one using the
Either
String
Int
Left
constructor and another using the Right
constructor. Then
we apply "either" the length
function (if we have a String
)
or the "times-two" function (if we have an Int
):
>>>
let s = Left "foo" :: Either String Int
>>>
let n = Right 3 :: Either String Int
>>>
either length (*2) s
3>>>
either length (*2) n
6
flip :: (a -> b -> c) -> b -> a -> c #
takes its (first) two arguments in the reverse order of flip
ff
.
const x
is a unary function which evaluates to x
for all inputs.
For instance,
>>>
map (const 42) [0..3]
[42,42,42,42]
error :: HasCallStack => [Char] -> a #
error
stops execution and displays an error message.
terror :: HasCallStack => Text -> a Source #
error
applied to Text
Since 0.4.1
uncurry :: (a -> b -> c) -> (a, b) -> c #
uncurry
converts a curried function to a function on pairs.
until :: (a -> Bool) -> (a -> a) -> a -> a #
yields the result of applying until
p ff
until p
holds.
undefined :: HasCallStack => a #
The value of seq a b
is bottom if a
is bottom, and
otherwise equal to b
. 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.
Type classes
The Ord
class is used for totally ordered datatypes.
Instances of Ord
can be derived for any user-defined
datatype whose constituent types are in Ord
. The declared order
of the constructors in the data declaration determines the ordering
in derived Ord
instances. The Ordering
datatype allows a single
comparison to determine the precise ordering of two objects.
Minimal complete definition: either compare
or <=
.
Using compare
can be more efficient for complex types.
compare :: a -> a -> Ordering #
(<) :: a -> a -> Bool infix 4 #
(<=) :: a -> a -> Bool infix 4 #
(>) :: a -> a -> Bool infix 4 #
Ord Bool | |
Ord Char | |
Ord Double | |
Ord Float | |
Ord Int | |
Ord Int8 | |
Ord Int16 | |
Ord Int32 | |
Ord Int64 | |
Ord Integer | |
Ord Ordering | |
Ord Word | |
Ord Word8 | |
Ord Word16 | |
Ord Word32 | |
Ord Word64 | |
Ord TypeRep | |
Ord () | |
Ord TyCon | |
Ord BigNat | |
Ord Void | |
Ord Version | |
Ord AsyncException | |
Ord ArrayException | |
Ord ExitCode | |
Ord BufferMode | |
Ord Newline | |
Ord NewlineMode | |
Ord CChar | |
Ord CSChar | |
Ord CUChar | |
Ord CShort | |
Ord CUShort | |
Ord CInt | |
Ord CUInt | |
Ord CLong | |
Ord CULong | |
Ord CLLong | |
Ord CULLong | |
Ord CFloat | |
Ord CDouble | |
Ord CPtrdiff | |
Ord CSize | |
Ord CWchar | |
Ord CSigAtomic | |
Ord CClock | |
Ord CTime | |
Ord CUSeconds | |
Ord CSUSeconds | |
Ord CIntPtr | |
Ord CUIntPtr | |
Ord CIntMax | |
Ord CUIntMax | |
Ord All | |
Ord Any | |
Ord Fixity | |
Ord Associativity | |
Ord SourceUnpackedness | |
Ord SourceStrictness | |
Ord DecidedStrictness | |
Ord ErrorCall | |
Ord ArithException | |
Ord SomeNat | |
Ord SomeSymbol | |
Ord ByteString | |
Ord ByteString | |
Ord IntSet | |
Ord a => Ord [a] | |
Ord a => Ord (Maybe a) | |
Integral a => Ord (Ratio a) | |
Ord (Ptr a) | |
Ord (FunPtr a) | |
Ord (V1 p) | |
Ord (U1 p) | |
Ord p => Ord (Par1 p) | |
Ord (ForeignPtr a) | |
Ord a => Ord (Identity a) | |
Ord a => Ord (Min a) | |
Ord a => Ord (Max a) | |
Ord a => Ord (First a) | |
Ord a => Ord (Last a) | |
Ord m => Ord (WrappedMonoid m) | |
Ord a => Ord (Option a) | |
Ord a => Ord (NonEmpty a) | |
Ord a => Ord (ZipList a) | |
Ord a => Ord (Dual a) | |
Ord a => Ord (Sum a) | |
Ord a => Ord (Product a) | |
Ord a => Ord (First a) | |
Ord a => Ord (Last a) | |
Ord a => Ord (Down a) | |
Ord a => Ord (IntMap a) | |
Ord a => Ord (Seq a) | |
Ord a => Ord (ViewL a) | |
Ord a => Ord (ViewR a) | |
Ord a => Ord (Set a) | |
Ord a => Ord (Hashed a) | |
Ord a => Ord (Array a) | |
Ord a => Ord (Vector a) | |
(Storable a, Ord a) => Ord (Vector a) | |
(Prim a, Ord a) => Ord (Vector a) | |
(Ord b, Ord a) => Ord (Either a b) | |
Ord (f p) => Ord (Rec1 f p) | |
Ord (URec Char p) | |
Ord (URec Double p) | |
Ord (URec Float p) | |
Ord (URec Int p) | |
Ord (URec Word p) | |
Ord (URec (Ptr ()) p) | |
(Ord a, Ord b) => Ord (a, b) | |
Ord a => Ord (Arg a b) | |
Ord (Proxy k s) | |
(Ord k, Ord v) => Ord (Map k v) | |
(Ord1 m, Ord a) => Ord (MaybeT m a) | |
(Ord1 m, Ord a) => Ord (ListT m a) | |
Ord c => Ord (K1 i c p) | |
(Ord (g p), Ord (f p)) => Ord ((:+:) f g p) | |
(Ord (g p), Ord (f p)) => Ord ((:*:) f g p) | |
Ord (f (g p)) => Ord ((:.:) f g p) | |
(Ord a, Ord b, Ord c) => Ord (a, b, c) | |
Ord a => Ord (Const k a b) | |
Ord (f a) => Ord (Alt k f a) | |
Ord ((:~:) k a b) | |
(Ord w, Ord1 m, Ord a) => Ord (WriterT w m a) | |
(Ord w, Ord1 m, Ord a) => Ord (WriterT w m a) | |
(Ord1 f, Ord a) => Ord (IdentityT * f a) | |
(Ord e, Ord1 m, Ord a) => Ord (ExceptT e m a) | |
(Ord e, Ord1 m, Ord a) => Ord (ErrorT e m a) | |
Ord (f p) => Ord (M1 i c f p) | |
(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) | |
(Ord1 f, Ord1 g, Ord a) => Ord (Sum * f g a) | |
(Ord1 f, Ord1 g, Ord a) => Ord (Product * f g a) | |
(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) | |
(Ord1 f, Ord1 g, Ord a) => Ord (Compose * * f g a) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (a, b, c, d, e, f, g, h) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (a, b, c, d, e, f, g, h, i) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (a, b, c, d, e, f, g, h, i, j) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (a, b, c, d, e, f, g, h, i, j, k) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (a, b, c, d, e, f, g, h, i, j, k, l) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
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
.
Eq Bool | |
Eq Char | |
Eq Double | |
Eq Float | |
Eq Int | |
Eq Int8 | |
Eq Int16 | |
Eq Int32 | |
Eq Int64 | |
Eq Integer | |
Eq Ordering | |
Eq Word | |
Eq Word8 | |
Eq Word16 | |
Eq Word32 | |
Eq Word64 | |
Eq TypeRep | |
Eq () | |
Eq TyCon | |
Eq Handle | |
Eq BigNat | |
Eq SpecConstrAnnotation | |
Eq Void | |
Eq Version | |
Eq AsyncException | |
Eq ArrayException | |
Eq ExitCode | |
Eq IOErrorType | |
Eq BufferMode | |
Eq Newline | |
Eq NewlineMode | |
Eq CChar | |
Eq CSChar | |
Eq CUChar | |
Eq CShort | |
Eq CUShort | |
Eq CInt | |
Eq CUInt | |
Eq CLong | |
Eq CULong | |
Eq CLLong | |
Eq CULLong | |
Eq CFloat | |
Eq CDouble | |
Eq CPtrdiff | |
Eq CSize | |
Eq CWchar | |
Eq CSigAtomic | |
Eq CClock | |
Eq CTime | |
Eq CUSeconds | |
Eq CSUSeconds | |
Eq CIntPtr | |
Eq CUIntPtr | |
Eq CIntMax | |
Eq CUIntMax | |
Eq All | |
Eq Any | |
Eq Fixity | |
Eq Associativity | |
Eq SourceUnpackedness | |
Eq SourceStrictness | |
Eq DecidedStrictness | |
Eq MaskingState | |
Eq IOException | |
Eq ErrorCall | |
Eq ArithException | |
Eq SomeNat | |
Eq SomeSymbol | |
Eq SrcLoc | |
Eq ByteString | |
Eq ByteString | |
Eq IntSet | |
Eq CodePoint | |
Eq DecoderState | |
Eq UnicodeException | |
Eq a => Eq [a] | |
Eq a => Eq (Maybe a) | |
Eq a => Eq (Ratio a) | |
Eq (Ptr a) | |
Eq (FunPtr a) | |
Eq (V1 p) | |
Eq (U1 p) | |
Eq p => Eq (Par1 p) | |
Eq (ForeignPtr a) | |
Eq a => Eq (Identity a) | |
Eq a => Eq (Min a) | |
Eq a => Eq (Max a) | |
Eq a => Eq (First a) | |
Eq a => Eq (Last a) | |
Eq m => Eq (WrappedMonoid m) | |
Eq a => Eq (Option a) | |
Eq a => Eq (NonEmpty a) | |
Eq a => Eq (Complex a) | |
Eq a => Eq (ZipList a) | |
Eq a => Eq (Dual a) | |
Eq a => Eq (Sum a) | |
Eq a => Eq (Product a) | |
Eq a => Eq (First a) | |
Eq a => Eq (Last a) | |
Eq a => Eq (Down a) | |
Eq a => Eq (IntMap a) | |
Eq a => Eq (Seq a) | |
Eq a => Eq (ViewL a) | |
Eq a => Eq (ViewR a) | |
Eq a => Eq (Set a) | |
Eq a => Eq (Hashed a) | Uses precomputed hash to detect inequality faster |
Eq a => Eq (Array a) | |
Eq a => Eq (HashSet a) | |
Eq a => Eq (Vector a) | |
(Storable a, Eq a) => Eq (Vector a) | |
(Prim a, Eq a) => Eq (Vector a) | |
(Eq b, Eq a) => Eq (Either a b) | |
Eq (f p) => Eq (Rec1 f p) | |
Eq (URec Char p) | |
Eq (URec Double p) | |
Eq (URec Float p) | |
Eq (URec Int p) | |
Eq (URec Word p) | |
Eq (URec (Ptr ()) p) | |
(Eq a, Eq b) => Eq (a, b) | |
Eq a => Eq (Arg a b) | |
Eq (Proxy k s) | |
(Eq k, Eq a) => Eq (Map k a) | |
Eq (MutableArray s a) | |
(Eq1 m, Eq a) => Eq (MaybeT m a) | |
(Eq1 m, Eq a) => Eq (ListT m a) | |
(Eq v, Eq k) => Eq (Leaf k v) | |
(Eq k, Eq v) => Eq (HashMap k v) | |
Eq c => Eq (K1 i c p) | |
(Eq (g p), Eq (f p)) => Eq ((:+:) f g p) | |
(Eq (g p), Eq (f p)) => Eq ((:*:) f g p) | |
Eq (f (g p)) => Eq ((:.:) f g p) | |
(Eq a, Eq b, Eq c) => Eq (a, b, c) | |
Eq a => Eq (Const k a b) | |
Eq (f a) => Eq (Alt k f a) | |
Eq ((:~:) k a b) | |
(Eq w, Eq1 m, Eq a) => Eq (WriterT w m a) | |
(Eq w, Eq1 m, Eq a) => Eq (WriterT w m a) | |
(Eq1 f, Eq a) => Eq (IdentityT * f a) | |
(Eq e, Eq1 m, Eq a) => Eq (ExceptT e m a) | |
(Eq e, Eq1 m, Eq a) => Eq (ErrorT e m a) | |
Eq (f p) => Eq (M1 i c f p) | |
(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) | |
(Eq1 f, Eq1 g, Eq a) => Eq (Sum * f g a) | |
(Eq1 f, Eq1 g, Eq a) => Eq (Product * f g a) | |
(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) | |
(Eq1 f, Eq1 g, Eq a) => Eq (Compose * * f g a) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
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
.
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..]
.
enumFromThen :: a -> a -> [a] #
Used in Haskell's translation of [n,n'..]
.
enumFromTo :: a -> a -> [a] #
Used in Haskell's translation of [n..m]
.
enumFromThenTo :: a -> a -> a -> [a] #
Used in Haskell's translation of [n,n'..m]
.
Enum Bool | |
Enum Char | |
Enum Int | |
Enum Int8 | |
Enum Int16 | |
Enum Int32 | |
Enum Int64 | |
Enum Integer | |
Enum Ordering | |
Enum Word | |
Enum Word8 | |
Enum Word16 | |
Enum Word32 | |
Enum Word64 | |
Enum () | |
Enum CChar | |
Enum CSChar | |
Enum CUChar | |
Enum CShort | |
Enum CUShort | |
Enum CInt | |
Enum CUInt | |
Enum CLong | |
Enum CULong | |
Enum CLLong | |
Enum CULLong | |
Enum CFloat | |
Enum CDouble | |
Enum CPtrdiff | |
Enum CSize | |
Enum CWchar | |
Enum CSigAtomic | |
Enum CClock | |
Enum CTime | |
Enum CUSeconds | |
Enum CSUSeconds | |
Enum CIntPtr | |
Enum CUIntPtr | |
Enum CIntMax | |
Enum CUIntMax | |
Enum Associativity | |
Enum SourceUnpackedness | |
Enum SourceStrictness | |
Enum DecidedStrictness | |
Integral a => Enum (Ratio a) | |
Enum a => Enum (Identity a) | |
Enum a => Enum (Min a) | |
Enum a => Enum (Max a) | |
Enum a => Enum (First a) | |
Enum a => Enum (Last a) | |
Enum a => Enum (WrappedMonoid a) | |
Enum (Proxy k s) | |
Enum a => Enum (Const k a b) | |
Enum (f a) => Enum (Alt k f a) | |
(~) k a b => Enum ((:~:) k a b) | |
Conversion of values to readable String
s.
Derived instances of Show
have the following properties, which
are compatible with derived instances of Read
:
- The result of
show
is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used. - If the constructor is defined to be an infix operator, then
showsPrec
will produce infix applications of the constructor. - the representation will be enclosed in parentheses if the
precedence of the top-level constructor in
x
is less thand
(associativity is ignored). Thus, ifd
is0
then the result is never surrounded in parentheses; ifd
is11
it is always surrounded in parentheses, unless it is an atomic expression. - If the constructor is defined using record syntax, then
show
will produce the record-syntax form, with the fields given in the same order as the original declaration.
For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Show
is equivalent to
instance (Show a) => Show (Tree a) where showsPrec d (Leaf m) = showParen (d > app_prec) $ showString "Leaf " . showsPrec (app_prec+1) m where app_prec = 10 showsPrec d (u :^: v) = showParen (d > up_prec) $ showsPrec (up_prec+1) u . showString " :^: " . showsPrec (up_prec+1) v where up_prec = 5
Note that right-associativity of :^:
is ignored. For example,
produces the stringshow
(Leaf 1 :^: Leaf 2 :^: Leaf 3)"Leaf 1 :^: (Leaf 2 :^: Leaf 3)"
.