-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Compatibility with Haskell 2010 -- -- This package provides exactly the library modules defined by the -- Haskell 2010 standard. @package haskell2010 @version 1.1.2.0 -- | The Haskell 2010 Prelude: a standard module imported by default into -- all Haskell modules. For more documentation, see the Haskell 2010 -- 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 Foreign.StablePtr -- | A stable pointer is a reference to a Haskell expression that is -- guaranteed not to be affected by garbage collection, i.e., it will -- neither be deallocated nor will the value of the stable pointer itself -- change during garbage collection (ordinary references may be relocated -- during garbage collection). Consequently, stable pointers can be -- passed to foreign code, which can treat it as an opaque reference to a -- Haskell value. -- -- A value of type StablePtr a is a stable pointer to a Haskell -- expression of type a. data StablePtr a :: * -> * -- | Create a stable pointer referring to the given Haskell value. newStablePtr :: a -> IO (StablePtr a) -- | Obtain the Haskell value referenced by a stable pointer, i.e., the -- same value that was passed to the corresponding call to -- makeStablePtr. If the argument to deRefStablePtr has -- already been freed using freeStablePtr, the behaviour of -- deRefStablePtr is undefined. deRefStablePtr :: StablePtr a -> IO a -- | Dissolve the association between the stable pointer and the Haskell -- value. Afterwards, if the stable pointer is passed to -- deRefStablePtr or freeStablePtr, the behaviour is -- undefined. However, the stable pointer may still be passed to -- castStablePtrToPtr, but the Ptr () value -- returned by castStablePtrToPtr, in this case, is undefined (in -- particular, it may be nullPtr). Nevertheless, the call to -- castStablePtrToPtr is guaranteed not to diverge. freeStablePtr :: StablePtr a -> IO () -- | Coerce a stable pointer to an address. No guarantees are made about -- the resulting value, except that the original stable pointer can be -- recovered by castPtrToStablePtr. In particular, the address may -- not refer to an accessible memory location and any attempt to pass it -- to the member functions of the class Storable leads to -- undefined behaviour. castStablePtrToPtr :: StablePtr a -> Ptr () -- | The inverse of castStablePtrToPtr, i.e., we have the identity -- --
--   sp == castPtrToStablePtr (castStablePtrToPtr sp)
--   
-- -- for any stable pointer sp on which freeStablePtr has -- not been executed yet. Moreover, castPtrToStablePtr may only be -- applied to pointers that have been produced by -- castStablePtrToPtr. castPtrToStablePtr :: Ptr () -> StablePtr a module Data.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 module Data.Char -- | 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] -- | Selects control characters, which are the non-printing characters of -- the Latin-1 subset of Unicode. isControl :: Char -> Bool -- | Returns True for any Unicode space character, and the control -- characters \t, \n, \r, \f, -- \v. isSpace :: Char -> Bool -- | Selects lower-case alphabetic Unicode characters (letters). isLower :: 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 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 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 -- | Selects printable Unicode characters (letters, numbers, marks, -- punctuation, symbols and spaces). isPrint :: 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 Unicode characters (lower-case, upper-case and -- title-case letters, plus letters of caseless scripts and modifiers -- letters). This function is equivalent to isAlpha. isLetter :: Char -> Bool -- | Selects Unicode mark characters, e.g. accents and the like, which -- combine with preceding letters. isMark :: Char -> Bool -- | Selects Unicode numeric characters, including digits from various -- scripts, Roman numerals, etc. isNumber :: Char -> Bool -- | Selects Unicode punctuation characters, including various kinds of -- connectors, brackets and quotes. isPunctuation :: Char -> Bool -- | Selects Unicode symbol characters, including mathematical and currency -- symbols. isSymbol :: Char -> Bool -- | Selects Unicode space and separator characters. isSeparator :: Char -> Bool -- | 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 ASCII upper-case letters, i.e. characters satisfying both -- isAscii and isUpper. isAsciiUpper :: Char -> Bool -- | Selects ASCII lower-case letters, i.e. characters satisfying both -- isAscii and isLower. isAsciiLower :: Char -> Bool -- | Unicode General Categories (column 2 of the UnicodeData table) in the -- order they are listed in the Unicode standard. data GeneralCategory :: * -- | Lu: Letter, Uppercase UppercaseLetter :: GeneralCategory -- | Ll: Letter, Lowercase LowercaseLetter :: GeneralCategory -- | Lt: Letter, Titlecase TitlecaseLetter :: GeneralCategory -- | Lm: Letter, Modifier ModifierLetter :: GeneralCategory -- | Lo: Letter, Other OtherLetter :: GeneralCategory -- | Mn: Mark, Non-Spacing NonSpacingMark :: GeneralCategory -- | Mc: Mark, Spacing Combining SpacingCombiningMark :: GeneralCategory -- | Me: Mark, Enclosing EnclosingMark :: GeneralCategory -- | Nd: Number, Decimal DecimalNumber :: GeneralCategory -- | Nl: Number, Letter LetterNumber :: GeneralCategory -- | No: Number, Other OtherNumber :: GeneralCategory -- | Pc: Punctuation, Connector ConnectorPunctuation :: GeneralCategory -- | Pd: Punctuation, Dash DashPunctuation :: GeneralCategory -- | Ps: Punctuation, Open OpenPunctuation :: GeneralCategory -- | Pe: Punctuation, Close ClosePunctuation :: GeneralCategory -- | Pi: Punctuation, Initial quote InitialQuote :: GeneralCategory -- | Pf: Punctuation, Final quote FinalQuote :: GeneralCategory -- | Po: Punctuation, Other OtherPunctuation :: GeneralCategory -- | Sm: Symbol, Math MathSymbol :: GeneralCategory -- | Sc: Symbol, Currency CurrencySymbol :: GeneralCategory -- | Sk: Symbol, Modifier ModifierSymbol :: GeneralCategory -- | So: Symbol, Other OtherSymbol :: GeneralCategory -- | Zs: Separator, Space Space :: GeneralCategory -- | Zl: Separator, Line LineSeparator :: GeneralCategory -- | Zp: Separator, Paragraph ParagraphSeparator :: GeneralCategory -- | Cc: Other, Control Control :: GeneralCategory -- | Cf: Other, Format Format :: GeneralCategory -- | Cs: Other, Surrogate Surrogate :: GeneralCategory -- | Co: Other, Private Use PrivateUse :: GeneralCategory -- | Cn: Other, Not Assigned NotAssigned :: GeneralCategory -- | The Unicode general category of the character. generalCategory :: Char -> GeneralCategory -- | 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 -- | Convert a letter to the corresponding title-case or upper-case letter, -- if any. (Title case differs from upper case only for a small number of -- ligature letters.) Any other character is returned unchanged. toTitle :: Char -> Char -- | 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 -- | The fromEnum method restricted to the type Char. ord :: Char -> Int -- | The toEnum method restricted to the type Char. chr :: Int -> 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 -- | 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 module Data.Int -- | 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 :: * -- | 8-bit signed integer type data Int8 :: * -- | 16-bit signed integer type data Int16 :: * -- | 32-bit signed integer type data Int32 :: * -- | 64-bit signed integer type data Int64 :: * module Data.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 Data.Word -- | A Word is an unsigned integral type, with the same size as -- Int. data Word :: * -- | 8-bit unsigned integer type data Word8 :: * -- | 16-bit unsigned integer type data Word16 :: * -- | 32-bit unsigned integer type data Word32 :: * -- | 64-bit unsigned integer type data Word64 :: * -- | The module Foreign.Ptr provides typed pointers to foreign -- entities. We distinguish two kinds of pointers: pointers to data and -- pointers to functions. It is understood that these two kinds of -- pointers may be represented differently as they may be references to -- data and text segments, respectively. module Foreign.Ptr -- | A value of type Ptr a represents a pointer to an -- object, or an array of objects, which may be marshalled to or from -- Haskell values of type a. -- -- The type a will often be an instance of class Storable -- which provides the marshalling operations. However this is not -- essential, and you can provide your own operations to access the -- pointer. For example you might write small foreign functions to get or -- set the fields of a C struct. data Ptr a :: * -> * -- | The constant nullPtr contains a distinguished value of -- Ptr that is not associated with a valid memory location. nullPtr :: Ptr a -- | The castPtr function casts a pointer from one type to another. castPtr :: Ptr a -> Ptr b -- | Advances the given address by the given offset in bytes. plusPtr :: Ptr a -> Int -> Ptr b -- | Given an arbitrary address and an alignment constraint, -- alignPtr yields the next higher address that fulfills the -- alignment constraint. An alignment constraint x is fulfilled -- by any address divisible by x. This operation is idempotent. alignPtr :: Ptr a -> Int -> Ptr a -- | Computes the offset required to get from the second to the first -- argument. We have -- --
--   p2 == p1 `plusPtr` (p2 `minusPtr` p1)
--   
minusPtr :: Ptr a -> Ptr b -> Int -- | A value of type FunPtr a is a pointer to a function -- callable from foreign code. The type a will normally be a -- foreign type, a function type with zero or more arguments where -- -- -- -- A value of type FunPtr a may be a pointer to a foreign -- function, either returned by another foreign function or imported with -- a a static address import like -- --
--   foreign import ccall "stdlib.h &free"
--     p_free :: FunPtr (Ptr a -> IO ())
--   
-- -- or a pointer to a Haskell function created using a wrapper stub -- declared to produce a FunPtr of the correct type. For example: -- --
--   type Compare = Int -> Int -> Bool
--   foreign import ccall "wrapper"
--     mkCompare :: Compare -> IO (FunPtr Compare)
--   
-- -- Calls to wrapper stubs like mkCompare allocate storage, which -- should be released with freeHaskellFunPtr when no longer -- required. -- -- To convert FunPtr values to corresponding Haskell functions, -- one can define a dynamic stub for the specific foreign type, -- e.g. -- --
--   type IntFunction = CInt -> IO ()
--   foreign import ccall "dynamic" 
--     mkFun :: FunPtr IntFunction -> IntFunction
--   
data FunPtr a :: * -> * -- | The constant nullFunPtr contains a distinguished value of -- FunPtr that is not associated with a valid memory location. nullFunPtr :: FunPtr a -- | Casts a FunPtr to a FunPtr of a different type. castFunPtr :: FunPtr a -> FunPtr b -- | Casts a FunPtr to a Ptr. -- -- Note: this is valid only on architectures where data and -- function pointers range over the same set of addresses, and should -- only be used for bindings to external libraries whose interface -- already relies on this assumption. castFunPtrToPtr :: FunPtr a -> Ptr b -- | Casts a Ptr to a FunPtr. -- -- Note: this is valid only on architectures where data and -- function pointers range over the same set of addresses, and should -- only be used for bindings to external libraries whose interface -- already relies on this assumption. castPtrToFunPtr :: Ptr a -> FunPtr b -- | Release the storage associated with the given FunPtr, which -- must have been obtained from a wrapper stub. This should be called -- whenever the return value from a foreign import wrapper function is no -- longer required; otherwise, the storage it uses will leak. freeHaskellFunPtr :: FunPtr a -> IO () -- | A signed integral type that can be losslessly converted to and from -- Ptr. This type is also compatible with the C99 type -- intptr_t, and can be marshalled to and from that type safely. data IntPtr :: * -- | casts a Ptr to an IntPtr ptrToIntPtr :: Ptr a -> IntPtr -- | casts an IntPtr to a Ptr intPtrToPtr :: IntPtr -> Ptr a -- | An unsigned integral type that can be losslessly converted to and from -- Ptr. This type is also compatible with the C99 type -- uintptr_t, and can be marshalled to and from that type -- safely. data WordPtr :: * -- | casts a Ptr to a WordPtr ptrToWordPtr :: Ptr a -> WordPtr -- | casts a WordPtr to a Ptr wordPtrToPtr :: WordPtr -> Ptr a module Data.Maybe -- | 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 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] 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 -- | This module defines bitwise operations for signed and unsigned -- integers. module Data.Bits -- | The Bits class defines bitwise operations over integral types. -- -- -- -- Minimal complete definition: .&., .|., xor, -- complement, (shift or (shiftL and -- shiftR)), (rotate or (rotateL and -- rotateR)), bitSize, isSigned, testBit, -- bit, and popCount. The latter three can be implemented -- using testBitDefault, bitDefault, and -- popCountDefault, if a is also an instance of -- Num. class Eq a => Bits a (.&.) :: Bits a => a -> a -> a (.|.) :: Bits a => a -> a -> a xor :: Bits a => a -> a -> a complement :: Bits a => a -> a shift :: Bits a => a -> Int -> a rotate :: Bits a => a -> Int -> a bit :: Bits a => Int -> a setBit :: Bits a => a -> Int -> a clearBit :: Bits a => a -> Int -> a complementBit :: Bits a => a -> Int -> a testBit :: Bits a => a -> Int -> Bool bitSize :: Bits a => a -> Int isSigned :: Bits a => a -> Bool shiftL :: Bits a => a -> Int -> a shiftR :: Bits a => a -> Int -> a rotateL :: Bits a => a -> Int -> a rotateR :: Bits a => a -> Int -> a module System.IO.Error -- | Errors of type IOError are used by the IO monad. This is -- an abstract type; the module System.IO.Error provides functions -- to interrogate and construct values of type IOError. type IOError = IOError -- | 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 -- | 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 -- | 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 -- | 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 -- | An abstract type that contains a value for each variant of -- IOError. data IOErrorType :: * -- | 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 -- | Raise an IOError in the IO monad. ioError :: IOError -> IO a -- | 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 -- catch. 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. catch :: IO a -> (IOError -> IO a) -> IO a -- | The construct try comp exposes IO errors which occur -- within a computation, and which are not fully handled. try :: IO a -> IO (Either IOError a) module Foreign.Storable -- | The member functions of this class facilitate writing values of -- primitive types to raw memory (which may have been allocated with the -- above mentioned routines) and reading values from blocks of raw -- memory. The class, furthermore, includes support for computing the -- storage requirements and alignment restrictions of storable types. -- -- Memory addresses are represented as values of type Ptr -- a, for some a which is an instance of class -- Storable. The type argument to Ptr helps provide some -- valuable type safety in FFI code (you can't mix pointers of different -- types without an explicit cast), while helping the Haskell type system -- figure out which marshalling method is needed for a given pointer. -- -- All marshalling between Haskell and a foreign language ultimately -- boils down to translating Haskell data structures into the binary -- representation of a corresponding data structure of the foreign -- language and vice versa. To code this marshalling in Haskell, it is -- necessary to manipulate primitive data types stored in unstructured -- memory blocks. The class Storable facilitates this manipulation -- on all types for which it is instantiated, which are the standard -- basic types of Haskell, the fixed size Int types -- (Int8, Int16, Int32, Int64), the fixed -- size Word types (Word8, Word16, Word32, -- Word64), StablePtr, all types from -- Foreign.C.Types, as well as Ptr. -- -- Minimal complete definition: sizeOf, alignment, one of -- peek, peekElemOff and peekByteOff, and one of -- poke, pokeElemOff and pokeByteOff. class Storable a sizeOf :: Storable a => a -> Int alignment :: Storable a => a -> Int peekElemOff :: Storable a => Ptr a -> Int -> IO a pokeElemOff :: Storable a => Ptr a -> Int -> a -> IO () peekByteOff :: Storable a => Ptr b -> Int -> IO a pokeByteOff :: Storable a => Ptr b -> Int -> a -> IO () peek :: Storable a => Ptr a -> IO a poke :: Storable a => Ptr a -> a -> IO () module Foreign.C.Types -- | Haskell type representing the C char type. data CChar :: * -- | Haskell type representing the C signed char type. data CSChar :: * -- | Haskell type representing the C unsigned char type. data CUChar :: * -- | Haskell type representing the C short type. data CShort :: * -- | Haskell type representing the C unsigned short type. data CUShort :: * -- | Haskell type representing the C int type. data CInt :: * -- | Haskell type representing the C unsigned int type. data CUInt :: * -- | Haskell type representing the C long type. data CLong :: * -- | Haskell type representing the C unsigned long type. data CULong :: * -- | Haskell type representing the C ptrdiff_t type. data CPtrdiff :: * -- | Haskell type representing the C size_t type. data CSize :: * -- | Haskell type representing the C wchar_t type. data CWchar :: * -- | Haskell type representing the C sig_atomic_t type. data CSigAtomic :: * -- | Haskell type representing the C long long type. data CLLong :: * -- | Haskell type representing the C unsigned long long type. data CULLong :: * data CIntPtr :: * data CUIntPtr :: * data CIntMax :: * data CUIntMax :: * -- | Haskell type representing the C clock_t type. data CClock :: * -- | Haskell type representing the C time_t type. data CTime :: * -- | Haskell type representing the C float type. data CFloat :: * -- | Haskell type representing the C double type. data CDouble :: * -- | Haskell type representing the C FILE type. data CFile :: * -- | Haskell type representing the C fpos_t type. data CFpos :: * -- | Haskell type representing the C jmp_buf type. data CJmpBuf :: * module System.Exit -- | 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 exitWith code terminates the program, -- returning code to the program's caller. The caller may -- interpret the return code as it wishes, but the program should return -- ExitSuccess to mean normal completion, and -- ExitFailure n to mean that the program encountered a -- problem from which it could not recover. The value exitFailure -- is equal to exitWith (ExitFailure exitfail), -- where exitfail is implementation-dependent. exitWith -- bypasses the error handling in the I/O monad and cannot be intercepted -- by catch from the Prelude. exitWith :: ExitCode -> IO a -- | The computation exitFailure is equivalent to exitWith -- (ExitFailure exitfail), where -- exitfail is implementation-dependent. exitFailure :: IO a -- | The computation exitSuccess is equivalent to exitWith -- ExitSuccess, It terminates the program successfully. exitSuccess :: IO a -- | The module Foreign.Marshal.Alloc provides operations to -- allocate and deallocate blocks of raw memory (i.e., unstructured -- chunks of memory outside of the area maintained by the Haskell storage -- manager). These memory blocks are commonly used to pass compound data -- structures to foreign functions or to provide space in which compound -- result values are obtained from foreign functions. -- -- If any of the allocation functions fails, a value of nullPtr -- is produced. If free or reallocBytes is applied to a -- memory area that has been allocated with alloca or -- allocaBytes, the behaviour is undefined. Any further access to -- memory areas allocated with alloca or allocaBytes, after -- the computation that was passed to the allocation function has -- terminated, leads to undefined behaviour. Any further access to the -- memory area referenced by a pointer passed to realloc, -- reallocBytes, or free entails undefined behaviour. -- -- All storage allocated by functions that allocate based on a size in -- bytes must be sufficiently aligned for any of the basic foreign -- types that fits into the newly allocated storage. All storage -- allocated by functions that allocate based on a specific type must be -- sufficiently aligned for that type. Array allocation routines need to -- obey the same alignment constraints for each array element. module Foreign.Marshal.Alloc -- | alloca f executes the computation f, passing -- as argument a pointer to a temporarily allocated block of memory -- sufficient to hold values of type a. -- -- The memory is freed when f terminates (either normally or via -- an exception), so the pointer passed to f must not be -- used after this. alloca :: Storable a => (Ptr a -> IO b) -> IO b -- | allocaBytes n f executes the computation f, -- passing as argument a pointer to a temporarily allocated block of -- memory of n bytes. The block of memory is sufficiently -- aligned for any of the basic foreign types that fits into a memory -- block of the allocated size. -- -- The memory is freed when f terminates (either normally or via -- an exception), so the pointer passed to f must not be -- used after this. allocaBytes :: Int -> (Ptr a -> IO b) -> IO b -- | Allocate a block of memory that is sufficient to hold values of type -- a. The size of the area allocated is determined by the -- sizeOf method from the instance of Storable for the -- appropriate type. -- -- The memory may be deallocated using free or -- finalizerFree when no longer required. malloc :: Storable a => IO (Ptr a) -- | Allocate a block of memory of the given number of bytes. The block of -- memory is sufficiently aligned for any of the basic foreign types that -- fits into a memory block of the allocated size. -- -- The memory may be deallocated using free or -- finalizerFree when no longer required. mallocBytes :: Int -> IO (Ptr a) -- | Resize a memory area that was allocated with malloc or -- mallocBytes to the size needed to store values of type -- b. The returned pointer may refer to an entirely different -- memory area, but will be suitably aligned to hold values of type -- b. The contents of the referenced memory area will be the -- same as of the original pointer up to the minimum of the original size -- and the size of values of type b. -- -- If the argument to realloc is nullPtr, realloc -- behaves like malloc. realloc :: Storable b => Ptr a -> IO (Ptr b) -- | Resize a memory area that was allocated with malloc or -- mallocBytes to the given size. The returned pointer may refer -- to an entirely different memory area, but will be sufficiently aligned -- for any of the basic foreign types that fits into a memory block of -- the given size. The contents of the referenced memory area will be the -- same as of the original pointer up to the minimum of the original size -- and the given size. -- -- If the pointer argument to reallocBytes is nullPtr, -- reallocBytes behaves like malloc. If the requested size -- is 0, reallocBytes behaves like free. reallocBytes :: Ptr a -> Int -> IO (Ptr a) -- | Free a block of memory that was allocated with malloc, -- mallocBytes, realloc, reallocBytes, new or -- any of the newX functions in -- Foreign.Marshal.Array or Foreign.C.String. free :: Ptr a -> IO () -- | A pointer to a foreign function equivalent to free, which may -- be used as a finalizer (cf ForeignPtr) for storage allocated -- with malloc, mallocBytes, realloc or -- reallocBytes. finalizerFree :: FinalizerPtr a module Foreign.Marshal.Utils -- | with val f executes the computation f, -- passing as argument a pointer to a temporarily allocated block of -- memory into which val has been marshalled (the combination of -- alloca and poke). -- -- The memory is freed when f terminates (either normally or via -- an exception), so the pointer passed to f must not be -- used after this. with :: Storable a => a -> (Ptr a -> IO b) -> IO b -- | Allocate a block of memory and marshal a value into it (the -- combination of malloc and poke). The size of the area -- allocated is determined by the sizeOf method from the instance -- of Storable for the appropriate type. -- -- The memory may be deallocated using free or -- finalizerFree when no longer required. new :: Storable a => a -> IO (Ptr a) -- | Convert a Haskell Bool to its numeric representation fromBool :: Num a => Bool -> a -- | Convert a Boolean in numeric representation to a Haskell value toBool :: (Eq a, Num a) => a -> Bool -- | Allocate storage and marshal a storable value wrapped into a -- Maybe -- -- maybeNew :: (a -> IO (Ptr b)) -> Maybe a -> IO (Ptr b) -- | Converts a withXXX combinator into one marshalling a value -- wrapped into a Maybe, using nullPtr to represent -- Nothing. maybeWith :: (a -> (Ptr b -> IO c) -> IO c) -> Maybe a -> (Ptr b -> IO c) -> IO c -- | Convert a peek combinator into a one returning Nothing if -- applied to a nullPtr maybePeek :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b) -- | Replicates a withXXX combinator over a list of objects, -- yielding a list of marshalled objects withMany :: (a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res -- | Copies the given number of bytes from the second area (source) into -- the first (destination); the copied areas may not overlap copyBytes :: Ptr a -> Ptr a -> Int -> IO () -- | Copies the given number of bytes from the second area (source) into -- the first (destination); the copied areas may overlap moveBytes :: Ptr a -> Ptr a -> Int -> IO () -- | The module Foreign.Marshal.Array provides operations for -- marshalling Haskell lists into monolithic arrays and vice versa. Most -- functions come in two flavours: one for arrays terminated by a special -- termination element and one where an explicit length parameter is used -- to determine the extent of an array. The typical example for the -- former case are C's NUL terminated strings. However, please note that -- C strings should usually be marshalled using the functions provided by -- Foreign.C.String as the Unicode encoding has to be taken into -- account. All functions specifically operating on arrays that are -- terminated by a special termination element have a name ending on -- 0---e.g., mallocArray allocates space for an array of -- the given size, whereas mallocArray0 allocates space for one -- more element to ensure that there is room for the terminator. module Foreign.Marshal.Array -- | Allocate storage for the given number of elements of a storable type -- (like malloc, but for multiple elements). mallocArray :: Storable a => Int -> IO (Ptr a) -- | Like mallocArray, but add an extra position to hold a special -- termination element. mallocArray0 :: Storable a => Int -> IO (Ptr a) -- | Temporarily allocate space for the given number of elements (like -- alloca, but for multiple elements). allocaArray :: Storable a => Int -> (Ptr a -> IO b) -> IO b -- | Like allocaArray, but add an extra position to hold a special -- termination element. allocaArray0 :: Storable a => Int -> (Ptr a -> IO b) -> IO b -- | Adjust the size of an array reallocArray :: Storable a => Ptr a -> Int -> IO (Ptr a) -- | Adjust the size of an array including an extra position for the end -- marker. reallocArray0 :: Storable a => Ptr a -> Int -> IO (Ptr a) -- | Convert an array of given length into a Haskell list. peekArray :: Storable a => Int -> Ptr a -> IO [a] -- | Convert an array terminated by the given end marker into a Haskell -- list peekArray0 :: (Storable a, Eq a) => a -> Ptr a -> IO [a] -- | Write the list elements consecutive into memory pokeArray :: Storable a => Ptr a -> [a] -> IO () -- | Write the list elements consecutive into memory and terminate them -- with the given marker element pokeArray0 :: Storable a => a -> Ptr a -> [a] -> IO () -- | Write a list of storable elements into a newly allocated, consecutive -- sequence of storable values (like new, but for multiple -- elements). newArray :: Storable a => [a] -> IO (Ptr a) -- | Write a list of storable elements into a newly allocated, consecutive -- sequence of storable values, where the end is fixed by the given end -- marker newArray0 :: Storable a => a -> [a] -> IO (Ptr a) -- | Temporarily store a list of storable values in memory (like -- with, but for multiple elements). withArray :: Storable a => [a] -> (Ptr a -> IO b) -> IO b -- | Like withArray, but a terminator indicates where the array ends withArray0 :: Storable a => a -> [a] -> (Ptr a -> IO b) -> IO b -- | Like withArray, but the action gets the number of values as an -- additional parameter withArrayLen :: Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b -- | Like withArrayLen, but a terminator indicates where the array -- ends withArrayLen0 :: Storable a => a -> [a] -> (Int -> Ptr a -> IO b) -> IO b -- | Copy the given number of elements from the second array (source) into -- the first array (destination); the copied areas may not overlap copyArray :: Storable a => Ptr a -> Ptr a -> Int -> IO () -- | Copy the given number of elements from the second array (source) into -- the first array (destination); the copied areas may overlap moveArray :: Storable a => Ptr a -> Ptr a -> Int -> IO () -- | Return the number of elements in an array, excluding the terminator lengthArray0 :: (Storable a, Eq a) => a -> Ptr a -> IO Int -- | Advance a pointer into an array by the given number of elements advancePtr :: Storable a => Ptr a -> Int -> Ptr a -- | Utilities for primitive marshalling of C strings. -- -- The marshalling converts each Haskell character, representing a -- Unicode code point, to one or more bytes in a manner that, by default, -- is determined by the current locale. As a consequence, no guarantees -- can be made about the relative length of a Haskell string and its -- corresponding C string, and therefore all the marshalling routines -- include memory allocation. The translation between Unicode and the -- encoding of the current locale may be lossy. module Foreign.C.String -- | A C string is a reference to an array of C characters terminated by -- NUL. type CString = Ptr CChar -- | A string with explicit length information in bytes instead of a -- terminating NUL (allowing NUL characters in the middle of the string). type CStringLen = (Ptr CChar, Int) -- | Marshal a NUL terminated C string into a Haskell string. peekCString :: CString -> IO String -- | Marshal a C string with explicit length into a Haskell string. peekCStringLen :: CStringLen -> IO String -- | Marshal a Haskell string into a NUL terminated C string. -- -- newCString :: String -> IO CString -- | Marshal a Haskell string into a C string (ie, character array) with -- explicit length information. -- -- newCStringLen :: String -> IO CStringLen -- | Marshal a Haskell string into a NUL terminated C string using -- temporary storage. -- -- withCString :: String -> (CString -> IO a) -> IO a -- | Marshal a Haskell string into a C string (ie, character array) in -- temporary storage, with explicit length information. -- -- withCStringLen :: String -> (CStringLen -> IO a) -> IO a charIsRepresentable :: Char -> IO Bool -- | Convert a Haskell character to a C character. This function is only -- safe on the first 256 characters. castCharToCChar :: Char -> CChar -- | Convert a C byte, representing a Latin-1 character, to the -- corresponding Haskell character. castCCharToChar :: CChar -> Char -- | Convert a Haskell character to a C unsigned char. This -- function is only safe on the first 256 characters. castCharToCUChar :: Char -> CUChar -- | Convert a C unsigned char, representing a Latin-1 character, -- to the corresponding Haskell character. castCUCharToChar :: CUChar -> Char -- | Convert a Haskell character to a C signed char. This function -- is only safe on the first 256 characters. castCharToCSChar :: Char -> CSChar -- | Convert a C signed char, representing a Latin-1 character, to -- the corresponding Haskell character. castCSCharToChar :: CSChar -> Char -- | Marshal a NUL terminated C string into a Haskell string. peekCAString :: CString -> IO String -- | Marshal a C string with explicit length into a Haskell string. peekCAStringLen :: CStringLen -> IO String -- | Marshal a Haskell string into a NUL terminated C string. -- -- newCAString :: String -> IO CString -- | Marshal a Haskell string into a C string (ie, character array) with -- explicit length information. -- -- newCAStringLen :: String -> IO CStringLen -- | Marshal a Haskell string into a NUL terminated C string using -- temporary storage. -- -- withCAString :: String -> (CString -> IO a) -> IO a -- | Marshal a Haskell string into a C string (ie, character array) in -- temporary storage, with explicit length information. -- -- withCAStringLen :: String -> (CStringLen -> IO a) -> IO a -- | A C wide string is a reference to an array of C wide characters -- terminated by NUL. type CWString = Ptr CWchar -- | A wide character string with explicit length information in -- CWchars instead of a terminating NUL (allowing NUL characters -- in the middle of the string). type CWStringLen = (Ptr CWchar, Int) -- | Marshal a NUL terminated C wide string into a Haskell string. peekCWString :: CWString -> IO String -- | Marshal a C wide string with explicit length into a Haskell string. peekCWStringLen :: CWStringLen -> IO String -- | Marshal a Haskell string into a NUL terminated C wide string. -- -- newCWString :: String -> IO CWString -- | Marshal a Haskell string into a C wide string (ie, wide character -- array) with explicit length information. -- -- newCWStringLen :: String -> IO CWStringLen -- | Marshal a Haskell string into a NUL terminated C wide string using -- temporary storage. -- -- withCWString :: String -> (CWString -> IO a) -> IO a -- | Marshal a Haskell string into a C wide string (i.e. wide character -- array) in temporary storage, with explicit length information. -- -- withCWStringLen :: String -> (CWStringLen -> IO a) -> IO a module Foreign.Marshal.Error -- | Execute an IO action, throwing a userError if the -- predicate yields True when applied to the result returned by -- the IO action. If no exception is raised, return the result of -- the computation. throwIf :: (a -> Bool) -> (a -> String) -> IO a -> IO a -- | Like throwIf, but discarding the result throwIf_ :: (a -> Bool) -> (a -> String) -> IO a -> IO () -- | Guards against negative result values throwIfNeg :: (Ord a, Num a) => (a -> String) -> IO a -> IO a -- | Like throwIfNeg, but discarding the result throwIfNeg_ :: (Ord a, Num a) => (a -> String) -> IO a -> IO () -- | Guards against null pointers throwIfNull :: String -> IO (Ptr a) -> IO (Ptr a) -- | Discard the return value of an IO action void :: IO a -> IO () -- | The module Foreign.C.Error facilitates C-specific error -- handling of errno. module Foreign.C.Error -- | Haskell representation for errno values. The implementation -- is deliberately exposed, to allow users to add their own definitions -- of Errno values. newtype Errno :: * Errno :: CInt -> Errno eOK :: Errno e2BIG :: Errno eACCES :: Errno eADDRINUSE :: Errno eADDRNOTAVAIL :: Errno eADV :: Errno eAFNOSUPPORT :: Errno eAGAIN :: Errno eALREADY :: Errno eBADF :: Errno eBADMSG :: Errno eBADRPC :: Errno eBUSY :: Errno eCHILD :: Errno eCOMM :: Errno eCONNABORTED :: Errno eCONNREFUSED :: Errno eCONNRESET :: Errno eDEADLK :: Errno eDESTADDRREQ :: Errno eDIRTY :: Errno eDOM :: Errno eDQUOT :: Errno eEXIST :: Errno eFAULT :: Errno eFBIG :: Errno eFTYPE :: Errno eHOSTDOWN :: Errno eHOSTUNREACH :: Errno eIDRM :: Errno eILSEQ :: Errno eINPROGRESS :: Errno eINTR :: Errno eINVAL :: Errno eIO :: Errno eISCONN :: Errno eISDIR :: Errno eLOOP :: Errno eMFILE :: Errno eMLINK :: Errno eMSGSIZE :: Errno eMULTIHOP :: Errno eNAMETOOLONG :: Errno eNETDOWN :: Errno eNETRESET :: Errno eNETUNREACH :: Errno eNFILE :: Errno eNOBUFS :: Errno eNODATA :: Errno eNODEV :: Errno eNOENT :: Errno eNOEXEC :: Errno eNOLCK :: Errno eNOLINK :: Errno eNOMEM :: Errno eNOMSG :: Errno eNONET :: Errno eNOPROTOOPT :: Errno eNOSPC :: Errno eNOSR :: Errno eNOSTR :: Errno eNOSYS :: Errno eNOTBLK :: Errno eNOTCONN :: Errno eNOTDIR :: Errno eNOTEMPTY :: Errno eNOTSOCK :: Errno eNOTTY :: Errno eNXIO :: Errno eOPNOTSUPP :: Errno ePERM :: Errno ePFNOSUPPORT :: Errno ePIPE :: Errno ePROCLIM :: Errno ePROCUNAVAIL :: Errno ePROGMISMATCH :: Errno ePROGUNAVAIL :: Errno ePROTO :: Errno ePROTONOSUPPORT :: Errno ePROTOTYPE :: Errno eRANGE :: Errno eREMCHG :: Errno eREMOTE :: Errno eROFS :: Errno eRPCMISMATCH :: Errno eRREMOTE :: Errno eSHUTDOWN :: Errno eSOCKTNOSUPPORT :: Errno eSPIPE :: Errno eSRCH :: Errno eSRMNT :: Errno eSTALE :: Errno eTIME :: Errno eTIMEDOUT :: Errno eTOOMANYREFS :: Errno eTXTBSY :: Errno eUSERS :: Errno eWOULDBLOCK :: Errno eXDEV :: Errno -- | Yield True if the given Errno value is valid on the -- system. This implies that the Eq instance of Errno is -- also system dependent as it is only defined for valid values of -- Errno. isValidErrno :: Errno -> Bool -- | Get the current value of errno in the current thread. getErrno :: IO Errno -- | Reset the current thread's errno value to eOK. resetErrno :: IO () -- | Construct an IOError based on the given Errno value. The -- optional information can be used to improve the accuracy of error -- messages. errnoToIOError :: String -> Errno -> Maybe Handle -> Maybe String -> IOError -- | Throw an IOError corresponding to the current value of -- getErrno. throwErrno :: String -> IO a -- | Throw an IOError corresponding to the current value of -- getErrno if the result value of the IO action meets the -- given predicate. throwErrnoIf :: (a -> Bool) -> String -> IO a -> IO a -- | as throwErrnoIf, but discards the result of the IO -- action after error handling. throwErrnoIf_ :: (a -> Bool) -> String -> IO a -> IO () -- | as throwErrnoIf, but retry the IO action when it yields -- the error code eINTR - this amounts to the standard retry loop -- for interrupted POSIX system calls. throwErrnoIfRetry :: (a -> Bool) -> String -> IO a -> IO a -- | as throwErrnoIfRetry, but discards the result. throwErrnoIfRetry_ :: (a -> Bool) -> String -> IO a -> IO () -- | Throw an IOError corresponding to the current value of -- getErrno if the IO action returns a result of -- -1. throwErrnoIfMinus1 :: (Eq a, Num a) => String -> IO a -> IO a -- | as throwErrnoIfMinus1, but discards the result. throwErrnoIfMinus1_ :: (Eq a, Num a) => String -> IO a -> IO () -- | Throw an IOError corresponding to the current value of -- getErrno if the IO action returns a result of -- -1, but retries in case of an interrupted operation. throwErrnoIfMinus1Retry :: (Eq a, Num a) => String -> IO a -> IO a -- | as throwErrnoIfMinus1, but discards the result. throwErrnoIfMinus1Retry_ :: (Eq a, Num a) => String -> IO a -> IO () -- | Throw an IOError corresponding to the current value of -- getErrno if the IO action returns nullPtr. throwErrnoIfNull :: String -> IO (Ptr a) -> IO (Ptr a) -- | Throw an IOError corresponding to the current value of -- getErrno if the IO action returns nullPtr, but -- retry in case of an interrupted operation. throwErrnoIfNullRetry :: String -> IO (Ptr a) -> IO (Ptr a) -- | as throwErrnoIfRetry, but additionally if the operation yields -- the error code eAGAIN or eWOULDBLOCK, an alternative -- action is executed before retrying. throwErrnoIfRetryMayBlock :: (a -> Bool) -> String -> IO a -> IO b -> IO a -- | as throwErrnoIfRetryMayBlock, but discards the result. throwErrnoIfRetryMayBlock_ :: (a -> Bool) -> String -> IO a -> IO b -> IO () -- | as throwErrnoIfMinus1Retry, but checks for operations that -- would block. throwErrnoIfMinus1RetryMayBlock :: (Eq a, Num a) => String -> IO a -> IO b -> IO a -- | as throwErrnoIfMinus1RetryMayBlock, but discards the result. throwErrnoIfMinus1RetryMayBlock_ :: (Eq a, Num a) => String -> IO a -> IO b -> IO () -- | as throwErrnoIfNullRetry, but checks for operations that would -- block. throwErrnoIfNullRetryMayBlock :: String -> IO (Ptr a) -> IO b -> IO (Ptr a) -- | as throwErrno, but exceptions include the given path when -- appropriate. throwErrnoPath :: String -> FilePath -> IO a -- | as throwErrnoIf, but exceptions include the given path when -- appropriate. throwErrnoPathIf :: (a -> Bool) -> String -> FilePath -> IO a -> IO a -- | as throwErrnoIf_, but exceptions include the given path when -- appropriate. throwErrnoPathIf_ :: (a -> Bool) -> String -> FilePath -> IO a -> IO () -- | as throwErrnoIfNull, but exceptions include the given path when -- appropriate. throwErrnoPathIfNull :: String -> FilePath -> IO (Ptr a) -> IO (Ptr a) -- | as throwErrnoIfMinus1, but exceptions include the given path -- when appropriate. throwErrnoPathIfMinus1 :: (Eq a, Num a) => String -> FilePath -> IO a -> IO a -- | as throwErrnoIfMinus1_, but exceptions include the given path -- when appropriate. throwErrnoPathIfMinus1_ :: (Eq a, Num a) => String -> FilePath -> IO a -> IO () module Data.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 -- | 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 -- | The conjugate of a complex number. conjugate :: RealFloat a => Complex a -> Complex a module System.Environment -- | 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 module Foreign.ForeignPtr -- | The type ForeignPtr represents references to objects that are -- maintained in a foreign language, i.e., that are not part of the data -- structures usually managed by the Haskell storage manager. The -- essential difference between ForeignPtrs and vanilla memory -- references of type Ptr a is that the former may be associated -- with finalizers. A finalizer is a routine that is invoked when -- the Haskell storage manager detects that - within the Haskell heap and -- stack - there are no more references left that are pointing to the -- ForeignPtr. Typically, the finalizer will, then, invoke -- routines in the foreign language that free the resources bound by the -- foreign object. -- -- The ForeignPtr is parameterised in the same way as Ptr. -- The type argument of ForeignPtr should normally be an instance -- of class Storable. data ForeignPtr a :: * -> * -- | A finalizer is represented as a pointer to a foreign function that, at -- finalisation time, gets as an argument a plain pointer variant of the -- foreign pointer that the finalizer is associated with. -- -- Note that the foreign function must use the ccall -- calling convention. type FinalizerPtr a = FunPtr (Ptr a -> IO ()) type FinalizerEnvPtr env a = FunPtr (Ptr env -> Ptr a -> IO ()) -- | Turns a plain memory reference into a foreign pointer, and associates -- a finalizer with the reference. The finalizer will be executed after -- the last reference to the foreign object is dropped. There is no -- guarantee of promptness, however the finalizer will be executed before -- the program exits. newForeignPtr :: FinalizerPtr a -> Ptr a -> IO (ForeignPtr a) -- | Turns a plain memory reference into a foreign pointer that may be -- associated with finalizers by using addForeignPtrFinalizer. newForeignPtr_ :: Ptr a -> IO (ForeignPtr a) -- | This function adds a finalizer to the given foreign object. The -- finalizer will run before all other finalizers for the same -- object which have already been registered. addForeignPtrFinalizer :: FinalizerPtr a -> ForeignPtr a -> IO () -- | This variant of newForeignPtr adds a finalizer that expects an -- environment in addition to the finalized pointer. The environment that -- will be passed to the finalizer is fixed by the second argument to -- newForeignPtrEnv. newForeignPtrEnv :: FinalizerEnvPtr env a -> Ptr env -> Ptr a -> IO (ForeignPtr a) -- | Like addForeignPtrFinalizerEnv but allows the finalizer to be -- passed an additional environment parameter to be passed to the -- finalizer. The environment passed to the finalizer is fixed by the -- second argument to addForeignPtrFinalizerEnv addForeignPtrFinalizerEnv :: FinalizerEnvPtr env a -> Ptr env -> ForeignPtr a -> IO () -- | This is a way to look at the pointer living inside a foreign object. -- This function takes a function which is applied to that pointer. The -- resulting IO action is then executed. The foreign object is -- kept alive at least during the whole action, even if it is not used -- directly inside. Note that it is not safe to return the pointer from -- the action and use it after the action completes. All uses of the -- pointer should be inside the withForeignPtr bracket. The reason -- for this unsafeness is the same as for unsafeForeignPtrToPtr -- below: the finalizer may run earlier than expected, because the -- compiler can only track usage of the ForeignPtr object, not a -- Ptr object made from it. -- -- This function is normally used for marshalling data to or from the -- object pointed to by the ForeignPtr, using the operations from -- the Storable class. withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b -- | Causes the finalizers associated with a foreign pointer to be run -- immediately. finalizeForeignPtr :: ForeignPtr a -> IO () -- | This function extracts the pointer component of a foreign pointer. -- This is a potentially dangerous operations, as if the argument to -- unsafeForeignPtrToPtr is the last usage occurrence of the given -- foreign pointer, then its finalizer(s) will be run, which potentially -- invalidates the plain pointer just obtained. Hence, -- touchForeignPtr must be used wherever it has to be guaranteed -- that the pointer lives on - i.e., has another usage occurrence. -- -- To avoid subtle coding errors, hand written marshalling code should -- preferably use withForeignPtr rather than combinations of -- unsafeForeignPtrToPtr and touchForeignPtr. However, the -- latter routines are occasionally preferred in tool generated -- marshalling code. unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a -- | This function ensures that the foreign object in question is alive at -- the given place in the sequence of IO actions. In particular -- withForeignPtr does a touchForeignPtr after it executes -- the user action. -- -- Note that this function should not be used to express dependencies -- between finalizers on ForeignPtrs. For example, if the -- finalizer for a ForeignPtr F1 calls -- touchForeignPtr on a second ForeignPtr F2, then -- the only guarantee is that the finalizer for F2 is never -- started before the finalizer for F1. They might be started -- together if for example both F1 and F2 are otherwise -- unreachable. -- -- In general, it is not recommended to use finalizers on separate -- objects with ordering constraints between them. To express the -- ordering robustly requires explicit synchronisation between -- finalizers. touchForeignPtr :: ForeignPtr a -> IO () -- | This function casts a ForeignPtr parameterised by one type into -- another type. castForeignPtr :: ForeignPtr a -> ForeignPtr b -- | Allocate some memory and return a ForeignPtr to it. The memory -- will be released automatically when the ForeignPtr is -- discarded. -- -- mallocForeignPtr is equivalent to -- --
--   do { p <- malloc; newForeignPtr finalizerFree p }
--   
-- -- although it may be implemented differently internally: you may not -- assume that the memory returned by mallocForeignPtr has been -- allocated with malloc. mallocForeignPtr :: Storable a => IO (ForeignPtr a) -- | This function is similar to mallocForeignPtr, except that the -- size of the memory required is given explicitly as a number of bytes. mallocForeignPtrBytes :: Int -> IO (ForeignPtr a) -- | This function is similar to mallocArray, but yields a memory -- area that has a finalizer attached that releases the memory area. As -- with mallocForeignPtr, it is not guaranteed that the block of -- memory was allocated by malloc. mallocForeignPtrArray :: Storable a => Int -> IO (ForeignPtr a) -- | This function is similar to mallocArray0, but yields a memory -- area that has a finalizer attached that releases the memory area. As -- with mallocForeignPtr, it is not guaranteed that the block of -- memory was allocated by malloc. mallocForeignPtrArray0 :: Storable a => Int -> IO (ForeignPtr a) module Foreign.Marshal -- | Sometimes an external entity is a pure function, except that it passes -- arguments and/or results via pointers. The function -- unsafeLocalState permits the packaging of such entities as -- pure functions. -- -- The only IO operations allowed in the IO action passed to -- unsafeLocalState are (a) local allocation (alloca, -- allocaBytes and derived operations such as withArray -- and withCString), and (b) pointer operations -- (Foreign.Storable and Foreign.Ptr) on the pointers -- to local storage, and (c) foreign functions whose only observable -- effect is to read and/or write the locally allocated memory. Passing -- an IO operation that does not obey these rules results in undefined -- behaviour. -- -- It is expected that this operation will be replaced in a future -- revision of Haskell. unsafeLocalState :: IO a -> a module Foreign module Foreign.C module Data.List -- | 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] -- | 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 -- | 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] -- | reverse xs returns the elements of xs in -- reverse order. xs must be finite. reverse :: [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] -- | intercalate xs xss is equivalent to (concat -- (intersperse xs xss)). It inserts the list xs in -- between the lists in xss and concatenates the result. intercalate :: [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 subsequences function returns the list of all subsequences -- of the argument. -- --
--   subsequences "abc" == ["","a","b","ab","c","ac","bc","abc"]
--   
subsequences :: [a] -> [[a]] -- | The permutations function returns the list of all permutations -- of the argument. -- --
--   permutations "abc" == ["abc","bac","cba","bca","cab","acb"]
--   
permutations :: [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 -- | A strict version of foldl. 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 -- | A strict version of foldl1 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 -- | Concatenate a list of lists. concat :: [[a]] -> [a] -- | Map a function over a list and concatenate the results. concatMap :: (a -> [b]) -> [a] -> [b] -- | 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 -- | 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] -- | 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]) -- | 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] -- | 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] -- | 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]) -- | The stripPrefix function drops the given prefix from a list. It -- returns Nothing if the list did not start with the prefix -- given, or Just the list after the prefix, if it does. -- --
--   stripPrefix "foo" "foobar" == Just "bar"
--   stripPrefix "foo" "foo" == Just ""
--   stripPrefix "foo" "barfoo" == Nothing
--   stripPrefix "foo" "barfoobaz" == Nothing
--   
stripPrefix :: Eq a => [a] -> [a] -> Maybe [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 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 isInfixOf function takes two lists and returns True -- iff the first list is contained, wholly and intact, anywhere within -- the second. -- -- Example: -- --
--   isInfixOf "Haskell" "I really like Haskell." == True
--   isInfixOf "Ial" "I really like Haskell." == False
--   
isInfixOf :: Eq a => [a] -> [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 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 -- | 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] -- | 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]) -- | 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 -- | 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 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] -- | 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)] -- | 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)] -- | 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] -- | 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] -- | 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]) -- | 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]) -- | 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 -- | 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] -- | 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 \\ 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 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 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 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 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 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] -- | The deleteBy function behaves like delete, but takes a -- user-supplied equality predicate. deleteBy :: (a -> a -> Bool) -> 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 unionBy function is the non-overloaded version of -- union. unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The intersectBy function is the non-overloaded version of -- intersect. intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] -- | The groupBy function is the non-overloaded version of -- group. groupBy :: (a -> a -> Bool) -> [a] -> [[a]] -- | The sortBy function is the non-overloaded version of -- sort. sortBy :: (a -> a -> Ordering) -> [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] module System.IO -- | 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 :: * -> * fixIO :: (a -> IO a) -> 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 -- | 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 :: * -- | 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 -- | withFile name mode act opens a file using -- openFile and passes the resulting handle to the computation -- act. The handle will be closed on exit from withFile, -- whether by normal termination or by raising an exception. If closing -- the handle raises an exception, then this exception will be raised by -- withFile rather than any exception raised by act. withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r -- | 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: -- -- openFile :: FilePath -> IOMode -> IO Handle -- | See openFile data IOMode :: * ReadMode :: IOMode WriteMode :: IOMode AppendMode :: IOMode ReadWriteMode :: IOMode -- | 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 () -- | 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 () -- | 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 -- | hSetFileSize hdl size truncates the physical -- file with handle hdl to size bytes. hSetFileSize :: Handle -> Integer -> IO () -- | 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 -- | 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 -- | 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 () data HandlePosn :: * -- | 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 () -- | 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 -- | Computation hTell hdl returns the current position of -- the handle hdl, as the number of bytes from the beginning of -- the file. The value returned may be subsequently passed to -- hSeek to reposition the handle to the current position. -- -- This operation may fail with: -- -- hTell :: Handle -> IO Integer hIsOpen :: Handle -> IO Bool hIsClosed :: Handle -> IO Bool hIsReadable :: Handle -> IO Bool hIsWritable :: Handle -> IO Bool hIsSeekable :: Handle -> IO Bool -- | Is the handle connected to a terminal? hIsTerminalDevice :: Handle -> IO Bool -- | Set the echoing status of a handle connected to a terminal. hSetEcho :: Handle -> Bool -> IO () -- | Get the echoing status of a handle connected to a terminal. hGetEcho :: Handle -> IO Bool -- | hShow is in the IO monad, and gives more comprehensive -- output than the (pure) instance of Show for Handle. hShow :: Handle -> IO String -- | 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: -- -- 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 () -- | 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 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 Control.Monad module provides the Functor, -- Monad and MonadPlus classes, together with some useful -- operations on monads. module Control.Monad -- | 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 -- | 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 -- | 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 -- | 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 () -- | forM is mapM with its arguments flipped forM :: Monad m => [a] -> (a -> m b) -> m [b] -- | forM_ is mapM_ with its arguments flipped forM_ :: Monad m => [a] -> (a -> m b) -> 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 -- | Left-to-right Kleisli composition of monads. (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c -- | Right-to-left Kleisli composition of monads. -- (>=>), with the arguments flipped (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c -- | forever act repeats the action infinitely. forever :: Monad m => m a -> m b -- | void value discards or ignores the result of -- evaluation, such as the return value of an IO action. void :: Functor f => f a -> f () -- | 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 -- | 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 -- | Like foldM, but discards the result. foldM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m () -- | replicateM n act performs the action n times, -- gathering the results. replicateM :: Monad m => Int -> m a -> m [a] -- | Like replicateM, but discards the result. replicateM_ :: Monad m => Int -> m a -> m () -- | 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 () -- | 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 -- | 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 module Data.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. If any two associations in the list have the same index, -- the value at that index is undefined (i.e. bottom). -- -- 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 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 -- | 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)] -- | 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: the resulting array is undefined (i.e. bottom), (//) :: 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