| Safe Haskell | None |
|---|
Prelude
- data Char
- type String = [Char]
- data Double
- data Int
- data Integer
- data Bool
- class Read a
- class Show a
- class Eq a where
- (==) :: Eq a => a -> a -> Bool
- (/=) :: Eq a => a -> a -> Bool
- data Maybe a
- maybe :: t -> (t1 -> t) -> Maybe t1 -> t
- (>>=) :: Ptr (Fay a) -> Ptr (a -> Fay b) -> Ptr (Fay b)
- (>>) :: Ptr (Fay a) -> Ptr (Fay b) -> Ptr (Fay b)
- return :: a -> Fay a
- fail :: String -> Fay a
- when :: Bool -> Fay a -> Fay ()
- forM_ :: [t] -> (t -> Fay a) -> Fay ()
- mapM_ :: (a -> Fay b) -> [a] -> Fay ()
- (=<<) :: (a -> Fay b) -> Fay a -> Fay b
- sequence :: [Fay a] -> Fay [a]
- sequence_ :: [Fay a] -> Fay ()
- (*) :: Num a => a -> a -> a
- (+) :: Num a => a -> a -> a
- (-) :: Num a => a -> a -> a
- class (Eq a, Ord a) => Ord a where
- data Ordering
- compare :: Ord a => a -> a -> Ordering
- succ :: Num a => a -> a
- pred :: Num a => a -> a
- enumFrom :: Num a => a -> [a]
- enumFromTo :: (Ord t, Num t) => t -> t -> [t]
- enumFromBy :: Num t => t -> t -> [t]
- enumFromThen :: Num t => t -> t -> [t]
- enumFromByTo :: (Ord t, Num t) => t -> t -> t -> [t]
- enumFromThenTo :: (Ord t, Num t) => t -> t -> t -> [t]
- (/) :: Fractional a => a -> a -> a
- fromIntegral :: (Num a, Num b) => Ptr a -> Ptr b
- fromInteger :: Num a => Ptr Integer -> Ptr a
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
- otherwise :: Bool
- show :: Automatic a -> String
- error :: String -> a
- undefined :: a
- data Either a b
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- until :: (a -> Bool) -> (a -> a) -> a -> a
- ($!) :: (a -> b) -> a -> b
- seq :: a -> b -> b
- const :: a -> b -> a
- id :: a -> a
- (.) :: (t1 -> t) -> (t2 -> t1) -> t2 -> t
- ($) :: (t1 -> t) -> t1 -> t
- flip :: (t1 -> t2 -> t) -> t2 -> t1 -> t
- curry :: ((a, b) -> c) -> a -> b -> c
- uncurry :: (a -> b -> c) -> (a, b) -> c
- snd :: (t, t1) -> t1
- fst :: (t, t1) -> t
- div :: Int -> Int -> Int
- mod :: Int -> Int -> Int
- divMod :: Int -> Int -> (Int, Int)
- min :: Num a => a -> a -> a
- max :: Num a => a -> a -> a
- recip :: Double -> Double
- negate :: Num a => a -> a
- abs :: (Num a, Ord a) => a -> a
- signum :: (Num a, Ord a) => a -> a
- pi :: Double
- exp :: Double -> Double
- sqrt :: Double -> Double
- log :: Double -> Double
- (**) :: Double -> Double -> Double
- (^^) :: Double -> Int -> Double
- unsafePow :: (Num a, Num b) => a -> b -> a
- (^) :: Num a => a -> Int -> a
- logBase :: Double -> Double -> Double
- sin :: Double -> Double
- tan :: Double -> Double
- cos :: Double -> Double
- asin :: Double -> Double
- atan :: Double -> Double
- acos :: Double -> Double
- sinh :: Double -> Double
- tanh :: Double -> Double
- cosh :: Double -> Double
- asinh :: Double -> Double
- atanh :: Double -> Double
- acosh :: Double -> Double
- properFraction :: Double -> (Int, Double)
- truncate :: Double -> Int
- round :: Double -> Int
- ceiling :: Double -> Int
- floor :: Double -> Int
- subtract :: Num a => a -> a -> a
- even :: Int -> Bool
- odd :: Int -> Bool
- gcd :: Int -> Int -> Int
- quot :: Int -> Int -> Int
- quot' :: Int -> Int -> Int
- quotRem :: Int -> Int -> (Int, Int)
- rem :: Int -> Int -> Int
- rem' :: Int -> Int -> Int
- lcm :: Int -> Int -> Int
- find :: (a -> Bool) -> [a] -> Maybe a
- filter :: (a -> Bool) -> [a] -> [a]
- null :: [t] -> Bool
- map :: (a -> b) -> [a] -> [b]
- nub :: Eq a => [a] -> [a]
- nub' :: Eq a => [a] -> [a] -> [a]
- elem :: Eq a => a -> [a] -> Bool
- notElem :: Eq a => a -> [a] -> Bool
- sort :: Ord a => [a] -> [a]
- sortBy :: (t -> t -> Ordering) -> [t] -> [t]
- insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]
- conc :: [a] -> [a] -> [a]
- concat :: [[a]] -> [a]
- concatMap :: (a -> [b]) -> [a] -> [b]
- foldr :: (t -> t1 -> t1) -> t1 -> [t] -> t1
- foldr1 :: (a -> a -> a) -> [a] -> a
- foldl :: (t1 -> t -> t1) -> t1 -> [t] -> t1
- foldl1 :: (a -> a -> a) -> [a] -> a
- (++) :: [a] -> [a] -> [a]
- (!!) :: [a] -> Int -> a
- head :: [a] -> a
- tail :: [a] -> [a]
- init :: [a] -> [a]
- last :: [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])
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
- zip :: [a] -> [b] -> [(a, b)]
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- unzip :: [(a, b)] -> ([a], [b])
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- lines :: String -> [String]
- unlines :: [String] -> String
- words :: String -> [String]
- unwords :: [String] -> String
- and :: [Bool] -> Bool
- or :: [Bool] -> Bool
- any :: (a -> Bool) -> [a] -> Bool
- all :: (a -> Bool) -> [a] -> Bool
- intersperse :: a -> [a] -> [a]
- prependToAll :: a -> [a] -> [a]
- intercalate :: [a] -> [[a]] -> [a]
- maximum :: Num a => [a] -> a
- minimum :: Num a => [a] -> a
- product :: Num a => [a] -> a
- sum :: Num 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]
- lookup :: Eq a1 => a1 -> [(a1, a)] -> Maybe a
- length :: [a] -> Int
- length' :: Int -> [a] -> Int
- reverse :: [a] -> [a]
- print :: Automatic a -> Fay ()
- putStrLn :: String -> Fay ()
- ifThenElse :: Bool -> t -> t -> t
- data Fay a
Documentation
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).
Instances
| Bounded Char | |
| Enum Char | |
| Eq Char | |
| Data Char | |
| Ord Char | |
| Read Char | |
| Show Char | |
| Typeable Char | |
| ToJSON Char | |
| FromJSON Char | |
| ModName String | |
| ErrorList Char | |
| Unbox Char | |
| GTraversable c Char | |
| Vector Vector Char | |
| MVector MVector Char | |
| IsString [Char] | |
| ToJSON [Char] | |
| FromJSON [Char] | |
| ToJSON v => ToJSON (HashMap String v) | |
| ToJSON v => ToJSON (Map String v) | |
| FromJSON v => FromJSON (HashMap String v) | |
| FromJSON v => FromJSON (Map String v) |
data Double
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.
Instances
data Int
data Integer
Arbitrary-precision integers.
data Bool
class Read a
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:
- If the constructor is defined to be an infix operator, then the
derived
Readinstance will parse only infix applications of the constructor (not the prefix form). - Associativity is not used to reduce the occurrence of parentheses, although precedence may be.
- If the constructor is defined using record syntax, the derived
Readwill parse only the record-syntax form, and furthermore, the fields must be given in the same order as the original declaration. - The derived
Readinstance allows arbitrary Haskell whitespace between tokens of the input string. Extra parentheses are also allowed.
For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Read in Haskell 98 is equivalent to
instance (Read a) => Read (Tree a) where
readsPrec d r = readParen (d > app_prec)
(\r -> [(Leaf m,t) |
("Leaf",s) <- lex r,
(m,t) <- readsPrec (app_prec+1) s]) r
++ readParen (d > up_prec)
(\r -> [(u:^:v,w) |
(u,s) <- readsPrec (up_prec+1) r,
(":^:",t) <- lex s,
(v,w) <- readsPrec (up_prec+1) t]) r
where app_prec = 10
up_prec = 5
Note that right-associativity of :^: is unused.
The derived instance in GHC is equivalent to
instance (Read a) => Read (Tree a) where
readPrec = parens $ (prec app_prec $ do
Ident "Leaf" <- lexP
m <- step readPrec
return (Leaf m))
+++ (prec up_prec $ do
u <- step readPrec
Symbol ":^:" <- lexP
v <- step readPrec
return (u :^: v))
where app_prec = 10
up_prec = 5
readListPrec = readListPrecDefault
Instances
| Read Bool | |
| Read Char | |
| Read Double | |
| Read Float | |
| Read Int | |
| Read Integer | |
| Read Ordering | |
| Read Word | |
| Read () | |
| Read Text | |
| Read UTCTime | |
| Read DotNetTime | |
| Read Lexeme | |
| Read Text | |
| Read SerializeContext | |
| Read LocalTime | |
| Read ZonedTime | |
| Read TimeOfDay | |
| Read TimeZone | |
| Read Day | |
| Read a => Read [a] | |
| (Integral a, Read a) => Read (Ratio a) | |
| Read a => Read (Maybe a) | |
| (Read a, Unbox a) => Read (Vector a) | |
| Read a => Read (Maybe a) | |
| (Read a, Read b) => Read (a, b) | |
| (Ix a, Read a, Read b) => Read (Array 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 a, Read b, Read c, Read d, Read e, Read f) => Read (a, b, c, d, e, f) | |
| (Read a, Read b, Read c, Read d, Read e, Read f, Read g) => Read (a, b, c, d, e, f, g) | |
| (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) => Read (a, b, c, d, e, f, g, h) | |
| (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i) => Read (a, b, c, d, e, f, g, h, i) | |
| (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j) => Read (a, b, c, d, e, f, g, h, i, j) | |
| (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k) => Read (a, b, c, d, e, f, g, h, i, j, k) | |
| (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l) => Read (a, b, c, d, e, f, g, h, i, j, k, l) | |
| (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
| (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
| (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n, Read o) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) |
class Show a
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:
- The result of
showis a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used. - If the constructor is defined to be an infix operator, then
showsPrecwill produce infix applications of the constructor. - the representation will be enclosed in parentheses if the
precedence of the top-level constructor in
xis less thand(associativity is ignored). Thus, ifdis0then the result is never surrounded in parentheses; ifdis11it is always surrounded in parentheses, unless it is an atomic expression. - If the constructor is defined using record syntax, then
showwill produce the record-syntax form, with the fields given in the same order as the original declaration.
For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Show is equivalent to
instance (Show a) => Show (Tree a) where
showsPrec d (Leaf m) = showParen (d > app_prec) $
showString "Leaf " . showsPrec (app_prec+1) m
where app_prec = 10
showsPrec d (u :^: v) = showParen (d > up_prec) $
showsPrec (up_prec+1) u .
showString " :^: " .
showsPrec (up_prec+1) v
where up_prec = 5
Note that right-associativity of :^: is ignored. For example,
-
produces the stringshow(Leaf 1 :^: Leaf 2 :^: Leaf 3)"Leaf 1 :^: (Leaf 2 :^: Leaf 3)".
Instances
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.
Instances
| Eq Bool | |
| Eq Char | |
| Eq Double | |
| Eq Float | |
| Eq Int | |
| Eq Integer | |
| Eq Ordering | |
| Eq Word | |
| Eq () | |
| Eq Field | |
| Eq Text | |
| Eq DotNetTime | |
| Eq Value | |
| Eq Constr | Equality of constructors |
| Eq DataRep | |
| Eq ConstrRep | |
| Eq Fixity | |
| Eq TypeRep | |
| Eq TyCon | |
| Eq Text | |
| Eq ModulePath | |
| Eq JsStmt | |
| Eq JsExp | |
| Eq JsName | |
| Eq JsLit | |
| Eq SerializeContext | |
| Eq Symbols | |
| Eq GName | |
| Eq OrigName | |
| Eq Table | |
| Eq LocalTime | |
| Eq a => Eq [a] | |
| Eq a => Eq (Ratio a) | |
| Eq a => Eq (Maybe a) | |
| Eq a => Eq (Result a) | |
| Eq name => Eq (SymValueInfo name) | |
| Eq name => Eq (SymTypeInfo name) | |
| Eq l => Eq (Scoped l) | |
| Eq l => Eq (NameInfo l) | |
| Eq l => Eq (Error l) | |
| (Unbox a, Eq a) => Eq (Vector a) | |
| (Eq a, Eq b) => Eq (a, b) | |
| Eq a => Eq (Stream Id a) | |
| (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) |
Maybe type.
sequence :: [Fay a] -> Fay [a]Source
Evaluate each action in the sequence from left to right, and collect the results.
enumFromTo :: (Ord t, Num t) => t -> t -> [t]Source
enumFromBy :: Num t => t -> t -> [t]Source
enumFromThen :: Num t => t -> t -> [t]Source
enumFromByTo :: (Ord t, Num t) => t -> t -> t -> [t]Source
enumFromThenTo :: (Ord t, Num t) => t -> t -> t -> [t]Source
fromIntegral :: (Num a, Num b) => Ptr a -> Ptr bSource
fromInteger :: Num a => Ptr Integer -> Ptr aSource
seq :: a -> b -> b
Evaluates its first argument to head normal form, and then returns its second argument as the result.
properFraction :: Double -> (Int, Double)Source
Implemented in Fay, not fast.
intersperse :: a -> [a] -> [a]Source
prependToAll :: a -> [a] -> [a]Source
intercalate :: [a] -> [[a]] -> [a]Source
ifThenElse :: Bool -> t -> t -> tSource
Default definition for using RebindableSyntax.