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.4.1 release.
The highlights, since the 8.4.1 release, are:
Use of quantified type variables in constraints is now allowed via the QuantifiedConstraints language extension. This long-awaited feature enables users to encode significantly more precision in their types. For instance, the common MonadTrans typeclass could now make the expectation that an applied transformer is must be a Monad
class (forall m. Monad m => Monad (t m)) => MonadTrans t where {- ... -}
Additionally, quantification can enable terminating instance resolution where this previously was not possible. See Quantified constraints for details.
A new DerivingVia language extension has been added which allows the use of the via deriving strategy. For instance:
newtype T = MkT Int
deriving Monoid via (Sum Int)
See Deriving via for more information.
A new StarIsType language extension has been added which controls whether * is parsed as Data.Kind.Type or a regular type operator. StarIsType is enabled by default.
GHC now permits the use of a wildcard type as the context of a standalone deriving declaration with the use of the PartialTypeSignatures language extension. For instance, this declaration:
deriving instance _ => Eq (Foo a)
Denotes a derived Eq (Foo a) instance, where the context is inferred in much the same way as ordinary deriving clauses do. See Partial Type Signatures.
Data declarations with empty where clauses are no longer valid without the extension GADTSyntax enabled. For instance, consider the following,
data T where
The grammar is invalid in Haskell2010. Previously it could be compiled successfully without GADTs. As of GHC 8.6.1, this is a parse error.
Incomplete patterns warning -Wincomplete-patterns is extended to guards in pattern bindings and if alternatives of MultiWayIf. For instance, consider the following,
foo :: Bool -> Int
foo b = if | b -> 1
In GHC 8.6.1, it will raise the warning:
<interactive>:2:12: warning: [-Wincomplete-patterns]
Pattern match(es) are non-exhaustive
In a multi-way if alternative:
Guards do not cover entire pattern space
See Trac #14773.
Scoped type variables now work in default methods of class declarations and in pattern synonyms in Template Haskell. See Trac #14885.
do expressions, lambda expressions, etc. to be directly used as a function argument, enabled with BlockArguments. See More liberal syntax for function arguments for the full details.
Underscores in numeric literals (e.g. 1_000_000), enabled with NumericUnderscores. See Numeric underscores for the full details.
CUSKs now require all kind variables to be explicitly quantified. This was already the case with TypeInType, but now PolyKinds also exhibits this behavior. This means that the following example is no longer considered to have a CUSK:
data T1 :: k -> Type -- No CUSK: `k` is not explicitly quantified
Functionality of TypeInType has been subsumed by PolyKinds, and it is now merely a shorthand for PolyKinds, DataKinds, and NoStarIsType. The users are advised to avoid TypeInType due to its misleading name: the Type :: Type axiom holds regardless of whether it is enabled.
GHC has become more diligent about catching illegal uses of kind polymorphism. For instance, GHC 8.4 would accept the following without the use of PolyKinds:
f :: forall k (a :: k). Proxy a
f = Proxy
This is now an error unless PolyKinds is enabled.
Type literals now could be used in type class instances without the extension FlexibleInstances.
See Trac #13833.
MonadFailDesugaring is now enabled by default. See MonadFail Proposal (MFP) for more details.
GHC’s plugin mechanism now offers plugin authors control over their plugin’s effect on recompilation checking. Specifically the Plugin record name has a new field
data Plugin = Plugin {
pluginRecompile :: [CommandLineOption] -> IO PluginRecompile
, {- ... -}
}
data PluginRecompile = ForceRecompile | NoForceRecompile | MaybeRecompile Fingerprint
Plugin based on defaultPlugin will have their previous recompilation behavior (ForceRecompile) preserved. However, plugins that are “pure” are encouraged to override this to either NoForceRecompile or MaybeRecompile. See Controlling Recompilation for details.
GHC now provides a class of new plugins: source plugins. These plugins can inspect and modify a variety of intermediate representations used by the compiler’s frontend. These include:
- The ability to modify the parser output
- The ability to inspect the renamer output
- The ability to modify the typechecked AST
- The ability to modify Template Haskell splices
- The ability to modify interface files as they are loaded
See Source plugins for details.
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.6.4 | The compiler itself |
Cabal | 2.4.0.1 | Dependency of ghc-pkg utility |
Win32 | 2.6.1.0 | Dependency of ghc library |
array | 0.5.3.0 | Dependency of ghc library |
base | 4.12.0.0 | Core library |
binary | 0.8.6.0 | Dependency of ghc library |
bytestring | 0.10.8.2 | Deppendency of ghc library |
containers | 0.6.0.1 | Dependency of ghc library |
deepseq | 1.4.4.0 | Dependency of ghc library |
directory | 1.3.3.0 | Dependency of ghc library |
filepath | 1.4.2.1 | Dependency of ghc library |
ghc-boot | 8.6.4 | Internal compiler library |
ghc-compact | 0.1.0.0 | Core library |
ghc-prim | 0.5.3 | Core library |
ghci | 8.6.4 | The REPL interface |
haskeline | 0.7.4.3 | Dependency of ghci executable |
hpc | 0.6.0.3 | Dependency of hpc executable |
integer-gmp | 1.0.2.0 | Core library |
mtl | 2.2.2 | Dependency of Cabal library |
parsec | 3.1.13.0 | Dependency of Cabal library |
process | 1.6.5.0 | Dependency of ghc library |
template-haskell | 2.14.0.0 | Core library |
text | 1.2.3.1 | Dependency of Cabal library |
time | 1.8.0.2 | Dependency of ghc library |
transformers | 0.5.6.2 | Dependency of ghc library |
unix | 2.7.2.2 | Dependency of ghc library |
xhtml | 3000.2.2.1 | Dependency of haddock executable |