The Maybe
type encapsulates an optional value. A value of type
either contains a value of type Maybe
aa
(represented as
), or it is empty (represented as Just
aNothing
). Using Maybe
is a good way to deal with errors or exceptional cases without resorting to drastic measures such as error
.
The Maybe
type is also a monad. It is a simple kind of error monad, where all errors are represented by Nothing
. A richer error monad can be built using the Either
type.
maybe :: b -> (a -> b) -> Maybe a -> bSource
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.
The Either
type represents values with two possibilities: a value of type
is either Either
a b
or Left
a
.Right
b
The Either
type is sometimes used to represent a value which is either correct or an error; by convention, the Left
constructor is used to hold an error value and the Right
constructor is used to hold a correct value (mnemonic: "right" also means "correct").
either :: (a -> c) -> (b -> c) -> Either a b -> cSource
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
.
The character type Char
is an enumeration whose values represent Unicode (or equivalently ISO/IEC 10646) characters (see http://www.unicode.org/ for details). This set extends the ISO 8859-1 (Latin-1) character set (the first 256 characters), which is itself an extension of the ASCII character set (the first 128 characters). A character literal in Haskell has type Char
.
To convert a Char
to or from the corresponding Int
value defined by Unicode, use toEnum
and fromEnum
from the Enum
class respectively (or equivalently ord
and chr
).
Extract the first component of a pair.
Extract the second component of a pair.
curry :: ((a, b) -> c) -> a -> b -> cSource
curry
converts an uncurried function to a curried function.
uncurry :: (a -> b -> c) -> (a, b) -> cSource
uncurry
converts a curried function to a function on pairs.
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
.
Minimal complete definition: either ==
or /=
.
Instances
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 () Eq TyCon Eq TypeRep Eq ArithException Eq IOException Eq MaskingState Eq Number Eq Lexeme Eq Fingerprint Eq IOMode Eq SeekMode Eq IODeviceType Eq CUIntMax Eq CIntMax Eq CUIntPtr Eq CIntPtr Eq CSUSeconds Eq CUSeconds Eq CTime Eq CClock Eq CSigAtomic Eq CWchar Eq CSize Eq CPtrdiff Eq CDouble Eq CFloat Eq CULLong Eq CLLong Eq CULong Eq CLong Eq CUInt Eq CInt Eq CUShort Eq CShort Eq CUChar Eq CSChar Eq CChar Eq GeneralCategory Eq TypeRepKey Eq Associativity Eq Fixity Eq Arity Eq Finalizers Eq IntPtr Eq WordPtr Eq Any Eq All Eq Inserts Eq HashData Eq BufferState Eq CodingProgress Eq NewlineMode Eq Newline Eq BufferMode Eq Handle Eq IOErrorType Eq ExitCode Eq ArrayException Eq AsyncException Eq Errno Eq ThreadStatus Eq BlockReason Eq ThreadId Eq Fd Eq CRLim Eq CTcflag Eq CSpeed Eq CCc Eq CUid Eq CNlink Eq CGid Eq CSsize Eq CPid Eq COff Eq CMode Eq CIno Eq CDev Eq ControlMessage Eq Event Eq EventType Eq EPollFd Eq Unique Eq State Eq TimeoutKey Eq FdKey Eq HandlePosn Eq Event Eq Fixity Eq ConstrRep Eq DataRep Eq ConstrEquality of constructors
Eq SpecConstrAnnotation Eq Unique Eq QSem Eq QSemN Eq Timeout Eq Version Eq a => Eq [a] Eq a => Eq (Ratio a) Eq (StablePtr a) Eq (Ptr a) Eq (FunPtr a) Eq a => Eq (Maybe a) Eq (MVar a) Eq a => Eq (Down a) Eq (IORef a) Eq (ForeignPtr a) Eq a => Eq (Last a) Eq a => Eq (First a) Eq a => Eq (Product a) Eq a => Eq (Sum a) Eq a => Eq (Dual a) Eq (TVar a) Eq a => Eq (IntMap a) Eq a => Eq (LTree a) Eq a => Eq (PSQ a) Eq a => Eq (Elem a) Eq (Chan a) Eq (SampleVar a) Eq a => Eq (Complex a) Eq (Fixed a) Eq (StableName a) (Eq a, Eq b) => Eq (Either a b) (Eq a, Eq b) => Eq (a, b) (Ix i, Eq e) => Eq (Array i e) Eq (IOArray i e) Eq (STRef s a) (Eq a, Eq b, Eq c) => Eq (a, b, c) Eq (STArray s i e) (Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) (Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) (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)class Eq a => Ord a whereSource
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.
Instances
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 () Ord TyCon Ord TypeRep Ord ArithException Ord Fingerprint Ord IOMode Ord SeekMode Ord CUIntMax Ord CIntMax Ord CUIntPtr Ord CIntPtr Ord CSUSeconds Ord CUSeconds Ord CTime Ord CClock Ord CSigAtomic Ord CWchar Ord CSize Ord CPtrdiff Ord CDouble Ord CFloat Ord CULLong Ord CLLong Ord CULong Ord CLong Ord CUInt Ord CInt Ord CUShort Ord CShort Ord CUChar Ord CSChar Ord CChar Ord GeneralCategory Ord TypeRepKey Ord Associativity Ord Fixity Ord Arity Ord IntPtr Ord WordPtr Ord Any Ord All Ord NewlineMode Ord Newline Ord BufferMode Ord ExitCode Ord ArrayException Ord AsyncException Ord ThreadStatus Ord BlockReason Ord ThreadId Ord Fd Ord CRLim Ord CTcflag Ord CSpeed Ord CCc Ord CUid Ord CNlink Ord CGid Ord CSsize Ord CPid Ord COff Ord CMode Ord CIno Ord CDev Ord Unique Ord Unique Ord Version (Eq [a], Ord a) => Ord [a] (Eq (Ratio a), Integral a) => Ord (Ratio a) Eq (Ptr a) => Ord (Ptr a) Eq (FunPtr a) => Ord (FunPtr a) (Eq (Maybe a), Ord a) => Ord (Maybe a) (Eq (Down a), Ord a) => Ord (Down a) Eq (ForeignPtr a) => Ord (ForeignPtr a) (Eq (Last a), Ord a) => Ord (Last a) (Eq (First a), Ord a) => Ord (First a) (Eq (Product a), Ord a) => Ord (Product a) (Eq (Sum a), Ord a) => Ord (Sum a) (Eq (Dual a), Ord a) => Ord (Dual a) Eq (Fixed a) => Ord (Fixed a) (Eq (Either a b), Ord a, Ord b) => Ord (Either a b) (Eq (a, b), Ord a, Ord b) => Ord (a, b) (Eq (Array i e), Ix i, Ord e) => Ord (Array i e) (Eq (a, b, c), Ord a, Ord b, Ord c) => Ord (a, b, c) (Eq (a, b, c, d), Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) (Eq (a, b, c, d, e), Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) (Eq (a, b, c, d, e, f), Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) (Eq (a, b, c, d, e, f, g), Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) (Eq (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 (a, b, c, d, e, f, g, h) (Eq (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 (a, b, c, d, e, f, g, h, i) (Eq (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 (a, b, c, d, e, f, g, h, i, j) (Eq (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 (a, b, c, d, e, f, g, h, i, j, k) (Eq (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 (a, b, c, d, e, f, g, h, i, j, k, l) (Eq (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 (a, b, c, d, e, f, g, h, i, j, k, l, m) (Eq (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 (a, b, c, d, e, f, g, h, i, j, k, l, m, n) (Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o), 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)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:
succ
maxBound
and pred
minBound
should result in a runtime error.fromEnum
and toEnum
should give a runtime error if the result value is not representable in the result type. For example, toEnum
7 :: Bool
is an error.enumFrom
and enumFromThen
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 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 Bool Bounded Char Bounded Int Bounded Int8 Bounded Int16 Bounded Int32 Bounded Int64 Bounded Ordering Bounded Word Bounded Word8 Bounded Word16 Bounded Word32 Bounded Word64 Bounded () Bounded CUIntMax Bounded CIntMax Bounded CUIntPtr Bounded CIntPtr Bounded CSigAtomic Bounded CWchar Bounded CSize Bounded CPtrdiff Bounded CULLong Bounded CLLong Bounded CULong Bounded CLong Bounded CUInt Bounded CInt Bounded CUShort Bounded CShort Bounded CUChar Bounded CSChar Bounded CChar Bounded GeneralCategory Bounded IntPtr Bounded WordPtr Bounded Any Bounded All Bounded Fd Bounded CRLim Bounded CTcflag Bounded CUid Bounded CNlink Bounded CGid Bounded CSsize Bounded CPid Bounded COff Bounded CMode Bounded CIno Bounded CDev Bounded a => Bounded (Product a) Bounded a => Bounded (Sum a) Bounded a => Bounded (Dual a) (Bounded a, Bounded b) => Bounded (a, b) (Bounded a, Bounded b, Bounded c) => Bounded (a, b, c) (Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (a, b, c, d) (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e) => Bounded (a, b, c, d, e) (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f) => Bounded (a, b, c, d, e, f) (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g) => Bounded (a, b, c, d, e, f, g) (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) (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) (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) (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) (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) (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) (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) (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) Numbers Numeric typesA fixed-precision integer type with at least the range [-2^29 .. 2^29-1]
. The exact range for a given implementation can be determined by using minBound
and maxBound
from the Bounded
class.
Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.
Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.
type Rational = Ratio IntegerSource
Arbitrary-precision rational numbers, represented as a ratio of two Integer
values. A rational number may be constructed using the %
operator.
Basic numeric class.
Minimal complete definition: all except negate
or (-)
class Fractional a => Floating a whereSource
Trigonometric and hyperbolic functions and related functions.
Minimal complete definition: pi
, exp
, log
, sin
, cos
, sinh
, cosh
, asin
, acos
, atan
, asinh
, acosh
and atanh
Methods
exp, sqrt, log :: a -> aSource
(**), logBase :: a -> a -> aSource
asin, atan, acos :: a -> aSource
sinh, tanh, cosh :: a -> aSource
asinh, atanh, acosh :: a -> aSource
class (RealFrac a, Floating a) => RealFloat a whereSource
Methods
floatRadix :: a -> IntegerSource
a constant function, returning the radix of the representation (often 2
)
floatDigits :: a -> IntSource
a constant function, returning the number of digits of floatRadix
in the significand
floatRange :: a -> (Int, Int)Source
a constant function, returning the lowest and highest values the exponent may assume
decodeFloat :: a -> (Integer, Int)Source
The function decodeFloat
applied to a real floating-point number returns the significand expressed as an Integer
and an appropriately scaled exponent (an Int
). If
yields decodeFloat
x(m,n)
, then x
is equal in value to m*b^^n
, where b
is the floating-point radix, and furthermore, either m
and n
are both zero or else b^(d-1) <=
, where abs
m < b^dd
is the value of
. In particular, floatDigits
x
. If the type contains a negative zero, also decodeFloat
0 = (0,0)
. The result of decodeFloat
(-0.0) = (0,0)
is unspecified if either of decodeFloat
x
or isNaN
x
is isInfinite
xTrue
.
encodeFloat :: Integer -> Int -> aSource
encodeFloat
performs the inverse of decodeFloat
in the sense that for finite x
with the exception of -0.0
,
. uncurry
encodeFloat
(decodeFloat
x) = x
is one of the two closest representable floating-point numbers to encodeFloat
m nm*b^^n
(or ±Infinity
if overflow occurs); usually the closer, but if m
contains too many bits, the result may be rounded in the wrong direction.
exponent
corresponds to the second component of decodeFloat
.
and for finite nonzero exponent
0 = 0x
,
. If exponent
x = snd (decodeFloat
x) + floatDigits
xx
is a finite floating-point number, it is equal in value to
, where significand
x * b ^^ exponent
xb
is the floating-point radix. The behaviour is unspecified on infinite or NaN
values.
significand :: a -> aSource
The first component of decodeFloat
, scaled to lie in the open interval (-1
,1
), either 0.0
or of absolute value >= 1/b
, where b
is the floating-point radix. The behaviour is unspecified on infinite or NaN
values.
scaleFloat :: Int -> a -> aSource
multiplies a floating-point number by an integer power of the radix
True
if the argument is an IEEE "not-a-number" (NaN) value
isInfinite :: a -> BoolSource
True
if the argument is an IEEE infinity or negative infinity
isDenormalized :: a -> BoolSource
True
if the argument is too small to be represented in normalized format
isNegativeZero :: a -> BoolSource
True
if the argument is an IEEE negative zero
True
if the argument is an IEEE floating point number
a version of arctangent taking two real floating-point arguments. For real floating x
and y
,
computes the angle (from the positive x-axis) of the vector from the origin to the point atan2
y x(x,y)
.
returns a value in the range [atan2
y x-pi
, pi
]. It follows the Common Lisp semantics for the origin when signed zeroes are supported.
, with atan2
y 1y
in a type that is RealFloat
, should return the same value as
. A default definition of atan
yatan2
is provided, but implementors can provide a more accurate implementation.
subtract :: Num a => a -> a -> aSource
Because -
is treated specially in the Haskell grammar, (-
e)
is not a section, but an application of prefix negation. However, (
expsubtract
)
is equivalent to the disallowed section.
even :: Integral a => a -> BoolSource
odd :: Integral a => a -> BoolSource
gcd :: Integral a => a -> a -> aSource
is the non-negative factor of both gcd
x yx
and y
of which every common factor of x
and y
is also a factor; for example
, gcd
4 2 = 2
, gcd
(-4) 6 = 2
= gcd
0 44
.
= gcd
0 00
. (That is, the common divisor that is "greatest" in the divisibility preordering.)
Note: Since for signed fixed-width integer types,
, the result may be negative if one of the arguments is abs
minBound
< 0
(and necessarily is if the other is minBound
0
or
) for such types.minBound
lcm :: Integral a => a -> a -> aSource
is the smallest positive integer that both lcm
x yx
and y
divide.
The Monad
class defines the basic operations over a monad, a concept from a branch of mathematics known as category theory. From the perspective of a Haskell programmer, however, it is best to think of a monad as an abstract datatype of actions. Haskell's do
expressions provide a convenient syntax for writing monadic expressions.
Minimal complete definition: >>=
and return
.
Instances of Monad
should satisfy the following laws:
return a >>= k == k a m >>= return == m m >>= (\x -> k x >>= h) == (m >>= k) >>= h
Instances of both Monad
and Functor
should additionally satisfy the law:
fmap f xs == xs >>= return . f
The instances of Monad
for lists, Maybe
and IO
defined in the Prelude satisfy these laws.
Methods
(>>=) :: forall a b. m a -> (a -> m b) -> m bSource
Sequentially compose two actions, passing any value produced by the first as an argument to the second.
(>>) :: forall a b. m a -> m b -> m bSource
Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.
Inject a value into the monadic type.
Fail with a message. This operation is not part of the mathematical definition of a monad, but is invoked on pattern-match failure in a do
expression.
The Functor
class is used for types that can be mapped over. Instances of Functor
should satisfy the following laws:
fmap id == id fmap (f . g) == fmap f . fmap g
The instances of Functor
for lists, Maybe
and IO
satisfy these laws.
sequence :: Monad m => [m a] -> m [a]Source
Evaluate each action in the sequence from left to right, and collect the results.
sequence_ :: Monad m => [m a] -> m ()Source
Evaluate each action in the sequence from left to right, and ignore the results.
(=<<) :: Monad m => (a -> m b) -> m a -> m bSource
Same as >>=
, but with the arguments interchanged.
(.) :: (b -> c) -> (a -> b) -> a -> cSource
Function composition.
flip :: (a -> b -> c) -> b -> a -> cSource
takes its (first) two arguments in the reverse order of flip
ff
.
($) :: (a -> b) -> a -> bSource
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
until :: (a -> Bool) -> (a -> a) -> a -> aSource
yields the result of applying until
p ff
until p
holds.
asTypeOf
is a type-restricted version of const
. It is usually used as an infix operator, and its typing forces its first argument (which is usually overloaded) to have the same type as the second.
A special case of error
. It is expected that compilers will recognize this and insert error messages which are more appropriate to the context in which undefined
appears.
Evaluates its first argument to head normal form, and then returns its second argument as the result.
($!) :: (a -> b) -> a -> bSource
Strict (call-by-value) application, defined in terms of seq
.
map :: (a -> b) -> [a] -> [b]Source
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, ...]
(++) :: [a] -> [a] -> [a]Source
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.
filter :: (a -> Bool) -> [a] -> [a]Source
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]
Extract the first element of a list, which must be non-empty.
Extract the last element of a list, which must be finite and non-empty.
Extract the elements after the head of a list, which must be non-empty.
Return all the elements of a list except the last one. The list must be non-empty.
O(n). length
returns the length of a finite list as an Int
. It is an instance of the more general genericLength
, the result type of which may be any kind of number.
List index (subscript) operator, starting from 0. It is an instance of the more general genericIndex
, which takes an index of any integral type.
reverse
xs
returns the elements of xs
in reverse order. xs
must be finite.
foldl :: (a -> b -> a) -> a -> [b] -> aSource
foldl
, applied to a binary operator, a starting value (typically the left-identity of the operator), and a list, reduces the list using the binary operator, from left to right:
foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
The list must be finite.
foldl1 :: (a -> a -> a) -> [a] -> aSource
foldl1
is a variant of foldl
that has no starting value argument, and thus must be applied to non-empty lists.
foldr :: (a -> b -> b) -> b -> [a] -> bSource
foldr
, applied to a binary operator, a starting value (typically the right-identity of the operator), and a list, reduces the list using the binary operator, from right to left:
foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
foldr1 :: (a -> a -> a) -> [a] -> aSource
foldr1
is a variant of foldr
that has no starting value argument, and thus must be applied to non-empty lists.
and
returns the conjunction of a Boolean list. For the result to be True
, the list must be finite; False
, however, results from a False
value at a finite index of a finite or infinite list.
or
returns the disjunction of a Boolean list. For the result to be False
, the list must be finite; True
, however, results from a True
value at a finite index of a finite or infinite list.
any :: (a -> Bool) -> [a] -> BoolSource
Applied to a predicate and a list, any
determines if any element of the list satisfies the predicate. For the result to be False
, the list must be finite; True
, however, results from a True
value for the predicate applied to an element at a finite index of a finite or infinite list.
all :: (a -> Bool) -> [a] -> BoolSource
Applied to a predicate and a list, all
determines if all elements of the list satisfy the predicate. For the result to be True
, the list must be finite; False
, however, results from a False
value for the predicate applied to an element at a finite index of a finite or infinite list.
sum :: Num a => [a] -> aSource
The sum
function computes the sum of a finite list of numbers.
concatMap :: (a -> [b]) -> [a] -> [b]Source
Map a function over a list and concatenate the results.
maximum :: Ord a => [a] -> aSource
maximum
returns the maximum value from a list, which must be non-empty, finite, and of an ordered type. It is a special case of maximumBy
, which allows the programmer to supply their own comparison function.
minimum :: Ord a => [a] -> aSource
minimum
returns the minimum value from a list, which must be non-empty, finite, and of an ordered type. It is a special case of minimumBy
, which allows the programmer to supply their own comparison function.
scanl :: (a -> b -> a) -> a -> [b] -> [a]Source
scanl
is similar to foldl
, but returns a list of successive reduced values from the left:
scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
Note that
last (scanl f z xs) == foldl f z xs.
scanl1 :: (a -> a -> a) -> [a] -> [a]Source
scanl1
is a variant of scanl
that has no starting value argument:
scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
scanr :: (a -> b -> b) -> b -> [a] -> [b]Source
scanr
is the right-to-left dual of scanl
. Note that
head (scanr f z xs) == foldr f z xs.Infinite lists
iterate :: (a -> a) -> a -> [a]Source
iterate
f x
returns an infinite list of repeated applications of f
to x
:
iterate f x == [x, f x, f (f x), ...]
cycle
ties a finite list into a circular one, or equivalently, the infinite repetition of the original list. It is the identity on infinite lists.
take :: Int -> [a] -> [a]Source
take
n
, applied to a list xs
, returns the prefix of xs
of length n
, or xs
itself if n >
:length
xs
take 5 "Hello World!" == "Hello" take 3 [1,2,3,4,5] == [1,2,3] take 3 [1,2] == [1,2] take 3 [] == [] take (-1) [1,2] == [] take 0 [1,2] == []
It is an instance of the more general genericTake
, in which n
may be of any integral type.
drop :: Int -> [a] -> [a]Source
drop
n xs
returns the suffix of xs
after the first n
elements, or []
if n >
:length
xs
drop 6 "Hello World!" == "World!" drop 3 [1,2,3,4,5] == [4,5] drop 3 [1,2] == [] drop 3 [] == [] drop (-1) [1,2] == [1,2] drop 0 [1,2] == [1,2]
It is an instance of the more general genericDrop
, in which n
may be of any integral type.
splitAt :: Int -> [a] -> ([a], [a])Source
splitAt
n xs
returns a tuple where first element is xs
prefix of length n
and second element is the remainder of the list:
splitAt 6 "Hello World!" == ("Hello ","World!") splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5]) splitAt 1 [1,2,3] == ([1],[2,3]) splitAt 3 [1,2,3] == ([1,2,3],[]) splitAt 4 [1,2,3] == ([1,2,3],[]) splitAt 0 [1,2,3] == ([],[1,2,3]) splitAt (-1) [1,2,3] == ([],[1,2,3])
It is equivalent to (
when take
n xs, drop
n xs)n
is not _|_
(splitAt _|_ xs = _|_
). splitAt
is an instance of the more general genericSplitAt
, in which n
may be of any integral type.
takeWhile :: (a -> Bool) -> [a] -> [a]Source
takeWhile
, applied to a predicate p
and a list xs
, returns the longest prefix (possibly empty) of xs
of elements that satisfy p
:
takeWhile (< 3) [1,2,3,4,1,2,3,4] == [1,2] takeWhile (< 9) [1,2,3] == [1,2,3] takeWhile (< 0) [1,2,3] == []
dropWhile :: (a -> Bool) -> [a] -> [a]Source
dropWhile
p xs
returns the suffix remaining after takeWhile
p xs
:
dropWhile (< 3) [1,2,3,4,5,1,2,3] == [3,4,5,1,2,3] dropWhile (< 9) [1,2,3] == [] dropWhile (< 0) [1,2,3] == [1,2,3]
span :: (a -> Bool) -> [a] -> ([a], [a])Source
span
, applied to a predicate p
and a list xs
, returns a tuple where first element is longest prefix (possibly empty) of xs
of elements that satisfy p
and second element is the remainder of the list:
span (< 3) [1,2,3,4,1,2,3,4] == ([1,2],[3,4,1,2,3,4]) span (< 9) [1,2,3] == ([1,2,3],[]) span (< 0) [1,2,3] == ([],[1,2,3])
span
p xs
is equivalent to (
takeWhile
p xs, dropWhile
p xs)
break :: (a -> Bool) -> [a] -> ([a], [a])Source
break
, applied to a predicate p
and a list xs
, returns a tuple where first element is longest prefix (possibly empty) of xs
of elements that do not satisfy p
and second element is the remainder of the list:
break (> 3) [1,2,3,4,1,2,3,4] == ([1,2,3],[4,1,2,3,4]) break (< 9) [1,2,3] == ([],[1,2,3]) break (> 9) [1,2,3] == ([1,2,3],[])
break
p
is equivalent to
.span
(not
. p)
elem :: Eq a => a -> [a] -> BoolSource
elem
is the list membership predicate, usually written in infix form, e.g., x `elem` xs
. For the result to be False
, the list must be finite; True
, however, results from an element equal to x
found at a finite index of a finite or infinite list.
zip :: [a] -> [b] -> [(a, b)]Source
zip
takes two lists and returns a list of corresponding pairs. If one input list is short, excess elements of the longer list are discarded.
zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]Source
zip3
takes three lists and returns a list of triples, analogous to zip
.
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]Source
zipWith
generalises zip
by zipping with the function given as the first argument, instead of a tupling function. For example,
is applied to two lists to produce the list of corresponding sums.zipWith
(+)
zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]Source
The zipWith3
function takes a function which combines three elements, as well as three lists and returns a list of their point-wise combination, analogous to zipWith
.
unzip :: [(a, b)] -> ([a], [b])Source
unzip
transforms a list of pairs into a list of first components and a list of second components.
unzip3 :: [(a, b, c)] -> ([a], [b], [c])Source
The unzip3
function takes a list of triples and returns three lists, analogous to unzip
.
lines :: String -> [String]Source
lines
breaks a string up into a list of strings at newline characters. The resulting strings do not contain newlines.
String
Converting to String
type ShowS = String -> StringSource
The shows
functions return a function that prepends the output String
to an existing String
. This allows constant-time concatenation of results using function composition.
Conversion of values to readable String
s.
Minimal complete definition: showsPrec
or show
.
Derived instances of Show
have the following properties, which are compatible with derived instances of Read
:
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.showsPrec
will produce infix applications of the constructor.x
is less than d
(associativity is ignored). Thus, if d
is 0
then the result is never surrounded in parentheses; if d
is 11
it is always surrounded in parentheses, unless it is an atomic expression.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,
show
(Leaf 1 :^: Leaf 2 :^: Leaf 3)
produces the string "Leaf 1 :^: (Leaf 2 :^: Leaf 3)"
.Methods
Arguments
:: Intthe operator precedence of the enclosing context (a number from 0
to 11
). Function application has precedence 10
.
the value to be converted to a String
Convert a value to a readable String
.
showsPrec
should satisfy the law
showsPrec d x r ++ s == showsPrec d x (r ++ s)
Derived instances of Read
and Show
satisfy the following:
That is, readsPrec
parses the string produced by showsPrec
, and delivers the value that showsPrec
started with.
A specialised variant of showsPrec
, using precedence context zero, and returning an ordinary String
.
showList :: [a] -> ShowSSource
The method showList
is provided to allow the programmer to give a specialised way of showing lists of values. For example, this is used by the predefined Show
instance of the Char
type, where values of type String
should be shown in double quotes, rather than between square brackets.
Instances
Show Bool Show Char Show Double Show Float Show Int Show Int8 Show Int16 Show Int32 Show Int64 Show Integer Show Ordering Show Word Show Word8 Show Word16 Show Word32 Show Word64 Show () Show TyCon Show TypeRep Show ArithException Show ErrorCall Show SomeException Show IOException Show MaskingState Show Number Show Lexeme Show IOMode Show SeekMode Show CUIntMax Show CIntMax Show CUIntPtr Show CIntPtr Show CSUSeconds Show CUSeconds Show CTime Show CClock Show CSigAtomic Show CWchar Show CSize Show CPtrdiff Show CDouble Show CFloat Show CULLong Show CLLong Show CULong Show CLong Show CUInt Show CInt Show CUShort Show CShort Show CUChar Show CSChar Show CChar Show GeneralCategory Show Associativity Show Fixity Show Arity Show Dynamic Show IntPtr Show WordPtr Show Any Show All Show HashData Show CodingProgress Show TextEncoding Show NewlineMode Show Newline Show BufferMode Show HandleType Show Handle Show IOErrorType Show ExitCode Show ArrayException Show AsyncException Show AssertionFailed Show Deadlock Show BlockedIndefinitelyOnSTM Show BlockedIndefinitelyOnMVar Show CodingFailureMode Show ThreadStatus Show BlockReason Show ThreadId Show NestedAtomically Show NonTermination Show NoMethodError Show RecUpdError Show RecConError Show RecSelError Show PatternMatchFail Show Fd Show CRLim Show CTcflag Show CSpeed Show CCc Show CUid Show CNlink Show CGid Show CSsize Show CPid Show COff Show CMode Show CIno Show CDev Show Control Show ControlMessage Show Timeout Show Event Show EventType Show Event Show EPollFd Show Unique Show State Show FdKey Show FD Show HandlePosn Show Event Show PollFd Show Fixity Show ConstrRep Show DataRep Show Constr Show DataType Show BlockedIndefinitely Show BlockedOnDeadMVar Show GCStats Show Timeout Show Version Show a => Show [a] (Integral a, Show a) => Show (Ratio a) Show (Ptr a) Show (FunPtr a) Show a => Show (Maybe a) Show (ForeignPtr a) Show (IsEven n) Show (IsZero n) Show a => Show (Last a) Show a => Show (First a) Show a => Show (Product a) Show a => Show (Sum a) Show a => Show (Dual a) Show a => Show (IntMap a) Show a => Show (Sequ a) Show a => Show (LTree a) Show a => Show (PSQ a) Show a => Show (Elem a) Show a => Show (Complex a) HasResolution a => Show (Fixed a) Show (a -> b) (Show a, Show b) => Show (Either a b) (Show a, Show b) => Show (a, b) Show (ST s a) (Ix a, Show a, Show b) => Show (Array a b) (SingE k (Kind k) rep, Show rep) => Show (Sing k a) (Show a, Show b, Show c) => Show (a, b, c) (Show a, Show b, Show c, Show d) => Show (a, b, c, d) (Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) (Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f) (Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g) (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (a, b, c, d, e, f, g, h) (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (a, b, c, d, e, f, g, h, i) (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (a, b, c, d, e, f, g, h, i, j) (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (a, b, c, d, e, f, g, h, i, j, k) (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l) => Show (a, b, c, d, e, f, g, h, i, j, k, l) (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m) (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n) (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Converting fromString
type ReadS a = String -> [(a, String)]Source
A parser for a type a
, represented as a function that takes a String
and returns a list of possible parses as (a,
pairs.String
)
Note that this kind of backtracking parser is very inefficient; reading a large structure may be quite slow (cf ReadP
).
Parsing of String
s, producing values.
Minimal complete definition: readsPrec
(or, for GHC only, readPrec
)
Derived instances of Read
make the following assumptions, which derived instances of Show
obey:
Read
instance will parse only infix applications of the constructor (not the prefix form).Read
will parse only the record-syntax form, and furthermore, the fields must be given in the same order as the original declaration.Read
instance allows arbitrary Haskell whitespace between tokens of the input string. Extra parentheses are also allowed.For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Read
in Haskell 98 is equivalent to
instance (Read a) => Read (Tree a) where readsPrec d r = readParen (d > app_prec) (\r -> [(Leaf m,t) | ("Leaf",s) <- lex r, (m,t) <- readsPrec (app_prec+1) s]) r ++ readParen (d > up_prec) (\r -> [(u:^:v,w) | (u,s) <- readsPrec (up_prec+1) r, (":^:",t) <- lex s, (v,w) <- readsPrec (up_prec+1) t]) r where app_prec = 10 up_prec = 5
Note that right-associativity of :^:
is unused.
The derived instance in GHC is equivalent to
instance (Read a) => Read (Tree a) where readPrec = parens $ (prec app_prec $ do Ident "Leaf" <- lexP m <- step readPrec return (Leaf m)) +++ (prec up_prec $ do u <- step readPrec Symbol ":^:" <- lexP v <- step readPrec return (u :^: v)) where app_prec = 10 up_prec = 5 readListPrec = readListPrecDefault
Methods
Arguments
:: Intthe operator precedence of the enclosing context (a number from 0
to 11
). Function application has precedence 10
.
attempts to parse a value from the front of the string, returning a list of (parsed value, remaining string) pairs. If there is no successful parse, the returned list is empty.
Derived instances of Read
and Show
satisfy the following:
That is, readsPrec
parses the string produced by showsPrec
, and delivers the value that showsPrec
started with.
The method readList
is provided to allow the programmer to give a specialised way of parsing lists of values. For example, this is used by the predefined Read
instance of the Char
type, where values of type String
should be are expected to use double quotes, rather than square brackets.
Instances
Read Bool Read Char Read Double Read Float Read Int Read Int8 Read Int16 Read Int32 Read Int64 Read Integer Read Ordering Read Word Read Word8 Read Word16 Read Word32 Read Word64 Read () Read Lexeme Read IOMode Read SeekMode Read CUIntMax Read CIntMax Read CUIntPtr Read CIntPtr Read CSUSeconds Read CUSeconds Read CTime Read CClock Read CSigAtomic Read CWchar Read CSize Read CPtrdiff Read CDouble Read CFloat Read CULLong Read CLLong Read CULong Read CLong Read CUInt Read CInt Read CUShort Read CShort Read CUChar Read CSChar Read CChar Read GeneralCategory Read Associativity Read Fixity Read Arity Read IntPtr Read WordPtr Read Any Read All Read NewlineMode Read Newline Read BufferMode Read ExitCode Read Fd Read CRLim Read CTcflag Read CSpeed Read CCc Read CUid Read CNlink Read CGid Read CSsize Read CPid Read COff Read CMode Read CIno Read CDev Read GCStats Read Version Read a => Read [a] (Integral a, Read a) => Read (Ratio a) Read a => Read (Maybe a) Read a => Read (Last a) Read a => Read (First a) Read a => Read (Product a) Read a => Read (Sum a) Read a => Read (Dual a) Read a => Read (Complex a) HasResolution a => Read (Fixed a) (Read a, Read b) => Read (Either a b) (Read a, Read b) => Read (a, b) (Ix a, Read a, Read b) => Read (Array a b) (SingRep k a rep, Read rep, Eq rep) => Read (Sing k a) (Read a, Read b, Read c) => Read (a, b, c) (Read a, Read b, Read c, Read d) => Read (a, b, c, d) (Read a, Read b, Read c, Read d, Read e) => Read (a, b, c, d, e) (Read a, Read b, Read c, Read d, Read e, Read f) => Read (a, b, c, d, e, f) (Read a, Read b, Read c, Read d, Read e, Read f, Read g) => Read (a, b, c, d, e, f, g) (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) => Read (a, b, c, d, e, f, g, h) (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i) => Read (a, b, c, d, e, f, g, h, i) (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j) => Read (a, b, c, d, e, f, g, h, i, j) (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k) => Read (a, b, c, d, e, f, g, h, i, j, k) (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l) => Read (a, b, c, d, e, f, g, h, i, j, k, l) (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m) (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n) (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n, Read o) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)read :: Read a => String -> aSource
The read
function reads input from a string, which must be completely consumed by the input process.
The lex
function reads a single lexeme from the input, discarding initial white space, and returning the characters that constitute the lexeme. If the input string contains only white space, lex
returns a single successful `lexeme' consisting of the empty string. (Thus
.) If there is no legal lexeme at the beginning of the input string, lex
"" = [("","")]lex
fails (i.e. returns []
).
This lexer is not completely faithful to the Haskell lexical syntax in the following respects:
A value of type
is a computation which, when performed, does some I/O before returning a value of type IO
aa
.
There is really only one way to "perform" an I/O action: bind it to Main.main
in your program. When your program is run, the I/O will be performed. It isn't possible to perform I/O from an arbitrary function, unless that function is itself in the IO
monad and called at some point, directly or indirectly, from Main.main
.
IO
is a monad, so IO
actions can be combined using either the do-notation or the >>
and >>=
operations from the Monad
class.
print :: Show a => a -> IO ()Source
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]])Input functions
interact :: (String -> String) -> IO ()Source
The interact
function takes a function of type String->String
as its argument. The entire input from the standard input device is passed to this function as its argument, and the resulting string is output on the standard output device.
File and directory names are values of type String
, whose precise meaning is operating system dependent. Files can be opened, yielding a handle which can then be used to operate on the contents of that file.
appendFile :: FilePath -> String -> IO ()Source
The computation appendFile
file str
function appends the string str
, to the file file
.
Note that writeFile
and appendFile
write a literal string to a file. To write a value of any printable type, as with print
, use the show
function to convert the value to a string first.
main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]])Exception handling in the I/O monad
type IOError = IOExceptionSource
The Haskell 98 type for exceptions in the IO
monad. Any I/O operation may raise an IOError
instead of returning a result. For a more general type of exception, including also those that arise in pure code, see Control.Exception.Exception.
In Haskell 98, this is an opaque type.
RetroSearch is an open source project built by @garambo | Open a GitHub Issue
Search and Browse the WWW like it's 1997 | Search results from DuckDuckGo
HTML:
3.2
| Encoding:
UTF-8
| Version:
0.7.4