-
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:`patsyn-impexp` 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
- :ghc-flag:`-XDeriveFoldable` and :ghc-flag:`-XDeriveTraversable` now
generate code without superfluous ``mempty`` or ``pure`` expressions. As a
result, :ghc-flag:`-XDeriveTraversable` now works on datatypes that contain
arguments which have unlifted types.
- Note that the :ghc-flag:`-XImpredicativeTypes` extension, which has been
:ghc-wiki:`known ` to be broken for many years, is even more
broken than usual in this release (see :ghc-ticket:`11319`,
:ghc-ticket:`11675`, and others). During pre-release testing we encountered
a number of projects that broke with confusing type errors due to (often
unnecessary) use of :ghc-flag:`-XImpredicativeTypes`. Users of
:ghc-flag:`-XImpredicativeTypes` do so at their own risk!
Compiler
~~~~~~~~
- The LLVM code generator now supports only LLVM 3.7. This is in contrast to our
previous policy where GHC would try to support a range of LLVM versions
concurrently. We hope that by supporting a narrower range of versions we can
provide more reliable support for each.
- Warnings can now be controlled with ``-W(no-)...`` flags in addition to
the old ``-f(no-)warn...`` ones. This was done as the first part of a
rewrite of the warning system to provide better control over warnings,
better warning messages, and more common syntax compared to other
compilers. The old ``-f``-based warning flags will remain functional for
the forseeable future.
- Added the option :ghc-flag:`-dth-dec-file`. This dumps out a ``.th.hs`` file of
all Template Haskell declarations in a corresponding .hs file. The
idea is that application developers can check this into their
repository so that they can grep for identifiers used elsewhere that
were defined in Template Haskell. This is similar to using
:ghc-flag:`-ddump-to-file` with :ghc-flag:`-ddump-splices` but it always generates a
file instead of being coupled to :ghc-flag:`-ddump-to-file` and only outputs
code that does not exist in the .hs file and a comment for the splice
location in the original file.
- Added the option :ghc-flag:`-fprint-expanded-types`. When enabled, GHC also
prints type-synonym-expanded types in type errors.
- Added the option :ghc-flag:`-fcpr-anal`. When enabled, the demand analyser
performs CPR analysis. It is implied by :ghc-flag:`-O`. Consequently,
:ghc-flag:`-fcpr-off` is now removed, run with :ghc-flag:`-fno-cpr-anal` to get the
old :ghc-flag:`-fcpr-off` behaviour.
- Added the option :ghc-flag:`-fworker-wrapper`. When enabled, the worker-wrapper
transformation is performed after a strictness analysis pass. It is implied
by :ghc-flag:`-O` and by :ghc-flag:`-fstrictness`. It is disabled by :ghc-flag:`-fno-strictness`.
Enabling :ghc-flag:`-fworker-wrapper` while strictness analysis is disabled (by
:ghc-flag:`-fno-strictness`) has no effect.
- :ghc-flag:`-ddump-strsigs` has been renamed to
:ghc-flag:`-ddump-str-signatures`.
- :ghc-flag:`-XDeriveGeneric` is now less picky about instantiating type
arguments when deriving (:ghc-ticket:`11732`). As a consequence, the
following code is now legal (whereas before it would have been rejected). ::
data T a b = T a b
deriving instance Generic (T Int b)
- Added the :ghc-flag:`-fmax-pmcheck-iterations` to control how many times
the pattern match checker iterates. Since coverage checking is exponential
in the general case, setting a default number of iterations prevents memory
and performance blowups. By default, the number of iterations is set to
2000000 but it can be set with: ``-fmax-pmcheck-iterations=``.
If the set number of iterations is exceeded, an informative warning is
issued.
- :ghc-flag:`-this-package-key` has been renamed again (hopefully for the last time!)
to :ghc-flag:`-this-unit-id`. The renaming was motivated by the fact that
the identifier you pass to GHC here doesn't have much to do with packages:
you may provide different unit IDs for libraries which are in the same
package. :ghc-flag:`-this-package-key` is deprecated; you should use
:ghc-flag:`-this-unit-id` or, if you need compatibility over multiple
versions of GHC, :ghc-flag:`-package-name`.
- When :ghc-flag:`-fdefer-type-errors` is enabled and an expression fails to
typecheck, ``Control.Exception.TypeError`` will now be thrown instead of
``Control.Exception.ErrorCall``.
Warnings
^^^^^^^^
- When printing an out-of-scope error message, GHC will give helpful advice if
the error might be caused by too restrictive imports.
- Warning messages now mention the name of the warning flag which the message is
controlled by (:ghc-ticket:`10752`) If the flag was implied via a warning
group then the name of the group will also be shown if
:ghc-flag:`-fshow-warning-groups` is used.
- Added the :ghc-flag:`-Weverything` warning group, along with its opposite
:ghc-flag:`-Wno-everything`. This group includes all warnings supported by
GHC. This is in contrast to `-Wall` which excludes some stylistic or
otherwise controversial warnings.
- Added the :ghc-flag:`-Wdefault` warning group, along with its opposite
:ghc-flag:`-Wno-default`. This group is defined to be the set of warnings
which ``ghc`` enables by default (e.g. when no additional ``-W`` flags are
used).