- TODO FIXME
- SCC annotations can now be used for declarations.
+- Heap overflow throws an exception in certain circumstances.
Full details
------------
+- Heap overflow throws a catchable exception, provided that it was detected
+ by the RTS during a GC cycle due to the program exceeding a limit set by
+ ``+RTS -M``, and not due to an allocation being refused by the operating
+ system. This exception is thrown to the same thread that receives
+ ``UserInterrupt`` exceptions, and may be caught by user programs.
+
Language
~~~~~~~~
syntax can be used, in addition to a new form for specifying the cost centre
name. See :ref:`scc-pragma` for examples.
+- GHC is now much more particular about :ghc-flag:`-XDefaultSignatures`. The
+ type signature for a default method of a type class must now be the same as
+ the corresponding main method's type signature modulo differences in the
+ signatures' contexts. Otherwise, the typechecker will reject that class's
+ definition. See :ref:`class-default-signatures` for further details.
+
+- It is now possible to explicitly pick a strategy to use when deriving a
+ class instance using the :ghc-flag:`-XDerivingStrategies` language extension
+ (see :ref:`deriving-strategies`).
+
+- GHC now allows standalone deriving using :ghc-flag:`-XDeriveAnyClass` on
+ any data type, even if its data constructors are not in scope. This is
+ consistent with the fact that this code (in the presence of
+ :ghc-flag:`-XDeriveAnyClass`): ::
+
+ deriving instance C T
+
+ is exactly equivalent to: ::
+
+ instance C T
+
+ and the latter code has no restrictions about whether the data constructors
+ of ``T`` are in scope.
+
+- :ghc-flag:`-XGeneralizedNewtypeDeriving` now supports deriving type classes
+ with associated type families. See the section on
+ :ref:`GeneralizedNewtypeDeriving and associated type families
+ <gnd-and-associated-types>`.
+
+- :ghc-flag:`-XGeneralizedNewtypeDeriving` will no longer infer constraints
+ when deriving a class with no methods. That is, this code: ::
+
+ class Throws e
+ newtype Id a = MkId a
+ deriving Throws
+
+ will now generate this instance: ::
+
+ instance Throws (Id a)
+
+ instead of this instance: ::
+
+ instance Throws a => Throws (Id a)
+
+ This change was motivated by the fact that the latter code has a strictly
+ redundant ``Throws a`` constraint, so it would emit a warning when compiled
+ with :ghc-flag:`-Wredundant-constraints`. The latter instance could still
+ be derived if so desired using :ghc-flag:`-XStandaloneDeriving`: ::
+
+ deriving instance Throws a => Throws (Id a)
+
+- Add warning flag :ghc-flag:`-Wcpp-undef` which passes ``-Wundef`` to the C
+ pre-processor causing the pre-processor to warn on uses of the ``#if``
+ directive on undefined identifiers.
+
+- GHC will no longer automatically infer the kind of higher-rank type synonyms;
+ you must explicitly explicitly annotate the synonym with a kind signature.
+ For example, given::
+
+ data T :: (forall k. k -> Type) -> Type
+
+ to define a synonym of ``T``, you must write::
+
+ type TSyn = (T :: (forall k. k -> Type) -> Type)
+
+- The Mingw-w64 toolchain for the Windows version of GHC has been updated. GHC now uses
+ `GCC 6.2.0` and `binutils 2.27`.
+
+- Previously, :ghc-flag:`-Wmissing-methods` would not warn whenever a type
+ class method beginning with an underscore was not implemented in an instance.
+ For instance, this code would compile without any warnings: ::
+
+ class Foo a where
+ _Bar :: a -> Int
+
+ instance Foo Int
+
+ :ghc-flag:`-Wmissing-methods` will now warn that ``_Bar`` is not implemented
+ in the ``Foo Int`` instance.
+
GHCi
~~~~
- TODO FIXME.
-- ``addModFinalizer`` now exposes the local typing environment at the splice
- point. This allows ``reify`` to see local and top-level definitions in the
- current declaration group when used as in
-
- .. code-block:: none
-
- f x = $(addModFinalizer (reify 'x >>= runIO . print) >> [| x |])
-
- Reifying types that contain unboxed tuples now works correctly. (Previously,
Template Haskell reified unboxed tuples as boxed tuples with twice their
appropriate arity.)
correctly. Previously, Template Haskell would implicitly remove the
parentheses when splicing, which would turn ``(# Int #)`` into ``Int``.
+- Add support for type signatures in patterns. (:ghc-ticket:`12164`)
+
+- Make quoting and reification return the same types. (:ghc-ticket:`11629`)
+
+- More kind annotations appear in the left-hand sides of reified closed
+ type family equations, in order to disambiguate types that would otherwise
+ be ambiguous in the presence of :ghc-flag:`-XPolyKinds`.
+ (:ghc-ticket:`12646`)
+
+- Quoted type signatures are more accurate with respect to implicitly
+ quantified type variables. Before, if you quoted this: ::
+
+ [d| id :: a -> a
+ id x = x
+ |]
+
+ then the code that Template Haskell would give back to you would actually be
+ this instead: ::
+
+ id :: forall a. a -> a
+ id x = x
+
+ That is, quoting would explicitly quantify all type variables, even ones
+ that were implicitly quantified in the source. This could be especially
+ harmful if a kind variable was implicitly quantified. For example, if
+ you took this quoted declaration: ::
+
+ [d| idProxy :: forall proxy (b :: k). proxy b -> proxy b
+ idProxy x = x
+ |]
+
+ and tried to splice it back in, you'd get this instead: ::
+
+ idProxy :: forall k proxy (b :: k). proxy b -> proxy b
+ idProxy x = x
+
+ Now ``k`` is explicitly quantified, and that requires turning on
+ :ghc-flag:`-XTypeInType`, whereas the original declaration did not!
+
+ Template Haskell quoting now respects implicit quantification in type
+ signatures, so the quoted declarations above now correctly leave the
+ type variables ``a`` and ``k`` as implicitly quantified.
+ (:ghc-ticket:`13018` and :ghc-ticket:`13123`)
+
+
Runtime system
~~~~~~~~~~~~~~
-- TODO FIXME.
+- TODO FIXME.
+
+- Added support for *Compact Regions*, which offer a way to manually
+ move long-lived data outside of the heap so that the garbage
+ collector does not have to trace it repeatedly. Compacted data can
+ also be serialized, stored, and deserialized again later by the same
+ program. For more details see the :compact-ref:`Data.Compact
+ <Data-Compact.html>` module.
+
+- There is new support for improving performance on machines with a
+ Non-Uniform Memory Architecture (NUMA). See :rts-flag:`--numa`.
+ This is supported on Linux and Windows systems.
+
+- The garbage collector can be told to use fewer threads than the
+ global number of capabilities set by :rts-flag:`-N`. See
+ :rts-flag:`-qn`, and a `blog post
+ <http://simonmar.github.io/posts/2016-12-08-Haskell-in-the-datacentre.html>`_
+ that describes this.
- The :ref:`heap profiler <prof-heap>` can now emit heap census data to the GHC
event log, allowing heap profiles to be correlated with other tracing events
(see :ghc-ticket:`11094`).
+- Some bugs have been fixed in the stack-trace implementation in the
+ profiler that sometimes resulted in incorrect stack traces and
+ costs attributed to the wrong cost centre stack (see :ghc-ticket:`5654`).
+
+- Added processor group support for Windows. This allows the runtime to allocate
+ threads to all cores in systems which have multiple processor groups.
+ (e.g. > 64 cores, see :ghc-ticket:`11054`)
+
Build system
~~~~~~~~~~~~
provided in GHC's version of the ``Read`` class, and allows users to write
more efficient ``Read1`` and ``Read2`` instances.
+- Add ``type family AppendSymbol (m :: Symbol) (n :: Symbol) :: Symbol`` to
+ ``GHC.TypeLits``
+
binary
~~~~~~
ghc
~~~
-- The ``GHC.initGhcMonad`` function no longer installs signal handlers by
- default. This means that the RTS won't attempt to handle Ctrl-C gracefully.
- If you would like to use GHC's signal handlers, call
- ``GHC.installSignalHandlers`` during initialization.
-
+-
ghc-boot
~~~~~~~~