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 Trac #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 -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 Trac #11744). This can be done by passing something like --with-nm=$(xcrun --find nm-classic) to configure.
The highlights, since the 7.10 series, are:
-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 Kind polymorphism and 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 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 <interactive>:2:1 in interactive:Ghci1
prints the call-site of errorWithCallStack.
See 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 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 Import and export of 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 -XUndecidableSuperClasses language extension, which relaxes GHC’s recursive superclass check (see Trac #10318). 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 Trac #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
-XDeriveFoldable and -XDeriveTraversable now generate code without superfluous mempty or pure expressions. As a result, -XDeriveTraversable now works on datatypes that contain arguments which have unlifted types.
Note that the -XImpredicativeTypes extension, which has been known to be broken for many years, is even more broken than usual in this release (see Trac #11319, Trac #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 -XImpredicativeTypes. Users of -XImpredicativeTypes do so at their own risk!
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 -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.
-ddump-strsigs has been renamed to -ddump-str-signatures.
-XDeriveGeneric is now less picky about instantiating type arguments when deriving (Trac #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 -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=<n>. If the set number of iterations is exceeded, an informative warning is issued.
-this-package-key has been renamed again (hopefully for the last time!) to -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. -this-package-key is deprecated; you should use -this-unit-id or, if you need compatibility over multiple versions of GHC, -package-name.
When -fdefer-type-errors is enabled and an expression fails to typecheck, Control.Exception.TypeError will now be thrown instead of Control.Exception.ErrorCall.
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
See changelog.md in the base package for full release notes.
Version number 4.9.0.0 (was 4.8.2.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 datatypes in GHC.Generics now have Enum, Bounded, Ix, Functor, Applicative, Monad, MonadFix, MonadPlus, MonadZip, Foldable, Foldable, Traversable, Generic1, and Data instances as appropriate. (Trac #9043)
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).
Add the TypeError datatype to Control.Exception, which represents the error that is thrown when an expression fails to typecheck when run using -fdefer-type-errors. (see Trac #10284)