-
Ben Gamari authoredBen Gamari authored
.. _release-8-0-1:
Release notes for version 8.0.1
===============================
The significant changes to the various parts of the compiler are listed
in the following sections. There have also been numerous bug fixes and
performance improvements over the 7.10 branch.
.. warning::
Only Cabal versions 1.24 and newer will function properly with this release.
(see :ghc-ticket:`11558`). Consequently it will likely be necessary to
recompile ``cabal-install`` before installing new packages.
The reason for this is a change in how packages are identified in GHC
8.0. While previous versions of Cabal identified packages to GHC with a
package key (with GHC's :ghc-flag:`-this-package-key` argument), GHC 8.0 and
later uses installed package IDs in place of package keys.
.. note::
Users compiling GHC on Mac OS X with XCode 7.3 will need to tell the build
system to use the ``nm-classic`` command instead of Apple's new ``nm``
implementation as the latter breaks POSIX compliance (see
:ghc-ticket:`11744`). This can be done by passing something like
``--with-nm=$(xcrun --find nm-classic)`` to ``configure``.
Highlights
----------
The highlights, since the 7.10 series, are:
- The new :ghc-flag:`-XTypeInType` allows promotion of all types into
kinds, allowing kind synonyms, kind families, promoted GADTs, and other
goodies.
- Support for :ref:`record pattern synonyms `
- The :ghc-flag:`-XDeriveAnyClass` extension learned to derive instances for
classes with associated types (see :ref:`derive-any-class`)
- More reliable DWARF debugging information
- Support for :ref:`injective type families `
- Applicative ``do`` notation (see :ref:`applicative-do`)
- Support for wildcards in data and type family instances
- :ghc-flag:`-XStrict` and :ghc-flag:`-XStrictData` extensions, allowing modules
to be compiled with strict-by-default bindings (see :ref:`strict-haskell`)
- :ghc-flag:`-XDuplicateRecordFields`, allowing multiple datatypes to declare the same
record field names provided they are used unambiguously (see :ref:`duplicate-record-fields`)
- Support for lightweight
:ref:`callstacks and source locations `
- User-defined error messages for type errors
- A rewritten (and greatly improved) pattern exhaustiveness checker
- GHC can run the interpreter in a separate process (see
:ref:`external-interpreter`), and the interpreter can now run profiled
code.
- GHCi now provides access to stack traces when used with
:ghc-flag:`-fexternal-interpreter` and :ghc-flag:`-prof` (see
:ref:`ghci-stack-traces`).
- A native code generator for powerpc64 and powerpc64le architectures, support
for AIX targets, and significantly improved support on ARM.
- The reworked users guide you are now reading
- Support for Windows XP and earlier has been dropped.
- GHC RTS No longer re-exports POSIX functions under their deprecated
names on Windows.
Full details
------------
Language
~~~~~~~~
- :ghc-flag:`-XTypeInType` supports universal type promotion and merges
the type and kind language. This allows, for example, higher-rank
kinds, along with kind families and type-level GADTs. Support is still
experimental, and it is expected to improve over the next several
releases. See :ref:`type-in-type` for the details.
- The parser now supports Haddock comments on GADT data constructors.
For example ::
data Expr a where
-- | Just a normal sum
Sum :: Int -> Int -> Expr Int
- The new ``base`` constraint :base-ref:`GHC.Stack.HasCallStack `
can be used by functions to request a partial call-stack. For example ::
errorWithCallStack :: HasCallStack => String -> a
errorWithCallStack msg = error (msg ++ "\n" ++ prettyCallStack callStack)
ghci> errorWithCallStack "die"
*** Exception: die
CallStack (from HasCallStack):
errorWithCallStack, called at :2:1 in interactive:Ghci1
prints the call-site of ``errorWithCallStack``.
See :ref:`hascallstack` for a description of ``HasCallStack``.
- GHC now supports visible type application, allowing
programmers to easily specify how type parameters should be
instantiated when calling a function. See
:ref:`visible-type-application` for the details.
- To conform to the common case, the default role assigned to
parameters of datatypes declared in ``hs-boot`` files is
``representational``. However, if the constructor(s) for the datatype
are given, it makes sense to do normal role inference. This is now
implemented, effectively making the default role for non-abstract
datatypes in ``hs-boot`` files to be ``phantom``, like it is in
regular Haskell code.
- Wildcards can be used in the type arguments of type/data family
instance declarations to indicate that the name of a type variable
doesn't matter. They will be replaced with new unique type variables.
See :ref:`data-instance-declarations` for more details.
- GHC now allows to declare type families as injective. Injectivity
information can then be used by the typechecker. See
:ref:`injective-ty-fams` for details.
- Due to a :ghc-ticket:`security issue <10826>`, Safe Haskell now forbids
annotations in programs marked as :ghc-flag:`-XSafe`.
- Generic instances can be derived for data types whose constructors have
arguments with certain unlifted types. See :ref:`generic-programming` for
more details.
- GHC generics can now provide strictness information for fields in a data
constructor via the ``Selector`` type class.
- The :ghc-flag:`-XDeriveAnyClass` extension now fills in associated type family
default instances when deriving a class that contains them.
- Users can now define record pattern synonyms. This allows pattern synonyms
to behave more like normal data constructors. For example, ::
pattern P :: a -> b -> (a, b)
pattern P{x,y} = (x,y)
will allow ``P`` to be used like a record data constructor and also defines
selector functions ``x :: (a, b) -> a`` and ``y :: (a, b) -> b``.
- Pattern synonyms can now be bundled with type constructors. For a pattern
synonym ``P`` and a type constructor ``T``, ``P`` can be bundled with ``T``
so that when ``T`` is imported ``P`` is also imported. With this change
a library author can provide either real data constructors or pattern
synonyms in an opaque manner. See :ref:`pattern-synonyms` for details. ::
-- Foo.hs
module Foo ( T(P) ) where
data T = T
pattern P = T
-- Baz.hs
module Baz where
-- P is imported
import Foo (T(..))
- Whenever a data instance is exported, the corresponding data family
is exported, too. This allows one to write ::
-- Foo.hs
module Foo where
data family T a
-- Bar.hs
module Bar where
import Foo
data instance T Int = MkT
-- Baz.hs
module Baz where
import Bar (T(MkT))
In previous versions of GHC, this required a workaround via an
explicit export list in ``Bar``.
- GHC has grown a :ghc-flag:`-XUndecidableSuperClasses` language extension,
which relaxes GHC's recursive superclass check (see :ghc-ticket:`11318`).
This allows class definitions which have mutually recursive superclass
constraints at the expense of potential non-termination in the solver.
- The compiler is now a bit more conservative in solving constraints previously
provided by superclasses (see :ghc-ticket:`11762`). For instance, consider
this program,::
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
class Super a
class (Super a) => Left a
class (Super a) => Right a
instance (Left a) => Right a -- this is now an error
GHC now rejects this instance, claiming it cannot deduce the ``Super a``
superclass constraint of the ``Right`` typeclass. This stands in contrast to
previous releases, which would accept this declaration, using the ``Super a``
constraint implied by the ``Left a`` constraint. To fix this simply add the
needed superclass constraint explicitly, ::
instance (Left a, Super a) => Right a