</sect2>
+ <!-- ===================== Pattern synonyms =================== -->
+
+<sect2 id="pattern-synonyms">
+<title>Pattern synonyms
+</title>
+
+<para>
+Pattern synonyms are enabled by the flag
+<literal>-XPatternSynonyms</literal>, which is required for both
+defining them <emphasis>and</emphasis> using them. More information
+and examples of view patterns can be found on the <ulink
+url="http://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms">Wiki
+page</ulink>.
+</para>
+
+<para>
+Pattern synonyms enable giving names to parametrized pattern
+schemes. They can also be thought of as abstract constructors that
+don't have a bearing on data representation. For example, in a
+programming language implementation, we might represent types of the
+language as follows:
+</para>
+
+<programlisting>
+data Type = App String [Type]
+</programlisting>
+
+<para>
+Here are some examples of using said representation.
+Consider a few types of the <literal>Type</literal> universe encoded
+like this:
+</para>
+
+<programlisting>
+ App "->" [t1, t2] -- t1 -> t2
+ App "Int" [] -- Int
+ App "Maybe" [App "Int" []] -- Maybe Int
+</programlisting>
+
+<para>
+This representation is very generic in that no types are given special
+treatment. However, some functions might need to handle some known
+types specially, for example the following two functions collect all
+argument types of (nested) arrow types, and recognize the
+<literal>Int</literal> type, respectively:
+</para>
+
+<programlisting>
+ collectArgs :: Type -> [Type]
+ collectArgs (App "->" [t1, t2]) = t1 : collectArgs t2
+ collectArgs _ = []
+
+ isInt :: Type -> Bool
+ isInt (App "Int" []) = True
+ isInt _ = False
+</programlisting>
+
+<para>
+Matching on <literal>App</literal> directly is both hard to read and
+error prone to write. And the situation is even worse when the
+matching is nested:
+</para>
+
+<programlisting>
+ isIntEndo :: Type -> Bool
+ isIntEndo (App "->" [App "Int" [], App "Int" []]) = True
+ isIntEndo _ = False
+</programlisting>
+
+<para>
+Pattern synonyms permit abstracting from the representation to expose
+matchers that behave in a constructor-like manner with respect to
+pattern matching. We can create pattern synonyms for the known types
+we care about, without committing the representation to them (note
+that these don't have to be defined in the same module as the
+<literal>Type</literal> type):
+</para>
+
+<programlisting>
+ pattern Arrow t1 t2 = App "->" [t1, t2]
+ pattern Int = App "Int" []
+ pattern Maybe t = App "Maybe" [t]
+</programlisting>
+
+<para>
+Which enables us to rewrite our functions in a much cleaner style:
+</para>
+
+<programlisting>
+ collectArgs :: Type -> [Type]
+ collectArgs (Arrow t1 t2) = t1 : collectArgs t2
+ collectArgs _ = []
+
+ isInt :: Type -> Bool
+ isInt Int = True
+ isInt _ = False
+
+ isIntEndo :: Type -> Bool
+ isIntEndo (Arrow Int Int) = True
+ isIntEndo _ = False
+</programlisting>
+
+<para>
+ Note that in this example, the pattern synonyms
+ <literal>Int</literal> and <literal>Arrow</literal> can also be used
+ as expressions (they are <emphasis>bidirectional</emphasis>). This
+ is not necessarily the case: <emphasis>unidirectional</emphasis>
+ pattern synonyms can also be declared with the following syntax:
+</para>
+
+<programlisting>
+ pattern Head x <- x:xs
+</programlisting>
+
+<para>
+In this case, <literal>Head</literal> <replaceable>x</replaceable>
+cannot be used in expressions, only patterns, since it wouldn't
+specify a value for the <replaceable>xs</replaceable> on the
+right-hand side.
+</para>
+
+<para>
+The semantics of a unidirectional pattern synonym declaration and
+usage are as follows:
+
+<itemizedlist>
+
+<listitem> Syntax:
+<para>
+A pattern synonym declaration can be either unidirectional or
+bidirectional. The syntax for unidirectional pattern synonyms is:
+</para>
+<programlisting>
+ pattern Name args <- pat
+</programlisting>
+<para>
+ and the syntax for bidirectional pattern synonyms is:
+</para>
+<programlisting>
+ pattern Name args = pat
+</programlisting>
+<para>
+ Pattern synonym declarations can only occur in the top level of a
+ module. In particular, they are not allowed as local
+ definitions. Currently, they also don't work in GHCi, but that is a
+ technical restriction that will be lifted in later versions.
+</para>
+<para>
+ The name of the pattern synonym itself is in the same namespace as
+ proper data constructors. Either prefix or infix syntax can be
+ used. In export/import specifications, you have to prefix pattern
+ names with the <literal>pattern</literal> keyword, e.g.:
+</para>
+<programlisting>
+ module Example (pattern Single) where
+ pattern Single x = [x]
+</programlisting>
+</listitem>
+
+<listitem> Scoping:
+
+<para>
+ The variables in the left-hand side of the definition are bound by
+ the pattern on the right-hand side. For bidirectional pattern
+ synonyms, all the variables of the right-hand side must also occur
+ on the left-hand side; also, wildcard patterns and view patterns are
+ not allowed. For unidirectional pattern synonyms, there is no
+ restriction on the right-hand side pattern.
+</para>
+
+<para>
+ Pattern synonyms cannot be defined recursively.
+</para>
+
+</listitem>
+
+<listitem> Typing:
+
+<para>
+ Given a pattern synonym definition of the form
+</para>
+<programlisting>
+ pattern P var1 var2 ... varN <- pat
+</programlisting>
+<para>
+ it is assigned a <emphasis>pattern type</emphasis> of the form
+</para>
+<programlisting>
+ pattern CProv => P t1 t2 ... tN :: CReq => t
+</programlisting>
+<para>
+ where <replaceable>CProv</replaceable> and
+ <replaceable>CReq</replaceable> are type contexts, and
+ <replaceable>t1</replaceable>, <replaceable>t2</replaceable>, ...,
+ <replaceable>tN</replaceable> and <replaceable>t</replaceable> are
+ types.
+</para>
+
+<para>
+A pattern synonym of this type can be used in a pattern if the
+instatiated (monomorphic) type satisfies the constraints of
+<replaceable>CReq</replaceable>. In this case, it extends the context
+available in the right-hand side of the match with
+<replaceable>CProv</replaceable>, just like how an existentially-typed
+data constructor can extend the context.
+</para>
+
+<para>
+For example, in the following program:
+</para>
+<programlisting>
+{-# LANGUAGE PatternSynonyms, GADTs #-}
+module ShouldCompile where
+
+data T a where
+ MkT :: (Show b) => a -> b -> T a
+
+pattern ExNumPat x = MkT 42 x
+</programlisting>
+
+<para>
+the pattern type of <literal>ExNumPat</literal> is
+</para>
+
+<programlisting>
+pattern (Show b) => ExNumPat b :: (Num a, Eq a) => T a
+</programlisting>
+
+<para>
+ and so can be used in a function definition like the following:
+</para>
+
+<programlisting>
+ f :: (Num t, Eq t) => T t -> String
+ f (ExNumPat x) = show x
+</programlisting>
+
+<para>
+ For bidirectional pattern synonyms, uses as expressions have the type
+</para>
+<programlisting>
+ (CProv, CReq) => t1 -> t2 -> ... -> tN -> t
+</programlisting>
+
+<para>
+ So in the previous example, <literal>ExNumPat</literal>,
+ when used in an expression, has type
+</para>
+<programlisting>
+ ExNumPat :: (Show b, Num a, Eq a) => b -> T t
+</programlisting>
+
+</listitem>
+
+<listitem> Matching:
+
+<para>
+A pattern synonym occurrence in a pattern is evaluated by first
+matching against the pattern synonym itself, and then on the argument
+patterns. For example, in the following program, <literal>f</literal>
+and <literal>f'</literal> are equivalent:
+</para>
+
+<programlisting>
+pattern Pair x y <- [x, y]
+
+f (Pair True True) = True
+f _ = False
+
+f' [x, y] | True <- x, True <- y = True
+f' _ = False
+</programlisting>
+
+<para>
+ Note that the strictness of <literal>f</literal> differs from that
+ of <literal>g</literal> defined below:
+</para>
+
+<programlisting>
+g [True, True] = True
+g _ = False
+
+*Main> f (False:undefined)
+*** Exception: Prelude.undefined
+*Main> g (False:undefined)
+False
+</programlisting>
+</listitem>
+</itemizedlist>
+</para>
+
+</sect2>
+
<!-- ===================== n+k patterns =================== -->
<sect2 id="n-k-patterns">
Stolen by: <option>-XBangPatterns</option>
</para></listitem>
</varlistentry>
+
+ <varlistentry>
+ <term>
+ <literal>pattern</literal>
+ </term>
+ <listitem><para>
+ Stolen by: <option>-XPatternSynonyms</option>
+ </para></listitem>
+ </varlistentry>
</variablelist>
</para>
</sect2>
</programlisting>
The syntax is identical to that of an ordinary instance declaration apart from (a) the keyword
<literal>deriving</literal>, and (b) the absence of the <literal>where</literal> part.
-Note the following points:
+</para>
+<para>
+However, standalone deriving differs from a <literal>deriving</literal> clause in a number
+of important ways:
<itemizedlist>
+<listitem><para>The standalone deriving declaration does not need to be in the
+same module as the data type declaration. (But be aware of the dangers of
+orphan instances (<xref linkend="orphan-modules"/>).
+</para></listitem>
+
<listitem><para>
You must supply an explicit context (in the example the context is <literal>(Eq a)</literal>),
exactly as you would in an ordinary instance declaration.
</para></listitem>
<listitem><para>
-A <literal>deriving instance</literal> declaration
-must obey the same rules concerning form and termination as ordinary instance declarations,
-controlled by the same flags; see <xref linkend="instance-decls"/>.
-</para></listitem>
-
-<listitem><para>
Unlike a <literal>deriving</literal>
declaration attached to a <literal>data</literal> declaration, the instance can be more specific
than the data type (assuming you also use
GHC does not restrict the form of the data type. Instead, GHC simply generates the appropriate
boilerplate code for the specified class, and typechecks it. If there is a type error, it is
your problem. (GHC will show you the offending code if it has a type error.)
+</para>
+<para>
The merit of this is that you can derive instances for GADTs and other exotic
data types, providing only that the boilerplate code does indeed typecheck. For example:
<programlisting>
because <literal>T</literal> is a GADT, but you <emphasis>can</emphasis> generate
the instance declaration using stand-alone deriving.
</para>
+<para>
+The down-side is that,
+if the boilerplate code fails to typecheck, you will get an error message about that
+code, which you did not write. Whereas, with a <literal>deriving</literal> clause
+the side-conditions are necessarily more conservative, but any error message
+may be more comprehensible.
+</para>
</listitem>
+</itemizedlist></para>
+
+<para>
+In other ways, however, a standalone deriving obeys the same rules as ordinary deriving:
+<itemizedlist>
+<listitem><para>
+A <literal>deriving instance</literal> declaration
+must obey the same rules concerning form and termination as ordinary instance declarations,
+controlled by the same flags; see <xref linkend="instance-decls"/>.
+</para></listitem>
<listitem>
<para>The stand-alone syntax is generalised for newtypes in exactly the same
</sect2>
-
-<sect2 id="deriving-typeable">
-<title>Deriving clause for extra classes (<literal>Typeable</literal>, <literal>Data</literal>, etc)</title>
+<sect2 id="deriving-extra">
+<title>Deriving instances of extra classes (<literal>Data</literal>, etc)</title>
<para>
Haskell 98 allows the programmer to add "<literal>deriving( Eq, Ord )</literal>" to a data type
<para>
GHC extends this list with several more classes that may be automatically derived:
<itemizedlist>
-<listitem><para> With <option>-XDeriveDataTypeable</option>, you can derive instances of the classes
-<literal>Typeable</literal>, and <literal>Data</literal>, defined in the library
-modules <literal>Data.Typeable</literal> and <literal>Data.Data</literal> respectively.
-</para>
-<para>Since GHC 7.8.1, <literal>Typeable</literal> is kind-polymorphic (see
-<xref linkend="kind-polymorphism"/>) and can be derived for any datatype and
-type class. Instances for datatypes can be derived by attaching a
-<literal>deriving Typeable</literal> clause to the datatype declaration, or by
-using standalone deriving (see <xref linkend="stand-alone-deriving"/>).
-Instances for type classes can only be derived using standalone deriving.
-For data families, <literal>Typeable</literal> should only be derived for the
-uninstantiated family type; each instance will then automatically have a
-<literal>Typeable</literal> instance too.
-See also <xref linkend="auto-derive-typeable"/>.
-</para>
-<para>
-Also since GHC 7.8.1, handwritten (ie. not derived) instances of
-<literal>Typeable</literal> are forbidden, and will result in an error.
-</para>
-</listitem>
-
<listitem><para> With <option>-XDeriveGeneric</option>, you can derive
instances of the classes <literal>Generic</literal> and
<literal>Generic1</literal>, defined in <literal>GHC.Generics</literal>.
defined in <literal>GHC.Base</literal>.
</para></listitem>
+<listitem><para> With <option>-XDeriveDataTypeable</option>, you can derive instances of
+the class <literal>Data</literal>,
+defined in <literal>Data.Data</literal>. See <xref linkend="deriving-typeable"/> for
+deriving <literal>Typeable</literal>.
+</para></listitem>
+
<listitem><para> With <option>-XDeriveFoldable</option>, you can derive instances of
the class <literal>Foldable</literal>,
defined in <literal>Data.Foldable</literal>.
<listitem><para> With <option>-XDeriveTraversable</option>, you can derive instances of
the class <literal>Traversable</literal>,
-defined in <literal>Data.Traversable</literal>.
+defined in <literal>Data.Traversable</literal>. Since the <literal>Traversable</literal>
+instance dictates the instances of <literal>Functor</literal> and
+<literal>Foldable</literal>, you'll probably want to derive them too, so
+<option>-XDeriveTraversable</option> implies
+<option>-XDeriveFunctor</option> and <option>-XDeriveFoldable</option>.
</para></listitem>
</itemizedlist>
+You can also use a standalone deriving declaration instead
+(see <xref linkend="stand-alone-deriving"/>).
+</para>
+<para>
In each case the appropriate class must be in scope before it
can be mentioned in the <literal>deriving</literal> clause.
</para>
</sect2>
-<sect2 id="auto-derive-typeable">
-<title>Automatically deriving <literal>Typeable</literal> instances</title>
+<sect2 id="deriving-typeable">
+<title>Deriving <literal>Typeable</literal> instances</title>
-<para>
+<para>The class <literal>Typeable</literal> is very special:
+<itemizedlist>
+<listitem><para>
+<literal>Typeable</literal> is kind-polymorphic (see
+<xref linkend="kind-polymorphism"/>).
+</para></listitem>
+
+<listitem><para>
+Only derived instances of <literal>Typeable</literal> are allowed;
+i.e. handwritten instances are forbidden. This ensures that the
+programmer cannot subert the type system by writing bogus instances.
+</para></listitem>
+
+<listitem><para>
+With <option>-XDeriveDataTypeable</option>
+GHC allows you to derive instances of <literal>Typeable</literal> for data types or newtypes,
+using a <literal>deriving</literal> clause, or using
+a standalone deriving declaration (<xref linkend="stand-alone-deriving"/>).
+</para></listitem>
+
+<listitem><para>
+With <option>-XDataKinds</option>, deriving <literal>Typeable</literal> for a data
+type (whether via a deriving clause or standalone deriving)
+also derives <literal>Typeable</literal> for the promoted data constructors (<xref linkend="promotion"/>).
+</para></listitem>
+
+<listitem><para>
+However, using standalone deriving, you can <emphasis>also</emphasis> derive
+a <literal>Typeable</literal> instance for a data family.
+You may not add a <literal>deriving(Typeable)</literal> clause to a
+<literal>data instance</literal> declaration; instead you must use a
+standalone deriving declaration for the data family.
+</para></listitem>
+
+<listitem><para>
+Using standalone deriving, you can <emphasis>also</emphasis> derive
+a <literal>Typeable</literal> instance for a type class.
+</para></listitem>
+
+<listitem><para>
The flag <option>-XAutoDeriveTypeable</option> triggers the generation
-of derived <literal>Typeable</literal> instances for every datatype and type
-class declaration in the module it is used. It will also generate
-<literal>Typeable</literal> instances for any promoted data constructors
-(<xref linkend="promotion"/>). This flag implies
-<option>-XDeriveDataTypeable</option> (<xref linkend="deriving-typeable"/>).
+of derived <literal>Typeable</literal> instances for every datatype, data family,
+and type class declaration in the module it is used, unless a manually-specified one is
+already provided.
+This flag implies <option>-XDeriveDataTypeable</option>.
+</para></listitem>
+</itemizedlist>
+
</para>
</sect2>
<sect3> <title> A more precise specification </title>
<para>
-Derived instance declarations are constructed as follows. Consider the
-declaration (after expansion of any type synonyms)
+A derived instance is derived only for declarations of these forms (after expansion of any type synonyms)
<programlisting>
- newtype T v1...vn = T' (t vk+1...vn) deriving (c1...cm)
+ newtype T v1..vn = MkT (t vk+1..vn) deriving (C t1..tj)
+ newtype instance T s1..sk vk+1..vn = MkT (t vk+1..vn) deriving (C t1..tj)
</programlisting>
-
where
<itemizedlist>
<listitem><para>
- The <literal>ci</literal> are partial applications of
- classes of the form <literal>C t1'...tj'</literal>, where the arity of <literal>C</literal>
+<literal>v1..vn</literal> are type variables, and <literal>t</literal>,
+<literal>s1..sk</literal>, <literal>t1..tj</literal> are types.
+</para></listitem>
+<listitem><para>
+ The <literal>(C t1..tj)</literal> is a partial applications of the class <literal>C</literal>,
+ where the arity of <literal>C</literal>
is exactly <literal>j+1</literal>. That is, <literal>C</literal> lacks exactly one type argument.
</para></listitem>
<listitem><para>
- The <literal>k</literal> is chosen so that <literal>ci (T v1...vk)</literal> is well-kinded.
+ <literal>k</literal> is chosen so that <literal>C t1..tj (T v1...vk)</literal> is well-kinded.
+(Or, in the case of a <literal>data instance</literal>, so that <literal>C t1..tj (T s1..sk)</literal> is
+well kinded.)
</para></listitem>
<listitem><para>
The type <literal>t</literal> is an arbitrary type.
</para></listitem>
<listitem><para>
- The type variables <literal>vk+1...vn</literal> do not occur in <literal>t</literal>,
- nor in the <literal>ci</literal>, and
+ The type variables <literal>vk+1...vn</literal> do not occur in the types <literal>t</literal>,
+ <literal>s1..sk</literal>, or <literal>t1..tj</literal>.
</para></listitem>
<listitem><para>
- None of the <literal>ci</literal> is <literal>Read</literal>, <literal>Show</literal>,
+ <literal>C</literal> is not <literal>Read</literal>, <literal>Show</literal>,
<literal>Typeable</literal>, or <literal>Data</literal>. These classes
should not "look through" the type or its constructor. You can still
derive these classes for a newtype, but it happens in the usual way, not
via this new mechanism.
</para></listitem>
<listitem><para>
- It is safe to coerce each of the methods of <literal>ci</literal>. That is,
- the missing last argument to each of the <literal>ci</literal> is not used
- at a nominal role in any of the <literal>ci</literal>'s methods.
+ It is safe to coerce each of the methods of <literal>C</literal>. That is,
+ the missing last argument to <literal>C</literal> is not used
+ at a nominal role in any of the <literal>C</literal>'s methods.
(See <xref linkend="roles"/>.)</para></listitem>
</itemizedlist>
-Then, for each <literal>ci</literal>, the derived instance
+Then the derived instance is of form
declaration is:
<programlisting>
- instance ci t => ci (T v1...vk)
+ instance C t1..tj t => C t1..tj (T v1...vk)
</programlisting>
As an example which does <emphasis>not</emphasis> work, consider
<programlisting>
<sect3 id="nullary-type-classes">
<title>Nullary type classes</title>
-Nullary (no parameter) type classes are enabled with <option>-XNullaryTypeClasses</option>.
+Nullary (no parameter) type classes are enabled with
+<option>-XMultiTypeClasses</option>; historically, they were enabled with the
+(now deprecated) <option>-XNullaryTypeClasses</option>.
Since there are no available parameters, there can be at most one instance
of a nullary class. A nullary type class might be used to document some assumption
in a type signature (such as reliance on the Riemann hypothesis) or add some
fromListN _ = fromList
</programlisting>
-<para>The <literal>FromList</literal> class and its methods are intended to be
+<para>The <literal>IsList</literal> class and its methods are intended to be
used in conjunction with the <option>OverloadedLists</option> extension.
<itemizedlist>
<listitem> <para> The type function
useful for completely new data types.
Here are several example instances:
<programlisting>
-instance FromList [a] where
+instance IsList [a] where
type Item [a] = a
fromList = id
toList = id
-instance (Ord a) => FromList (Set a) where
+instance (Ord a) => IsList (Set a) where
type Item (Set a) = a
fromList = Set.fromList
toList = Set.toList
-instance (Ord k) => FromList (Map k v) where
+instance (Ord k) => IsList (Map k v) where
type Item (Map k v) = (k,v)
fromList = Map.fromList
toList = Map.toList
-instance FromList (IntMap v) where
+instance IsList (IntMap v) where
type Item (IntMap v) = (Int,v)
fromList = IntMap.fromList
toList = IntMap.toList
-instance FromList Text where
+instance IsList Text where
type Item Text = Char
fromList = Text.pack
toList = Text.unpack
-instance FromList (Vector a) where
+instance IsList (Vector a) where
type Item (Vector a) = a
fromList = Vector.fromList
fromListN = Vector.fromListN
type safety.
</para>
</sect3>
+
+ <sect3><title>Instance contexts and associated type and data instances</title>
+ <para>Associated type and data instance declarations do not inherit any
+ context specified on the enclosing instance. For type instance declarations,
+ it is unclear what the context would mean. For data instance declarations,
+ it is unlikely a user would want the context repeated for every data constructor.
+ The only place where the context might likely be useful is in a
+ <literal>deriving</literal> clause of an associated data instance. However,
+ even here, the role of the outer instance context is murky. So, for
+ clarity, we just stick to the rule above: the enclosing instance context
+ is ignored. If you need to use
+ a non-trivial context on a derived instance,
+ use a <link linkend="stand-alone-deriving">standalone
+ deriving</link> clause (at the top level).
+ </para>
+ </sect3>
+
</sect2>
<sect2 id="data-family-import-export">
</para>
</sect2>
+
+<sect2><title>Kind inference in class instance declarations</title>
+
+<para>Consider the following example of a poly-kinded class and an instance for it:</para>
+
+<programlisting>
+class C a where
+ type F a
+
+instance C b where
+ type F b = b -> b
+</programlisting>
+
+<para>In the class declaration, nothing constrains the kind of the type
+<literal>a</literal>, so it becomes a poly-kinded type variable <literal>(a :: k)</literal>.
+Yet, in the instance declaration, the right-hand side of the associated type instance
+<literal>b -> b</literal> says that <literal>b</literal> must be of kind <literal>*</literal>. GHC could theoretically propagate this information back into the instance head, and
+make that instance declaration apply only to type of kind <literal>*</literal>, as opposed
+to types of any kind. However, GHC does <emphasis>not</emphasis> do this.</para>
+
+<para>In short: GHC does <emphasis>not</emphasis> propagate kind information from
+the members of a class instance declaration into the instance declaration head.</para>
+
+<para>This lack of kind inference is simply an engineering problem within GHC, but
+getting it to work would make a substantial change to the inference infrastructure,
+and it's not clear the payoff is worth it. If you want to restrict <literal>b</literal>'s
+kind in the instance above, just use a kind signature in the instance head.</para>
+
+</sect2>
</sect1>
<sect1 id="promotion">
</para>
</sect2>
-<sect2 id="promoted-literals">
-<title>Promoted Literals</title>
+<sect2 id="promotion-existentials">
+<title>Promoting existential data constructors</title>
+<para>
+Note that we do promote existential data constructors that are otherwise suitable.
+For example, consider the following:
+<programlisting>
+data Ex :: * where
+ MkEx :: forall a. a -> Ex
+</programlisting>
+Both the type <literal>Ex</literal> and the data constructor <literal>MkEx</literal>
+get promoted, with the polymorphic kind <literal>'MkEx :: forall k. k -> Ex</literal>.
+Somewhat surprisingly, you can write a type family to extract the member
+of a type-level existential:
+<programlisting>
+type family UnEx (ex :: Ex) :: k
+type instance UnEx (MkEx x) = x
+</programlisting>
+At first blush, <literal>UnEx</literal> seems poorly-kinded. The return kind
+<literal>k</literal> is not mentioned in the arguments, and thus it would seem
+that an instance would have to return a member of <literal>k</literal>
+<emphasis>for any</emphasis> <literal>k</literal>. However, this is not the
+case. The type family <literal>UnEx</literal> is a kind-indexed type family.
+The return kind <literal>k</literal> is an implicit parameter to <literal>UnEx</literal>.
+The elaborated definitions are as follows:
+<programlisting>
+type family UnEx (k :: BOX) (ex :: Ex) :: k
+type instance UnEx k (MkEx k x) = x
+</programlisting>
+Thus, the instance triggers only when the implicit parameter to <literal>UnEx</literal>
+matches the implicit parameter to <literal>MkEx</literal>. Because <literal>k</literal>
+is actually a parameter to <literal>UnEx</literal>, the kind is not escaping the
+existential, and the above code is valid.
+</para>
+
+<para>
+See also <ulink url="http://ghc.haskell.org/trac/ghc/ticket/7347">Trac #7347</ulink>.
+</para>
+</sect2>
+
+<sect2>
+<title>Promoting type operators</title>
+<para>
+Type operators are <emphasis>not</emphasis> promoted to the kind level. Why not? Because
+<literal>*</literal> is a kind, parsed the way identifiers are. Thus, if a programmer
+tried to write <literal>Either * Bool</literal>, would it be <literal>Either</literal>
+applied to <literal>*</literal> and <literal>Bool</literal>? Or would it be
+<literal>*</literal> applied to <literal>Either</literal> and <literal>Bool</literal>.
+To avoid this quagmire, we simply forbid promoting type operators to the kind level.
+</para>
+</sect2>
+
+
+</sect1>
+
+<sect1 id="type-level-literals">
+<title>Type-Level Literals</title>
+<para>
+GHC supports numeric and string literals at the type level, giving convenient
+access to a large number of predefined type-level constants.
+Numeric literals are of kind <literal>Nat</literal>, while string literals
+are of kind <literal>Symbol</literal>.
+This feature is enabled by the <literal>XDataKinds</literal>
+language extension.
+</para>
+
<para>
-Numeric and string literals are promoted to the type level, giving convenient
-access to a large number of predefined type-level constants. Numeric literals
-are of kind <literal>Nat</literal>, while string literals are of kind
-<literal>Symbol</literal>. These kinds are defined in the module
-<literal>GHC.TypeLits</literal>.
+The kinds of the literals and all other low-level operations for this feature
+are defined in module <literal>GHC.TypeLits</literal>. Note that the module
+defines some type-level operators that clash with their value-level
+counterparts (e.g. <literal>(+)</literal>). Import and export declarations
+referring to these operators require an explicit namespace
+annotation (see <xref linkend="explicit-namespaces"/>).
</para>
<para>
example = from (Point 1 2) (Get :: Label "x")
</programlisting>
</para>
-</sect2>
-<sect2 id="promotion-existentials">
-<title>Promoting existential data constructors</title>
+<sect2 id="typelit-runtime">
+<title>Runtime Values for Type-Level Literals</title>
<para>
-Note that we do promote existential data constructors that are otherwise suitable.
-For example, consider the following:
+Sometimes it is useful to access the value-level literal assocaited with
+a type-level literal. This is done with the functions
+<literal>natVal</literal> and <literal>symbolVal</literal>. For example:
<programlisting>
-data Ex :: * where
- MkEx :: forall a. a -> Ex
+GHC.TypeLits> natVal (Proxy :: Proxy 2)
+2
</programlisting>
-Both the type <literal>Ex</literal> and the data constructor <literal>MkEx</literal>
-get promoted, with the polymorphic kind <literal>'MkEx :: forall k. k -> Ex</literal>.
-Somewhat surprisingly, you can write a type family to extract the member
-of a type-level existential:
+These functions are overloaded because they need to return a different
+result, depending on the type at which they are instantiated.
<programlisting>
-type family UnEx (ex :: Ex) :: k
-type instance UnEx (MkEx x) = x
+natVal :: KnownNat n => proxy n -> Integer
+
+-- instance KnownNat 0
+-- instance KnownNat 1
+-- instance KnownNat 2
+-- ...
</programlisting>
-At first blush, <literal>UnEx</literal> seems poorly-kinded. The return kind
-<literal>k</literal> is not mentioned in the arguments, and thus it would seem
-that an instance would have to return a member of <literal>k</literal>
-<emphasis>for any</emphasis> <literal>k</literal>. However, this is not the
-case. The type family <literal>UnEx</literal> is a kind-indexed type family.
-The return kind <literal>k</literal> is an implicit parameter to <literal>UnEx</literal>.
-The elaborated definitions are as follows:
+GHC discharges the constraint as soon as it knows what concrete
+type-level literal is being used in the program. Note that this works
+only for <emphasis>literals</emphasis> and not arbitrary type expressions.
+For example, a constraint of the form <literal>KnownNat (a + b)</literal>
+will <emphasis>not</emphasis> be simplified to
+<literal>(KnownNat a, KnownNat b)</literal>; instead, GHC will keep the
+constraint as is, until it can simplify <literal>a + b</literal> to
+a constant value.
+</para>
+</sect2>
+
+<para>
+It is also possible to convert a run-time integer or string value to
+the corresponding type-level literal. Of course, the resulting type
+literal will be unknown at compile-time, so it is hidden in an existential
+type. The conversion may be performed using <literal>someNatVal</literal>
+for integers and <literal>someSymbolVal</literal> for strings:
<programlisting>
-type family UnEx (k :: BOX) (ex :: Ex) :: k
-type instance UnEx k (MkEx k x) = x
+someNatVal :: Integer -> Maybe SomeNat
+SomeNat :: KnownNat n => Proxy n -> SomeNat
</programlisting>
-Thus, the instance triggers only when the implicit parameter to <literal>UnEx</literal>
-matches the implicit parameter to <literal>MkEx</literal>. Because <literal>k</literal>
-is actually a parameter to <literal>UnEx</literal>, the kind is not escaping the
-existential, and the above code is valid.
+The operations on strings are similar.
</para>
+<sect2 id="typelit-tyfuns">
+<title>Computing With Type-Level Naturals</title>
<para>
-See also <ulink url="http://ghc.haskell.org/trac/ghc/ticket/7347">Trac #7347</ulink>.
+GHC 7.8 can evaluate arithmetic expressions involving type-level natural
+numbers. Such expressions may be constructed using the type-families
+<literal>(+), (*), (^)</literal> for addition, multiplication,
+and exponentiation. Numbers may be compared using <literal>(<=?)</literal>,
+which returns a promoted boolean value, or <literal>(<=)</literal>, which
+compares numbers as a constraint. For example:
+<programlisting>
+GHC.TypeLits> natVal (Proxy :: Proxy (2 + 3))
+5
+</programlisting>
+</para>
+<para>
+At present, GHC is quite limited in its reasoning about arithmetic:
+it will only evalute the arithmetic type functions and compare the results---
+in the same way that it does for any other type function. In particular,
+it does not know more general facts about arithmetic, such as the commutativity
+and associativity of <literal>(+)</literal>, for example.
+</para>
+
+<para>
+However, it is possible to perform a bit of "backwards" evaluation.
+For example, here is how we could get GHC to compute arbitrary logarithms
+at the type level:
+<programlisting>
+lg :: Proxy base -> Proxy (base ^ pow) -> Proxy pow
+lg _ _ = Proxy
+
+GHC.TypeLits> natVal (lg (Proxy :: Proxy 2) (Proxy :: Proxy 8))
+3
+</programlisting>
</para>
</sect2>
with the class head. Method signatures are not affected by that
process.
</para>
+
+ <sect2 id="coercible">
+ <title>The <literal>Coercible</literal> constraint</title>
+ <para>
+ The constraint <literal>Coercible t1 t2</literal> is similar to <literal>t1 ~
+ t2</literal>, but denotes representational equality between
+ <literal>t1</literal> and <literal>t2</literal> in the sense of Roles
+ (<xref linkend="roles"/>). It is exported by
+ <ulink url="&libraryBaseLocation;/Data-Coerce.html"><literal>Data.Coerce</literal></ulink>,
+ which also contains the documentation. More details and discussion can be found in
+ the paper
+ <ulink href="http://www.cis.upenn.edu/~eir/papers/2014/coercible/coercible.pdf">Safe Coercions"</ulink>.
+ </para>
+ </sect2>
+
</sect1>
<sect1 id="constraint-kind">
4.5.5</ulink>
of the Haskell Report)
can be completely switched off by
-<option>-XNoMonomorphismRestriction</option>.
+<option>-XNoMonomorphismRestriction</option>. Since GHC 7.8.1, the monomorphism
+restriction is switched off by default in GHCi.
</para>
</sect3>
<para>
An ML-style language usually generalises the type of any let-bound or where-bound variable,
so that it is as polymorphic as possible.
-With the flag <option>-XMonoLocalBinds</option> GHC implements a slightly more conservative policy:
-<emphasis>it generalises only "closed" bindings</emphasis>.
-A binding is considered "closed" if either
+With the flag <option>-XMonoLocalBinds</option> GHC implements a slightly more conservative policy,
+using the following rules:
<itemizedlist>
-<listitem><para>It is one of the top-level bindings of a module, or </para></listitem>
-<listitem><para>Its free variables are all themselves closed</para></listitem>
+ <listitem><para>
+ A variable is <emphasis>closed</emphasis> if and only if
+ <itemizedlist>
+ <listitem><para> the variable is let-bound</para></listitem>
+ <listitem><para> one of the following holds:
+ <itemizedlist>
+ <listitem><para>the variable has an explicit type signature that has no free type variables, or</para></listitem>
+ <listitem><para>its binding group is fully generalised (see next bullet) </para></listitem>
+ </itemizedlist>
+ </para></listitem>
+ </itemizedlist>
+ </para></listitem>
+
+ <listitem><para>
+ A binding group is <emphasis>fully generalised</emphasis> if and only if
+ <itemizedlist>
+ <listitem><para>each of its free variables is either imported or closed, and</para></listitem>
+ <listitem><para>the binding is not affected by the monomorphism restriction
+ (<ulink url="http://www.haskell.org/onlinereport/decls.html#sect4.5.5">Haskell Report, Section 4.5.5</ulink>)</para></listitem>
+ </itemizedlist>
+ </para></listitem>
</itemizedlist>
For example, consider
<programlisting>
k z = z+x
in h x + k x
</programlisting>
-Here <literal>f</literal> and <literal>g</literal> are closed because they are bound at top level.
-Also <literal>h</literal> is closed because its only free variable <literal>f</literal> is closed.
-But <literal>k</literal> is not closed because it mentions <literal>x</literal> which is locally bound.
-Another way to think of it is this: all closed bindings <literal>could</literal> be defined at top level.
-(In the example, we could move <literal>h</literal> to top level.)
-</para><para>
-All of this applies only to bindings that lack an explicit type signature, so that GHC has to
-infer its type. If you supply a type signature, then that fixes type of the binding, end of story.
-</para><para>
+Here <literal>f</literal> is generalised because it has no free variables; and its binding group
+is unaffected by the monomorphism restriction; and hence <literal>f</literal> is closed.
+The same reasoning applies to <literal>g</literal>, except that it has one closed free variable, namely <literal>f</literal>.
+Similarly <literal>h</literal> is closed, <emphasis>even though it is not bound at top level</emphasis>,
+because its only free variable <literal>f</literal> is closed.
+But <literal>k</literal> is not closed, because it mentions <literal>x</literal> which is not closed (because it is not let-bound).
+</para>
+<para>
+Notice that a top-level binding that is affected by the monomorphism restriction is not closed, and hence may
+in turn prevent generalisation of bindings that mention it.
+</para>
+<para>
The rationale for this more conservative strategy is given in
<ulink url="http://research.microsoft.com/~simonpj/papers/constraints/index.htm">the papers</ulink> "Let should not be generalised" and "Modular type inference with local assumptions", and
a related <ulink url="http://ghc.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7">blog post</ulink>.
</sect3>
</sect2>
-<sect2 id="type-holes">
-<title>Type Holes</title>
+</sect1>
+<!-- ==================== End of type system extensions ================= -->
-<para>Type hole support is enabled with the option
-<option>-XTypeHoles</option>.</para>
+<sect1 id="typed-holes">
+<title>Typed Holes</title>
-<para>
-The goal of the type holes extension is not to change the type system, but to help with writing Haskell
-code. Type holes can be used to obtain extra information from the type checker, which might otherwise be hard
-to get.
-Normally, the type checker is used to decide if a module is well typed or not. Using GHCi,
-users can inspect the (inferred) type signatures of all top-level bindings. However, determining the
-type of a single term is still hard. Yet while writing code, it could be helpful to know the type of
-the term you're about to write.
-</para>
+<para>Typed hole support is enabled with the option
+<option>-fwarn-typed-holes</option>, which is enabled by default.</para>
<para>
-This extension allows special placeholders, written with a leading underscore (e.g. "<literal>_</literal>",
+This option allows special placeholders, written with a leading underscore (e.g. "<literal>_</literal>",
"<literal>_foo</literal>", "<literal>_bar</literal>"), to be used as an expression.
During compilation these holes will generate an error message describing what type is expected there,
information about the origin of any free type variables, and a list of local bindings
</para>
<para>
+The goal of the typed holes warning is not to change the type system, but to help with writing Haskell
+code. Typed holes can be used to obtain extra information from the type checker, which might otherwise be hard
+to get.
+Normally, using GHCi, users can inspect the (inferred) type signatures of all top-level bindings.
+However, this method is less convenient with terms which are not defined on top-level or
+inside complex expressions. Holes allow to check the type of the term you're about to write.
+</para>
+
+<para>
Holes work together well with <link linkend="defer-type-errors">deferring type errors to runtime</link>:
with <literal>-fdefer-type-errors</literal>, the error from a hole is also deferred, effctively making the hole
typecheck just like <literal>undefined</literal>, but with the added benefit that it will show its warning message
</para>
<para>
-Multiple type holes can be used to find common type variables between expressions. For example:
+Multiple typed holes can be used to find common type variables between expressions. For example:
<programlisting>
sum :: [Int] -> Int
-sum xx = foldr _f _z xs
+sum xs = foldr _f _z xs
</programlisting>
Shows:
<programlisting>
holes.hs:2:15:
- Found hole `_f' with type: Int-> Int -> Int
+ Found hole `_f' with type: Int -> Int -> Int
In the first argument of `foldr', namely `_'
In the expression: foldr _a _b _c
In an equation for `sum': sum x = foldr _a _b _c
In the second argument of `(:)', namely `_x'
In the expression: _x : _x
In an equation for `cons': cons = _x : _x
-Failed, modules loaded: none.
</programlisting>
This ensures that an unbound identifier is never reported with a too polymorphic type, like
<literal>forall a. a</literal>, when used multiple times for types that can not be unified.
</para>
-</sect2>
-
</sect1>
-<!-- ==================== End of type system extensions ================= -->
+<!-- ==================== Deferring type errors ================= -->
<sect1 id="defer-type-errors">
<title>Deferring type errors to runtime</title>
constructions. You need to use the flag
<option>-XTemplateHaskell</option>
<indexterm><primary><option>-XTemplateHaskell</option></primary>
- </indexterm>to switch these syntactic extensions on
- (<option>-XTemplateHaskell</option> is no longer implied by
- <option>-fglasgow-exts</option>).</para>
+ </indexterm>to switch these syntactic extensions on.</para>
<itemizedlist>
<listitem><para>
</sect2>
-<sect2 id="core-pragma">
- <title>CORE pragma</title>
-
- <indexterm><primary>CORE pragma</primary></indexterm>
- <indexterm><primary>pragma, CORE</primary></indexterm>
- <indexterm><primary>core, annotation</primary></indexterm>
-
-<para>
- The external core format supports <quote>Note</quote> annotations;
- the <literal>CORE</literal> pragma gives a way to specify what these
- should be in your Haskell source code. Syntactically, core
- annotations are attached to expressions and take a Haskell string
- literal as an argument. The following function definition shows an
- example:
-
-<programlisting>
-f x = ({-# CORE "foo" #-} show) ({-# CORE "bar" #-} x)
-</programlisting>
-
- Semantically, this is equivalent to:
-
-<programlisting>
-g x = show x
-</programlisting>
-</para>
-
-<para>
- However, when external core is generated (via
- <option>-fext-core</option>), there will be Notes attached to the
- expressions <function>show</function> and <varname>x</varname>.
- The core function declaration for <function>f</function> is:
-</para>
-
-<programlisting>
- f :: %forall a . GHCziShow.ZCTShow a ->
- a -> GHCziBase.ZMZN GHCziBase.Char =
- \ @ a (zddShow::GHCziShow.ZCTShow a) (eta::a) ->
- (%note "foo"
- %case zddShow %of (tpl::GHCziShow.ZCTShow a)
- {GHCziShow.ZCDShow
- (tpl1::GHCziBase.Int ->
- a ->
- GHCziBase.ZMZN GHCziBase.Char -> GHCziBase.ZMZN GHCziBase.Cha
-r)
- (tpl2::a -> GHCziBase.ZMZN GHCziBase.Char)
- (tpl3::GHCziBase.ZMZN a ->
- GHCziBase.ZMZN GHCziBase.Char -> GHCziBase.ZMZN GHCziBase.Cha
-r) ->
- tpl2})
- (%note "bar"
- eta);
-</programlisting>
-
-<para>
- Here, we can see that the function <function>show</function> (which
- has been expanded out to a case expression over the Show dictionary)
- has a <literal>%note</literal> attached to it, as does the
- expression <varname>eta</varname> (which used to be called
- <varname>x</varname>).
-</para>
-
-</sect2>
-
</sect1>
<sect1 id="special-ids">
url="http://www.seas.upenn.edu/~sweirich/papers/popl163af-weirich.pdf">Generative
type abstraction and type-level computation</ulink>, published at POPL 2011.</para>
-<sect2>
+<sect2 id="nominal-representational-and-phantom">
<title>Nominal, Representational, and Phantom</title>
<para>The goal of the roles system is to track when two types have the same
</sect2>
-<sect2>
+<sect2 id="role-inference">
<title>Role inference</title>
<para>
</sect2>
-<sect2>
+<sect2 id="role-annotations">
<title>Role annotations
<indexterm><primary>-XRoleAnnotations</primary></indexterm>
</title>
</programlisting>
<para>Role annotations can also be used should a programmer wish to write
-a class with a representational (or phantom) role.</para>
+a class with a representational (or phantom) role. However, as a class
+with non-nominal roles can quickly lead to class instance incoherence,
+it is necessary to also specify <option>-XIncoherentInstances</option>
+to allow non-nominal roles for classes.</para>
<para>The other place where role annotations may be necessary are in
<literal>hs-boot</literal> files (<xref linkend="mutual-recursion"/>), where
the right-hand sides of definitions can be omitted. As usual, the
types/classes declared in an <literal>hs-boot</literal> file must match up
with the definitions in the <literal>hs</literal> file, including down to the
-roles. The default role is representational in <literal>hs-boot</literal> files,
+roles. The default role for datatypes
+is representational in <literal>hs-boot</literal> files,
corresponding to the common use case.</para>
<para>
type role T4 nominal
data T4 a = MkT4 (a Int) -- OK, but nominal is higher than necessary
- type role C representational _
+ type role C representational _ -- OK, with -XIncoherentInstances
class C a b where ... -- OK, b will get a nominal role
type role X nominal