-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Compatibility with Haskell 98 -- -- This package provides compatibility with the modules of Haskell 98 and -- the FFI addendum, by means of wrappers around modules from the base -- package (which in many cases have additional features). However -- Prelude, Numeric and Foreign are provided -- directly by the base package. @package haskell98 @version 2.0.0.3 -- | The Haskell 98 Prelude: a standard module imported by default into all -- Haskell modules. For more documentation, see the Haskell 98 Report -- http://www.haskell.org/onlinereport/. module Prelude data Bool :: * False :: Bool True :: Bool -- | Boolean "and" (&&) :: Bool -> Bool -> Bool -- | Boolean "or" (||) :: Bool -> Bool -> Bool -- | Boolean "not" not :: Bool -> Bool -- | otherwise is defined as the value True. It helps to make -- guards more readable. eg. -- --
--   f x | x < 0     = ...
--       | otherwise = ...
--   
otherwise :: Bool -- | The Maybe type encapsulates an optional value. A value of type -- Maybe a either contains a value of type a -- (represented as Just a), or it is empty (represented -- as Nothing). 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. data Maybe a :: * -> * Nothing :: Maybe a Just :: a -> Maybe a -- | 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. maybe :: b -> (a -> b) -> Maybe a -> b -- | The Either type represents values with two possibilities: a -- value of type Either a b is either Left -- a or 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"). data Either a b :: * -> * -> * Left :: a -> Either a b Right :: b -> Either a b -- | Case analysis for the Either type. If the value is -- Left a, apply the first function to a; if it -- is Right b, apply the second function to b. either :: (a -> c) -> (b -> c) -> Either a b -> c data Ordering :: * LT :: Ordering EQ :: Ordering GT :: Ordering -- | 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). data Char :: * -- | A String is a list of characters. String constants in Haskell -- are values of type String. type String = [Char] -- | Extract the first component of a pair. fst :: (a, b) -> a -- | Extract the second component of a pair. snd :: (a, b) -> b -- | curry converts an uncurried function to a curried function. curry :: ((a, b) -> c) -> a -> b -> c -- | uncurry converts a curried function to a function on pairs. uncurry :: (a -> b -> c) -> (a, b) -> c -- | 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 /=. class Eq a (==) :: Eq a => a -> a -> Bool (/=) :: Eq a => a -> a -> Bool -- | 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. class Eq a => Ord a compare :: Ord a => a -> a -> Ordering (<) :: Ord a => a -> a -> Bool (>=) :: Ord a => a -> a -> Bool (>) :: Ord a => a -> a -> Bool (<=) :: Ord a => a -> a -> Bool max :: Ord a => a -> a -> a min :: Ord a => a -> a -> a -- | 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: -- -- -- --
--   enumFrom     x   = enumFromTo     x maxBound
--   enumFromThen x y = enumFromThenTo x y bound
--     where
--       bound | fromEnum y >= fromEnum x = maxBound
--             | otherwise                = minBound
--   
class Enum a succ :: Enum a => a -> a pred :: Enum a => a -> a toEnum :: Enum a => Int -> a fromEnum :: Enum a => a -> Int enumFrom :: Enum a => a -> [a] enumFromThen :: Enum a => a -> a -> [a] enumFromTo :: Enum a => a -> a -> [a] enumFromThenTo :: Enum a => a -> a -> a -> [a] -- | 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 Bounded a minBound :: Bounded a => a maxBound :: Bounded a => a -- | A 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. data Int :: * -- | Arbitrary-precision integers. data Integer :: * -- | 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. data Float :: * -- | 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. data Double :: * -- | Arbitrary-precision rational numbers, represented as a ratio of two -- Integer values. A rational number may be constructed using the -- % operator. type Rational = Ratio Integer -- | Basic numeric class. -- -- Minimal complete definition: all except negate or (-) class Num a (+) :: Num a => a -> a -> a (*) :: Num a => a -> a -> a (-) :: Num a => a -> a -> a negate :: Num a => a -> a abs :: Num a => a -> a signum :: Num a => a -> a fromInteger :: Num a => Integer -> a class (Num a, Ord a) => Real a toRational :: Real a => a -> Rational -- | Integral numbers, supporting integer division. -- -- Minimal complete definition: quotRem and toInteger class (Real a, Enum a) => Integral a quot :: Integral a => a -> a -> a rem :: Integral a => a -> a -> a div :: Integral a => a -> a -> a mod :: Integral a => a -> a -> a quotRem :: Integral a => a -> a -> (a, a) divMod :: Integral a => a -> a -> (a, a) toInteger :: Integral a => a -> Integer -- | Fractional numbers, supporting real division. -- -- Minimal complete definition: fromRational and (recip or -- (/)) class Num a => Fractional a (/) :: Fractional a => a -> a -> a recip :: Fractional a => a -> a fromRational :: Fractional a => Rational -> a -- | Trigonometric and hyperbolic functions and related functions. -- -- Minimal complete definition: pi, exp, log, -- sin, cos, sinh, cosh, asin, -- acos, atan, asinh, acosh and atanh class Fractional a => Floating a pi :: Floating a => a exp :: Floating a => a -> a sqrt :: Floating a => a -> a log :: Floating a => a -> a (**) :: Floating a => a -> a -> a logBase :: Floating a => a -> a -> a sin :: Floating a => a -> a tan :: Floating a => a -> a cos :: Floating a => a -> a asin :: Floating a => a -> a atan :: Floating a => a -> a acos :: Floating a => a -> a sinh :: Floating a => a -> a tanh :: Floating a => a -> a cosh :: Floating a => a -> a asinh :: Floating a => a -> a atanh :: Floating a => a -> a acosh :: Floating a => a -> a -- | Extracting components of fractions. -- -- Minimal complete definition: properFraction class (Real a, Fractional a) => RealFrac a properFraction :: (RealFrac a, Integral b) => a -> (b, a) truncate :: (RealFrac a, Integral b) => a -> b round :: (RealFrac a, Integral b) => a -> b ceiling :: (RealFrac a, Integral b) => a -> b floor :: (RealFrac a, Integral b) => a -> b -- | Efficient, machine-independent access to the components of a -- floating-point number. -- -- Minimal complete definition: all except exponent, -- significand, scaleFloat and atan2 class (RealFrac a, Floating a) => RealFloat a floatRadix :: RealFloat a => a -> Integer floatDigits :: RealFloat a => a -> Int floatRange :: RealFloat a => a -> (Int, Int) decodeFloat :: RealFloat a => a -> (Integer, Int) encodeFloat :: RealFloat a => Integer -> Int -> a exponent :: RealFloat a => a -> Int significand :: RealFloat a => a -> a scaleFloat :: RealFloat a => Int -> a -> a isNaN :: RealFloat a => a -> Bool isInfinite :: RealFloat a => a -> Bool isDenormalized :: RealFloat a => a -> Bool isNegativeZero :: RealFloat a => a -> Bool isIEEE :: RealFloat a => a -> Bool atan2 :: RealFloat a => a -> a -> a -- | the same as flip (-). -- -- Because - is treated specially in the Haskell grammar, -- (- e) is not a section, but an application of -- prefix negation. However, (subtract -- exp) is equivalent to the disallowed section. subtract :: Num a => a -> a -> a even :: Integral a => a -> Bool odd :: Integral a => a -> Bool -- | gcd x y is the greatest (positive) integer that -- divides both x and y; for example gcd -- (-3) 6 = 3, gcd (-3) (-6) = 3, -- gcd 0 4 = 4. gcd 0 0 raises a -- runtime error. gcd :: Integral a => a -> a -> a -- | lcm x y is the smallest positive integer that both -- x and y divide. lcm :: Integral a => a -> a -> a -- | raise a number to a non-negative integral power (^) :: (Num a, Integral b) => a -> b -> a -- | raise a number to an integral power (^^) :: (Fractional a, Integral b) => a -> b -> a -- | general coercion from integral types fromIntegral :: (Integral a, Num b) => a -> b -- | general coercion to fractional types realToFrac :: (Real a, Fractional b) => a -> b -- | 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. class Monad (m :: * -> *) (>>=) :: Monad m => m a -> (a -> m b) -> m b (>>) :: Monad m => m a -> m b -> m b return :: Monad m => a -> m a fail :: Monad m => String -> m a -- | 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. class Functor (f :: * -> *) fmap :: Functor f => (a -> b) -> f a -> f b -- | mapM f is equivalent to sequence . -- map f. mapM :: Monad m => (a -> m b) -> [a] -> m [b] -- | mapM_ f is equivalent to sequence_ . -- map f. mapM_ :: Monad m => (a -> m b) -> [a] -> m () -- | Evaluate each action in the sequence from left to right, and collect -- the results. sequence :: Monad m => [m a] -> m [a] -- | Evaluate each action in the sequence from left to right, and ignore -- the results. sequence_ :: Monad m => [m a] -> m () -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b -- | Identity function. id :: a -> a -- | Constant function. const :: a -> b -> a -- | Function composition. (.) :: (b -> c) -> (a -> b) -> a -> c -- | flip f takes its (first) two arguments in the reverse -- order of f. flip :: (a -> b -> c) -> b -> a -> c -- | Application operator. This operator is redundant, since ordinary -- application (f x) means the same as (f $ x). -- However, $ 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 map -- ($ 0) xs, or zipWith ($) fs xs. ($) :: (a -> b) -> a -> b -- | until p f yields the result of applying f -- until p holds. until :: (a -> Bool) -> (a -> a) -> a -> a -- | 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. asTypeOf :: a -> a -> a -- | error stops execution and displays an error message. error :: [Char] -> a -- | 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. undefined :: a -- | Evaluates its first argument to head normal form, and then returns its -- second argument as the result. seq :: a -> b -> b -- | Strict (call-by-value) application, defined in terms of seq. ($!) :: (a -> b) -> a -> b -- | 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 :: (a -> b) -> [a] -> [b] -- | 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. (++) :: [a] -> [a] -> [a] -- | 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 :: (a -> Bool) -> [a] -> [a] -- | Extract the first element of a list, which must be non-empty. head :: [a] -> a -- | Extract the last element of a list, which must be finite and -- non-empty. last :: [a] -> a -- | Extract the elements after the head of a list, which must be -- non-empty. tail :: [a] -> [a] -- | Return all the elements of a list except the last one. The list must -- be non-empty. init :: [a] -> [a] -- | Test whether a list is empty. null :: [a] -> Bool -- | 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. length :: [a] -> Int -- | List index (subscript) operator, starting from 0. It is an instance of -- the more general genericIndex, which takes an index of any -- integral type. (!!) :: [a] -> Int -> a -- | reverse xs returns the elements of xs in -- reverse order. xs must be finite. reverse :: [a] -> [a] -- | 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. foldl :: (b -> a -> b) -> b -> [a] -> b -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty lists. foldl1 :: (a -> a -> a) -> [a] -> a -- | 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)...)
--   
foldr :: (a -> b -> b) -> b -> [a] -> b -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty lists. foldr1 :: (a -> a -> a) -> [a] -> a -- | 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. and :: [Bool] -> Bool -- | 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. or :: [Bool] -> Bool -- | 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. any :: (a -> Bool) -> [a] -> Bool -- | 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. all :: (a -> Bool) -> [a] -> Bool -- | The sum function computes the sum of a finite list of numbers. sum :: Num a => [a] -> a -- | The product function computes the product of a finite list of -- numbers. product :: Num a => [a] -> a -- | Concatenate a list of lists. concat :: [[a]] -> [a] -- | Map a function over a list and concatenate the results. concatMap :: (a -> [b]) -> [a] -> [b] -- | 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. maximum :: Ord a => [a] -> a -- | 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. minimum :: Ord a => [a] -> a -- | 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.
--   
scanl :: (b -> a -> b) -> b -> [a] -> [b] -- | scanl1 is a variant of scanl that has no starting value -- argument: -- --
--   scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--   
scanl1 :: (a -> a -> a) -> [a] -> [a] -- | scanr is the right-to-left dual of scanl. Note that -- --
--   head (scanr f z xs) == foldr f z xs.
--   
scanr :: (a -> b -> b) -> b -> [a] -> [b] -- | scanr1 is a variant of scanr that has no starting value -- argument. scanr1 :: (a -> a -> a) -> [a] -> [a] -- | iterate f x returns an infinite list of repeated -- applications of f to x: -- --
--   iterate f x == [x, f x, f (f x), ...]
--   
iterate :: (a -> a) -> a -> [a] -- | repeat x is an infinite list, with x the -- value of every element. repeat :: a -> [a] -- | replicate n x is a list of length n with -- x the value of every element. It is an instance of the more -- general genericReplicate, in which n may be of any -- integral type. replicate :: Int -> a -> [a] -- | 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. cycle :: [a] -> [a] -- | 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. take :: Int -> [a] -> [a] -- | 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. drop :: Int -> [a] -> [a] -- | 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 (take n xs, drop n xs). -- splitAt is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. splitAt :: Int -> [a] -> ([a], [a]) -- | 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] == []
--   
takeWhile :: (a -> Bool) -> [a] -> [a] -- | 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]
--   
dropWhile :: (a -> Bool) -> [a] -> [a] -- | 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) span :: (a -> Bool) -> [a] -> ([a], [a]) -- | 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). break :: (a -> Bool) -> [a] -> ([a], [a]) -- | 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. elem :: Eq a => a -> [a] -> Bool -- | notElem is the negation of elem. notElem :: Eq a => a -> [a] -> Bool -- | lookup key assocs looks up a key in an association -- list. lookup :: Eq a => a -> [(a, b)] -> Maybe b -- | 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. zip :: [a] -> [b] -> [(a, b)] -- | zip3 takes three lists and returns a list of triples, analogous -- to zip. zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] -- | zipWith generalises zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, zipWith (+) is applied to two lists to -- produce the list of corresponding sums. zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] -- | 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. zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] -- | unzip transforms a list of pairs into a list of first -- components and a list of second components. unzip :: [(a, b)] -> ([a], [b]) -- | The unzip3 function takes a list of triples and returns three -- lists, analogous to unzip. unzip3 :: [(a, b, c)] -> ([a], [b], [c]) -- | lines breaks a string up into a list of strings at newline -- characters. The resulting strings do not contain newlines. lines :: String -> [String] -- | words breaks a string up into a list of words, which were -- delimited by white space. words :: String -> [String] -- | unlines is an inverse operation to lines. It joins -- lines, after appending a terminating newline to each. unlines :: [String] -> String -- | unwords is an inverse operation to words. It joins words -- with separating spaces. unwords :: [String] -> String -- | 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. type ShowS = String -> String -- | Conversion of values to readable Strings. -- -- Minimal complete definition: showsPrec or show. -- -- Derived instances of Show have the following properties, which -- are compatible with derived instances of Read: -- -- -- -- 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, -- -- class Show a showsPrec :: Show a => Int -> a -> ShowS show :: Show a => a -> String showList :: Show a => [a] -> ShowS -- | equivalent to showsPrec with a precedence of 0. shows :: Show a => a -> ShowS -- | utility function converting a Char to a show function that -- simply prepends the character unchanged. showChar :: Char -> ShowS -- | utility function converting a String to a show function that -- simply prepends the string unchanged. showString :: String -> ShowS -- | utility function that surrounds the inner show function with -- parentheses when the Bool parameter is True. showParen :: Bool -> ShowS -> ShowS -- | A parser for a type a, represented as a function that takes a -- String and returns a list of possible parses as -- (a,String) pairs. -- -- Note that this kind of backtracking parser is very inefficient; -- reading a large structure may be quite slow (cf ReadP). type ReadS a = String -> [(a, String)] -- | Parsing of Strings, 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: -- -- -- -- For example, given the declarations -- --
--   infixr 5 :^:
--   data Tree a =  Leaf a  |  Tree a :^: Tree a
--   
-- -- the derived instance of Read in Haskell 2010 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
--   
class Read a readsPrec :: Read a => Int -> ReadS a readList :: Read a => ReadS [a] -- | equivalent to readsPrec with a precedence of 0. reads :: Read a => ReadS a -- | readParen True p parses what p parses, -- but surrounded with parentheses. -- -- readParen False p parses what p -- parses, but optionally surrounded with parentheses. readParen :: Bool -> ReadS a -> ReadS a -- | The read function reads input from a string, which must be -- completely consumed by the input process. read :: Read a => String -> a -- | 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 lex "" = [("","")].) If there is -- no legal lexeme at the beginning of the input string, lex fails -- (i.e. returns []). -- -- This lexer is not completely faithful to the Haskell lexical syntax in -- the following respects: -- -- lex :: ReadS String -- | A value of type IO a is a computation which, when -- performed, does some I/O before returning a value of type a. -- -- 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. data IO a :: * -> * -- | Write a character to the standard output device (same as -- hPutChar stdout). putChar :: Char -> IO () -- | Write a string to the standard output device (same as hPutStr -- stdout). putStr :: String -> IO () -- | The same as putStr, but adds a newline character. putStrLn :: String -> 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]])
--   
print :: Show a => a -> IO () -- | Read a character from the standard input device (same as -- hGetChar stdin). getChar :: IO Char -- | Read a line from the standard input device (same as hGetLine -- stdin). getLine :: IO String -- | The getContents operation returns all user input as a single -- string, which is read lazily as it is needed (same as -- hGetContents stdin). getContents :: IO String -- | 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. interact :: (String -> String) -> IO () -- | 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. type FilePath = String -- | The readFile function reads a file and returns the contents of -- the file as a string. The file is read lazily, on demand, as with -- getContents. readFile :: FilePath -> IO String -- | The computation writeFile file str function writes the -- string str, to the file file. writeFile :: FilePath -> String -> IO () -- | 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]])
--   
appendFile :: FilePath -> String -> IO () -- | The readIO function is similar to read except that it -- signals parse failure to the IO monad instead of terminating -- the program. readIO :: Read a => String -> IO a -- | The readLn function combines getLine and readIO. readLn :: Read a => IO a -- | The Haskell 2010 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 2010, this is an opaque type. type IOError = IOException -- | Raise an IOError in the IO monad. ioError :: IOError -> IO a -- | Construct an IOError value with a string describing the error. -- The fail method of the IO instance of the Monad -- class raises a userError, thus: -- --
--   instance Monad IO where
--     ...
--     fail s = ioError (userError s)
--   
userError :: String -> IOError -- | The catch function establishes a handler that receives any -- IOError raised in the action protected by catch. An -- IOError is caught by the most recent handler established by one -- of the exception handling functions. These handlers are not selective: -- all IOErrors are caught. Exception propagation must be -- explicitly provided in a handler by re-raising any unwanted -- exceptions. For example, in -- --
--   f = catch g (\e -> if IO.isEOFError e then return [] else ioError e)
--   
-- -- the function f returns [] when an end-of-file -- exception (cf. isEOFError) occurs in g; otherwise, the -- exception is propagated to the next outer handler. -- -- When an exception propagates outside the main program, the Haskell -- system prints the associated IOError value and exits the -- program. -- -- Non-I/O exceptions are not caught by this variant; to catch all -- exceptions, use catch from Control.Exception. catch :: IO a -> (IOError -> IO a) -> IO a module Numeric -- | Converts a possibly-negative Real value to a string. showSigned :: Real a => (a -> ShowS) -> Int -> a -> ShowS -- | Shows a non-negative Integral number using the base -- specified by the first argument, and the character representation -- specified by the second. showIntAtBase :: (Integral a, Show a) => a -> (Int -> Char) -> a -> ShowS -- | Show non-negative Integral numbers in base 10. showInt :: Integral a => a -> ShowS -- | Show non-negative Integral numbers in base 16. showHex :: (Integral a, Show a) => a -> ShowS -- | Show non-negative Integral numbers in base 8. showOct :: (Integral a, Show a) => a -> ShowS -- | Show a signed RealFloat value using scientific (exponential) -- notation (e.g. 2.45e2, 1.5e-3). -- -- In the call showEFloat digs val, if digs is -- Nothing, the value is shown to full precision; if digs -- is Just d, then at most d digits after the -- decimal point are shown. showEFloat :: RealFloat a => Maybe Int -> a -> ShowS -- | Show a signed RealFloat value using standard decimal notation -- (e.g. 245000, 0.0015). -- -- In the call showFFloat digs val, if digs is -- Nothing, the value is shown to full precision; if digs -- is Just d, then at most d digits after the -- decimal point are shown. showFFloat :: RealFloat a => Maybe Int -> a -> ShowS -- | Show a signed RealFloat value using standard decimal notation -- for arguments whose absolute value lies between 0.1 and -- 9,999,999, and scientific notation otherwise. -- -- In the call showGFloat digs val, if digs is -- Nothing, the value is shown to full precision; if digs -- is Just d, then at most d digits after the -- decimal point are shown. showGFloat :: RealFloat a => Maybe Int -> a -> ShowS -- | Show a signed RealFloat value to full precision using standard -- decimal notation for arguments whose absolute value lies between -- 0.1 and 9,999,999, and scientific notation -- otherwise. showFloat :: RealFloat a => a -> ShowS -- | floatToDigits takes a base and a non-negative RealFloat -- number, and returns a list of digits and an exponent. In particular, -- if x>=0, and -- --
--   floatToDigits base x = ([d1,d2,...,dn], e)
--   
-- -- then -- --
    --
  1. n >= 1
    1. x = 0.d1d2...dn *
      --   (base**e)
    2. 0 <= di <=
      --   base-1
  2. --
floatToDigits :: RealFloat a => Integer -> a -> ([Int], Int) -- | Reads a signed Real value, given a reader for an -- unsigned value. readSigned :: Real a => ReadS a -> ReadS a -- | Reads an unsigned Integral value in an arbitrary base. readInt :: Num a => a -> (Char -> Bool) -> (Char -> Int) -> ReadS a -- | Read an unsigned number in decimal notation. readDec :: (Eq a, Num a) => ReadS a -- | Read an unsigned number in octal notation. readOct :: (Eq a, Num a) => ReadS a -- | Read an unsigned number in hexadecimal notation. Both upper or lower -- case letters are allowed. readHex :: (Eq a, Num a) => ReadS a -- | Reads an unsigned RealFrac value, expressed in decimal -- scientific notation. readFloat :: RealFrac a => ReadS a -- | Reads a non-empty string of decimal digits. lexDigits :: ReadS String -- | Converts a Rational value into any type in class -- RealFloat. fromRat :: RealFloat a => Rational -> a module Maybe -- | The isJust function returns True iff its argument is of -- the form Just _. isJust :: Maybe a -> Bool -- | The isNothing function returns True iff its argument is -- Nothing. isNothing :: Maybe a -> Bool -- | The fromJust function extracts the element out of a Just -- and throws an error if its argument is Nothing. fromJust :: Maybe a -> a -- | The fromMaybe function takes a default value and and -- Maybe value. If the Maybe is Nothing, it returns -- the default values; otherwise, it returns the value contained in the -- Maybe. fromMaybe :: a -> Maybe a -> a -- | The listToMaybe function returns Nothing on an empty -- list or Just a where a is the first element -- of the list. listToMaybe :: [a] -> Maybe a -- | The maybeToList function returns an empty list when given -- Nothing or a singleton list when not given Nothing. maybeToList :: Maybe a -> [a] -- | The catMaybes function takes a list of Maybes and -- returns a list of all the Just values. catMaybes :: [Maybe a] -> [a] -- | The mapMaybe function is a version of map which can -- throw out elements. In particular, the functional argument returns -- something of type Maybe b. If this is Nothing, -- no element is added on to the result list. If it just Just -- b, then b is included in the result list. mapMaybe :: (a -> Maybe b) -> [a] -> [b] -- | The Maybe type encapsulates an optional value. A value of type -- Maybe a either contains a value of type a -- (represented as Just a), or it is empty (represented -- as Nothing). 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. data Maybe a :: * -> * Nothing :: Maybe a Just :: a -> Maybe a -- | 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. maybe :: b -> (a -> b) -> Maybe a -> b module Storable module Bits module Directory data Permissions Permissions :: Bool -> Bool -> Bool -> Bool -> Permissions readable :: Permissions -> Bool writable :: Permissions -> Bool executable :: Permissions -> Bool searchable :: Permissions -> Bool -- | createDirectory dir creates a new directory -- dir which is initially empty, or as near to empty as the -- operating system allows. -- -- The operation may fail with: -- -- createDirectory :: FilePath -> IO () -- | removeDirectory dir removes an existing directory -- dir. The implementation may specify additional constraints -- which must be satisfied before a directory can be removed (e.g. the -- directory has to be empty, or may not be in use by other processes). -- It is not legal for an implementation to partially remove a directory -- unless the entire directory is removed. A conformant implementation -- need not support directory removal in all situations (e.g. removal of -- the root directory). -- -- The operation may fail with: -- -- removeDirectory :: FilePath -> IO () -- | removeFile file removes the directory entry for an -- existing file file, where file is not itself a -- directory. The implementation may specify additional constraints which -- must be satisfied before a file can be removed (e.g. the file may not -- be in use by other processes). -- -- The operation may fail with: -- -- removeFile :: FilePath -> IO () -- | renameDirectory old new changes the name of an -- existing directory from old to new. If the new -- directory already exists, it is atomically replaced by the old -- directory. If the new directory is neither the old -- directory nor an alias of the old directory, it is removed as -- if by removeDirectory. A conformant implementation need not -- support renaming directories in all situations (e.g. renaming to an -- existing directory, or across different physical devices), but the -- constraints must be documented. -- -- On Win32 platforms, renameDirectory fails if the new -- directory already exists. -- -- The operation may fail with: -- -- renameDirectory :: FilePath -> FilePath -> IO () -- | renameFile old new changes the name of an existing -- file system object from old to new. If the new -- object already exists, it is atomically replaced by the old -- object. Neither path may refer to an existing directory. A conformant -- implementation need not support renaming files in all situations (e.g. -- renaming across different physical devices), but the constraints must -- be documented. -- -- The operation may fail with: -- -- renameFile :: FilePath -> FilePath -> IO () -- | getDirectoryContents dir returns a list of all -- entries in dir. -- -- The operation may fail with: -- -- getDirectoryContents :: FilePath -> IO [FilePath] -- | If the operating system has a notion of current directories, -- getCurrentDirectory returns an absolute path to the current -- directory of the calling process. -- -- The operation may fail with: -- -- -- -- Note that in a concurrent program, the current directory is global -- state shared between all threads of the process. When using filesystem -- operations from multiple threads, it is therefore highly recommended -- to use absolute rather than relative FilePaths. getCurrentDirectory :: IO FilePath -- | If the operating system has a notion of current directories, -- setCurrentDirectory dir changes the current directory -- of the calling process to dir. -- -- The operation may fail with: -- -- -- -- Note that in a concurrent program, the current directory is global -- state shared between all threads of the process. When using filesystem -- operations from multiple threads, it is therefore highly recommended -- to use absolute rather than relative FilePaths. setCurrentDirectory :: FilePath -> IO () -- | The operation doesFileExist returns True if the argument -- file exists and is not a directory, and False otherwise. doesFileExist :: FilePath -> IO Bool -- | The operation doesDirectoryExist returns True if the -- argument file exists and is either a directory or a symbolic link to a -- directory, and False otherwise. doesDirectoryExist :: FilePath -> IO Bool getPermissions :: FilePath -> IO Permissions setPermissions :: FilePath -> Permissions -> IO () -- | The getModificationTime operation returns the clock time at -- which the file or directory was last modified. -- -- The operation may fail with: -- -- -- -- Note: When linked against unix-2.6.0.0 or later the reported -- time supports sub-second precision if provided by the underlying -- system call. getModificationTime :: FilePath -> IO UTCTime instance Eq Permissions instance Ord Permissions instance Read Permissions instance Show Permissions module CString module Complex -- | Complex numbers are an algebraic type. -- -- For a complex number z, abs z is a number -- with the magnitude of z, but oriented in the positive real -- direction, whereas signum z has the phase of -- z, but unit magnitude. data Complex a :: * -> * -- | forms a complex number from its real and imaginary rectangular -- components. (:+) :: SrictNotUnpackeda -> SrictNotUnpackeda -> Complex a -- | Extracts the real part of a complex number. realPart :: RealFloat a => Complex a -> a -- | Extracts the imaginary part of a complex number. imagPart :: RealFloat a => Complex a -> a -- | The conjugate of a complex number. conjugate :: RealFloat a => Complex a -> Complex a -- | Form a complex number from polar components of magnitude and phase. mkPolar :: RealFloat a => a -> a -> Complex a -- | cis t is a complex value with magnitude 1 and -- phase t (modulo 2*pi). cis :: RealFloat a => a -> Complex a -- | The function polar takes a complex number and returns a -- (magnitude, phase) pair in canonical form: the magnitude is -- nonnegative, and the phase in the range (-pi, -- pi]; if the magnitude is zero, then so is the phase. polar :: RealFloat a => Complex a -> (a, a) -- | The nonnegative magnitude of a complex number. magnitude :: RealFloat a => Complex a -> a -- | The phase of a complex number, in the range (-pi, -- pi]. If the magnitude is zero, then so is the phase. phase :: RealFloat a => Complex a -> a module System -- | Defines the exit codes that a program can return. data ExitCode :: * -- | indicates successful termination; ExitSuccess :: ExitCode -- | indicates program failure with an exit code. The exact interpretation -- of the code is operating-system dependent. In particular, some values -- may be prohibited (e.g. 0 on a POSIX-compliant system). ExitFailure :: Int -> ExitCode -- | Computation getArgs returns a list of the program's command -- line arguments (not including the program name). getArgs :: IO [String] -- | Computation getProgName returns the name of the program as it -- was invoked. -- -- However, this is hard-to-impossible to implement on some non-Unix -- OSes, so instead, for maximum portability, we just return the leafname -- of the program as invoked. Even then there are some differences -- between platforms: on Windows, for example, a program invoked as foo -- is probably really FOO.EXE, and that is what -- getProgName will return. getProgName :: IO String -- | Computation getEnv var returns the value of the -- environment variable var. For the inverse, POSIX users can -- use putEnv. -- -- This computation may fail with: -- -- getEnv :: String -> IO String -- | Computation system cmd returns the exit code produced when -- the operating system runs the shell command cmd. -- -- This computation may fail with one of the following IOErrorType -- exceptions: -- -- -- -- On Windows, system passes the command to the Windows command -- interpreter (CMD.EXE or COMMAND.COM), hence Unixy -- shell tricks will not work. -- -- On Unix systems, see waitForProcess for the meaning of exit -- codes when the process died as the result of a signal. system :: String -> IO ExitCode -- | Computation exitWith code throws ExitCode -- code. Normally this terminates the program, returning -- code to the program's caller. -- -- On program termination, the standard Handles stdout -- and stderr are flushed automatically; any other buffered -- Handles need to be flushed manually, otherwise the buffered -- data will be discarded. -- -- A program that fails in any other way is treated as if it had called -- exitFailure. A program that terminates successfully without -- calling exitWith explicitly is treated as it it had called -- exitWith ExitSuccess. -- -- As an ExitCode is not an IOError, exitWith -- bypasses the error handling in the IO monad and cannot be -- intercepted by catch from the Prelude. However it is a -- SomeException, and can be caught using the functions of -- Control.Exception. This means that cleanup computations added -- with bracket (from Control.Exception) are also executed -- properly on exitWith. -- -- Note: in GHC, exitWith should be called from the main program -- thread in order to exit the process. When called from another thread, -- exitWith will throw an ExitException as normal, but -- the exception will not cause the process itself to exit. exitWith :: ExitCode -> IO a -- | The computation exitFailure is equivalent to exitWith -- (ExitFailure exitfail), where -- exitfail is implementation-dependent. exitFailure :: IO a module List -- | The elemIndex function returns the index of the first element -- in the given list which is equal (by ==) to the query element, -- or Nothing if there is no such element. elemIndex :: Eq a => a -> [a] -> Maybe Int -- | The elemIndices function extends elemIndex, by returning -- the indices of all elements equal to the query element, in ascending -- order. elemIndices :: Eq a => a -> [a] -> [Int] -- | The find function takes a predicate and a list and returns the -- first element in the list matching the predicate, or Nothing if -- there is no such element. find :: (a -> Bool) -> [a] -> Maybe a -- | The findIndex function takes a predicate and a list and returns -- the index of the first element in the list satisfying the predicate, -- or Nothing if there is no such element. findIndex :: (a -> Bool) -> [a] -> Maybe Int -- | The findIndices function extends findIndex, by returning -- the indices of all elements satisfying the predicate, in ascending -- order. findIndices :: (a -> Bool) -> [a] -> [Int] -- | O(n^2). The nub function removes duplicate elements from -- a list. In particular, it keeps only the first occurrence of each -- element. (The name nub means `essence'.) It is a special case -- of nubBy, which allows the programmer to supply their own -- equality test. nub :: Eq a => [a] -> [a] -- | The nubBy function behaves just like nub, except it uses -- a user-supplied equality predicate instead of the overloaded == -- function. nubBy :: (a -> a -> Bool) -> [a] -> [a] -- | delete x removes the first occurrence of x -- from its list argument. For example, -- --
--   delete 'a' "banana" == "bnana"
--   
-- -- It is a special case of deleteBy, which allows the programmer -- to supply their own equality test. delete :: Eq a => a -> [a] -> [a] -- | The deleteBy function behaves like delete, but takes a -- user-supplied equality predicate. deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a] -- | The \\ function is list difference (non-associative). In the -- result of xs \\ ys, the first occurrence of -- each element of ys in turn (if any) has been removed from -- xs. Thus -- --
--   (xs ++ ys) \\ xs == ys.
--   
-- -- It is a special case of deleteFirstsBy, which allows the -- programmer to supply their own equality test. (\\) :: Eq a => [a] -> [a] -> [a] -- | The deleteFirstsBy function takes a predicate and two lists and -- returns the first list with the first occurrence of each element of -- the second list removed. deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The union function returns the list union of the two lists. For -- example, -- --
--   "dog" `union` "cow" == "dogcw"
--   
-- -- Duplicates, and elements of the first list, are removed from the the -- second list, but if the first list contains duplicates, so will the -- result. It is a special case of unionBy, which allows the -- programmer to supply their own equality test. union :: Eq a => [a] -> [a] -> [a] -- | The unionBy function is the non-overloaded version of -- union. unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The intersect function takes the list intersection of two -- lists. For example, -- --
--   [1,2,3,4] `intersect` [2,4,6,8] == [2,4]
--   
-- -- If the first list contains duplicates, so will the result. -- --
--   [1,2,2,3,4] `intersect` [6,4,4,2] == [2,2,4]
--   
-- -- It is a special case of intersectBy, which allows the -- programmer to supply their own equality test. If the element is found -- in both the first and the second list, the element from the first list -- will be used. intersect :: Eq a => [a] -> [a] -> [a] -- | The intersectBy function is the non-overloaded version of -- intersect. intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The intersperse function takes an element and a list and -- `intersperses' that element between the elements of the list. For -- example, -- --
--   intersperse ',' "abcde" == "a,b,c,d,e"
--   
intersperse :: a -> [a] -> [a] -- | The transpose function transposes the rows and columns of its -- argument. For example, -- --
--   transpose [[1,2,3],[4,5,6]] == [[1,4],[2,5],[3,6]]
--   
transpose :: [[a]] -> [[a]] -- | The partition function takes a predicate a list and returns the -- pair of lists of elements which do and do not satisfy the predicate, -- respectively; i.e., -- --
--   partition p xs == (filter p xs, filter (not . p) xs)
--   
partition :: (a -> Bool) -> [a] -> ([a], [a]) -- | The group function takes a list and returns a list of lists -- such that the concatenation of the result is equal to the argument. -- Moreover, each sublist in the result contains only equal elements. For -- example, -- --
--   group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]
--   
-- -- It is a special case of groupBy, which allows the programmer to -- supply their own equality test. group :: Eq a => [a] -> [[a]] -- | The groupBy function is the non-overloaded version of -- group. groupBy :: (a -> a -> Bool) -> [a] -> [[a]] -- | The inits function returns all initial segments of the -- argument, shortest first. For example, -- --
--   inits "abc" == ["","a","ab","abc"]
--   
-- -- Note that inits has the following strictness property: -- inits _|_ = [] : _|_ inits :: [a] -> [[a]] -- | The tails function returns all final segments of the argument, -- longest first. For example, -- --
--   tails "abc" == ["abc", "bc", "c",""]
--   
-- -- Note that tails has the following strictness property: -- tails _|_ = _|_ : _|_ tails :: [a] -> [[a]] -- | The isPrefixOf function takes two lists and returns True -- iff the first list is a prefix of the second. isPrefixOf :: Eq a => [a] -> [a] -> Bool -- | The isSuffixOf function takes two lists and returns True -- iff the first list is a suffix of the second. Both lists must be -- finite. isSuffixOf :: Eq a => [a] -> [a] -> Bool -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a list, -- passing an accumulating parameter from left to right, and returning a -- final value of this accumulator together with the new list. mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a list, -- passing an accumulating parameter from right to left, and returning a -- final value of this accumulator together with the new list. mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) -- | The sort function implements a stable sorting algorithm. It is -- a special case of sortBy, which allows the programmer to supply -- their own comparison function. sort :: Ord a => [a] -> [a] -- | The sortBy function is the non-overloaded version of -- sort. sortBy :: (a -> a -> Ordering) -> [a] -> [a] -- | The insert function takes an element and a list and inserts the -- element into the list at the first position where it is less than or -- equal to the next element. In particular, if the list is sorted before -- the call, the result will also be sorted. It is a special case of -- insertBy, which allows the programmer to supply their own -- comparison function. insert :: Ord a => a -> [a] -> [a] -- | The non-overloaded version of insert. insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] -- | The maximumBy function takes a comparison function and a list -- and returns the greatest element of the list by the comparison -- function. The list must be finite and non-empty. maximumBy :: (a -> a -> Ordering) -> [a] -> a -- | The minimumBy function takes a comparison function and a list -- and returns the least element of the list by the comparison function. -- The list must be finite and non-empty. minimumBy :: (a -> a -> Ordering) -> [a] -> a -- | The genericLength function is an overloaded version of -- length. In particular, instead of returning an Int, it -- returns any type which is an instance of Num. It is, however, -- less efficient than length. genericLength :: Num i => [a] -> i -- | The genericTake function is an overloaded version of -- take, which accepts any Integral value as the number of -- elements to take. genericTake :: Integral i => i -> [a] -> [a] -- | The genericDrop function is an overloaded version of -- drop, which accepts any Integral value as the number of -- elements to drop. genericDrop :: Integral i => i -> [a] -> [a] -- | The genericSplitAt function is an overloaded version of -- splitAt, which accepts any Integral value as the -- position at which to split. genericSplitAt :: Integral i => i -> [a] -> ([a], [a]) -- | The genericIndex function is an overloaded version of -- !!, which accepts any Integral value as the index. genericIndex :: Integral i => [a] -> i -> a -- | The genericReplicate function is an overloaded version of -- replicate, which accepts any Integral value as the -- number of repetitions to make. genericReplicate :: Integral i => i -> a -> [a] -- | The zip4 function takes four lists and returns a list of -- quadruples, analogous to zip. zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)] -- | The zip5 function takes five lists and returns a list of -- five-tuples, analogous to zip. zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)] -- | The zip6 function takes six lists and returns a list of -- six-tuples, analogous to zip. zip6 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)] -- | The zip7 function takes seven lists and returns a list of -- seven-tuples, analogous to zip. zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)] -- | The zipWith4 function takes a function which combines four -- elements, as well as four lists and returns a list of their point-wise -- combination, analogous to zipWith. zipWith4 :: (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e] -- | The zipWith5 function takes a function which combines five -- elements, as well as five lists and returns a list of their point-wise -- combination, analogous to zipWith. zipWith5 :: (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -- | The zipWith6 function takes a function which combines six -- elements, as well as six lists and returns a list of their point-wise -- combination, analogous to zipWith. zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -- | The zipWith7 function takes a function which combines seven -- elements, as well as seven lists and returns a list of their -- point-wise combination, analogous to zipWith. zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -- | The unzip4 function takes a list of quadruples and returns four -- lists, analogous to unzip. unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) -- | The unzip5 function takes a list of five-tuples and returns -- five lists, analogous to unzip. unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e]) -- | The unzip6 function takes a list of six-tuples and returns six -- lists, analogous to unzip. unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) -- | The unzip7 function takes a list of seven-tuples and returns -- seven lists, analogous to unzip. unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) -- | The unfoldr function is a `dual' to foldr: while -- foldr reduces a list to a summary value, unfoldr builds -- a list from a seed value. The function takes the element and returns -- Nothing if it is done producing the list or returns Just -- (a,b), in which case, a is a prepended to the list -- and b is used as the next element in a recursive call. For -- example, -- --
--   iterate f == unfoldr (\x -> Just (x, f x))
--   
-- -- In some cases, unfoldr can undo a foldr operation: -- --
--   unfoldr f' (foldr f z xs) == xs
--   
-- -- if the following holds: -- --
--   f' (f x y) = Just (x,y)
--   f' z       = Nothing
--   
-- -- A simple use of unfoldr: -- --
--   unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
--    [10,9,8,7,6,5,4,3,2,1]
--   
unfoldr :: (b -> Maybe (a, b)) -> b -> [a] -- | 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 :: (a -> b) -> [a] -> [b] -- | 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. (++) :: [a] -> [a] -> [a] -- | Concatenate a list of lists. concat :: [[a]] -> [a] -- | 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 :: (a -> Bool) -> [a] -> [a] -- | Extract the first element of a list, which must be non-empty. head :: [a] -> a -- | Extract the last element of a list, which must be finite and -- non-empty. last :: [a] -> a -- | Extract the elements after the head of a list, which must be -- non-empty. tail :: [a] -> [a] -- | Return all the elements of a list except the last one. The list must -- be non-empty. init :: [a] -> [a] -- | Test whether a list is empty. null :: [a] -> Bool -- | 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. length :: [a] -> Int -- | List index (subscript) operator, starting from 0. It is an instance of -- the more general genericIndex, which takes an index of any -- integral type. (!!) :: [a] -> Int -> a -- | 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. foldl :: (b -> a -> b) -> b -> [a] -> b -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty lists. foldl1 :: (a -> a -> a) -> [a] -> a -- | 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.
--   
scanl :: (b -> a -> b) -> b -> [a] -> [b] -- | scanl1 is a variant of scanl that has no starting value -- argument: -- --
--   scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--   
scanl1 :: (a -> a -> a) -> [a] -> [a] -- | 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)...)
--   
foldr :: (a -> b -> b) -> b -> [a] -> b -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty lists. foldr1 :: (a -> a -> a) -> [a] -> a -- | scanr is the right-to-left dual of scanl. Note that -- --
--   head (scanr f z xs) == foldr f z xs.
--   
scanr :: (a -> b -> b) -> b -> [a] -> [b] -- | scanr1 is a variant of scanr that has no starting value -- argument. scanr1 :: (a -> a -> a) -> [a] -> [a] -- | iterate f x returns an infinite list of repeated -- applications of f to x: -- --
--   iterate f x == [x, f x, f (f x), ...]
--   
iterate :: (a -> a) -> a -> [a] -- | repeat x is an infinite list, with x the -- value of every element. repeat :: a -> [a] -- | replicate n x is a list of length n with -- x the value of every element. It is an instance of the more -- general genericReplicate, in which n may be of any -- integral type. replicate :: Int -> a -> [a] -- | 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. cycle :: [a] -> [a] -- | 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. take :: Int -> [a] -> [a] -- | 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. drop :: Int -> [a] -> [a] -- | 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 (take n xs, drop n xs). -- splitAt is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. splitAt :: Int -> [a] -> ([a], [a]) -- | 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] == []
--   
takeWhile :: (a -> Bool) -> [a] -> [a] -- | 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]
--   
dropWhile :: (a -> Bool) -> [a] -> [a] -- | 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) span :: (a -> Bool) -> [a] -> ([a], [a]) -- | 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). break :: (a -> Bool) -> [a] -> ([a], [a]) -- | lines breaks a string up into a list of strings at newline -- characters. The resulting strings do not contain newlines. lines :: String -> [String] -- | words breaks a string up into a list of words, which were -- delimited by white space. words :: String -> [String] -- | unlines is an inverse operation to lines. It joins -- lines, after appending a terminating newline to each. unlines :: [String] -> String -- | unwords is an inverse operation to words. It joins words -- with separating spaces. unwords :: [String] -> String -- | reverse xs returns the elements of xs in -- reverse order. xs must be finite. reverse :: [a] -> [a] -- | 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. and :: [Bool] -> Bool -- | 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. or :: [Bool] -> Bool -- | 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. any :: (a -> Bool) -> [a] -> Bool -- | 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. all :: (a -> Bool) -> [a] -> Bool -- | 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. elem :: Eq a => a -> [a] -> Bool -- | notElem is the negation of elem. notElem :: Eq a => a -> [a] -> Bool -- | lookup key assocs looks up a key in an association -- list. lookup :: Eq a => a -> [(a, b)] -> Maybe b -- | The sum function computes the sum of a finite list of numbers. sum :: Num a => [a] -> a -- | The product function computes the product of a finite list of -- numbers. product :: Num a => [a] -> a -- | 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. maximum :: Ord a => [a] -> a -- | 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. minimum :: Ord a => [a] -> a -- | Map a function over a list and concatenate the results. concatMap :: (a -> [b]) -> [a] -> [b] -- | 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. zip :: [a] -> [b] -> [(a, b)] -- | zip3 takes three lists and returns a list of triples, analogous -- to zip. zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] -- | zipWith generalises zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, zipWith (+) is applied to two lists to -- produce the list of corresponding sums. zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] -- | 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. zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] -- | unzip transforms a list of pairs into a list of first -- components and a list of second components. unzip :: [(a, b)] -> ([a], [b]) -- | The unzip3 function takes a list of triples and returns three -- lists, analogous to unzip. unzip3 :: [(a, b, c)] -> ([a], [b], [c]) module CPUTime -- | Computation getCPUTime returns the number of picoseconds CPU -- time used by the current program. The precision of this result is -- implementation-dependent. getCPUTime :: IO Integer -- | The cpuTimePrecision constant is the smallest measurable -- difference in CPU time that the implementation can record, and is -- given as an integral number of picoseconds. cpuTimePrecision :: Integer module Locale data TimeLocale :: * TimeLocale :: [(String, String)] -> [(String, String)] -> [(String, String)] -> (String, String) -> String -> String -> String -> String -> TimeLocale defaultTimeLocale :: TimeLocale module Time -- | A representation of the internal clock time. Clock times may be -- compared, converted to strings, or converted to an external calendar -- time CalendarTime for I/O or other manipulations. data ClockTime :: * -- | A month of the year. data Month :: * January :: Month February :: Month March :: Month April :: Month May :: Month June :: Month July :: Month August :: Month September :: Month October :: Month November :: Month December :: Month -- | A day of the week. data Day :: * Sunday :: Day Monday :: Day Tuesday :: Day Wednesday :: Day Thursday :: Day Friday :: Day Saturday :: Day -- | CalendarTime is a user-readable and manipulable representation -- of the internal ClockTime type. data CalendarTime :: * CalendarTime :: Int -> Month -> Int -> Int -> Int -> Int -> Integer -> Day -> Int -> String -> Int -> Bool -> CalendarTime -- | Year (pre-Gregorian dates are inaccurate) ctYear :: CalendarTime -> Int -- | Month of the year ctMonth :: CalendarTime -> Month -- | Day of the month (1 to 31) ctDay :: CalendarTime -> Int -- | Hour of the day (0 to 23) ctHour :: CalendarTime -> Int -- | Minutes (0 to 59) ctMin :: CalendarTime -> Int -- | Seconds (0 to 61, allowing for up to two leap seconds) ctSec :: CalendarTime -> Int -- | Picoseconds ctPicosec :: CalendarTime -> Integer -- | Day of the week ctWDay :: CalendarTime -> Day -- | Day of the year (0 to 364, or 365 in leap years) ctYDay :: CalendarTime -> Int -- | Name of the time zone ctTZName :: CalendarTime -> String -- | Variation from UTC in seconds ctTZ :: CalendarTime -> Int -- | True if Daylight Savings Time would be in effect, and -- False otherwise ctIsDST :: CalendarTime -> Bool -- | records the difference between two clock times in a user-readable way. data TimeDiff :: * TimeDiff :: Int -> Int -> Int -> Int -> Int -> Int -> Integer -> TimeDiff tdYear :: TimeDiff -> Int tdMonth :: TimeDiff -> Int tdDay :: TimeDiff -> Int tdHour :: TimeDiff -> Int tdMin :: TimeDiff -> Int tdSec :: TimeDiff -> Int tdPicosec :: TimeDiff -> Integer getClockTime :: IO ClockTime -- | addToClockTime d t adds a time difference d -- and a clock time t to yield a new clock time. The difference -- d may be either positive or negative. addToClockTime :: TimeDiff -> ClockTime -> ClockTime -- | diffClockTimes t1 t2 returns the difference between -- two clock times t1 and t2 as a TimeDiff. diffClockTimes :: ClockTime -> ClockTime -> TimeDiff -- | converts an internal clock time to a local time, modified by the -- timezone and daylight savings time settings in force at the time of -- conversion. Because of this dependence on the local environment, -- toCalendarTime is in the IO monad. toCalendarTime :: ClockTime -> IO CalendarTime -- | converts an internal clock time into a CalendarTime in standard -- UTC format. toUTCTime :: ClockTime -> CalendarTime -- | converts a CalendarTime into the corresponding internal -- ClockTime, ignoring the contents of the ctWDay, -- ctYDay, ctTZName and ctIsDST fields. toClockTime :: CalendarTime -> ClockTime -- | formats calendar times using local conventions. calendarTimeToString :: CalendarTime -> String -- | formats calendar times using local conventions and a formatting -- string. The formatting string is that understood by the ISO C -- strftime() function. formatCalendarTime :: TimeLocale -> String -> CalendarTime -> String module CError module CForeign module CTypes module MarshalAlloc module MarshalArray module MarshalError -- | An abstract type that contains a value for each variant of -- IOError. data IOErrorType :: * -- | Construct an IOError of the given type where the second -- argument describes the error location and the third and fourth -- argument contain the file handle and file path of the file involved in -- the error if applicable. mkIOError :: IOErrorType -> String -> Maybe Handle -> Maybe FilePath -> IOError -- | I/O error where the operation failed because one of its arguments -- already exists. alreadyExistsErrorType :: IOErrorType -- | I/O error where the operation failed because one of its arguments does -- not exist. doesNotExistErrorType :: IOErrorType -- | I/O error where the operation failed because one of its arguments is a -- single-use resource, which is already being used. alreadyInUseErrorType :: IOErrorType -- | I/O error where the operation failed because the device is full. fullErrorType :: IOErrorType -- | I/O error where the operation failed because the end of file has been -- reached. eofErrorType :: IOErrorType -- | I/O error where the operation is not possible. illegalOperationErrorType :: IOErrorType -- | I/O error where the operation failed because the user does not have -- sufficient operating system privilege to perform that operation. permissionErrorType :: IOErrorType -- | I/O error that is programmer-defined. userErrorType :: IOErrorType -- | Adds a location description and maybe a file path and file handle to -- an IOError. If any of the file handle or file path is not given -- the corresponding value in the IOError remains unaltered. annotateIOError :: IOError -> String -> Maybe Handle -> Maybe FilePath -> IOError module MarshalUtils module Random -- | The class RandomGen provides a common interface to random -- number generators. -- -- Minimal complete definition: next and split. class RandomGen g where genRange _ = (minBound, maxBound) next :: RandomGen g => g -> (Int, g) split :: RandomGen g => g -> (g, g) genRange :: RandomGen g => g -> (Int, Int) -- | The StdGen instance of RandomGen has a genRange -- of at least 30 bits. -- -- The result of repeatedly using next should be at least as -- statistically robust as the Minimal Standard Random Number -- Generator described by ["Random#Park", "Random#Carta"]. Until more -- is known about implementations of split, all we require is that -- split deliver generators that are (a) not identical and (b) -- independently robust in the sense just given. -- -- The Show and Read instances of StdGen provide a -- primitive way to save the state of a random number generator. It is -- required that read (show g) == g. -- -- In addition, reads may be used to map an arbitrary string (not -- necessarily one produced by show) onto a value of type -- StdGen. In general, the Read instance of StdGen -- has the following properties: -- -- data StdGen -- | The function mkStdGen provides an alternative way of producing -- an initial generator, by mapping an Int into a generator. -- Again, distinct arguments should be likely to produce distinct -- generators. mkStdGen :: Int -> StdGen -- | Uses the supplied function to get a value from the current global -- random generator, and updates the global generator with the new -- generator returned by the function. For example, rollDice -- gets a random integer between 1 and 6: -- --
--   rollDice :: IO Int
--   rollDice = getStdRandom (randomR (1,6))
--   
getStdRandom :: (StdGen -> (a, StdGen)) -> IO a -- | Gets the global random number generator. getStdGen :: IO StdGen -- | Sets the global random number generator. setStdGen :: StdGen -> IO () -- | Applies split to the current global random generator, updates -- it with one of the results, and returns the other. newStdGen :: IO StdGen -- | With a source of random number supply in hand, the Random class -- allows the programmer to extract random values of a variety of types. -- -- Minimal complete definition: randomR and random. class Random a where randomRs ival g = x : randomRs ival g' where (x, g') = randomR ival g randoms g = (\ (x, g') -> x : randoms g') (random g) randomRIO range = getStdRandom (randomR range) randomIO = getStdRandom random randomR :: (Random a, RandomGen g) => (a, a) -> g -> (a, g) random :: (Random a, RandomGen g) => g -> (a, g) randomRs :: (Random a, RandomGen g) => (a, a) -> g -> [a] randoms :: (Random a, RandomGen g) => g -> [a] randomRIO :: Random a => (a, a) -> IO a randomIO :: Random a => IO a instance Random Float instance Random Double instance Random Integer instance Random Bool instance Random Char instance Random Int instance Read StdGen instance Show StdGen instance RandomGen StdGen module Ptr module StablePtr module Monad -- | Monads that also support choice and failure. class Monad m => MonadPlus (m :: * -> *) mzero :: MonadPlus m => m a mplus :: MonadPlus m => m a -> 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. join :: Monad m => m (m a) -> m a -- | guard b is return () if b is -- True, and mzero if b is False. guard :: MonadPlus m => Bool -> m () -- | Conditional execution of monadic expressions. For example, -- --
--   when debug (putStr "Debugging\n")
--   
-- -- will output the string Debugging\n if the Boolean value -- debug is True, and otherwise do nothing. when :: Monad m => Bool -> m () -> m () -- | The reverse of when. unless :: Monad m => Bool -> m () -> m () -- | In many situations, the liftM operations can be replaced by -- uses of ap, which promotes function application. -- --
--   return f `ap` x1 `ap` ... `ap` xn
--   
-- -- is equivalent to -- --
--   liftMn f x1 x2 ... xn
--   
ap :: Monad m => m (a -> b) -> m a -> m b -- | This generalizes the list-based concat function. msum :: MonadPlus m => [m a] -> m a -- | This generalizes the list-based filter function. filterM :: Monad m => (a -> m Bool) -> [a] -> m [a] -- | The mapAndUnzipM function maps its first argument over a list, -- returning the result as a pair of lists. This function is mainly used -- with complicated data structures or a state-transforming monad. mapAndUnzipM :: Monad m => (a -> m (b, c)) -> [a] -> m ([b], [c]) -- | The zipWithM function generalizes zipWith to arbitrary -- monads. zipWithM :: Monad m => (a -> b -> m c) -> [a] -> [b] -> m [c] -- | zipWithM_ is the extension of zipWithM which ignores the -- final result. zipWithM_ :: Monad m => (a -> b -> m c) -> [a] -> [b] -> m () -- | The foldM function is analogous to foldl, except that -- its result is encapsulated in a monad. Note that foldM works -- from left-to-right over the list arguments. This could be an issue -- where (>>) and the `folded function' are not -- commutative. -- --
--   foldM f a1 [x1, x2, ..., xm]
--   
-- -- == -- --
--   do
--     a2 <- f a1 x1
--     a3 <- f a2 x2
--     ...
--     f am xm
--   
-- -- If right-to-left evaluation is required, the input list should be -- reversed. foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a -- | Promote a function to a monad. liftM :: Monad m => (a1 -> r) -> m a1 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right. For example, -- --
--   liftM2 (+) [0,1] [0,2] = [0,2,1,3]
--   liftM2 (+) (Just 1) Nothing = Nothing
--   
liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right (cf. liftM2). liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right (cf. liftM2). liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right (cf. liftM2). liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r -- | 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. class Monad (m :: * -> *) (>>=) :: Monad m => m a -> (a -> m b) -> m b (>>) :: Monad m => m a -> m b -> m b return :: Monad m => a -> m a fail :: Monad m => String -> m a -- | 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. class Functor (f :: * -> *) fmap :: Functor f => (a -> b) -> f a -> f b -- | mapM f is equivalent to sequence . -- map f. mapM :: Monad m => (a -> m b) -> [a] -> m [b] -- | mapM_ f is equivalent to sequence_ . -- map f. mapM_ :: Monad m => (a -> m b) -> [a] -> m () -- | Evaluate each action in the sequence from left to right, and collect -- the results. sequence :: Monad m => [m a] -> m [a] -- | Evaluate each action in the sequence from left to right, and ignore -- the results. sequence_ :: Monad m => [m a] -> m () -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b module Ratio -- | Rational numbers, with numerator and denominator of some -- Integral type. data Ratio a :: * -> * -- | Arbitrary-precision rational numbers, represented as a ratio of two -- Integer values. A rational number may be constructed using the -- % operator. type Rational = Ratio Integer -- | Forms the ratio of two integral numbers. (%) :: Integral a => a -> a -> Ratio a -- | Extract the numerator of the ratio in reduced form: the numerator and -- denominator have no common factor and the denominator is positive. numerator :: Integral a => Ratio a -> a -- | Extract the denominator of the ratio in reduced form: the numerator -- and denominator have no common factor and the denominator is positive. denominator :: Integral a => Ratio a -> a -- | approxRational, applied to two real fractional numbers -- x and epsilon, returns the simplest rational number -- within epsilon of x. A rational number y is -- said to be simpler than another y' if -- -- -- -- Any real interval contains a unique simplest rational; in particular, -- note that 0/1 is the simplest rational of all. approxRational :: RealFrac a => a -> a -> Rational module Word module ForeignPtr module IO -- | Haskell defines operations to read and write characters from and to -- files, represented by values of type Handle. Each value of -- this type is a handle: a record used by the Haskell run-time -- system to manage I/O with file system objects. A handle has at -- least the following properties: -- -- -- -- Most handles will also have a current I/O position indicating where -- the next input or output operation will occur. A handle is -- readable if it manages only input or both input and output; -- likewise, it is writable if it manages only output or both -- input and output. A handle is open when first allocated. Once -- it is closed it can no longer be used for either input or output, -- though an implementation cannot re-use its storage while references -- remain to it. Handles are in the Show and Eq classes. -- The string produced by showing a handle is system dependent; it should -- include enough information to identify the handle for debugging. A -- handle is equal according to == only to itself; no attempt is -- made to compare the internal state of different handles for equality. data Handle :: * data HandlePosn :: * -- | See openFile data IOMode :: * ReadMode :: IOMode WriteMode :: IOMode AppendMode :: IOMode ReadWriteMode :: IOMode -- | Three kinds of buffering are supported: line-buffering, -- block-buffering or no-buffering. These modes have the following -- effects. For output, items are written out, or flushed, from -- the internal buffer according to the buffer mode: -- -- -- -- An implementation is free to flush the buffer more frequently, but not -- less frequently, than specified above. The output buffer is emptied as -- soon as it has been written out. -- -- Similarly, input occurs according to the buffer mode for the handle: -- -- -- -- The default buffering mode when a handle is opened is -- implementation-dependent and may depend on the file system object -- which is attached to that handle. For most implementations, physical -- files will normally be block-buffered and terminals will normally be -- line-buffered. data BufferMode :: * -- | buffering is disabled if possible. NoBuffering :: BufferMode -- | line-buffering should be enabled if possible. LineBuffering :: BufferMode -- | block-buffering should be enabled if possible. The size of the buffer -- is n items if the argument is Just n and is -- otherwise implementation-dependent. BlockBuffering :: Maybe Int -> BufferMode -- | A mode that determines the effect of hSeek hdl mode -- i. data SeekMode :: * -- | the position of hdl is set to i. AbsoluteSeek :: SeekMode -- | the position of hdl is set to offset i from the -- current position. RelativeSeek :: SeekMode -- | the position of hdl is set to offset i from the end -- of the file. SeekFromEnd :: SeekMode -- | A handle managing input from the Haskell program's standard input -- channel. stdin :: Handle -- | A handle managing output to the Haskell program's standard output -- channel. stdout :: Handle -- | A handle managing output to the Haskell program's standard error -- channel. stderr :: Handle -- | Computation openFile file mode allocates and returns a -- new, open handle to manage the file file. It manages input if -- mode is ReadMode, output if mode is -- WriteMode or AppendMode, and both input and output if -- mode is ReadWriteMode. -- -- If the file does not exist and it is opened for output, it should be -- created as a new file. If mode is WriteMode and the -- file already exists, then it should be truncated to zero length. Some -- operating systems delete empty files, so there is no guarantee that -- the file will exist following an openFile with mode -- WriteMode unless it is subsequently written to successfully. -- The handle is positioned at the end of the file if mode is -- AppendMode, and otherwise at the beginning (in which case its -- internal position is 0). The initial buffer mode is -- implementation-dependent. -- -- This operation may fail with: -- -- -- -- Note: if you will be working with files containing binary data, you'll -- want to be using openBinaryFile. openFile :: FilePath -> IOMode -> IO Handle -- | Computation hClose hdl makes handle hdl -- closed. Before the computation finishes, if hdl is writable -- its buffer is flushed as for hFlush. Performing hClose -- on a handle that has already been closed has no effect; doing so is -- not an error. All other operations on a closed handle will fail. If -- hClose fails for any reason, any further operations (apart from -- hClose) on the handle will still fail as if hdl had -- been successfully closed. hClose :: Handle -> IO () -- | For a handle hdl which attached to a physical file, -- hFileSize hdl returns the size of that file in 8-bit -- bytes. hFileSize :: Handle -> IO Integer -- | For a readable handle hdl, hIsEOF hdl returns -- True if no further input can be taken from hdl or for -- a physical file, if the current I/O position is equal to the length of -- the file. Otherwise, it returns False. -- -- NOTE: hIsEOF may block, because it has to attempt to read from -- the stream to determine whether there is any more data to be read. hIsEOF :: Handle -> IO Bool -- | The computation isEOF is identical to hIsEOF, except -- that it works only on stdin. isEOF :: IO Bool -- | Computation hSetBuffering hdl mode sets the mode of -- buffering for handle hdl on subsequent reads and writes. -- -- If the buffer mode is changed from BlockBuffering or -- LineBuffering to NoBuffering, then -- -- -- -- This operation may fail with: -- -- hSetBuffering :: Handle -> BufferMode -> IO () -- | Computation hGetBuffering hdl returns the current -- buffering mode for hdl. hGetBuffering :: Handle -> IO BufferMode -- | The action hFlush hdl causes any items buffered for -- output in handle hdl to be sent immediately to the operating -- system. -- -- This operation may fail with: -- -- hFlush :: Handle -> IO () -- | Computation hGetPosn hdl returns the current I/O -- position of hdl as a value of the abstract type -- HandlePosn. hGetPosn :: Handle -> IO HandlePosn -- | If a call to hGetPosn hdl returns a position -- p, then computation hSetPosn p sets the -- position of hdl to the position it held at the time of the -- call to hGetPosn. -- -- This operation may fail with: -- -- hSetPosn :: HandlePosn -> IO () -- | Computation hSeek hdl mode i sets the position of -- handle hdl depending on mode. The offset i -- is given in terms of 8-bit bytes. -- -- If hdl is block- or line-buffered, then seeking to a position -- which is not in the current buffer will first cause any items in the -- output buffer to be written to the device, and then cause the input -- buffer to be discarded. Some handles may not be seekable (see -- hIsSeekable), or only support a subset of the possible -- positioning operations (for instance, it may only be possible to seek -- to the end of a tape, or to a positive offset from the beginning or -- current position). It is not possible to set a negative I/O position, -- or for a physical file, an I/O position beyond the current -- end-of-file. -- -- This operation may fail with: -- -- hSeek :: Handle -> SeekMode -> Integer -> IO () -- | Computation hWaitForInput hdl t waits until input is -- available on handle hdl. It returns True as soon as -- input is available on hdl, or False if no input is -- available within t milliseconds. Note that -- hWaitForInput waits until one or more full characters -- are available, which means that it needs to do decoding, and hence may -- fail with a decoding error. -- -- If t is less than zero, then hWaitForInput waits -- indefinitely. -- -- This operation may fail with: -- -- -- -- NOTE for GHC users: unless you use the -threaded flag, -- hWaitForInput hdl t where t >= 0 will block all -- other Haskell threads for the duration of the call. It behaves like a -- safe foreign call in this respect. hWaitForInput :: Handle -> Int -> IO Bool -- | Computation hReady hdl indicates whether at least one -- item is available for input from handle hdl. -- -- This operation may fail with: -- -- hReady :: Handle -> IO Bool -- | Computation hGetChar hdl reads a character from the -- file or channel managed by hdl, blocking until a character is -- available. -- -- This operation may fail with: -- -- hGetChar :: Handle -> IO Char -- | Computation hGetLine hdl reads a line from the file or -- channel managed by hdl. -- -- This operation may fail with: -- -- -- -- If hGetLine encounters end-of-file at any other point while -- reading in a line, it is treated as a line terminator and the -- (partial) line is returned. hGetLine :: Handle -> IO String -- | Computation hLookAhead returns the next character from the -- handle without removing it from the input buffer, blocking until a -- character is available. -- -- This operation may fail with: -- -- hLookAhead :: Handle -> IO Char -- | Computation hGetContents hdl returns the list of -- characters corresponding to the unread portion of the channel or file -- managed by hdl, which is put into an intermediate state, -- semi-closed. In this state, hdl is effectively closed, -- but items are read from hdl on demand and accumulated in a -- special list returned by hGetContents hdl. -- -- Any operation that fails because a handle is closed, also fails if a -- handle is semi-closed. The only exception is hClose. A -- semi-closed handle becomes closed: -- -- -- -- Once a semi-closed handle becomes closed, the contents of the -- associated list becomes fixed. The contents of this final list is only -- partially specified: it will contain at least all the items of the -- stream that were evaluated prior to the handle becoming closed. -- -- Any I/O errors encountered while a handle is semi-closed are simply -- discarded. -- -- This operation may fail with: -- -- hGetContents :: Handle -> IO String -- | Computation hPutChar hdl ch writes the character -- ch to the file or channel managed by hdl. Characters -- may be buffered if buffering is enabled for hdl. -- -- This operation may fail with: -- -- hPutChar :: Handle -> Char -> IO () -- | Computation hPutStr hdl s writes the string s -- to the file or channel managed by hdl. -- -- This operation may fail with: -- -- hPutStr :: Handle -> String -> IO () -- | The same as hPutStr, but adds a newline character. hPutStrLn :: Handle -> String -> IO () -- | Computation hPrint hdl t writes the string -- representation of t given by the shows function to the -- file or channel managed by hdl and appends a newline. -- -- This operation may fail with: -- -- hPrint :: Show a => Handle -> a -> IO () hIsOpen :: Handle -> IO Bool hIsClosed :: Handle -> IO Bool hIsReadable :: Handle -> IO Bool hIsWritable :: Handle -> IO Bool hIsSeekable :: Handle -> IO Bool -- | An error indicating that an IO operation failed because one of -- its arguments already exists. isAlreadyExistsError :: IOError -> Bool -- | An error indicating that an IO operation failed because one of -- its arguments does not exist. isDoesNotExistError :: IOError -> Bool -- | An error indicating that an IO operation failed because one of -- its arguments is a single-use resource, which is already being used -- (for example, opening the same file twice for writing might give this -- error). isAlreadyInUseError :: IOError -> Bool -- | An error indicating that an IO operation failed because the -- device is full. isFullError :: IOError -> Bool -- | An error indicating that an IO operation failed because the end -- of file has been reached. isEOFError :: IOError -> Bool -- | An error indicating that an IO operation failed because the -- operation was not possible. Any computation which returns an IO -- result may fail with isIllegalOperation. In some cases, an -- implementation will not be able to distinguish between the possible -- error causes. In this case it should fail with -- isIllegalOperation. isIllegalOperation :: IOError -> Bool -- | An error indicating that an IO operation failed because the -- user does not have sufficient operating system privilege to perform -- that operation. isPermissionError :: IOError -> Bool -- | A programmer-defined error value constructed using userError. isUserError :: IOError -> Bool ioeGetErrorString :: IOError -> String ioeGetHandle :: IOError -> Maybe Handle ioeGetFileName :: IOError -> Maybe FilePath -- | The construct try comp exposes IO errors which occur -- within a computation, and which are not fully handled. -- -- Non-I/O exceptions are not caught by this variant; to catch all -- exceptions, use try from Control.Exception. try :: IO a -> IO (Either IOError a) -- | The bracket function captures a common allocate, compute, -- deallocate idiom in which the deallocation step must occur even in the -- case of an error during computation. This is similar to -- try-catch-finally in Java. -- -- This version handles only IO errors, as defined by Haskell 98. The -- version of bracket in Control.Exception handles all -- exceptions, and should be used instead. bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c -- | A variant of bracket where the middle computation doesn't want -- x. -- -- This version handles only IO errors, as defined by Haskell 98. The -- version of bracket_ in Control.Exception handles all -- exceptions, and should be used instead. bracket_ :: IO a -> (a -> IO b) -> IO c -> IO c -- | A value of type IO a is a computation which, when -- performed, does some I/O before returning a value of type a. -- -- 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. data IO a :: * -> * -- | 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. type FilePath = String -- | The Haskell 2010 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 2010, this is an opaque type. type IOError = IOException -- | Raise an IOError in the IO monad. ioError :: IOError -> IO a -- | Construct an IOError value with a string describing the error. -- The fail method of the IO instance of the Monad -- class raises a userError, thus: -- --
--   instance Monad IO where
--     ...
--     fail s = ioError (userError s)
--   
userError :: String -> IOError -- | The catch function establishes a handler that receives any -- IOError raised in the action protected by catch. An -- IOError is caught by the most recent handler established by one -- of the exception handling functions. These handlers are not selective: -- all IOErrors are caught. Exception propagation must be -- explicitly provided in a handler by re-raising any unwanted -- exceptions. For example, in -- --
--   f = catch g (\e -> if IO.isEOFError e then return [] else ioError e)
--   
-- -- the function f returns [] when an end-of-file -- exception (cf. isEOFError) occurs in g; otherwise, the -- exception is propagated to the next outer handler. -- -- When an exception propagates outside the main program, the Haskell -- system prints the associated IOError value and exits the -- program. -- -- Non-I/O exceptions are not caught by this variant; to catch all -- exceptions, use catch from Control.Exception. catch :: IO a -> (IOError -> IO a) -> IO a -- | 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. interact :: (String -> String) -> IO () -- | Write a character to the standard output device (same as -- hPutChar stdout). putChar :: Char -> IO () -- | Write a string to the standard output device (same as hPutStr -- stdout). putStr :: String -> IO () -- | The same as putStr, but adds a newline character. putStrLn :: String -> 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]])
--   
print :: Show a => a -> IO () -- | Read a character from the standard input device (same as -- hGetChar stdin). getChar :: IO Char -- | Read a line from the standard input device (same as hGetLine -- stdin). getLine :: IO String -- | The getContents operation returns all user input as a single -- string, which is read lazily as it is needed (same as -- hGetContents stdin). getContents :: IO String -- | The readFile function reads a file and returns the contents of -- the file as a string. The file is read lazily, on demand, as with -- getContents. readFile :: FilePath -> IO String -- | The computation writeFile file str function writes the -- string str, to the file file. writeFile :: FilePath -> String -> IO () -- | 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]])
--   
appendFile :: FilePath -> String -> IO () -- | The readIO function is similar to read except that it -- signals parse failure to the IO monad instead of terminating -- the program. readIO :: Read a => String -> IO a -- | The readLn function combines getLine and readIO. readLn :: Read a => IO a module Char -- | Selects the first 128 characters of the Unicode character set, -- corresponding to the ASCII character set. isAscii :: Char -> Bool -- | Selects the first 256 characters of the Unicode character set, -- corresponding to the ISO 8859-1 (Latin-1) character set. isLatin1 :: Char -> Bool -- | Selects control characters, which are the non-printing characters of -- the Latin-1 subset of Unicode. isControl :: Char -> Bool -- | Selects printable Unicode characters (letters, numbers, marks, -- punctuation, symbols and spaces). isPrint :: Char -> Bool -- | Returns True for any Unicode space character, and the control -- characters \t, \n, \r, \f, -- \v. isSpace :: Char -> Bool -- | Selects upper-case or title-case alphabetic Unicode characters -- (letters). Title case is used by a small number of letter ligatures -- like the single-character form of Lj. isUpper :: Char -> Bool -- | Selects lower-case alphabetic Unicode characters (letters). isLower :: Char -> Bool -- | Selects alphabetic Unicode characters (lower-case, upper-case and -- title-case letters, plus letters of caseless scripts and modifiers -- letters). This function is equivalent to isLetter. isAlpha :: Char -> Bool -- | Selects ASCII digits, i.e. '0'..'9'. isDigit :: Char -> Bool -- | Selects ASCII octal digits, i.e. '0'..'7'. isOctDigit :: Char -> Bool -- | Selects ASCII hexadecimal digits, i.e. '0'..'9', -- 'a'..'f', 'A'..'F'. isHexDigit :: Char -> Bool -- | Selects alphabetic or numeric digit Unicode characters. -- -- Note that numeric digits outside the ASCII range are selected by this -- function but not by isDigit. Such digits may be part of -- identifiers but are not used by the printer and reader to represent -- numbers. isAlphaNum :: Char -> Bool -- | Convert a single digit Char to the corresponding Int. -- This function fails unless its argument satisfies isHexDigit, -- but recognises both upper and lower-case hexadecimal digits (i.e. -- '0'..'9', 'a'..'f', -- 'A'..'F'). digitToInt :: Char -> Int -- | Convert an Int in the range 0..15 to the -- corresponding single digit Char. This function fails on other -- inputs, and generates lower-case hexadecimal digits. intToDigit :: Int -> Char -- | Convert a letter to the corresponding upper-case letter, if any. Any -- other character is returned unchanged. toUpper :: Char -> Char -- | Convert a letter to the corresponding lower-case letter, if any. Any -- other character is returned unchanged. toLower :: Char -> Char -- | The fromEnum method restricted to the type Char. ord :: Char -> Int -- | The toEnum method restricted to the type Char. chr :: Int -> Char -- | Read a string representation of a character, using Haskell -- source-language escape conventions, and convert it to the character -- that it encodes. For example: -- --
--   readLitChar "\\nHello"  =  [('\n', "Hello")]
--   
readLitChar :: ReadS Char -- | Convert a character to a string using only printable characters, using -- Haskell source-language escape conventions. For example: -- --
--   showLitChar '\n' s  =  "\\n" ++ s
--   
showLitChar :: Char -> ShowS -- | Read a string representation of a character, using Haskell -- source-language escape conventions. For example: -- --
--   lexLitChar  "\\nHello"  =  [("\\n", "Hello")]
--   
lexLitChar :: ReadS String -- | 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). data Char :: * -- | A String is a list of characters. String constants in Haskell -- are values of type String. type String = [Char] module Int module Ix -- | The Ix class is used to map a contiguous subrange of values in -- a type onto integers. It is used primarily for array indexing (see the -- array package). -- -- The first argument (l,u) of each of these operations is a -- pair specifying the lower and upper bounds of a contiguous subrange of -- values. -- -- An implementation is entitled to assume the following laws about these -- operations: -- -- -- -- Minimal complete instance: range, index and -- inRange. class Ord a => Ix a range :: Ix a => (a, a) -> [a] index :: Ix a => (a, a) -> a -> Int inRange :: Ix a => (a, a) -> a -> Bool rangeSize :: Ix a => (a, a) -> Int -- | The size of the subrange defined by a bounding pair. rangeSize :: Ix a => (a, a) -> Int module Array -- | The type of immutable non-strict (boxed) arrays with indices in -- i and elements in e. data Array i e :: * -> * -> * -- | Construct an array with the specified bounds and containing values for -- given indices within these bounds. -- -- The array is undefined (i.e. bottom) if any index in the list is out -- of bounds. The Haskell 2010 Report further specifies that if any two -- associations in the list have the same index, the value at that index -- is undefined (i.e. bottom). However in GHC's implementation, the value -- at such an index is the value part of the last association with that -- index in the list. -- -- Because the indices must be checked for these errors, array is -- strict in the bounds argument and in the indices of the association -- list, but non-strict in the values. Thus, recurrences such as the -- following are possible: -- --
--   a = array (1,100) ((1,1) : [(i, i * a!(i-1)) | i <- [2..100]])
--   
-- -- Not every index within the bounds of the array need appear in the -- association list, but the values associated with indices that do not -- appear will be undefined (i.e. bottom). -- -- If, in any dimension, the lower bound is greater than the upper bound, -- then the array is legal, but empty. Indexing an empty array always -- gives an array-bounds error, but bounds still yields the bounds -- with which the array was constructed. array :: Ix i => (i, i) -> [(i, e)] -> Array i e -- | Construct an array from a pair of bounds and a list of values in index -- order. listArray :: Ix i => (i, i) -> [e] -> Array i e -- | The value at the given index in an array. (!) :: Ix i => Array i e -> i -> e -- | The bounds with which an array was constructed. bounds :: Ix i => Array i e -> (i, i) -- | The list of indices of an array in ascending order. indices :: Ix i => Array i e -> [i] -- | The list of elements of an array in index order. elems :: Ix i => Array i e -> [e] -- | The list of associations of an array in index order. assocs :: Ix i => Array i e -> [(i, e)] -- | The accumArray function deals with repeated indices in the -- association list using an accumulating function which combines -- the values of associations with the same index. For example, given a -- list of values of some index type, hist produces a histogram -- of the number of occurrences of each index within a specified range: -- --
--   hist :: (Ix a, Num b) => (a,a) -> [a] -> Array a b
--   hist bnds is = accumArray (+) 0 bnds [(i, 1) | i<-is, inRange bnds i]
--   
-- -- If the accumulating function is strict, then accumArray is -- strict in the values, as well as the indices, in the association list. -- Thus, unlike ordinary arrays built with array, accumulated -- arrays should not in general be recursive. accumArray :: Ix i => (e -> a -> e) -> e -> (i, i) -> [(i, a)] -> Array i e -- | Constructs an array identical to the first argument except that it has -- been updated by the associations in the right argument. For example, -- if m is a 1-origin, n by n matrix, then -- --
--   m//[((i,i), 0) | i <- [1..n]]
--   
-- -- is the same matrix, except with the diagonal zeroed. -- -- Repeated indices in the association list are handled as for -- array: Haskell 2010 specifies that the resulting array is -- undefined (i.e. bottom), but GHC's implementation uses the last -- association for each index. (//) :: Ix i => Array i e -> [(i, e)] -> Array i e -- | accum f takes an array and an association list and -- accumulates pairs from the list into the array with the accumulating -- function f. Thus accumArray can be defined using -- accum: -- --
--   accumArray f z b = accum f (array b [(i, z) | i <- range b])
--   
accum :: Ix i => (e -> a -> e) -> Array i e -> [(i, a)] -> Array i e -- | ixmap allows for transformations on array indices. It may be -- thought of as providing function composition on the right with the -- mapping that the original array embodies. -- -- A similar transformation of array values may be achieved using -- fmap from the Array instance of the Functor -- class. ixmap :: (Ix i, Ix j) => (i, i) -> (i -> j) -> Array j e -> Array i e