|  | 
| | Prelude | | Portability | portable |  | Stability | stable |  | Maintainer | libraries@haskell.org | 
 | 
 | 
|  | 
|  | 
|  | 
| Description | 
| The Prelude: a standard module imported by default into all Haskell
modules.  For more documentation, see the Haskell 98 Report
http://www.haskell.org/onlinereport/. | 
|  | 
| Synopsis | 
|  | 
| |  |  |  |  | (&&) :: Bool -> Bool -> Bool |  |  |  | (||) :: Bool -> Bool -> Bool |  |  |  | not :: Bool -> Bool |  |  |  | otherwise :: Bool |  |  |  |  |  |  |  | maybe :: b -> (a -> b) -> Maybe a -> b |  |  |  |  |  |  |  | either :: (a -> c) -> (b -> c) -> Either a b -> c |  |  |  |  |  |  |  | data Char |  |  |  | type String = [Char] |  |  |  | fst :: (a, b) -> a |  |  |  | snd :: (a, b) -> b |  |  |  | curry :: ((a, b) -> c) -> a -> b -> c |  |  |  | uncurry :: (a -> b -> c) -> (a, b) -> c |  |  |  | class Eq a  where |  |  |  |  |  | class Eq a => Ord a  where |  |  |  |  |  | class Enum a  where |  |  |  |  |  | class Bounded a  where |  |  |  |  |  | data Int |  |  |  | data Integer |  |  |  | data Float |  |  |  | data Double |  |  |  | type Rational = Ratio Integer |  |  |  | class (Eq a, Show a) => Num a  where |  |  |  |  |  | class (Num a, Ord a) => Real a  where |  |  |  |  |  | class (Real a, Enum a) => Integral a  where |  |  |  |  |  | class Num a => Fractional a  where |  |  |  |  |  | class Fractional a => Floating a  where |  |  |  |  |  | class (Real a, Fractional a) => RealFrac a  where |  |  |  |  |  | class (RealFrac a, Floating a) => RealFloat a  where |  |  |  |  |  | subtract :: Num a => a -> a -> a |  |  |  | even :: Integral a => a -> Bool |  |  |  | odd :: Integral a => a -> Bool |  |  |  | gcd :: Integral a => a -> a -> a |  |  |  | lcm :: Integral a => a -> a -> a |  |  |  | (^) :: (Num a, Integral b) => a -> b -> a |  |  |  | (^^) :: (Fractional a, Integral b) => a -> b -> a |  |  |  | fromIntegral :: (Integral a, Num b) => a -> b |  |  |  | realToFrac :: (Real a, Fractional b) => a -> b |  |  |  | class Monad m  where |  |  |  |  |  | class Functor f  where |  | | fmap :: (a -> b) -> f a -> f b | 
 |  |  |  | mapM :: Monad m => (a -> m b) -> [a] -> m [b] |  |  |  | mapM_ :: Monad m => (a -> m b) -> [a] -> m () |  |  |  | sequence :: Monad m => [m a] -> m [a] |  |  |  | sequence_ :: Monad m => [m a] -> m () |  |  |  | (=<<) :: Monad m => (a -> m b) -> m a -> m b |  |  |  | id :: a -> a |  |  |  | const :: a -> b -> a |  |  |  | (.) :: (b -> c) -> (a -> b) -> a -> c |  |  |  | flip :: (a -> b -> c) -> b -> a -> c |  |  |  | ($) :: (a -> b) -> a -> b |  |  |  | until :: (a -> Bool) -> (a -> a) -> a -> a |  |  |  | asTypeOf :: a -> a -> a |  |  |  | error :: String -> a |  |  |  | undefined :: a |  |  |  | ($!) :: (a -> b) -> a -> b |  |  |  | map :: (a -> b) -> [a] -> [b] |  |  |  | (++) :: [a] -> [a] -> [a] |  |  |  | filter :: (a -> Bool) -> [a] -> [a] |  |  |  | head :: [a] -> a |  |  |  | last :: [a] -> a |  |  |  | tail :: [a] -> [a] |  |  |  | init :: [a] -> [a] |  |  |  | null :: [a] -> Bool |  |  |  | length :: [a] -> Int |  |  |  | (!!) :: [a] -> Int -> a |  |  |  | reverse :: [a] -> [a] |  |  |  | foldl :: (a -> b -> a) -> a -> [b] -> a |  |  |  | foldl1 :: (a -> a -> a) -> [a] -> a |  |  |  | foldr :: (a -> b -> b) -> b -> [a] -> b |  |  |  | foldr1 :: (a -> a -> a) -> [a] -> a |  |  |  | and :: [Bool] -> Bool |  |  |  | or :: [Bool] -> Bool |  |  |  | any :: (a -> Bool) -> [a] -> Bool |  |  |  | all :: (a -> Bool) -> [a] -> Bool |  |  |  | sum :: Num a => [a] -> a |  |  |  | product :: Num a => [a] -> a |  |  |  | concat :: [[a]] -> [a] |  |  |  | concatMap :: (a -> [b]) -> [a] -> [b] |  |  |  | maximum :: Ord a => [a] -> a |  |  |  | minimum :: Ord a => [a] -> a |  |  |  | scanl :: (a -> b -> a) -> a -> [b] -> [a] |  |  |  | scanl1 :: (a -> a -> a) -> [a] -> [a] |  |  |  | scanr :: (a -> b -> b) -> b -> [a] -> [b] |  |  |  | scanr1 :: (a -> a -> a) -> [a] -> [a] |  |  |  | iterate :: (a -> a) -> a -> [a] |  |  |  | repeat :: a -> [a] |  |  |  | replicate :: Int -> a -> [a] |  |  |  | cycle :: [a] -> [a] |  |  |  | take :: Int -> [a] -> [a] |  |  |  | drop :: Int -> [a] -> [a] |  |  |  | splitAt :: Int -> [a] -> ([a], [a]) |  |  |  | takeWhile :: (a -> Bool) -> [a] -> [a] |  |  |  | dropWhile :: (a -> Bool) -> [a] -> [a] |  |  |  | span :: (a -> Bool) -> [a] -> ([a], [a]) |  |  |  | break :: (a -> Bool) -> [a] -> ([a], [a]) |  |  |  | elem :: Eq a => a -> [a] -> Bool |  |  |  | notElem :: Eq a => a -> [a] -> Bool |  |  |  | lookup :: Eq a => a -> [(a, b)] -> Maybe b |  |  |  | zip :: [a] -> [b] -> [(a, b)] |  |  |  | zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] |  |  |  | zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] |  |  |  | zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] |  |  |  | unzip :: [(a, b)] -> ([a], [b]) |  |  |  | unzip3 :: [(a, b, c)] -> ([a], [b], [c]) |  |  |  | lines :: String -> [String] |  |  |  | words :: String -> [String] |  |  |  | unlines :: [String] -> String |  |  |  | unwords :: [String] -> String |  |  |  | type ReadS a = String -> [(a, String)] |  |  |  | type ShowS = String -> String |  |  |  | class Read a  where |  |  |  |  |  | class Show a  where |  |  |  |  |  | reads :: Read a => ReadS a |  |  |  | shows :: Show a => a -> ShowS |  |  |  | read :: Read a => String -> a |  |  |  | lex :: ReadS String |  |  |  | showChar :: Char -> ShowS |  |  |  | showString :: String -> ShowS |  |  |  | readParen :: Bool -> ReadS a -> ReadS a |  |  |  | showParen :: Bool -> ShowS -> ShowS |  |  |  | data IO a |  |  |  | putChar :: Char -> IO () |  |  |  | putStr :: String -> IO () |  |  |  | putStrLn :: String -> IO () |  |  |  | print :: Show a => a -> IO () |  |  |  | getChar :: IO Char |  |  |  | getLine :: IO String |  |  |  | getContents :: IO String |  |  |  | interact :: (String -> String) -> IO () |  |  |  | type FilePath = String |  |  |  | readFile :: FilePath -> IO String |  |  |  | writeFile :: FilePath -> String -> IO () |  |  |  | appendFile :: FilePath -> String -> IO () |  |  |  | readIO :: Read a => String -> IO a |  |  |  | readLn :: Read a => IO a |  |  |  | type IOError = IOException |  |  |  | ioError :: IOError -> IO a |  |  |  | userError :: String -> IOError |  |  |  | catch :: IO a -> (IOError -> IO a) -> IO a | 
 | 
|  | 
|  | 
| Standard types, classes and related functions | 
|  | 
| Basic data types | 
|  | 
| data Bool | 
| | The Bool type is an enumeration.  It is defined with False
first so that the corresponding Enum instance will give
fromEnum False the value zero, and
fromEnum True the value 1. |  | Constructors |  |  |  | Instances |  |  | 
 | 
|  | 
| (&&) :: Bool -> Bool -> Bool | 
| Boolean "and" | 
|  | 
| (||) :: Bool -> Bool -> Bool | 
| Boolean "or" | 
|  | 
| not :: Bool -> Bool | 
| Boolean "not" | 
|  | 
| otherwise :: Bool | 
| otherwise is defined as the value True.  It helps to make
guards more readable.  eg.
   f x | x < 0     = ...
      | otherwise = ... | 
|  | 
| data Maybe a | 
| | 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. |  | Constructors |  |  |  | Instances |  |  | 
 | 
|  | 
| maybe :: b -> (a -> b) -> Maybe a -> b | 
| The maybe function takes a default value, a function, and a Maybe
value.  If the Maybe value is Nothing, the function returns the
default value.  Otherwise, it applies the function to the value inside
the Just and returns that. | 
|  | 
| data Either 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").
 |  | Constructors |  |  |  | Instances |  |  | 
 | 
|  | 
| either :: (a -> c) -> (b -> c) -> Either a b -> c | 
| 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. | 
|  | 
| data Ordering | 
| | Represents an ordering relationship between two values: less
than, equal to, or greater than.  An Ordering is returned by
compare. |  | Constructors |  |  |  | Instances |  |  | 
 | 
|  | 
| data Char | 
| | The character type Char is an enumeration whose values represent
Unicode (or equivalently ISO 10646) characters.
This set extends the ISO 8859-1 (Latin-1) character set
(the first 256 charachers), 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).
 |  | Instances |  |  | 
 | 
|  | 
| type String = [Char] | 
| A String is a list of characters.  String constants in Haskell are values
of type String. | 
|  | 
| Tuples | 
|  | 
| fst :: (a, b) -> a | 
|  | 
| snd :: (a, b) -> b | 
|  | 
| curry :: ((a, b) -> c) -> a -> b -> c | 
|  | 
| uncurry :: (a -> b -> c) -> (a, b) -> c | 
|  | 
| Basic type classes | 
|  | 
| class Eq a  where | 
| | 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 /=.
 |  |  |  | Methods |  | | (==) :: a -> a -> Bool |  |  |  | (/=) :: a -> a -> Bool | 
 |  |  |  | Instances |  | | Eq ThreadId |  | Ix ix => Eq (UArray ix Bool) |  | Ix ix => Eq (UArray ix Char) |  | Ix ix => Eq (UArray ix Int) |  | Ix ix => Eq (UArray ix Word) |  | Ix ix => Eq (UArray ix (Ptr a)) |  | Ix ix => Eq (UArray ix (FunPtr a)) |  | Ix ix => Eq (UArray ix Float) |  | Ix ix => Eq (UArray ix Double) |  | Ix ix => Eq (UArray ix (StablePtr a)) |  | Ix ix => Eq (UArray ix Int8) |  | Ix ix => Eq (UArray ix Int16) |  | Ix ix => Eq (UArray ix Int32) |  | Ix ix => Eq (UArray ix Int64) |  | Ix ix => Eq (UArray ix Word8) |  | Ix ix => Eq (UArray ix Word16) |  | Ix ix => Eq (UArray ix Word32) |  | Ix ix => Eq (UArray ix Word64) |  | (RealFloat a, Eq a) => Eq (Complex a) |  | (Eq a, Eq b) => Eq (Either a b) |  | (Eq key, Eq elt) => Eq (FiniteMap key elt) |  | Eq Constr |  | Eq Fixity |  | Eq a => Eq (Maybe a) |  | Eq PackedString |  | Eq a => Eq (Set a) |  | (Eq a, Eq b) => Eq (a, b) |  | (Eq a, Eq b, Eq c) => Eq (a, b, c) |  | (Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) |  | (Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) |  | (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) |  | (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) |  | (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) |  | (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) |  | (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) |  | (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k) |  | (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l) |  | (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m) |  | (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n) |  | (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) |  | Eq TypeRep |  | Eq TyCon |  | Eq Key |  | Eq KeyPr |  | Eq Unique |  | Eq Errno |  | Eq CChar |  | Eq CSChar |  | Eq CUChar |  | Eq CShort |  | Eq CUShort |  | Eq CInt |  | Eq CUInt |  | Eq CLong |  | Eq CULong |  | Eq CLLong |  | Eq CULLong |  | Eq CFloat |  | Eq CDouble |  | Eq CLDouble |  | Eq CPtrdiff |  | Eq CSize |  | Eq CWchar |  | Eq CSigAtomic |  | Eq CClock |  | Eq CTime |  | Eq (STArray s i e) |  | (Ix i, Eq e) => Eq (Array i e) |  | Eq a => Eq [a] |  | Eq () |  | Eq Char |  | Eq Int |  | Eq Bool |  | Eq Ordering |  | Eq Float |  | Eq Double |  | Eq (ForeignPtr a) |  | Eq HandlePosn |  | Eq SeekMode |  | Eq (MVar a) |  | Eq Handle |  | Eq (IORef a) |  | Eq (IOArray i e) |  | Eq Exception |  | Eq IOException |  | Eq IOErrorType |  | Eq BufferState |  | Eq BufferMode |  | Eq ArithException |  | Eq AsyncException |  | Eq ArrayException |  | Eq ExitCode |  | Eq IOMode |  | Eq Int64 |  | Eq Int8 |  | Eq Int16 |  | Eq Int32 |  | Eq Integer |  | Eq (Ptr a) |  | Eq (FunPtr a) |  | (Integral a, Eq a) => Eq (Ratio a) |  | Eq (STRef s a) |  | Eq (StablePtr a) |  | Eq Word64 |  | Eq Word |  | Eq Word8 |  | Eq Word16 |  | Eq Word32 |  | Eq Permissions |  | Eq TimeLocale |  | Eq (StableName a) |  | Eq FDType |  | Eq CDev |  | Eq CIno |  | Eq CMode |  | Eq COff |  | Eq CPid |  | Eq CSsize |  | Eq CGid |  | Eq CNlink |  | Eq CUid |  | Eq CCc |  | Eq CSpeed |  | Eq CTcflag |  | Eq CRLim |  | Eq Fd |  | Eq Month |  | Eq Day |  | Eq ClockTime |  | Eq CalendarTime |  | Eq TimeDiff |  | Eq Lexeme | 
 | 
 | 
|  | 
| class Eq a => Ord a  where | 
| |  |  | Methods |  | | compare :: a -> a -> Ordering |  |  |  | (<) :: a -> a -> Bool |  |  |  | (<=) :: a -> a -> Bool |  |  |  | (>) :: a -> a -> Bool |  |  |  | (>=) :: a -> a -> Bool |  |  |  | max :: a -> a -> a |  |  |  | min :: a -> a -> a | 
 |  |  |  | Instances |  | | Ord ThreadId |  | Ix ix => Ord (UArray ix Bool) |  | Ix ix => Ord (UArray ix Char) |  | Ix ix => Ord (UArray ix Int) |  | Ix ix => Ord (UArray ix Word) |  | Ix ix => Ord (UArray ix (Ptr a)) |  | Ix ix => Ord (UArray ix (FunPtr a)) |  | Ix ix => Ord (UArray ix Float) |  | Ix ix => Ord (UArray ix Double) |  | Ix ix => Ord (UArray ix Int8) |  | Ix ix => Ord (UArray ix Int16) |  | Ix ix => Ord (UArray ix Int32) |  | Ix ix => Ord (UArray ix Int64) |  | Ix ix => Ord (UArray ix Word8) |  | Ix ix => Ord (UArray ix Word16) |  | Ix ix => Ord (UArray ix Word32) |  | Ix ix => Ord (UArray ix Word64) |  | (Ord a, Ord b) => Ord (Either a b) |  | Ord a => Ord (Maybe a) |  | Ord PackedString |  | (Ord a, Ord b) => Ord (a, b) |  | (Ord a, Ord b, Ord c) => Ord (a, b, c) |  | (Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) |  | (Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) |  | (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) |  | (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) |  | (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (a, b, c, d, e, f, g, h) |  | (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (a, b, c, d, e, f, g, h, i) |  | (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (a, b, c, d, e, f, g, h, i, j) |  | (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (a, b, c, d, e, f, g, h, i, j, k) |  | (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (a, b, c, d, e, f, g, h, i, j, k, l) |  | (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m) |  | (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) |  | (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) |  | Ord Unique |  | Ord CChar |  | Ord CSChar |  | Ord CUChar |  | Ord CShort |  | Ord CUShort |  | Ord CInt |  | Ord CUInt |  | Ord CLong |  | Ord CULong |  | Ord CLLong |  | Ord CULLong |  | Ord CFloat |  | Ord CDouble |  | Ord CLDouble |  | Ord CPtrdiff |  | Ord CSize |  | Ord CWchar |  | Ord CSigAtomic |  | Ord CClock |  | Ord CTime |  | (Ix i, Ord e) => Ord (Array i e) |  | Ord a => Ord [a] |  | Ord () |  | Ord Char |  | Ord Int |  | Ord Bool |  | Ord Ordering |  | Ord Float |  | Ord Double |  | Ord (ForeignPtr a) |  | Ord SeekMode |  | Ord BufferMode |  | Ord ArithException |  | Ord AsyncException |  | Ord ArrayException |  | Ord ExitCode |  | Ord IOMode |  | Ord Int64 |  | Ord Int8 |  | Ord Int16 |  | Ord Int32 |  | Ord Integer |  | Ord (Ptr a) |  | Ord (FunPtr a) |  | Integral a => Ord (Ratio a) |  | Ord Word64 |  | Ord Word |  | Ord Word8 |  | Ord Word16 |  | Ord Word32 |  | Ord Permissions |  | Ord TimeLocale |  | Ord CDev |  | Ord CIno |  | Ord CMode |  | Ord COff |  | Ord CPid |  | Ord CSsize |  | Ord CGid |  | Ord CNlink |  | Ord CUid |  | Ord CCc |  | Ord CSpeed |  | Ord CTcflag |  | Ord CRLim |  | Ord Fd |  | Ord Month |  | Ord Day |  | Ord ClockTime |  | Ord CalendarTime |  | Ord TimeDiff | 
 | 
 | 
|  | 
| class Enum a  where | 
| |  |  | Methods |  | | succ :: a -> a |  |  |  | pred :: a -> a |  |  |  | toEnum :: Int -> a |  |  |  | fromEnum :: a -> Int |  |  |  | enumFrom :: a -> [a] |  |  |  | enumFromThen :: a -> a -> [a] |  |  |  | enumFromTo :: a -> a -> [a] |  |  |  | enumFromThenTo :: a -> a -> a -> [a] | 
 |  |  |  | Instances |  |  | 
 | 
|  | 
| class Bounded a  where | 
| |  |  | Methods |  | | minBound :: a |  |  |  | maxBound :: a | 
 |  |  |  | Instances |  | | Bounded CChar |  | Bounded CSChar |  | Bounded CUChar |  | Bounded CShort |  | Bounded CUShort |  | Bounded CInt |  | Bounded CUInt |  | Bounded CLong |  | Bounded CULong |  | Bounded CLLong |  | Bounded CULLong |  | Bounded CPtrdiff |  | Bounded CSize |  | Bounded CWchar |  | Bounded CSigAtomic |  | Bounded CClock |  | Bounded CTime |  | Bounded () |  | (Bounded a, Bounded b) => Bounded (a, b) |  | (Bounded a, Bounded b, Bounded c) => Bounded (a, b, c) |  | (Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (a, b, c, d) |  | Bounded Bool |  | Bounded Ordering |  | Bounded Char |  | Bounded Int |  | Bounded Int8 |  | Bounded Int16 |  | Bounded Int32 |  | Bounded Int64 |  | Bounded Word |  | Bounded Word8 |  | Bounded Word16 |  | Bounded Word32 |  | Bounded Word64 |  | Bounded CIno |  | Bounded CMode |  | Bounded COff |  | Bounded CPid |  | Bounded CSsize |  | Bounded CGid |  | Bounded CNlink |  | Bounded CUid |  | Bounded CTcflag |  | Bounded CRLim |  | Bounded Fd |  | Bounded Month |  | Bounded Day | 
 | 
 | 
|  | 
| Numbers | 
|  | 
| Numeric types | 
|  | 
| 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. |  | Instances |  |  | 
 | 
|  | 
| data Integer | 
| | Arbitrary-precision integers. |  | Instances |  |  | 
 | 
|  | 
| data Float | 
| | Single-precision floating point numbers. |  | Instances |  |  | 
 | 
|  | 
| data Double | 
| | Double-precision floating point numbers. |  | Instances |  |  | 
 | 
|  | 
| type Rational = Ratio Integer | 
| Arbitrary-precision rational numbers, represented as a ratio of
two Integer values.  A rational number may be constructed using
the % operator. | 
|  | 
| Numeric type classes | 
|  | 
| class (Eq a, Show a) => Num a  where | 
| |  |  | Methods |  | | (+) :: a -> a -> a |  |  |  | (-) :: a -> a -> a |  |  |  | (*) :: a -> a -> a |  |  |  | negate :: a -> a |  |  |  | abs :: a -> a |  |  |  | signum :: a -> a |  |  |  | fromInteger :: Integer -> a | 
 |  |  |  | Instances |  |  | 
 | 
|  | 
| class (Num a, Ord a) => Real a  where | 
|  | 
|  | 
| class (Real a, Enum a) => Integral a  where | 
| |  |  | Methods |  | | quot :: a -> a -> a |  |  |  | rem :: a -> a -> a |  |  |  | div :: a -> a -> a |  |  |  | mod :: a -> a -> a |  |  |  | quotRem :: a -> a -> (a, a) |  |  |  | divMod :: a -> a -> (a, a) |  |  |  | toInteger :: a -> Integer | 
 |  |  |  | Instances |  |  | 
 | 
|  | 
| class Num a => Fractional a  where | 
| |  |  | Methods |  | | (/) :: a -> a -> a |  |  |  | recip :: a -> a |  |  |  | fromRational :: Rational -> a | 
 |  |  |  | Instances |  |  | 
 | 
|  | 
| class Fractional a => Floating a  where | 
| |  |  | Methods |  | | pi :: a |  |  |  | exp :: a -> a |  |  |  | log :: a -> a |  |  |  | sqrt :: a -> a |  |  |  | (**) :: a -> a -> a |  |  |  | logBase :: a -> a -> a |  |  |  | sin :: a -> a |  |  |  | cos :: a -> a |  |  |  | tan :: a -> a |  |  |  | asin :: a -> a |  |  |  | acos :: a -> a |  |  |  | atan :: a -> a |  |  |  | sinh :: a -> a |  |  |  | cosh :: a -> a |  |  |  | tanh :: a -> a |  |  |  | asinh :: a -> a |  |  |  | acosh :: a -> a |  |  |  | atanh :: a -> a | 
 |  |  |  | Instances |  |  | 
 | 
|  | 
| class (Real a, Fractional a) => RealFrac a  where | 
|  | 
|  | 
| class (RealFrac a, Floating a) => RealFloat a  where | 
| |  |  | Methods |  | | floatRadix :: a -> Integer |  |  |  | floatDigits :: a -> Int |  |  |  | floatRange :: a -> (Int, Int) |  |  |  | decodeFloat :: a -> (Integer, Int) |  |  |  | encodeFloat :: Integer -> Int -> a |  |  |  | exponent :: a -> Int |  |  |  | significand :: a -> a |  |  |  | scaleFloat :: Int -> a -> a |  |  |  | isNaN :: a -> Bool |  |  |  | isInfinite :: a -> Bool |  |  |  | isDenormalized :: a -> Bool |  |  |  | isNegativeZero :: a -> Bool |  |  |  | isIEEE :: a -> Bool |  |  |  | atan2 :: a -> a -> a | 
 |  |  |  | Instances |  |  | 
 | 
|  | 
| Numeric functions | 
|  | 
| subtract :: Num a => a -> a -> a | 
|  | 
| even :: Integral a => a -> Bool | 
|  | 
| odd :: Integral a => a -> Bool | 
|  | 
| gcd :: Integral a => a -> a -> a | 
|  | 
| lcm :: Integral a => a -> a -> a | 
|  | 
| (^) :: (Num a, Integral b) => a -> b -> a | 
|  | 
| (^^) :: (Fractional a, Integral b) => a -> b -> a | 
|  | 
| fromIntegral :: (Integral a, Num b) => a -> b | 
|  | 
| realToFrac :: (Real a, Fractional b) => a -> b | 
|  | 
| Monads and functors | 
|  | 
| class Monad m  where | 
| | The Monad class defines the basic operations over a monad.
Instances of Monad should satisfy the following laws:
  return a >>= k  ==  k a
 m >>= return  ==  m
 m >>= (\x -> k x >>= h)  ==  (m >>= k) >>= h
 Instances of both Monad and Functor should additionally satisfy the law:
  fmap f xs  ==  xs >>= return . f
 The instances of Monad for lists, Maybe and IO defined in the Prelude
satisfy these laws.
 |  |  |  | Methods |  | | (>>=) :: m a -> (a -> m b) -> m b |  |  |  | (>>) :: m a -> m b -> m b |  |  |  | return :: a -> m a |  |  |  | fail :: String -> m a | 
 |  |  |  | Instances |  |  | 
 | 
|  | 
| class Functor f  where | 
| | 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 defined in the Prelude
satisfy these laws.
 |  |  |  | Methods |  | | fmap :: (a -> b) -> f a -> f b | 
 |  |  |  | Instances |  |  | 
 | 
|  | 
| mapM :: Monad m => (a -> m b) -> [a] -> m [b] | 
|  | 
| mapM_ :: Monad m => (a -> m b) -> [a] -> m () | 
|  | 
| sequence :: Monad m => [m a] -> m [a] | 
|  | 
| sequence_ :: Monad m => [m a] -> m () | 
|  | 
| (=<<) :: Monad m => (a -> m b) -> m a -> m b | 
|  | 
| Miscellaneous functions | 
|  | 
| id :: a -> a | 
|  | 
| const :: a -> b -> a | 
|  | 
| (.) :: (b -> c) -> (a -> b) -> a -> c | 
|  | 
| flip :: (a -> b -> c) -> b -> a -> c | 
|  | 
| ($) :: (a -> b) -> a -> b | 
|  | 
| until :: (a -> Bool) -> (a -> a) -> a -> a | 
|  | 
| asTypeOf :: a -> a -> a | 
|  | 
| error :: String -> a | 
|  | 
| undefined :: a | 
|  | 
| ($!) :: (a -> b) -> a -> b | 
|  | 
| List operations | 
|  | 
| map :: (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, ...] | 
|  | 
| (++) :: [a] -> [a] -> [a] | 
| Append two lists, i.e.,
  [x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn]
 [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
 If the first list is not finite, the result is the first list. | 
|  | 
| filter :: (a -> Bool) -> [a] -> [a] | 
| 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] | 
|  | 
| head :: [a] -> a | 
| Extract the first element of a list, which must be non-empty. | 
|  | 
| last :: [a] -> a | 
| Extract the last element of a list, which must be finite and non-empty. | 
|  | 
| tail :: [a] -> [a] | 
| Extract the elements after the head of a list, which must be non-empty. | 
|  | 
| init :: [a] -> [a] | 
| Return all the elements of a list except the last one.
The list must be finite and non-empty. | 
|  | 
| null :: [a] -> Bool | 
| Test whether a list is empty. | 
|  | 
| length :: [a] -> Int | 
| 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. | 
|  | 
| (!!) :: [a] -> Int -> 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. | 
|  | 
| reverse :: [a] -> [a] | 
| reverse xs returns the elements of xs in reverse order.
xs must be finite. | 
|  | 
| Reducing lists (folds) | 
|  | 
| foldl :: (a -> b -> a) -> a -> [b] -> 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. | 
|  | 
| foldl1 :: (a -> a -> a) -> [a] -> a | 
| foldl1 is a variant of foldl that has no starting value argument,
and thus must be applied to non-empty lists. | 
|  | 
| foldr :: (a -> b -> b) -> b -> [a] -> b | 
| foldr, applied to a binary operator, a starting value (typically
the right-identity of the operator), and a list, reduces the list
using the binary operator, from right to left:
  foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...) | 
|  | 
| foldr1 :: (a -> a -> a) -> [a] -> a | 
| foldr1 is a variant of foldr that has no starting value argument,
and thus must be applied to non-empty lists. | 
|  | 
| Special folds | 
|  | 
| and :: [Bool] -> Bool | 
| and returns the conjunction of a Boolean list.  For the result to be
True, the list must be finite; False, however, results from a False
value at a finite index of a finite or infinite list. | 
|  | 
| or :: [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. | 
|  | 
| any :: (a -> Bool) -> [a] -> Bool | 
| Applied to a predicate and a list, any determines if any element
of the list satisfies the predicate. | 
|  | 
| all :: (a -> Bool) -> [a] -> Bool | 
| Applied to a predicate and a list, all determines if all elements
of the list satisfy the predicate. | 
|  | 
| sum :: Num a => [a] -> a | 
| The sum function computes the sum of a finite list of numbers. | 
|  | 
| product :: Num a => [a] -> a | 
| The product function computes the product of a finite list of numbers. | 
|  | 
| concat :: [[a]] -> [a] | 
| Concatenate a list of lists. | 
|  | 
| concatMap :: (a -> [b]) -> [a] -> [b] | 
| Map a function over a list and concatenate the results. | 
|  | 
| maximum :: Ord 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. | 
|  | 
| minimum :: 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. | 
|  | 
| Building lists | 
|  | 
| Scans | 
|  | 
| scanl :: (a -> b -> a) -> a -> [b] -> [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. | 
|  | 
| scanl1 :: (a -> a -> a) -> [a] -> [a] | 
| scanl1 is a variant of scanl that has no starting value argument:
  scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...] | 
|  | 
| scanr :: (a -> b -> b) -> b -> [a] -> [b] | 
| scanr is the right-to-left dual of scanl.
Note that
  head (scanr f z xs) == foldr f z xs. | 
|  | 
| scanr1 :: (a -> a -> a) -> [a] -> [a] | 
| scanr1 is a variant of scanr that has no starting value argument. | 
|  | 
| Infinite lists | 
|  | 
| iterate :: (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), ...] | 
|  | 
| repeat :: a -> [a] | 
| repeat x is an infinite list, with x the value of every element. | 
|  | 
| replicate :: Int -> 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. | 
|  | 
| cycle :: [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. | 
|  | 
| Sublists | 
|  | 
| take :: Int -> [a] -> [a] | 
| take n, applied to a list xs, returns the prefix of xs
of length n, or xs itself if n > length xs.
It is an instance of the more general genericTake,
in which n may be of any integral type. | 
|  | 
| drop :: Int -> [a] -> [a] | 
| drop n xs returns the suffix of xs
after the first n elements, or [] if n > length xs.
It is an instance of the more general genericDrop,
in which n may be of any integral type. | 
|  | 
| splitAt :: Int -> [a] -> ([a], [a]) | 
| splitAt n xs is equivalent to (take n xs, drop n xs).
It is an instance of the more general genericSplitAt,
in which n may be of any integral type. | 
|  | 
| takeWhile :: (a -> Bool) -> [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. | 
|  | 
| dropWhile :: (a -> Bool) -> [a] -> [a] | 
| dropWhile p xs returns the suffix remaining after takeWhile p xs. | 
|  | 
| span :: (a -> Bool) -> [a] -> ([a], [a]) | 
| span p xs is equivalent to (takeWhile p xs, dropWhile p xs) | 
|  | 
| break :: (a -> Bool) -> [a] -> ([a], [a]) | 
| break p is equivalent to span (not . p). | 
|  | 
| Searching lists | 
|  | 
| elem :: Eq a => a -> [a] -> Bool | 
| elem is the list membership predicate, usually written in infix form,
e.g., x elem xs. | 
|  | 
| notElem :: Eq a => a -> [a] -> Bool | 
| notElem is the negation of elem. | 
|  | 
| lookup :: Eq a => a -> [(a, b)] -> Maybe b | 
| lookup key assocs looks up a key in an association list. | 
|  | 
| Zipping and unzipping lists | 
|  | 
| zip :: [a] -> [b] -> [(a, b)] | 
| zip takes two lists and returns a list of corresponding pairs.
If one input list is short, excess elements of the longer list are
discarded. | 
|  | 
| zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] | 
| zip3 takes three lists and returns a list of triples, analogous to
zip. | 
|  | 
| zipWith :: (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. | 
|  | 
| zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] | 
| The zipWith3 function takes a function which combines three
elements, as well as three lists and returns a list of their point-wise
combination, analogous to zipWith. | 
|  | 
| unzip :: [(a, b)] -> ([a], [b]) | 
| unzip transforms a list of pairs into a list of first components
and a list of second components. | 
|  | 
| unzip3 :: [(a, b, c)] -> ([a], [b], [c]) | 
| The unzip3 function takes a list of triples and returns three
lists, analogous to unzip. | 
|  | 
| Functions on strings | 
|  | 
| lines :: String -> [String] | 
| lines breaks a string up into a list of strings at newline
characters.  The resulting strings do not contain newlines. | 
|  | 
| words :: String -> [String] | 
| words breaks a string up into a list of words, which were delimited
by white space. | 
|  | 
| unlines :: [String] -> String | 
| unlines is an inverse operation to lines.
It joins lines, after appending a terminating newline to each. | 
|  | 
| unwords :: [String] -> String | 
| unwords is an inverse operation to words.
It joins words with separating spaces. | 
|  | 
| Converting to and from String | 
|  | 
| type ReadS a = String -> [(a, String)] | 
| A parser for a type a, represented as a function that takes a
String and returns a list of possible parses (a,String) pairs. | 
|  | 
| type ShowS = String -> String | 
|  | 
| class Read a  where | 
| |  |  | Methods |  |  |  |  |  | Instances |  | | (RealFloat a, Read a) => Read (Complex a) |  | Read CChar |  | Read CSChar |  | Read CUChar |  | Read CShort |  | Read CUShort |  | Read CInt |  | Read CUInt |  | Read CLong |  | Read CULong |  | Read CLLong |  | Read CULLong |  | Read CFloat |  | Read CDouble |  | Read CLDouble |  | Read CPtrdiff |  | Read CSize |  | Read CWchar |  | Read CSigAtomic |  | Read CClock |  | Read CTime |  | Read SeekMode |  | Read BufferMode |  | Read ExitCode |  | Read IOMode |  | Read Int8 |  | Read Int16 |  | Read Int32 |  | Read Int64 |  | Read Char |  | Read Bool |  | Read Ordering |  | Read a => Read (Maybe a) |  | (Read a, Read b) => Read (Either a b) |  | Read a => Read [a] |  | (Ix a, Read a, Read b) => Read (Array a b) |  | Read Lexeme |  | Read Int |  | Read Integer |  | Read Float |  | Read Double |  | (Integral a, Read a) => Read (Ratio a) |  | Read () |  | (Read a, Read b) => Read (a, b) |  | (Read a, Read b, Read c) => Read (a, b, c) |  | (Read a, Read b, Read c, Read d) => Read (a, b, c, d) |  | (Read a, Read b, Read c, Read d, Read e) => Read (a, b, c, d, e) |  | Read Word |  | Read Word8 |  | Read Word16 |  | Read Word32 |  | Read Word64 |  | Read Permissions |  | Read CDev |  | Read CIno |  | Read CMode |  | Read COff |  | Read CPid |  | Read CSsize |  | Read CGid |  | Read CNlink |  | Read CUid |  | Read CCc |  | Read CSpeed |  | Read CTcflag |  | Read CRLim |  | Read Fd |  | Read StdGen |  | Read Month |  | Read Day |  | Read CalendarTime |  | Read TimeDiff | 
 | 
 | 
|  | 
| class Show a  where | 
| |  |  | Methods |  |  |  |  |  | Instances |  | | Show ThreadId |  | (Ix ix, Show ix) => Show (UArray ix Bool) |  | (Ix ix, Show ix) => Show (UArray ix Char) |  | (Ix ix, Show ix) => Show (UArray ix Int) |  | (Ix ix, Show ix) => Show (UArray ix Word) |  | (Ix ix, Show ix) => Show (UArray ix Float) |  | (Ix ix, Show ix) => Show (UArray ix Double) |  | (Ix ix, Show ix) => Show (UArray ix Int8) |  | (Ix ix, Show ix) => Show (UArray ix Int16) |  | (Ix ix, Show ix) => Show (UArray ix Int32) |  | (Ix ix, Show ix) => Show (UArray ix Int64) |  | (Ix ix, Show ix) => Show (UArray ix Word8) |  | (Ix ix, Show ix) => Show (UArray ix Word16) |  | (Ix ix, Show ix) => Show (UArray ix Word32) |  | (Ix ix, Show ix) => Show (UArray ix Word64) |  | (Ix ix, Show ix, Show e) => Show (DiffArray ix e) |  | (Ix ix, Show ix) => Show (DiffUArray ix Char) |  | (Ix ix, Show ix) => Show (DiffUArray ix Int) |  | (Ix ix, Show ix) => Show (DiffUArray ix Word) |  | (Ix ix, Show ix) => Show (DiffUArray ix Float) |  | (Ix ix, Show ix) => Show (DiffUArray ix Double) |  | (Ix ix, Show ix) => Show (DiffUArray ix Int8) |  | (Ix ix, Show ix) => Show (DiffUArray ix Int16) |  | (Ix ix, Show ix) => Show (DiffUArray ix Int32) |  | (Ix ix, Show ix) => Show (DiffUArray ix Int64) |  | (Ix ix, Show ix) => Show (DiffUArray ix Word8) |  | (Ix ix, Show ix) => Show (DiffUArray ix Word16) |  | (Ix ix, Show ix) => Show (DiffUArray ix Word32) |  | (Ix ix, Show ix) => Show (DiffUArray ix Word64) |  | (RealFloat a, Show a) => Show (Complex a) |  | Show Dynamic |  | Show Constr |  | Show Fixity |  | Show DataType |  | Show PackedString |  | Show TypeRep |  | Show TyCon |  | Show CChar |  | Show CSChar |  | Show CUChar |  | Show CShort |  | Show CUShort |  | Show CInt |  | Show CUInt |  | Show CLong |  | Show CULong |  | Show CLLong |  | Show CULLong |  | Show CFloat |  | Show CDouble |  | Show CLDouble |  | Show CPtrdiff |  | Show CSize |  | Show CWchar |  | Show CSigAtomic |  | Show CClock |  | Show CTime |  | Show (Ptr a) |  | Show (FunPtr a) |  | (Ix a, Show a, Show b) => Show (Array a b) |  | Show Float |  | Show Double |  | Show (ForeignPtr a) |  | Show HandlePosn |  | Show SeekMode |  | Show HandleType |  | Show Handle |  | Show ArithException |  | Show AsyncException |  | Show ArrayException |  | Show Exception |  | Show IOErrorType |  | Show IOException |  | Show BufferMode |  | Show ExitCode |  | Show IOMode |  | Show Int8 |  | Show Int16 |  | Show Int32 |  | Show Int64 |  | Show Integer |  | Integral a => Show (Ratio a) |  | Show (ST s a) |  | Show () |  | Show a => Show [a] |  | Show Bool |  | Show Ordering |  | Show Char |  | Show Int |  | Show a => Show (Maybe a) |  | (Show a, Show b) => Show (Either a b) |  | (Show a, Show b) => Show (a, b) |  | (Show a, Show b, Show c) => Show (a, b, c) |  | (Show a, Show b, Show c, Show d) => Show (a, b, c, d) |  | (Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) |  | Show Word |  | Show Word8 |  | Show Word16 |  | Show Word32 |  | Show Word64 |  | Show Permissions |  | Show TimeLocale |  | Show CDev |  | Show CIno |  | Show CMode |  | Show COff |  | Show CPid |  | Show CSsize |  | Show CGid |  | Show CNlink |  | Show CUid |  | Show CCc |  | Show CSpeed |  | Show CTcflag |  | Show CRLim |  | Show Fd |  | Show StdGen |  | Show ClockTime |  | Show Month |  | Show Day |  | Show CalendarTime |  | Show TimeDiff |  | Show Html |  | Show HtmlAttr |  | Show HtmlTable |  | Show HotLink |  | Show a => Show (BlockTable a) |  | Show Doc |  | Show Lexeme |  | Show (a -> b) | 
 | 
 | 
|  | 
| reads :: Read a => ReadS a | 
|  | 
| shows :: Show a => a -> ShowS | 
|  | 
| read :: Read a => String -> a | 
|  | 
| lex :: ReadS String | 
|  | 
| showChar :: Char -> ShowS | 
|  | 
| showString :: String -> ShowS | 
|  | 
| readParen :: Bool -> ReadS a -> ReadS a | 
|  | 
| showParen :: Bool -> ShowS -> ShowS | 
|  | 
| Basic Input and output | 
|  | 
| data IO a | 
| | 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.
 |  | Instances |  |  | 
 | 
|  | 
| Simple I/O operations | 
|  | 
| Output functions | 
|  | 
| putChar :: Char -> IO () | 
| Write a character to the standard output device
(same as hPutChar stdout). | 
|  | 
| putStr :: String -> IO () | 
| Write a string to the standard output device
(same as hPutStr stdout). | 
|  | 
| putStrLn :: String -> IO () | 
| The same as putStrLn, but adds a newline character. | 
|  | 
| print :: Show a => a -> IO () | 
| The print function outputs a value of any printable type to the
standard output device.
Printable types are those that are instances of class Show; print
converts values to strings for output using the show operation and
adds a newline.
 For example, a program to print the first 20 integers and their
powers of 2 could be written as:
  main = print ([(n, 2^n) | n <- [0..19]]) | 
|  | 
| Input functions | 
|  | 
| getChar :: IO Char | 
| Read a character from the standard input device
(same as hGetChar stdin). | 
|  | 
| getLine :: IO String | 
| Read a line from the standard input device
(same as hGetLine stdin). | 
|  | 
| getContents :: 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). | 
|  | 
| interact :: (String -> String) -> 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. | 
|  | 
| Files | 
|  | 
| type FilePath = String | 
| 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. | 
|  | 
| readFile :: FilePath -> IO String | 
| The readFile function reads a file and
returns the contents of the file as a string.
The file is read lazily, on demand, as with getContents. | 
|  | 
| writeFile :: FilePath -> String -> IO () | 
| The computation writeFile file str function writes the string str,
to the file file. | 
|  | 
| appendFile :: 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]]) | 
|  | 
| readIO :: Read a => String -> IO a | 
| The readIO function is similar to read except that it signals
parse failure to the IO monad instead of terminating the program. | 
|  | 
| readLn :: Read a => IO a | 
| The readLn function combines getLine and readIO. | 
|  | 
| Exception handling in the I/O monad | 
|  | 
| type IOError = IOException | 
| The Haskell 98 type for exceptions in the IO monad.
Any I/O operation may raise an IOError instead of returning a result.
For a more general type of exception, including also those that arise
in pure code, see Exception.
 In Haskell 98, this is an opaque type. | 
|  | 
| ioError :: IOError -> IO a | 
| Raise an IOError in the IO monad. | 
|  | 
| userError :: String -> 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)
 | 
|  | 
| catch :: IO a -> (IOError -> IO a) -> 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.
 Non-I/O exceptions are not caught by this variant; to catch all
exceptions, use catch from Control.Exception. | 
|  | 
| Produced by Haddock version 0.6 |