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.2.1 release.
Note
This compiling this release requires GCC 4.7 or newer due to Trac #14244.
The highlights, since the 8.2.1 release, are:
Data families have been generalised a bit: a data family declaration can now end with a kind variable k instead of Type. Additionally, data/newtype instance no longer need to list all the patterns of the family if they don’t wish to; this is quite like how regular datatypes with a kind signature can omit some type variables.
There are now fewer restrictions regarding whether kind variables can appear on the right-hand sides of type and data family instances. Before, there was a strict requirements that all kind variables on the RHS had to be explicitly bound by type patterns on the LHS. Now, kind variables can be implicitly bound, which allows constructions like these:
data family Nat :: k -> k -> *
-- k is implicitly bound by an invisible kind pattern
newtype instance Nat :: (k -> *) -> (k -> *) -> * where
Nat :: (forall xx. f xx -> g xx) -> Nat f g
class Funct f where
type Codomain f :: *
instance Funct ('KProxy :: KProxy o) where
-- o is implicitly bound by the kind signature
-- of the LHS type pattern ('KProxy)
type Codomain 'KProxy = NatTr (Proxy :: o -> *)
Implicitly bidirectional pattern synonyms no longer allow bang patterns (!) or irrefutable patterns (~) on the right-hand side. Previously, this was allowed, although the bang patterns and irrefutable patterns would be silently ignored when used in an expression context. This is now a proper error, and explicitly bidirectional pattern synonyms should be used in their stead. That is, instead of using this (which is an error):
data StrictJust a = Just !a
Use this:
data StrictJust a <- Just !a where
StrictJust !a = Just a
GADTs with kind-polymorphic type arguments now require -XTypeInType. For instance, consider the following,
data G :: k -> * where
GInt :: G Int
GMaybe :: G Maybe
In previous releases this would compile with -XPolyKinds alone due to bug Trac #13391. As of GHC 8.4, however, this requires -XTypeInType. Note that since GADT kind signatures aren’t generalized, this will also require that you provide a CUSK by explicitly quantifying over the kind argument, k,
data G :: forall k. k -> * where
GInt :: G Int
GMaybe :: G Maybe
The order in which type variables are quantified in GADT constructor type signatures has changed. Before, if you had MkT as below:
data T a where
MkT :: forall b a. b -> T a
Then the type of MkT would (counterintuitively) be forall a b. b -> T a! Now, GHC quantifies the type variables in the order that the users writes them, so the type of MkT is now forall b a. b -> T a (this matters for -XTypeApplications).
The new -XEmptyDataDeriving extension allows deriving Eq, Ord, Read, and Show instances directly for empty data types, as in data Empty deriving Eq. (Previously, this would require the use of -XStandaloneDeriving to accomplish.)
One can also now derive Data instances directly for empty data types (as in data Empty deriving Data) without needing to use -XStandaloneDeriving. However, since already requires a GHC extension (-XDeriveDataTypeable), one does not need to enable -XEmptyDataDeriving to do so. This also goes for other classes which require extensions to derive, such as -XDeriveFunctor.
Hexadecimal floating point literals (e.g. 0x0.1p4), enabled with -XHexFloatLiterals. See Hexadecimal floating point literals for the full details.
LLVM code generator (e.g. -fllvm) compatible with LLVM releases in the 5.0 series.
Add warning flag -Wmissing-export-lists which causes the type checker to warn when a module does not include an explicit export list.
The configure script now no longer accepts --with-TOOL flags (e.g. --with-nm, --with-ld, etc.). Instead, these are taken from environment variables, as is typical in autoconf scripts. For instance, ./configure --with-nm=/usr/local/bin/nm turns into ./configure NM=/usr/local/bin/nm.
Derived Functor, Foldable, and Traversable instances are now optimized when their last type parameters have phantom roles. Specifically,
fmap _ = coerce
traverse _ x = pure (coerce x)
foldMap _ _ = mempty
These definitions of foldMap and traverse are lazier than the ones we would otherwise derive, as they may produce results without inspecting their arguments at all.
See also Deriving Functor instances, Deriving Foldable instances, and Deriving Traversable instances.
Derived instances for empty data types are now substantially different than before. Here is an overview of what has changed. These examples will use a running example of data Empty a to describe what happens when an instance is derived for Empty:
Derived Eq and Ord instances would previously emit code that used error:
instance Eq (Empty a) where
(==) = error "Void =="
instance Ord (Empty a) where
compare = error "Void compare"
Now, they emit code that uses maximally defined, lazier semantics:
instance Eq (Empty a) where
_ == _ = True
instance Ord (Empty a) where
compare _ _ = EQ
Derived Read instances would previous emit code that used parens:
instance Read (Empty a) where
readPrec = parens pfail
But parens forces parts of the parsed string that it doesn’t need to. Now, the derived instance will not use parens (that it, parsing Empty will always fail, without reading any input):
instance Read (Empty a) where
readPrec = pfail
Derived Show instances would previously emit code that used error:
instance Show (Empty a) where
showsPrec = "Void showsPrec"
Now, they emit code that inspects the argument. That is, if the argument diverges, then showing it will also diverge:
instance Show (Empty a) where
showsPrec _ x = case x of {}
Derived Functor, Foldable, Traversable, Generic, Generic1, Lift, and Data instances previously emitted code that used error:
instance Functor Empty where
fmap = error "Void fmap"
instance Foldable Empty where
foldMap = error "Void foldMap"
instance Traversable Empty where
traverse = error "Void traverse"
instance Generic (Empty a) where
from = M1 (error "No generic representation for empty datatype Empty")
to (M1 _) = error "No values for empty datatype Empty"
-- Similarly for Generic1
instance Lift (Empty a) where
lift _ = error "Can't lift value of empty datatype Empty"
instance Data a => Data (Empty a) where
gfoldl _ _ _ = error "Void gfoldl"
toConstr _ = error "Void toConstr"
...
Now, derived Functor, Traversable, ``Generic, Generic1, Lift, and Data instances emit code which inspects their arguments:
instance Functor Empty where
fmap _ x = case x of {}
instance Traversable Empty where
traverse _ x = pure (case x of {})
instance Generic (Empty a) where
from x = M1 (case x of {})
to (M1 x) = case x of {}
-- Similarly for Generic1
instance Lift (Empty a) where
lift x = pure (case x of {})
instance Data a => Data (Empty a) where
gfoldl _ x = case x of {}
toConstr x = case x of {}
...
Derived Foldable instances now are maximally lazy:
instance Foldable Empty where
foldMap _ _ = mempty
Derived Foldable instances now derive custom definitions for null instead of using the default one. This leads to asymptotically better performance for recursive types not shaped like cons-lists, and allows null to terminate for more (but not all) infinitely large structures.
Configure on Windows now supports the --enable-distro-toolchain configure flag, which can be used to build a GHC using compilers on your PATH instead of using the bundled bindist. See Trac #13792
GHC now enables -fllvm-pass-vectors-in-regs by default. This means that GHC will now use native vector registers to pass vector arguments across function calls.
The optional instance keyword is now usable in type family instance declarations. See Trac #13747
Lots of other bugs. See Trac for a complete list.
New flags -fignore-optim-changes and -fignore-hpc-changes allow GHC to reuse previously compiled modules even if they were compiled with different optimisation or HPC flags. These options are enabled by default by --interactive. See Trac #13604
Template Haskell now reifies data types with GADT syntax accurately. Previously, TH used heuristics to determine whether a data type should be reified using GADT syntax, which could lead to incorrect results, such as data T1 a = (a ~ Int) => MkT1 being reified as a GADT and data T2 a where MkT2 :: Show a => T2 a not being reified as a GADT.
In addition, reified GADT constructors now more accurately track the order in which users write type variables. Before, if you reified MkT as below:
data T a where
MkT :: forall b a. b -> T a
Then the reified type signature of MkT would have been headed by ForallC [PlainTV a, PlainTV b]. Now, reifying MkT will give a type headed by ForallC [PlainTV b, PlainTV a], as one would expect.
Language.Haskell.TH.FamFlavour, which was deprecated in GHC 8.2, has been removed.
hsSyn Abstract Syntax Tree (AST) is now extensible via the mechanism described in Trees that Grow
The main change for users of the GHC API is that the AST is no longer indexed by the type used as the identifier, but by a specific index type,
type GhcPs = GhcPass 'Parsed -- Old 'RdrName' type param
type GhcRn = GhcPass 'Renamed -- Old 'Name' type param
type GhcTc = GhcPass 'Typechecked -- Old 'Id' type para,
type GhcTcId = GhcTc -- Old 'TcId' type param
The simplest way to support the current GHC as well as earlier ones is to define
#if MIN_VERSION_ghc(8,3,0)
type ParseI = GhcPs
type RenameI = GhcRn
type TypecheckI = GhcTc
#else
type ParseI = RdrName
type RenameI = Name
type TypecheckI = Var
#endif
and then replace all hardcoded index types accordingly. For polymorphic types, the constraint
#if MIN_VERSION_ghc(8,3,0)
-- |bundle up the constraints required for a trees that grow pass
type IsPass pass = (DataId pass, OutputableBndrId pass, SourceTextX pass)
else
type IsPass pass = (DataId pass, OutputableBndrId pass)
#endif
can be used.
The package database provided with this distribution also contains a number of packages other than GHC itself. See the changelogs provided with these packages for further change information.
Package | Version | Reason for inclusion |
---|---|---|
ghc | 8.4.0.20180204 | The compiler itself |
Cabal | 2.1.0.0 | Dependency of ghc-pkg utility |
Win32 | 2.6.1.0 | Dependency of ghc library |
array | 0.5.2.0 | Dependency of ghc library |
base | 2.1 | Core library |
binary | 0.8.5.1 | Dependency of ghc library |
bytestring | 0.10.8.2 | Deppendency of ghc library |
containers | 0.5.11.0 | Dependency of ghc library |
deepseq | 1.4.3.0 | Dependency of ghc library |
directory | 1.3.1.5 | Dependency of ghc library |
filepath | 1.4.2 | Dependency of ghc library |
ghc-boot | 8.4.0.20180204 | Internal compiler library |
ghc-compact | 0.1.0.0 | Core library |
ghc-prim | 2.1 | Core library |
ghci | 8.4.0.20180204 | The REPL interface |
haskeline | 0.7.4.0 | Dependency of ghci executable |
hpc | 0.6.0.3 | Dependency of hpc executable |
integer-gmp | 1.0.1.0 | Core library |
mtl | 2.2.2 | Dependency of Cabal library |
parsec | 3.1.12 | Dependency of Cabal library |
process | 1.6.3.0 | Dependency of ghc library |
template-haskell | 2.13.0.0 | Core library |
text | 1.2.3.0 | Dependency of Cabal library |
time | 1.8.0.2 | Dependency of ghc library |
transformers | 0.5.4.0 | Dependency of ghc library |
unix | 2.7.2.2 | Dependency of ghc library |
xhtml | 3000.2.2 | Dependency of haddock executable |