3. 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.

3.1. Highlights

The highlights, since the 7.10 branch, are:

3.2. Full details

3.2.1. Language

  • TODO FIXME.

  • 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
    
  • Implicit parameters of the new base type GHC.Stack.CallStack are treated specially in function calls, the solver automatically appends the source location of the call to the CallStack in the environment. For example

    myerror :: (?callStack :: CallStack) => String -> a
    myerror msg = error (msg ++ "\n" ++ prettyCallStack ?callStack)
    
    ghci> myerror "die"
    *** Exception: die
    CallStack (from ImplicitParams):
      myerror, called at <interactive>:2:1 in interactive:Ghci1
    

    prints the call-site of myerror. The name of the implicit parameter does not matter, but within base we call it ?callStack.

    See base for a description of the CallStack type.

  • GHC now supports visible type application, allowing programmers to easily specify how type parameters should be instantiated when calling a function. See 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 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 Injective type families for details.

  • Due to a security issue, Safe Haskell now forbids annotations in programs marked as -XSafe.

  • Generic instances can be derived for data types whose constructors have arguments with certain unlifted types. See Generic programming for more details.

  • GHC generics can now provide strictness information for fields in a data constructor via the Selector type class.

  • The -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 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.

3.2.2. Compiler

  • 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 -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 -ddump-to-file with -ddump-splices but it always generates a file instead of being coupled to -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 -fprint-expanded-types. When enabled, GHC also prints type-synonym-expanded types in type errors.
  • Added the option -fcpr-anal. When enabled, the demand analyser performs CPR analysis. It is implied by -O. Consequently, -fcpr-off is now removed, run with -fno-cpr-anal to get the old -fcpr-off behaviour.
  • Added the option -fworker-wrapper. When enabled, the worker-wrapper transformation is performed after a strictness analysis pass. It is implied by -O and by -fstrictness. It is disabled by -fno-strictness. Enabling -fworker-wrapper while strictness analysis is disabled (by -fno-strictness) has no effect.
  • Added the options -Wmissed-specialisations and -Wall-missed-specialisations. When enabled, the simplifier will produce a warning when a overloaded imported function cannot be specialised (typically due to a missing INLINEABLE pragma). This is intended to alert users to cases where they apply INLINEABLE but may not get the speed-up they expect.
  • Added the option -Wnoncanonical-monad-instances which helps detect noncanonical Applicative/Monad instance definitions. See flag description in Warnings and sanity-checking for more details.
  • When printing an out-of-scope error message, GHC will give helpful advice if the error might be caused by too restrictive imports.
  • Added the -Wcompat warning group, along with its opposite -Wno-compat. Turns on warnings that will be enabled by default in the future, but remain off in normal compilations for the time being. This allows library authors eager to make their code future compatible to adapt to new features before they even generate warnings.
  • Added the -Wmissing-monadfail-instance flag. When enabled, this will issue a warning if a failable pattern is used in a context that does not have a MonadFail constraint. This flag represents phase 1 of the MonadFail Proposal (MFP).
  • Added the -Wsemigroup flag. When enabled, this will issue a warning if a type is an instance of Monoid but not Semigroup, and when a custom definition (<>) is made. Fixing these warnings makes sure the definition of Semigroup as a superclass of Monoid does not break any code.
  • Added the -Wmissing-pat-syn-sigs flag. When enabled, this will issue a warning when a pattern synonym definition doesn’t have a type signature. It is turned off by default but enabled by -Wall.
  • Changed the -fwarn-unused-matches flag to report unused type variables in data and type families in addition to its previous behaviour. To avoid warnings, unused type variables should be prefixed or replaced with underscores.
  • Added the -Wtoo-many-guards flag. When enabled, this will issue a warning if a pattern match contains too many guards (over 20 at the moment). Makes a difference only if pattern match checking is also enabled.
  • Added the -ffull-guard-reasoning flag. When enabled, pattern match checking tries its best to reason about guards. Since the additional expressivity may come with a high price in terms of compilation time and memory consumption, it is turned off by default.

3.2.3. GHCi

  • Main with an explicit module header but without main is now an error (Trac #7765).
  • The :back and :forward commands now take an optional count allowing the user to move forward or backward in history several steps at a time.
  • Added commands :load! and :reload!, effectively setting -fdefer-type-errors before loading a module and unsetting it after loading if it has not been set before (Trac #8353).
  • ghci -e now behaves like ghc -e (Trac #9360).
  • Added support for top-level function declarations (Trac #7253).
  • The new commands :all-types, :loc-at, :type-at, and :uses designed for editor-integration (such as Emacs’ haskell-mode) originally premiered by ghci-ng have been integrated into GHCi (Trac #10874).

3.2.4. Template Haskell

  • The new -XTemplateHaskellQuotes flag allows to use the quotes (not quasi-quotes) subset of TemplateHaskell. This is particularly useful for use with a stage 1 compiler (i.e. GHC without interpreter support). Also, -XTemplateHaskellQuotes is considered safe under Safe Haskell.
  • The __GLASGOW_HASKELL_TH__ CPP constant denoting support for -XTemplateHaskell introduced in GHC 7.10.1 has been changed to use the values 1/0 instead of the previous YES/NO values.
  • Partial type signatures can now be used in splices, see Where can they occur?.
  • Template Haskell now fully supports typed holes and quoting unbound variables. This means it is now possible to use pattern splices nested inside quotation brackets.
  • Template Haskell now supports the use of UInfixT in types to resolve infix operator fixities, in the same vein as UInfixP and UInfixE in patterns and expressions. ParensT and InfixT have also been introduced, serving the same functions as their pattern and expression counterparts.
  • Template Haskell has now explicit support for representing GADTs. Until now GADTs were encoded using NormalC, RecC (record syntax) and ForallC constructors. Two new constructors - GadtC and RecGadtC - are now supported during quoting, splicing and reification.
  • Primitive chars (e.g., [| 'a'# |]) and primitive strings (e.g., [| "abc"# |]) can now be quoted with Template Haskell. The Lit data type also has a new constructor, CharPrimL, for primitive char literals.
  • addTopDecls now accepts annotation pragmas.
  • Internally, the implementation of quasi-quotes has been unified with that of normal Template Haskell splices. Under the previous implementation, top-level declaration quasi-quotes did not cause a break in the declaration groups, unlike splices of the form $(...). This behavior has been preserved under the new implementation, and is now recognized and documented in Syntax.
  • The Lift class is now derivable via the -XDeriveLift extension. See Deriving Lift instances for more information.
  • The FamilyD data constructor and FamFlavour data type have been removed. Data families are now represented by DataFamilyD and open type families are now represented by OpenTypeFamilyD instead of FamilyD. Common elements of OpenTypeFamilyD and ClosedTypeFamilyD have been moved to TypeFamilyHead.
  • The representation of data, newtype, data instance, and newtype instance declarations has been changed to allow for multi-parameter type classes in the deriving clause. In particular, dataD and newtypeD now take a CxtQ instead of a [Name] for the list of derived classes.
  • isExtEnabled can now be used to determine whether a language extension is enabled in the Q monad. Similarly, extsEnabled can be used to list all enabled language extensions.
  • One can now reify the strictness information of a constructors’ fields using Template Haskell’s reifyConStrictness function, which takes into account whether flags such as -XStrictData or -funbox-strict-fields are enabled.

3.2.5. Runtime system

  • Support for performance monitoring with PAPI has been dropped.
  • -maxN⟨x⟩ flag added to complement -N. It will choose to use at most ⟨x⟩ capabilities, limited by the number of processors as -N is.

3.2.6. Build system

  • TODO FIXME.

3.2.7. Package system

  • TODO FIXME.

3.2.8. hsc2hs

  • hsc2hs now supports the #alignment macro, which can be used to calculate the alignment of a struct in bytes. Previously, #alignment had to be implemented manually via a #let directive, e.g.,

    #let alignment t = "%lu", (unsigned long)offsetof(struct {char x__; t (y__); }, y__)
    

    As a result, if you have the above directive in your code, it will now emit a warning when compiled with GHC 8.0.

    Module.hsc:24:0: warning: "hsc_alignment" redefined [enabled by default]
    In file included from dist/build/Module_hsc_make.c:1:0:
    /path/to/ghc/lib/template-hsc.h:88:0: note: this is the location of the previous definition
     #define hsc_alignment(t...) \
     ^
    

    To make your code free of warnings on GHC 8.0 and still support earlier versions, surround the directive with a pragma checking for the right GHC version.

    #if __GLASGOW_HASKELL__ < 800
    #let alignment t = "%lu", (unsigned long)offsetof(struct {char x__; t (y__); }, y__)
    #endif
    

3.3. Libraries

3.3.1. array

  • Version number XXXXX (was 0.5.0.0)

3.3.2. base

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

  • Version number 4.9.0.0 (was 4.7.0.0)

  • GHC.Stack exports two new types SrcLoc and CallStack. A SrcLoc contains package, module, and file names, as well as start and end positions. A CallStack is essentially a [(String, SrcLoc)], sorted by most-recent call.

  • error and undefined will now report a partial stack-trace using the new CallStack feature (and the -prof stack if available).

  • A new function, interruptible, was added to GHC.IO allowing an IO action to be run such that it can be interrupted by an asynchronous exception, even if exceptions are masked (except if masked with interruptibleMask).

    This was introduced to fix the behavior of allowInterrupt, which would previously incorrectly allow exceptions in uninterruptible regions (see Trac #9516).

  • Per-thread allocation counters (setAllocationCounter and getAllocationCounter) and limits (enableAllocationLimit, disableAllocationLimit are now available from System.Mem. Previously this functionality was only available from GHC.Conc.

  • forever, filterM, mapAndUnzipM, zipWithM, zipWithM_, replicateM, and replicateM were generalized from Monad to Applicative. If this causes performance regressions, try to make the implementation of (*>) match that of (>>) (see Trac #10168).

  • Add URec, UAddr, UChar, UDouble, UFloat, UInt, and UWord to GHC.Generics as part of making GHC generics capable of handling unlifted types (Trac #10868)

  • Expand Floating class to include operations that allow for better precision: log1p, expm1, log1pexp and log1mexp. These are not available from Prelude, but the full class is exported from Numeric.

  • Add Data.List.NonEmpty and Data.Semigroup (to become super-class of Monoid in the future). These modules were provided by the semigroups package previously. (Trac #10365)

  • Add GHC.TypeLits.TypeError and ErrorMessage to allow users to define custom compile-time error messages. (see Custom compile-time errors and the original proposal).

  • The Generic instance for Proxy is now poly-kinded (see Trac #10775)

  • The IsString instance for [Char] has been modified to eliminate ambiguity arising from overloaded strings and functions like (++).

  • Move Const from Control.Applicative to its own module in Data.Functor.Const. (see Trac #11135)

  • Enable PolyKinds in the Data.Functor.Const module to give Const the kind * -> k -> * (see Trac #10039).

3.3.3. binary

  • Version number XXXXX (was 0.7.1.0)

3.3.4. bytestring

  • Version number XXXXX (was 0.10.4.0)

3.3.5. Cabal

  • Version number XXXXX (was 1.18.1.3)

3.3.6. containers

  • Version number XXXXX (was 0.5.4.0)

3.3.7. deepseq

  • Version number XXXXX (was 1.3.0.2)

3.3.8. directory

  • Version number XXXXX (was 1.2.0.2)

3.3.9. filepath

  • Version number XXXXX (was 1.3.0.2)

3.3.10. ghc

  • TODO FIXME.
  • The HsBang type has been removed in favour of HsSrcBang and HsImplBang. Data constructors now always carry around their strictness annotations as the user wrote them, whether from an imported module or not.
  • Moved startsVarSym, startsVarId, startsConSym, startsConId, startsVarSymASCII, and isVarSymChar from Lexeme to the GHC.Lemexe module of the ghc-boot library.
  • Add isImport, isDecl, and isStmt functions.

3.3.11. ghc-boot

  • This is an internal package. Use with caution.
  • This package was renamed from bin-package-db to reflect its new purpose of containing intra-GHC functionality that needs to be shared across multiple GHC boot libraries.
  • Added GHC.Lexeme, which contains functions for determining if a character can be the first letter of a variable or data constructor in Haskell, as defined by GHC. (These functions were moved from Lexeme in ghc.)
  • Added GHC.LanguageExtensions which contains a type listing all supported language extensions.

3.3.12. ghc-prim

  • Version number XXXXX (was 0.3.1.0)

3.3.13. haskell98

  • Version number XXXXX (was 2.0.0.3)

3.3.14. haskell2010

  • Version number XXXXX (was 1.1.1.1)

3.3.15. hoopl

  • Version number XXXXX (was 3.10.0.0)

3.3.16. hpc

  • Version number XXXXX (was 0.6.0.1)

3.3.17. integer-gmp

  • Version number XXXXX (was 0.5.1.0)

3.3.18. old-locale

  • Version number XXXXX (was 1.0.0.6)

3.3.19. old-time

  • Version number XXXXX (was 1.1.0.2)

3.3.20. process

  • Version number XXXXX (was 1.2.0.0)

3.3.21. template-haskell

  • Version number XXXXX (was 2.9.0.0)
  • The Lift type class for lifting values into Template Haskell splices now has a default signature lift :: Data a => a -> Q Exp, which means that you do not have to provide an explicit implementation of lift for types which have a Data instance. To manually use this default implementation, you can use the liftData function which is now exported from Language.Haskell.TH.Syntax.
  • Info‘s constructors no longer have Fixity fields. A qReifyFixity function was added to the Quasi type class (as well as the reifyFixity function, specialized for Q) to allow lookup of fixity information for any given Name.

3.3.22. time

  • Version number XXXXX (was 1.4.1)

3.3.23. unix

  • Version number XXXXX (was 2.7.0.0)

3.3.24. Win32

  • Version number XXXXX (was 2.3.0.1)

3.4. Known bugs

  • TODO FIXME