|
GHC.Base | Portability | non-portable (GHC extensions) | Stability | internal | Maintainer | cvs-ghc@haskell.org |
|
|
|
|
|
Description |
Basic data types and classes.
|
|
Synopsis |
|
|
|
Documentation |
|
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 | |
|
|
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 | |
|
|
class Functor f where |
| Methods | fmap :: (a -> b) -> f a -> f b |
| | Instances | |
|
|
class Monad m where |
| Methods | (>>=) :: m a -> (a -> m b) -> m b | | (>>) :: m a -> m b -> m b | | return :: a -> m a | | fail :: String -> m a |
| | Instances | |
|
|
data [] a |
|
|
foldr :: (a -> b -> b) -> b -> [a] -> b |
|
build :: forall a . (forall b . (a -> b -> b) -> b -> b) -> [a] |
|
augment :: forall a . (forall b . (a -> b -> b) -> b -> b) -> [a] -> [a] |
|
map :: (a -> b) -> [a] -> [b] |
|
mapFB :: (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst |
|
(++) :: [a] -> [a] -> [a] |
|
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 () |
The unit datatype () has one non-undefined member, the nullary
constructor (). | Constructors | |
|
|
data Ordering |
Represents an ordering relationship between two values: less
than, equal to, or greater than. An Ordering is returned by
compare. | Constructors | | Instances | |
|
|
type String = [Char] |
A String is a list of characters. String constants in Haskell are values
of type String.
|
|
data Char |
The character type Char is an enumeration whose values represent
Unicode characters. A character literal in Haskell has type Char. To convert a Char to or from an Int, use toEnum and
fromEnum from the Enum class respectively (equivalently
ord and chr also do the trick).
| Constructors | | Instances | |
|
|
chr :: Int -> Char |
|
unsafeChr :: Int -> Char |
|
ord :: Char -> Int |
|
eqString :: String -> String -> Bool |
|
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. | Constructors | | Instances | |
|
|
zeroInt :: Int |
|
oneInt :: Int |
|
twoInt :: Int |
|
maxInt :: Int |
|
minInt :: Int |
|
compareInt :: Int -> Int -> Ordering |
|
compareInt# :: Int# -> Int# -> Ordering |
|
id :: a -> a |
|
lazy :: 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 |
|
data Unit |
|
|
divInt# :: Int# -> Int# -> Int# |
|
modInt# :: Int# -> Int# -> Int# |
|
plusInt :: Int -> Int -> Int |
|
minusInt :: Int -> Int -> Int |
|
timesInt :: Int -> Int -> Int |
|
quotInt :: Int -> Int -> Int |
|
remInt :: Int -> Int -> Int |
|
divInt :: Int -> Int -> Int |
|
modInt :: Int -> Int -> Int |
|
gcdInt :: Int -> Int -> Int |
|
negateInt :: Int -> Int |
|
gtInt :: Int -> Int -> Bool |
|
geInt :: Int -> Int -> Bool |
|
eqInt :: Int -> Int -> Bool |
|
neInt :: Int -> Int -> Bool |
|
ltInt :: Int -> Int -> Bool |
|
leInt :: Int -> Int -> Bool |
|
shiftL# :: Word# -> Int# -> Word# |
|
shiftRL# :: Word# -> Int# -> Word# |
|
iShiftL# :: Int# -> Int# -> Int# |
|
iShiftRA# :: Int# -> Int# -> Int# |
|
iShiftRL# :: Int# -> Int# -> Int# |
|
unpackCString# :: Addr# -> [Char] |
|
unpackAppendCString# :: Addr# -> [Char] -> [Char] |
|
unpackFoldrCString# :: Addr# -> (Char -> a -> a) -> a -> a |
|
unpackCStringUtf8# :: Addr# -> [Char] |
|
unpackNBytes# :: Addr# -> Int# -> [Char] |
|
module GHC.Err |
|
Produced by Haddock version 0.4 |