Table Of Contents

Previous topic

2. Introduction to GHC

Next topic

4. Using GHCi

This Page

3. Release notes for version 8.2.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 8.0 branch.

3.1. Highlights

The highlights since the 8.0 release include:

  • A new, more expressive Typeable mechanism, Type.Reflection
  • Colorful error messages with caret diagnostics
  • SCC annotations can now be used for declarations.
  • Heap overflow throws an exception in certain circumstances.
  • Improved code generation of join points
  • Deriving strategies
  • Compact regions support, allowing efficient garbage collection of large heaps
  • More reliable DWARF debug information

3.2. Full details

3.2.1. Language

  • Pattern synonym signatures can now be applied to multiple patterns, just like value-level binding signatures. See Typing of pattern synonyms for details.
  • It is now possible to explicitly pick a strategy to use when deriving a class instance using the -XDerivingStrategies language extension (see Deriving strategies).

3.2.2. Compiler

  • GHC will now use ld.gold or ld.lld instead of the system’s default ld, if available. Linker availability will be evaluated at configure time. The user can manually override which linker to use by passing the LD variable to configure. You can revert to the old behavior of using the system’s default ld by passing the --disable-ld-override flag to configure.

  • GHC now uses section splitting (i.e. -split-sections) instead of object splitting (i.e. -split-objs) as the default mechanism for linker-based dead code removal. While the effect is the same, split sections tends to produce significantly smaller objects than split objects and more closely mirrors the approach used by other compilers. Split objects will be deprecated and eventually removed in a future GHC release.

    Note that some versions of the ubiquitous BFD linker exhibit performance trouble with large libraries with section splitting enabled (see Trac #13739). It is recommended that you use either the gold or lld linker if you observe this. This will require that you install one of these compilers, rerun configure, and reinstall GHC.

    Split sections is enabled by default in the official binary distributions for platforms that support it.

  • Old profiling flags -auto-all, -auto, and -caf-all are deprecated and their usage provokes a compile-time warning.

  • Support for adding cost centres to declarations is added. The same SCC syntax can be used, in addition to a new form for specifying the cost centre name. See Inserting cost centres by hand for examples.

  • GHC is now much more particular about -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 Default method signatures for further details.

  • -XDeriveAnyClass is no longer limited to type classes whose argument is of kind * or * -> *.

  • The means by which -XDeriveAnyClass infers instance contexts has been completely overhauled. The instance context is now inferred using the type signatures (and default type signatures) of the derived class’s methods instead of using the datatype’s definition, which often led to over-constrained instances or instances that didn’t typecheck (or worse, triggered GHC panics). See the section on DeriveAnyClass for more details.

  • GHC now allows standalone deriving using -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 -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.

  • -XGeneralizedNewtypeDeriving now supports deriving type classes with associated type families. See the section on GeneralizedNewtypeDeriving and associated type families.

  • -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 -Wredundant-constraints. The latter instance could still be derived if so desired using -XStandaloneDeriving:

    deriving instance Throws a => Throws (Id a)
    
  • Add warning 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, -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
    

    -Wmissing-methods will now warn that _Bar is not implemented in the Foo Int instance.

  • A new flag -ddump-json has been added. This flag dumps compiler output as JSON documents. It is experimental and will be refined depending on feedback from tooling authors for the next release.

  • GHC is now able to better optimize polymorphic expressions by using known superclass dictionaries where possible. Some examples:

    -- uses of `Monad IO` or `Applicative IO` here are improved
    foo :: MonadBaseControl IO m => ...
    
    -- uses of `Monoid MyMonoid` here are improved
    bar :: MonadWriter MyMonoid m => ...
    
  • GHC now derives the definition of <$ when using DeriveFunctor rather than using the default definition. This prevents unnecessary allocation and a potential space leak when deriving Functor for a recursive type.

  • The -XExtendedDefaultRules extension now defaults multi-parameter typeclasses. See Trac #12923.

  • GHC now ignores RULES for data constructors (Trac #13290). Previously, it accepted:

    {-# RULES "NotAllowed" forall x. Just x = e #-}
    

    That rule will no longer take effect, and a warning will be issued. RULES may still mention data constructors, but not in the outermost position:

    {-# RULES "StillWorks" forall x. f (Just x) = e #-}
    
  • Type synonyms can no longer appear in the class position of an instance. This means something like this is no longer allowed:

    type ReadShow a = (Read a, Show a)
    instance Read Foo
    instance Show Foo
    instance ReadShow Foo -- illegal
    

    See Trac #13267.

  • Validity checking for associated type family instances has tightened somewhat. Before, this would be accepted:

    class Foo a where
      type Bar a
    
    instance Foo (Either a b) where
      type Bar (Either c d) = d -> c
    

    This is now disallowed, as the type variables used in the Bar instance do not match those in the instance head. This instance can be fixed by changing it to:

    instance Foo (Either a b) where
      type Bar (Either a b) = b -> a
    

    See the section on associated type family instances <assoc-data-inst> for more information.

  • A bug involving the interaction between -XMonoLocalBinds and -XPolyKinds has been fixed. This can cause some programs to fail to typecheck in case explicit kind signatures are not provided. See Kind generalisation for an example.

3.2.3. GHCi

  • Added -flocal-ghci-history which uses current directory for .ghci-history.
  • Added support for -XStaticPointers in interpreted modules. Note, however, that static expressions are still not allowed in expressions evaluated in the REPL.

3.2.4. Template Haskell

  • Reifying types that contain unboxed tuples now works correctly. (Previously, Template Haskell reified unboxed tuples as boxed tuples with twice their appropriate arity.)

  • Splicing singleton unboxed tuple types (e.g., (# Int #)) now works correctly. Previously, Template Haskell would implicitly remove the parentheses when splicing, which would turn (# Int #) into Int.

  • Add support for type signatures in patterns. (Trac #12164)

  • Make quoting and reification return the same types. (Trac #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 -XPolyKinds. (Trac #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 -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. (Trac #13018 and Trac #13123)

  • Looking up type constructors with symbol names (e.g., +) now works as expected (Trac #11046)

3.2.5. Runtime system

  • 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 (see -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.
  • 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 GHC.Compact module.
  • There is new support for improving performance on machines with a Non-Uniform Memory Architecture (NUMA). See --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 -N. By default, the garbage collector will use a number of threads equal to the lesser of the global number of capabilities or the number of physical cores. See -qn, and a blog post that describes this.
  • The heap profiler can now emit heap census data to the GHC event log, allowing heap profiles to be correlated with other tracing events (see Trac #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 Trac #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 Trac #11054)
  • Output of Event log data can now be configured. Enabling external tools to collect and analyze the event log data while the application is still running.
  • advapi32, shell32 and user32 are now automatically loaded in GHCi. libGCC is also loaded when a depencency requires it. See Trac #13189.

3.2.6. hsc2hs

  • Version number 0.68.2

3.3. Libraries

3.3.1. array

  • Version number 0.5.2.0 (was 0.5.0.0)

3.3.2. base

See changelog.md in the base package for full release notes.

  • Version number 4.10.0.0 (was 4.9.0.0)
  • Data.Either now provides fromLeft and fromRight
  • Data.Type.Coercion now provides gcoerceWith, which is analogous to gcastWith from Data.Type.Equality.
  • The Read1 and Read2 classes in Data.Functor.Classes have new methods, liftReadList(2) and liftReadListPrec(2), that are defined in terms of ReadPrec instead of ReadS. This matches the interface 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
  • Add GHC.TypeNats module with Natural-based KnownNat. The Nat operations in GHC.TypeLits are a thin compatibility layer on top. Note: the KnownNat evidence is changed from an Integer to a Natural.
  • liftA2 is now a method of the Applicative class. Traversable deriving has been modified to use liftA2 for the first two elements traversed in each constructor. liftA2 is not yet in the Prelude, and must currently be imported from Control.Applicative. It is likely to be added to the Prelude in the future.

3.3.3. binary

  • Version number 0.8.5.1 (was 0.7.1.0)

3.3.4. bytestring

  • Version number 0.10.8.2 (was 0.10.4.0)

3.3.5. Cabal

  • Version number 2.0.0.0 (was 1.24.2.0)

3.3.6. containers

  • Version number 0.5.10.2 (was 0.5.4.0)

3.3.7. deepseq

  • Version number 1.4.3.0 (was 1.3.0.2)

3.3.8. directory

  • Version number 1.3.0.2 (was 1.2.0.2)

3.3.9. filepath

  • Version number 1.4.1.2 (was 1.3.0.2)

3.3.10. ghc

  • Version number 8.2.1

3.3.11. ghc-boot

  • This is an internal package. Use with caution.

3.3.12. ghc-compact

The ghc-compact library provides an experimental API for placing immutable data structures into a contiguous memory region. Data in these regions is not traced during garbage collection and can be serialized to disk or over the network.

  • Version number 0.1.0.0 (newly added)

3.3.13. ghc-prim

  • Version number 0.5.1.0 (was 0.3.1.0)
  • Added new isByteArrayPinned# and isMutableByteArrayPinned# operation.
  • New function noinline in GHC.Magic lets you mark that a function should not be inlined. It is optimized away after the simplifier runs.

3.3.14. hoopl

  • Version number 3.10.2.2 (was 3.10.2.1)

3.3.15. hpc

  • Version number 0.6.0.3 (was 0.6.0.2)

3.3.16. integer-gmp

  • Version number 1.0.0.1 (was 1.0.0.1)

3.3.17. process

  • Version number 1.6.1.0 (was 1.4.3.0)

3.3.18. template-haskell

  • Version 2.12.0.0 (was 2.11.1.0)
  • Added support for unboxed sums Trac #12478.
  • Added support for visible type applications Trac #12530.

3.3.19. time

  • Version number 1.8.0.1 (was 1.6.0.1)

3.3.20. unix

  • Version number 2.7.2.2 (was 2.7.2.1)

3.3.21. Win32

  • Version number 2.5.4.1 (was 2.3.1.1)

3.4. Known bugs