Difference between revisions of "Keywords"

From HaskellWiki
Jump to navigation Jump to search
m (Update link to Smart constructors, following redirection)
(→‎#: remove unboxed kind)
(121 intermediate revisions by 23 users not shown)
Line 1: Line 1:
 
This page lists all Haskell keywords, feel free to edit. [[Hoogle]] searches will return results from this page. Please respect the Anchor macros.
 
This page lists all Haskell keywords, feel free to edit. [[Hoogle]] searches will return results from this page. Please respect the Anchor macros.
   
For additional information you might want to look at [http://www.haskell.org/onlinereport/ the Haskell 98 report].
+
For additional information you might want to look at [http://www.haskell.org/onlinereport/haskell2010/ the Haskell 2010 report].
   
== | ==
+
== ! ==
   
  +
Whenever a data [[constructor]] is applied, each argument to the
safeTail x | null x = []
 
  +
constructor is evaluated if and only if the corresponding type in the
| otherwise = tail x
 
  +
algebraic data[[type]] declaration has a strictness flag, denoted by an
  +
exclamation point. For example:
  +
  +
<haskell>
  +
data STList a
  +
= STCons a !(STList a) -- the second argument to STCons will be
  +
-- evaluated before STCons is applied
  +
| STNil
  +
</haskell>
  +
  +
to illustrate the difference between strict versus lazy constructor
  +
application, consider the following:
  +
  +
<haskell>
  +
stList = STCons 1 undefined
  +
lzList = (:) 1 undefined
  +
stHead (STCons h _) = h -- this evaluates to undefined when applied to stList
  +
lzHead (h : _) = h -- this evaluates to 1 when applied to lzList
  +
</haskell>
  +
  +
! is also used in the [http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html "bang patterns"] (GHC extension), to indicate
  +
strictness in patterns:
  +
  +
<haskell>
  +
f !x !y = x + y
  +
</haskell>
  +
  +
== ' ==
  +
* Character literal: <hask>'a'</hask>
  +
* [[Template Haskell]]: Name of a (value) variable or data constructor: <hask>'length</hask>, <hask>'Left</hask>
  +
* (in types, GHC specific) Promoted data constructor: <hask>'True</hask>
  +
  +
== <nowiki>''</nowiki> ==
  +
* [[Template Haskell]]: Name of a type constructor or class: <hask>''Int</hask>, <hask>''Either</hask>, <hask>''Show</hask>
  +
  +
== - ==
  +
This operator token is magic/irregular in the sense that
  +
<haskell>(- 1)</haskell>
  +
is parsed as the negative integer -1, rather than as an operator [[Section of an infix operator|section]], as it would be for any other operator:
  +
<haskell>(* 1) :: Num a => a -> a</haskell>
  +
<haskell>(++ "foo") :: String -> String</haskell>
  +
  +
It is syntactic sugar for the <hask>negate</hask> function in Prelude. See [[unary operator]].
  +
If you want the section, you can use the <hask>subtract</hask> function or <hask>(+(-1))</hask>.
  +
  +
== -- ==
  +
  +
Starts a single-line comment, unless immediately followed by an operator character other than <hask>-</hask>:
  +
  +
<haskell>
  +
main = print "hello world" -- this is a comment
  +
--this is a comment as well
  +
---this too
  +
foobar --+ this_is_the_second_argument_of_the_dash_dash_plus_operator
  +
</haskell>
  +
  +
The multi-line variant for comments is <hask>{- comment -}</hask>.
  +
  +
== -< ==
  +
[[Arrow notation]]
  +
  +
== -<< ==
  +
[[Arrow notation]]
   
squares = [a*a | a <- [1..]]
 
   
 
== -> ==
 
== -> ==
   
  +
* The function type constructor:
Please write this
 
  +
<haskell>
  +
length :: [a] -> Int
  +
</haskell>
  +
  +
* In lambda functions:
  +
<haskell>
  +
\x -> x + 1
  +
</haskell>
  +
  +
* To denote alternatives in case statements:
  +
<haskell>
  +
case Just 3 of
  +
Nothing -> False
  +
Just x -> True
  +
</haskell>
  +
  +
* On the kind level (GHC specific):
  +
<haskell>
  +
ghci> :kind (->)
  +
(->) :: * -> * -> *
  +
</haskell>
  +
  +
* [[Functional dependencies]]
  +
<haskell>
  +
-- This examples assumes that each type 'c' can "contain" only one type
  +
-- i.e. type 'c' uniquely determines type 'elt'
  +
class Contains c elt | c -> elt where
  +
...
  +
</haskell>
  +
  +
* [[View patterns]]
  +
  +
== :: ==
  +
  +
Read as "has type":
  +
  +
<haskell>
  +
length :: [a] -> Int
  +
</haskell>
  +
  +
"Length has type list-of-'a' to Int"
  +
  +
Or "has kind" (GHC specific):
  +
  +
<haskell>
  +
Either :: * -> * -> *
  +
</haskell>
  +
  +
== ; ==
  +
* Statement separator in an explicit block (see [[layout]])
   
 
== <- ==
 
== <- ==
   
  +
* In do-notation, "draw from":
Please write this
 
  +
<haskell>
  +
do x <- getChar
  +
putChar x
  +
</haskell>
   
  +
* In list comprehension generators, "in":
== @ ==
 
  +
<haskell>
  +
[ (x,y) | x <- [1..10], y <- ['a'..'z'] ]
  +
</haskell>
   
  +
* In [[pattern guard]]s, "matches":
Patterns of the form var@pat are called as-patterns, and allow one to use var as a name for the value being matched by pat. For example:
 
  +
<haskell>
  +
f x y | Just z <- g x = True
  +
| otherwise = False
  +
</haskell>
  +
  +
== , ==
  +
  +
In list comprehensions, "and":
  +
<haskell>
  +
[ (x,y) | x <- [1..10], y <- ['a'..'z'], x > 42 ]
  +
</haskell>
  +
  +
== = ==
  +
Used in definitions.
  +
  +
<haskell>
  +
x = 4
  +
</haskell>
  +
  +
== => ==
  +
  +
Used to indicate instance contexts, for example:
  +
  +
<haskell>
  +
sort :: Ord a => [a] -> [a]
  +
</haskell>
  +
  +
== > ==
  +
  +
In a Bird's style [[Literate_programming|Literate Haskell file]], the > character is used to introduce a code line.
  +
  +
<haskell>
  +
comment line
  +
  +
> main = print "hello world"
  +
</haskell>
  +
  +
== ? ==
  +
  +
* [[Implicit parameters]]
  +
  +
<haskell>
  +
ghci> :t ?foo ++ "bar"
  +
?foo ++ "bar" :: (?foo::[Char]) => [Char]
  +
</haskell>
  +
  +
== # ==
  +
  +
* [http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#magic-hash MagicHash]
  +
  +
== * ==
  +
  +
* Is an ordinary operator name on the value level
  +
  +
* On the [[kind]] level: The kind of boxed types (GHC-specific)
  +
  +
<haskell>
  +
ghci> :kind Int
  +
Int :: *
  +
</haskell>
  +
  +
== @ ==
   
  +
Patterns of the form var@pat are called as-patterns, and allow one to
  +
use var as a name for the value being matched by pat. For example:
  +
<haskell>
 
case e of { xs@(x:rest) -> if x==0 then rest else xs }
 
case e of { xs@(x:rest) -> if x==0 then rest else xs }
  +
</haskell>
   
 
is equivalent to:
 
is equivalent to:
   
  +
<haskell>
 
let { xs = e } in
 
let { xs = e } in
 
case xs of { (x:rest) -> if x==0 then rest else xs }
 
case xs of { (x:rest) -> if x==0 then rest else xs }
  +
</haskell>
   
== ! ==
+
== [|, |] ==
  +
* [[Template Haskell]]
  +
** Expression quotation: <hask> [| print 1 |] </hask>
  +
** Declaration quotation: <hask> [d| main = print 1 |] </hask>
  +
** Type quotation: <hask> [t| Either Int () |] </hask>
  +
** Pattern quotation: <hask> [p| (x,y) |] </hask>
  +
** [[Quasiquotation]]: <hask> [nameOfQuasiQuoter| ... |] </hask>
   
  +
== \ ==
Whenever a data [[constructor]] is applied, each argument to the constructor is evaluated if and only if the corresponding type in the algebraic data[[type]] declaration has a strictness flag, denoted by an exclamation point. For example:
 
  +
The backslash "\" is used
   
  +
* in multiline strings
data STList a
 
  +
<haskell>
= STCons a !(STList a) -- the second argument to STCons will be
 
  +
"foo\
-- evaluated before STCons is applied
 
  +
\bar"
| STNil
 
  +
</haskell>
   
  +
* in lambda functions
to illustrate the difference between strict versus lazy constructor application, consider the following:
 
  +
<haskell>
 
  +
\x -> x + 1
stList = STCons 1 undefined
 
  +
</haskell>
lzList = (:) 1 undefined
 
stHead (STCons h _) = h -- this evaluates to undefined when applied to stList
 
lzHead (h : _) = h -- this evaluates to 1 when applied to lzList
 
 
== :: ==
 
   
Please write this
 
   
 
== _ ==
 
== _ ==
   
Patterns of the form _ are wildcards and are useful when some part of a pattern is not referenced on the right-hand-side. It is as if an identifier not used elsewhere were put in its place. For example,
+
Patterns of the form _ are wildcards and are useful when some part of a
  +
pattern is not referenced on the right-hand-side. It is as if an
  +
identifier not used elsewhere were put in its place. For example,
   
  +
<haskell>
 
case e of { [x,_,_] -> if x==0 then True else False }
 
case e of { [x,_,_] -> if x==0 then True else False }
  +
</haskell>
   
 
is equivalent to:
 
is equivalent to:
   
  +
<haskell>
 
case e of { [x,y,z] -> if x==0 then True else False }
 
case e of { [x,y,z] -> if x==0 then True else False }
  +
</haskell>
  +
  +
  +
  +
  +
  +
== ` ==
  +
  +
A function enclosed in back ticks "`" can be used as an infix operator.
  +
  +
<haskell>2 `subtract` 10</haskell>
  +
is the same as
  +
<haskell>subtract 2 10</haskell>
  +
  +
== {, } ==
  +
* Explicit block (disable [[layout]]), possibly with ";" .
  +
  +
* Record update notation
  +
<haskell>
  +
changePrice :: Thing -> Price -> Thing
  +
changePrice x new = x { price = new }
  +
</haskell>
  +
  +
* Comments (see below)
  +
  +
== {-, -} ==
  +
  +
Everything between "{-" followed by a space and "-}" is a block comment.
  +
  +
<haskell>
  +
{-
  +
hello
  +
world
  +
-}
  +
</haskell>
  +
  +
== | ==
  +
  +
The "pipe" is used in several places
  +
  +
* Data type definitions, "or"
  +
<haskell>
  +
data Maybe a = Just a | Nothing
  +
</haskell>
  +
  +
* List comprehensions, "for" (as in, "list of <code>a*a</code> for <code>a</code> in <code>[1..]</code>)
  +
<haskell>
  +
squares = [a*a | a <- [1..]]
  +
</haskell>
  +
  +
* Guards, "when"
  +
<haskell>
  +
safeTail x | null x = []
  +
| otherwise = tail x
  +
</haskell>
  +
  +
* [[Functional dependencies]], "where"
  +
<haskell>
  +
class Contains c elt | c -> elt where
  +
...
  +
</haskell>
   
 
== ~ ==
 
== ~ ==
   
  +
* Lazy pattern bindings. Matching the pattern ~pat against a value always
Please write this
 
  +
succeeds, and matching will only diverge when one of the variables bound
  +
in the pattern is used.
  +
  +
<haskell>
  +
f1, f2 :: Maybe Int -> String
  +
f1 x = case x of
  +
Just n -> "Got it"
  +
f2 x = case x of
  +
~(Just n) -> "Got it"
  +
  +
(+++), (++++) :: (a -> b) -> (c -> d) -> (a, c) -> (b, d)
  +
(f +++ g) ~(x, y) = (f x, g y)
  +
(f ++++ g) (x, y) = (f x, g y)
  +
</haskell>
  +
  +
Then we have:
  +
  +
<haskell>
  +
f1 Nothing
  +
Exception: Non-exhaustive patterns in case
  +
  +
f2 Nothing
  +
"Got it"
  +
  +
(const 1 +++ const 2) undefined
  +
(1,2)
  +
  +
(const 1 ++++ const 2) undefined
  +
Exception: Prelude.undefined
  +
</haskell>
  +
  +
For more details see [http://en.wikibooks.org/wiki/Haskell/Laziness#Lazy_pattern_matching the Haskell Wikibook].
  +
  +
* Equality constraints. Assert that two types in a context must be the same:
  +
  +
<haskell>
  +
example :: F a ~ b => a -> b
  +
</haskell>
  +
  +
Here the type "F a" must be the same as the type "b", which allows one to constrain polymorphism (especially where type families are involved), but to a lesser extent than functional dependencies. See [[Type_families#Equality_constraints|Type Families]].
   
 
== as ==
 
== as ==
   
  +
Renaming module imports. Like <hask>qualified</hask> and <hask>hiding</hask>, <hask>as</hask> is not a reserved word but may be used as function or variable name.
Please write this
 
   
  +
<haskell>
== case, of ==
 
  +
import qualified Data.Map as M
  +
  +
main = print (M.empty :: M.Map Int ())
  +
</haskell>
  +
  +
== <span id="case">case</span>, <span id="of">of</span> ==
   
 
A case expression has the general form
 
A case expression has the general form
   
  +
<haskell>
 
case e of { p1 match1 ; ... ; pn matchn }
 
case e of { p1 match1 ; ... ; pn matchn }
  +
</haskell>
   
where each match is of the general form
+
where each <code>match</code><sub>i</sub> is of the general form
   
  +
<haskell>
| g1 -> e1
 
...
+
| g1 -> e1
  +
...
| gm -> em
 
  +
| gm -> em
where decls
 
  +
where decls
  +
</haskell>
   
  +
Each alternative consists of patterns <code>p</code><sub>i</sub> and their matches, <code>match</code><sub>i</sub>. Each
Each alternative consists of a pattern pi and its matches, matchi. Each match in turn consists of a sequence of pairs of guards gj and bodies ej (expressions), followed by optional bindings (decls) that scope over all of the guards and expressions of the alternative. An alternative of the form
 
  +
<code>match</code><sub>i</sub> in turn consists of a sequence of pairs of guards <code>g</code><sub>ij</sub> and bodies <code>e</code><sub>ij</sub>
  +
(expressions), followed by optional bindings (<code>decls</code><sub>i</sub>) that scope over all
  +
of the guards and expressions of the alternative. An alternative of the
  +
form
   
  +
<haskell>
 
pat -> exp where decls
 
pat -> exp where decls
  +
</haskell>
   
 
is treated as shorthand for:
 
is treated as shorthand for:
   
  +
<haskell>
 
pat | True -> exp
 
pat | True -> exp
where decls
+
where decls
  +
</haskell>
   
A case expression must have at least one alternative and each alternative must have at least one body. Each body must have the same type, and the type of the whole expression is that type.
+
A case expression must have at least one alternative and each
  +
alternative must have at least one body. Each body must have the same
  +
type, and the type of the whole expression is that type.
   
  +
A case expression is evaluated by pattern matching the expression <code>e</code>
A case expression is evaluated by pattern matching the expression e against the individual alternatives. The alternatives are tried sequentially, from top to bottom. If e matches the pattern in the alternative, the guards for that alternative are tried sequentially from top to bottom, in the environment of the case expression extended first by the bindings created during the matching of the pattern, and then by the declsi in the where clause associated with that alternative. If one of the guards evaluates to True, the corresponding right-hand side is evaluated in the same environment as the guard. If all the guards evaluate to False, matching continues with the next alternative. If no match succeeds, the result is _|_.
 
  +
against the individual alternatives. The alternatives are tried
  +
sequentially, from top to bottom. If <code>e</code> matches the pattern in the
  +
alternative, the guards for that alternative are tried sequentially from
  +
top to bottom, in the environment of the case expression extended first
  +
by the bindings created during the matching of the pattern, and then by
  +
the <code>decls</code><sub>i</sub>&nbsp; in the <code>where</code> clause associated with that alternative. If one
  +
of the guards evaluates to <code>True</code>, the corresponding right-hand side is
  +
evaluated in the same environment as the guard. If all the guards
  +
evaluate to <code>False</code>, matching continues with the next alternative. If no
  +
match succeeds, the result is _|_.
   
 
== class ==
 
== class ==
   
  +
A [http://haskell.org/onlinereport/decls.html#class-decls class declaration]
Please write this
 
  +
introduces a new type class and the overloaded operations that must be
  +
supported by any type that is an instance of that class.
  +
<haskell>
  +
class Num a where
  +
(+) :: a -> a -> a
  +
negate :: a -> a
  +
</haskell>
   
 
== data ==
 
== data ==
   
  +
The [http://haskell.org/onlinereport/decls.html#user-defined-datatypes data]
The <code>data</code> declaration is how one introduces new algebraic data [[type]]s into Haskell. As an example, to create a datatype to hold an [[Abstract syntax tree]] for an expression, one could use:
 
  +
declaration is how one introduces new algebraic data [[type]]s into
  +
Haskell. For example:
 
 
  +
<haskell>
data Exp = Ebin Operator Exp Exp |
 
  +
data Set a = NilSet
Eunary Operator Exp |
 
Efun FunctionIdentifier [Exp] |
+
| ConsSet a (Set a)
  +
</haskell>
Eid SimpleIdentifier
 
  +
  +
Another example, to create a datatype to hold an [[Abstract_syntax_tree|abstract syntax tree]] for an expression, one could use:
  +
  +
<haskell>
  +
data Exp = Ebin Operator Exp Exp
  +
| Eunary Operator Exp
  +
| Efun FunctionIdentifier [Exp]
  +
| Eid SimpleIdentifier
  +
</haskell>
   
 
where the [[type]]s <code>Operator, FunctionIdentifier</code> and <code>SimpleIdentifier</code> are defined elsewhere.
 
where the [[type]]s <code>Operator, FunctionIdentifier</code> and <code>SimpleIdentifier</code> are defined elsewhere.
   
 
See the page on [[type]]s for more information, links and examples.
 
See the page on [[type]]s for more information, links and examples.
  +
  +
== data family ==
  +
Declares a datatype family (see [[type families]]). GHC language extension.
  +
  +
== data instance ==
  +
Declares a datatype family instance (see [[type families]]). GHC language extension.
  +
   
 
== default ==
 
== default ==
   
  +
Ambiguities in the class Num are most common, so Haskell provides
Please write this
 
  +
a way to resolve them---with a default declaration:
  +
  +
<haskell>
  +
default (Int)
  +
</haskell>
  +
  +
Only one default declaration is permitted per module, and its effect is
  +
limited to that module. If no default declaration is given in a module
  +
then it assumed to be:
  +
  +
<haskell>
  +
default (Integer, Double)
  +
</haskell>
   
 
== deriving ==
 
== deriving ==
   
  +
data and newtype declarations contain an optional deriving form. If the
Please write this
 
  +
form is included, then derived instance declarations are automatically
  +
generated for the datatype in each of the named classes.
  +
  +
[http://haskell.org/onlinereport/decls.html#derived-decls Derived instances] provide convenient commonly-used operations for user-defined
  +
datatypes. For example, derived instances for datatypes in the class Eq
  +
define the operations == and /=, freeing the programmer from the need to
  +
define them.
  +
  +
<haskell>
  +
data T = A
  +
| B
  +
| C
  +
deriving (Eq, Ord, Show)
  +
</haskell>
  +
  +
In the case of newtypes, GHC extends this mechanism to [[Cunning Newtype Deriving]].
  +
  +
== deriving instance ==
  +
  +
Standalone deriving (GHC language extension).
  +
  +
<haskell>
  +
{-# LANGUAGE StandaloneDeriving #-}
  +
data A = A
  +
  +
deriving instance Show A
  +
</haskell>
   
 
== do ==
 
== do ==
Line 122: Line 513:
 
Syntactic sugar for use with monadic expressions. For example:
 
Syntactic sugar for use with monadic expressions. For example:
   
  +
<haskell>
 
do { x ; result <- y ; foo result }
 
do { x ; result <- y ; foo result }
  +
</haskell>
   
 
is shorthand for:
 
is shorthand for:
   
  +
<haskell>
 
x >>
 
x >>
 
y >>= \result ->
 
y >>= \result ->
 
foo result
 
foo result
  +
</haskell>
   
 
== forall ==
 
== forall ==
   
This is a GHC/Hugs extension, and as such is not portable Haskell 98.
+
This is a GHC/Hugs extension, and as such is not portable Haskell 98/2010.
  +
It is only a reserved word within types.
  +
  +
Type variables in a Haskell type expression are all assumed to be
  +
universally quantified; there is no explicit syntax for universal
  +
quantification, in standard Haskell 98/2010. For example, the type expression
  +
<hask>a -> a</hask> denotes the type <hask>forall a. a ->a</hask>.
  +
For clarity, however, we often write quantification explicitly when
  +
discussing the types of Haskell programs. When we write an explicitly
  +
quantified type, the scope of the forall extends as far to the right as
  +
possible; for example,
  +
<haskell>
  +
forall a. a -> a
  +
</haskell>
  +
means
  +
<haskell>
  +
forall a. (a -> a)
  +
</haskell>
  +
  +
GHC [http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html#type-synonyms introduces] a <hask>forall</hask> keyword, allowing explicit quantification, for example, to encode
  +
[http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html#existential-quantification existential types]:
  +
<haskell>
  +
data Foo = forall a. MkFoo a (a -> Bool)
  +
| Nil
  +
  +
MkFoo :: forall a. a -> (a -> Bool) -> Foo
  +
Nil :: Foo
  +
  +
[MkFoo 3 even, MkFoo 'c' isUpper] :: [Foo]
  +
</haskell>
  +
  +
== foreign ==
  +
  +
A keyword for the [[Foreign Function Interface]] (commonly called the FFI) that introduces either a <hask>foreign import</hask> declaration, which makes a function from a non-Haskell library available in a Haskell program, or a <hask>foreign export</hask> declaration, which allows a function from a Haskell module to be called in non-Haskell contexts.
   
 
== hiding ==
 
== hiding ==
   
  +
When importing modules, without introducing a name into scope, entities can be excluded by using the form
Please write this
 
  +
<haskell>
  +
hiding (import1 , ... , importn )
  +
</haskell>
  +
which specifies that all entities exported by the named module should be
  +
imported except for those named in the list.
  +
  +
For example:
  +
<haskell>
  +
import Prelude hiding (lookup,filter,foldr,foldl,null,map)
  +
</haskell>
   
== if, then, else ==
+
== <span id="if">if</span>, <span id="then">then</span>, <span id="else">else</span> ==
   
 
A conditional expression has the form:
 
A conditional expression has the form:
   
  +
<haskell>
 
if e1 then e2 else e3
 
if e1 then e2 else e3
  +
</haskell>
   
...and returns the value of e2 if the value of e1 is True, e3 if e1 is False, and _|_ otherwise.
+
and returns the value of e2 if the value of e1 is True, e3 if e1 is False, and _|_ otherwise.
   
  +
<haskell>
 
max a b = if a > b then a else b
 
max a b = if a > b then a else b
  +
</haskell>
   
 
== import ==
 
== import ==
   
  +
[http://haskell.org/onlinereport/modules.html Modules] may reference
Please write this
 
  +
other modules via explicit import declarations, each giving the name of
  +
a module to be imported and specifying its entities to be imported.
   
  +
For example:
== infix, infixl, infixr ==
 
  +
<haskell>
  +
module Main where
  +
import A
  +
import B
  +
main = A.f >> B.f
   
  +
module A where
Please write this
 
  +
f = ...
  +
  +
module B where
  +
f = ...
  +
</haskell>
  +
  +
See also [[#as | as]], [[#hiding | hiding]] , [[#qualified | qualified]] and the page [[Import]]
  +
  +
== <span id="infix">infix</span>, <span id="infixl">infixl</span>, <span id="infixr">infixr</span> ==
  +
  +
A [http://haskell.org/onlinereport/decls.html fixity declaration] gives
  +
the fixity and binding precedence of one or more operators. The integer
  +
in a fixity declaration must be in the range 0 to 9. A fixity
  +
declaration may appear anywhere that a [[type signature]] appears and, like
  +
a type signature, declares a property of a particular operator.
  +
  +
There are three kinds of fixity, non-, left- and right-associativity
  +
(infix, infixl, and infixr, respectively), and ten precedence levels, 0
  +
to 9 inclusive (level 0 binds least tightly, and level 9 binds most
  +
tightly).
  +
  +
<haskell>
  +
module Bar where
  +
infixr 7 `op`
  +
op = ...
  +
</haskell>
   
 
== instance ==
 
== instance ==
   
  +
An instance declaration declares that a type is an instance of a class
Please write this
 
  +
and includes the definitions of the overloaded operations - called class
  +
methods - instantiated on the named type.
   
  +
<haskell>
== let, in ==
 
  +
instance Num Int where
  +
x + y = addInt x y
  +
negate x = negateInt x
  +
</haskell>
  +
  +
== <span id="let">let</span>, <span id="in">in</span> ==
   
 
Let expressions have the general form:
 
Let expressions have the general form:
   
let { d1 ; ... ; dn } in e
+
<haskell>let { d1 ; ... ; dn } in e</haskell>
   
 
They introduce a nested, lexically-scoped, mutually-recursive list of declarations (let is often called letrec in other languages). The scope of the declarations is the expression e and the right hand side of the declarations.
 
They introduce a nested, lexically-scoped, mutually-recursive list of declarations (let is often called letrec in other languages). The scope of the declarations is the expression e and the right hand side of the declarations.
  +
  +
Within <hask>do</hask>-blocks or list comprehensions <hask>let { d1 ; ... ; dn }</hask> without <hask>in</hask> serves to introduce local bindings.
  +
  +
== [http://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#the-mdo-notation mdo] ==
  +
  +
The recursive <hask>do</hask> keyword enabled by -fglasgow-exts.
   
 
== module ==
 
== module ==
   
  +
Taken from: [http://www.haskell.org/tutorial/modules.html A Gentle Introduction to Haskell, Version 98]
Please write this
 
  +
  +
Technically speaking, a module is really just one big declaration which begins with the keyword module; here's an example for a module whose name is Tree:
  +
  +
<haskell>
  +
module Tree ( Tree(Leaf,Branch), fringe ) where
  +
  +
data Tree a = Leaf a | Branch (Tree a) (Tree a)
  +
  +
fringe :: Tree a -> [a]
  +
fringe (Leaf x) = [x]
  +
fringe (Branch left right) = fringe left ++ fringe right
  +
</haskell>
   
 
== newtype ==
 
== newtype ==
Line 180: Line 681:
 
newtype FunctionIdentifier = FunctionIdentifier Identifier
 
newtype FunctionIdentifier = FunctionIdentifier Identifier
   
Most often, one supplies [[smart constructors]] and [[destructor]]s for these to ease working with them.
+
Most often, one supplies [[smart constructors]] and [[smart destructors|destructors]] for these to ease working with them.
   
 
See the page on [[type]]s for more information, links and examples.
 
See the page on [[type]]s for more information, links and examples.
  +
  +
For the differences between <code>newtype</code> and <code>data</code>, see [[Newtype]].
  +
  +
== proc ==
  +
proc (arrow abstraction)
  +
is a kind of lambda, except that it constructs an arrow instead of a function.
  +
  +
[[Arrow notation]]
   
 
== qualified ==
 
== qualified ==
   
  +
Used to import a module, but not introduce a name into scope. For example, Data.Map exports lookup, which would clash with the Prelude version of lookup, to fix this:
Please write this
 
  +
  +
<haskell>
  +
import qualified Data.Map
  +
  +
f x = lookup x -- use the Prelude version
  +
g x = Data.Map.lookup x -- use the Data.Map version
  +
</haskell>
  +
  +
Of course, Data.Map is a bit of a mouthful, so qualified also allows the use of as.
  +
  +
<haskell>
  +
import qualified Data.Map as M
  +
  +
f x = lookup x -- use Prelude version
  +
g x = M.lookup x -- use Data.Map version
  +
</haskell>
  +
  +
== rec ==
  +
The [http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#mdo-notation rec] keyword can be used when the <code>-XDoRec</code> flag is given; it allows recursive bindings in a do-block.
  +
  +
<haskell>
  +
{-# LANGUAGE DoRec #-}
  +
justOnes = do { rec { xs <- Just (1:xs) }
  +
; return (map negate xs) }
  +
</haskell>
   
 
== type ==
 
== type ==
Line 192: Line 726:
 
The <code>type</code> declaration is how one introduces an alias for an algebraic data [[type]] into Haskell. As an example, when writing a compiler
 
The <code>type</code> declaration is how one introduces an alias for an algebraic data [[type]] into Haskell. As an example, when writing a compiler
 
one often creates an alias for identifiers:
 
one often creates an alias for identifiers:
  +
 
  +
<haskell>
type Identifier = String
 
  +
type Identifier = String
  +
</haskell>
   
 
This allows you to use <code>Identifer</code> wherever you had used <code>String</code> and if something is of type <code>Identifier</code> it
 
This allows you to use <code>Identifer</code> wherever you had used <code>String</code> and if something is of type <code>Identifier</code> it
Line 199: Line 735:
   
 
See the page on [[type]]s for more information, links and examples.
 
See the page on [[type]]s for more information, links and examples.
  +
  +
Some common <code>type</code> declarations in the Prelude include:
  +
  +
<haskell>
  +
type FilePath = String
  +
type String = [Char]
  +
type Rational = Ratio Integer
  +
type ReadS a = String -> [(a,String)]
  +
type ShowS = String -> String
  +
</haskell>
  +
  +
== type family ==
  +
Declares a type synonym family (see [[type families]]). GHC language extension.
  +
  +
== type instance ==
  +
Declares a type synonym family instance (see [[type families]]). GHC language extension.
  +
  +
   
 
== where ==
 
== where ==
   
  +
Used to introduce a module, instance, class or [[GADT]]:
Please write this
 
  +
<haskell>
  +
module Main where
  +
  +
class Num a where
  +
...
  +
  +
instance Num Int where
  +
...
  +
  +
data Something a where
  +
...
  +
</haskell>
  +
  +
And to bind local variables:
  +
<haskell>
  +
f x = y
  +
where y = x * 2
  +
  +
g z | z > 2 = y
  +
where y = x * 2
  +
</haskell>
   
   

Revision as of 22:06, 1 November 2016

This page lists all Haskell keywords, feel free to edit. Hoogle searches will return results from this page. Please respect the Anchor macros.

For additional information you might want to look at the Haskell 2010 report.

!

Whenever a data constructor is applied, each argument to the constructor is evaluated if and only if the corresponding type in the algebraic datatype declaration has a strictness flag, denoted by an exclamation point. For example:

 data STList a 
         = STCons a !(STList a)  -- the second argument to STCons will be 
                                 -- evaluated before STCons is applied
         | STNil

to illustrate the difference between strict versus lazy constructor application, consider the following:

 stList = STCons 1 undefined
 lzList = (:)    1 undefined
 stHead (STCons h _) = h -- this evaluates to undefined when applied to stList
 lzHead (h : _)      = h -- this evaluates to 1 when applied to lzList

! is also used in the "bang patterns" (GHC extension), to indicate strictness in patterns:

f !x !y = x + y

'

  • Character literal: 'a'
  • Template Haskell: Name of a (value) variable or data constructor: 'length, 'Left
  • (in types, GHC specific) Promoted data constructor: 'True

''

-

This operator token is magic/irregular in the sense that

(- 1)

is parsed as the negative integer -1, rather than as an operator section, as it would be for any other operator:

(* 1) :: Num a => a -> a
(++ "foo") :: String -> String

It is syntactic sugar for the negate function in Prelude. See unary operator. If you want the section, you can use the subtract function or (+(-1)).

--

Starts a single-line comment, unless immediately followed by an operator character other than -:

main = print "hello world" -- this is a comment
--this is a comment as well
---this too
foobar --+ this_is_the_second_argument_of_the_dash_dash_plus_operator

The multi-line variant for comments is {- comment -}.

-<

Arrow notation

-<<

Arrow notation


->

  • The function type constructor:
length :: [a] -> Int
  • In lambda functions:
\x -> x + 1
  • To denote alternatives in case statements:
case Just 3 of
    Nothing -> False
    Just x  -> True
  • On the kind level (GHC specific):
ghci> :kind (->)
(->) :: * -> * -> *
-- This examples assumes that each type 'c' can "contain" only one type
--  i.e. type 'c' uniquely determines type 'elt'
class Contains c elt | c -> elt where
   ...

::

Read as "has type":

length :: [a] -> Int

"Length has type list-of-'a' to Int"

Or "has kind" (GHC specific):

Either :: * -> * -> *

;

  • Statement separator in an explicit block (see layout)

<-

  • In do-notation, "draw from":
do x <- getChar
   putChar x
  • In list comprehension generators, "in":
[ (x,y) | x <- [1..10], y <- ['a'..'z'] ]
f x y | Just z <- g x = True
      | otherwise     = False

,

In list comprehensions, "and":

[ (x,y) | x <- [1..10], y <- ['a'..'z'], x > 42 ]

=

Used in definitions.

x = 4

=>

Used to indicate instance contexts, for example:

sort :: Ord a => [a] -> [a]

>

In a Bird's style Literate Haskell file, the > character is used to introduce a code line.

comment line

> main = print "hello world"

?

ghci> :t ?foo ++ "bar"
?foo ++ "bar" :: (?foo::[Char]) => [Char]

#

*

  • Is an ordinary operator name on the value level
  • On the kind level: The kind of boxed types (GHC-specific)
ghci> :kind Int
Int :: *

@

Patterns of the form var@pat are called as-patterns, and allow one to use var as a name for the value being matched by pat. For example:

 case e of { xs@(x:rest) -> if x==0 then rest else xs }

is equivalent to:

 let { xs = e } in
   case xs of { (x:rest) -> if x==0 then rest else xs }

[|, |]

  • Template Haskell
    • Expression quotation: [| print 1 |]
    • Declaration quotation: [d| main = print 1 |]
    • Type quotation: [t| Either Int () |]
    • Pattern quotation: [p| (x,y) |]
    • Quasiquotation: [nameOfQuasiQuoter| ... |]

\

The backslash "\" is used

  • in multiline strings
"foo\
  \bar"
  • in lambda functions
\x -> x + 1


_

Patterns of the form _ are wildcards and are useful when some part of a pattern is not referenced on the right-hand-side. It is as if an identifier not used elsewhere were put in its place. For example,

 case e of { [x,_,_]  ->  if x==0 then True else False }

is equivalent to:

 case e of { [x,y,z]  ->  if x==0 then True else False }



`

A function enclosed in back ticks "`" can be used as an infix operator.

2 `subtract` 10

is the same as

subtract 2 10

{, }

  • Explicit block (disable layout), possibly with ";" .
  • Record update notation
changePrice :: Thing -> Price -> Thing
changePrice x new = x { price = new }
  • Comments (see below)

{-, -}

Everything between "{-" followed by a space and "-}" is a block comment.

{-
hello
world
-}

|

The "pipe" is used in several places

  • Data type definitions, "or"
data Maybe a = Just a | Nothing
  • List comprehensions, "for" (as in, "list of a*a for a in [1..])
squares = [a*a | a <- [1..]]
  • Guards, "when"
safeTail x | null x    = []
           | otherwise = tail x
class Contains c elt | c -> elt where
   ...

~

  • Lazy pattern bindings. Matching the pattern ~pat against a value always

succeeds, and matching will only diverge when one of the variables bound in the pattern is used.

f1, f2 :: Maybe Int -> String
f1 x = case x of 
    Just n -> "Got it"
f2 x = case x of
    ~(Just n) -> "Got it"

(+++), (++++) :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) 
(f +++ g) ~(x, y) = (f x, g y)
(f ++++ g) (x, y) = (f x, g y)

Then we have:

f1 Nothing
Exception: Non-exhaustive patterns in case

f2 Nothing
"Got it"

(const 1 +++ const 2) undefined
(1,2)

(const 1 ++++ const 2) undefined
Exception: Prelude.undefined

For more details see the Haskell Wikibook.

  • Equality constraints. Assert that two types in a context must be the same:
example :: F a ~ b => a -> b

Here the type "F a" must be the same as the type "b", which allows one to constrain polymorphism (especially where type families are involved), but to a lesser extent than functional dependencies. See Type Families.

as

Renaming module imports. Like qualified and hiding, as is not a reserved word but may be used as function or variable name.

import qualified Data.Map as M

main = print (M.empty :: M.Map Int ())

case, of

A case expression has the general form

 case e of { p1 match1 ; ... ; pn matchn }

where each matchi is of the general form

| g1 -> e1
  ...
| gm -> em
    where decls

Each alternative consists of patterns pi and their matches, matchi. Each matchi in turn consists of a sequence of pairs of guards gij and bodies eij (expressions), followed by optional bindings (declsi) that scope over all of the guards and expressions of the alternative. An alternative of the form

 pat -> exp where decls

is treated as shorthand for:

  pat | True -> exp
    where decls

A case expression must have at least one alternative and each alternative must have at least one body. Each body must have the same type, and the type of the whole expression is that type.

A case expression is evaluated by pattern matching the expression e against the individual alternatives. The alternatives are tried sequentially, from top to bottom. If e matches the pattern in the alternative, the guards for that alternative are tried sequentially from top to bottom, in the environment of the case expression extended first by the bindings created during the matching of the pattern, and then by the declsi  in the where clause associated with that alternative. If one of the guards evaluates to True, the corresponding right-hand side is evaluated in the same environment as the guard. If all the guards evaluate to False, matching continues with the next alternative. If no match succeeds, the result is _|_.

class

A class declaration introduces a new type class and the overloaded operations that must be supported by any type that is an instance of that class.

  class Num a  where
    (+)    :: a -> a -> a
    negate :: a -> a

data

The data declaration is how one introduces new algebraic data types into Haskell. For example:

data Set a = NilSet 
           | ConsSet a (Set a)

Another example, to create a datatype to hold an abstract syntax tree for an expression, one could use:

 data Exp = Ebin   Operator Exp Exp 
          | Eunary Operator Exp 
          | Efun   FunctionIdentifier [Exp] 
          | Eid    SimpleIdentifier

where the types Operator, FunctionIdentifier and SimpleIdentifier are defined elsewhere.

See the page on types for more information, links and examples.

data family

Declares a datatype family (see type families). GHC language extension.

data instance

Declares a datatype family instance (see type families). GHC language extension.


default

Ambiguities in the class Num are most common, so Haskell provides a way to resolve them---with a default declaration:

default (Int)

Only one default declaration is permitted per module, and its effect is limited to that module. If no default declaration is given in a module then it assumed to be:

  default (Integer, Double)

deriving

data and newtype declarations contain an optional deriving form. If the form is included, then derived instance declarations are automatically generated for the datatype in each of the named classes.

Derived instances provide convenient commonly-used operations for user-defined datatypes. For example, derived instances for datatypes in the class Eq define the operations == and /=, freeing the programmer from the need to define them.

data T = A
       | B
       | C
       deriving (Eq, Ord, Show)

In the case of newtypes, GHC extends this mechanism to Cunning Newtype Deriving.

deriving instance

Standalone deriving (GHC language extension).

{-# LANGUAGE StandaloneDeriving #-}
data A = A

deriving instance Show A

do

Syntactic sugar for use with monadic expressions. For example:

 do { x ; result <- y ; foo result }

is shorthand for:

 x >> 
 y >>= \result ->
 foo result

forall

This is a GHC/Hugs extension, and as such is not portable Haskell 98/2010. It is only a reserved word within types.

Type variables in a Haskell type expression are all assumed to be universally quantified; there is no explicit syntax for universal quantification, in standard Haskell 98/2010. For example, the type expression a -> a denotes the type forall a. a ->a. For clarity, however, we often write quantification explicitly when discussing the types of Haskell programs. When we write an explicitly quantified type, the scope of the forall extends as far to the right as possible; for example,

forall a. a -> a

means

forall a. (a -> a)

GHC introduces a forall keyword, allowing explicit quantification, for example, to encode existential types:

data Foo = forall a. MkFoo a (a -> Bool)
         | Nil

MkFoo :: forall a. a -> (a -> Bool) -> Foo
Nil   :: Foo

[MkFoo 3 even, MkFoo 'c' isUpper] :: [Foo]

foreign

A keyword for the Foreign Function Interface (commonly called the FFI) that introduces either a foreign import declaration, which makes a function from a non-Haskell library available in a Haskell program, or a foreign export declaration, which allows a function from a Haskell module to be called in non-Haskell contexts.

hiding

When importing modules, without introducing a name into scope, entities can be excluded by using the form

hiding (import1 , ... , importn )

which specifies that all entities exported by the named module should be imported except for those named in the list.

For example:

import Prelude hiding (lookup,filter,foldr,foldl,null,map)

if, then, else

A conditional expression has the form:

 if e1 then e2 else e3

and returns the value of e2 if the value of e1 is True, e3 if e1 is False, and _|_ otherwise.

 max a b = if a > b then a else b

import

Modules may reference other modules via explicit import declarations, each giving the name of a module to be imported and specifying its entities to be imported.

For example:

  module Main where
    import A
    import B
    main = A.f >> B.f

  module A where
    f = ...

  module B where
    f = ...

See also as, hiding , qualified and the page Import

infix, infixl, infixr

A fixity declaration gives the fixity and binding precedence of one or more operators. The integer in a fixity declaration must be in the range 0 to 9. A fixity declaration may appear anywhere that a type signature appears and, like a type signature, declares a property of a particular operator.

There are three kinds of fixity, non-, left- and right-associativity (infix, infixl, and infixr, respectively), and ten precedence levels, 0 to 9 inclusive (level 0 binds least tightly, and level 9 binds most tightly).

  module Bar where
    infixr 7 `op`
    op = ...

instance

An instance declaration declares that a type is an instance of a class and includes the definitions of the overloaded operations - called class methods - instantiated on the named type.

  instance Num Int  where
    x + y       =  addInt x y
    negate x    =  negateInt x

let, in

Let expressions have the general form:

let { d1 ; ... ; dn } in e

They introduce a nested, lexically-scoped, mutually-recursive list of declarations (let is often called letrec in other languages). The scope of the declarations is the expression e and the right hand side of the declarations.

Within do-blocks or list comprehensions let { d1 ; ... ; dn } without in serves to introduce local bindings.

mdo

The recursive do keyword enabled by -fglasgow-exts.

module

Taken from: A Gentle Introduction to Haskell, Version 98

Technically speaking, a module is really just one big declaration which begins with the keyword module; here's an example for a module whose name is Tree:

module Tree ( Tree(Leaf,Branch), fringe ) where

data Tree a                = Leaf a | Branch (Tree a) (Tree a) 

fringe :: Tree a -> [a]
fringe (Leaf x)            = [x]
fringe (Branch left right) = fringe left ++ fringe right

newtype

The newtype declaration is how one introduces a renaming for an algebraic data type into Haskell. This is different from type below, as a newtype requires a new constructor as well. As an example, when writing a compiler one sometimes further qualifies Identifiers to assist in type safety checks:

newtype SimpleIdentifier = SimpleIdentifier Identifier
newtype FunctionIdentifier = FunctionIdentifier Identifier

Most often, one supplies smart constructors and destructors for these to ease working with them.

See the page on types for more information, links and examples.

For the differences between newtype and data, see Newtype.

proc

proc (arrow abstraction) is a kind of lambda, except that it constructs an arrow instead of a function.

Arrow notation

qualified

Used to import a module, but not introduce a name into scope. For example, Data.Map exports lookup, which would clash with the Prelude version of lookup, to fix this:

import qualified Data.Map

f x = lookup x -- use the Prelude version
g x = Data.Map.lookup x -- use the Data.Map version

Of course, Data.Map is a bit of a mouthful, so qualified also allows the use of as.

import qualified Data.Map as M

f x = lookup x -- use Prelude version
g x = M.lookup x -- use Data.Map version

rec

The rec keyword can be used when the -XDoRec flag is given; it allows recursive bindings in a do-block.

{-# LANGUAGE DoRec #-}
justOnes = do { rec { xs <- Just (1:xs) }
              ; return (map negate xs) }

type

The type declaration is how one introduces an alias for an algebraic data type into Haskell. As an example, when writing a compiler one often creates an alias for identifiers:

type Identifier = String

This allows you to use Identifer wherever you had used String and if something is of type Identifier it may be used wherever a String is expected.

See the page on types for more information, links and examples.

Some common type declarations in the Prelude include:

type FilePath = String
type String = [Char]
type Rational = Ratio Integer
type ReadS a = String -> [(a,String)]
type ShowS = String -> String

type family

Declares a type synonym family (see type families). GHC language extension.

type instance

Declares a type synonym family instance (see type families). GHC language extension.


where

Used to introduce a module, instance, class or GADT:

module Main where

class Num a where
    ...

instance Num Int  where
    ...

data Something a where
   ...

And to bind local variables:

f x = y
    where y = x * 2

g z | z > 2 = y
    where y = x * 2