3. Release notes for version 8.8.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.6.1 release.
3.1. Highlights¶
The highlights, since the 8.6.1 release, are:
- Many, many bug fixes.
- A new code layout algorithm for x86.
3.2. Full details¶
3.2.1. Language¶
GHC now supports visible kind applications, as described in GHC proposal #15. This extends the existing visible type applications feature to permit type applications at the type level (e.g.,
f :: Proxy ('Just @Bool 'True)
) in addition to the term level (e.g.,g = Just @Bool True
).GHC now allows explicitly binding type variables in type family instances and rewrite rules, as described in GHC proposal #7. For instance:
type family G a b where forall x y. G [x] (Proxy y) = Double forall z. G z z = Bool {-# RULES "example" forall a. forall (x :: a). id x = x #-}
ScopedTypeVariables
: The type variable that a type signature on a pattern can bring into scope can now stand for arbitrary types. Previously, they could only stand in for other type variables, but this restriction was deemed unnecessary in GHC proposal #29. Also see Trac #15050.The pattern-match coverage checker now checks for cases that are unreachable due to constructors have strict argument types. For instance, in the following example:
data K = K1 | K2 !Void f :: K -> () f K1 = ()
K2
cannot be matched on inf
, since it is impossible to construct a terminating value of typeVoid
. Accordingly, GHC will not warn aboutK2
(whereas previous versions of GHC would).(!)
and(.)
are now valid type operators:type family a ! b type family a . b
forall
is now always a keyword in types to provide more helpful error messages when-XExplicitForall
is off.An existential context no longer requires parenthesization:
class a + b data D1 = forall a b. (a + b) => D1 a b data D2 = forall a b. a + b => D2 a b -- now allowed
{-# UNPACK #-}
annotation no longer requires parenthesization:data T = MkT1 { a :: {-# UNPACK #-} (Maybe Int && Bool) } | MkT2 { a :: {-# UNPACK #-} Maybe Int && Bool } -- now allowed data G where MkG1 :: {-# UNPACK #-} (Maybe Int && Bool) -> G MkG2 :: {-# UNPACK #-} Maybe Int && Bool -> G -- now allowed
The requirement that kind signatures always be parenthesized has been relaxed. For instance, it is now permissible to write
Proxy '(a :: A, b :: B)
(previous GHC versions required extra parens:Proxy '((a :: A), (b :: B))
).-Woverflowed-literals
checks all literals. Previously, it would only inspect boxed expression literals.-Wempty-enumerations
now also works forNumeric.Natural
.
3.2.2. Compiler¶
- The final phase of the
MonadFail
proposal has been implemented. Accordingly, theMonadFailDesugaring
language extension is now deprecated, as its effects are always enabled. Similarly, the-Wnoncanonical-monadfail-instances
flag is also deprecated, as there is no longer any way to define a “non-canonical”Monad
orMonadFail
instance. - New
-keep-hscpp-files
to keep the output of the CPP pre-processor. - The
-Wcompat
warning group now includes-Wstar-is-type
. - The
-fllvm-pass-vectors-in-regs
flag is now deprecated as vector arguments are now passed in registers by default. - The
-fblock-layout-cfg
flag enables a new code layout algorithm on x86. This is enabled by default at-O
and-O2
. - The deprecated ghc-flag
-Wamp
has been removed. - Add new
-Wmissing-deriving-strategies
flag that warns users when they are not taking advantage ofDerivingStrategies
. The warning is supplied at eachderiving
site. - When loading modules that use
UnboxedTuples
into GHCi, it will now automatically enable -fobject-code for these modules and all modules they depend on. Before this change, attempting to load these modules into the interpreter would just fail, and the only convenient workaround was to enable -fobject-code for all modules.
3.2.3. Runtime system¶
- Add and document new FFI functions
hs_lock_stable_ptr_table
andhs_unlock_stable_ptr_table
. These replace the undocumented functionshs_lock_stable_tables
andhs_unlock_stable_tables
, respectively. The latter should now be considered deprecated. - Document the heretofore undocumented FFI function
hs_free_stable_ptr_unsafe
, used in conjunction with manual locking and unlocking. - The runtime linker on Windows has been overhauled to properly handle section alignment, lower the amount of wasted memory and lower the amount of in use memory. See Trac #13617. Note that committed memory may be slightly higher.
- The output filename used for eventlog output can now be
specified with the
-ol
flag. - Add support for generating a new type of output: extended interfaces files.
Generation of these files, which sport a
.hie
suffix, is enabled via the-fwrite-ide-info
flag. See Options related to extended interface files for more information.
3.2.4. Template Haskell¶
Reifying type classes no longer shows redundant class type variables and contexts in the type signature of each class method. For instance, reifying the following class:
class C a where method :: a
Used to produce the following:
class C a where method :: forall a. C a => a
Where the
forall a. C a =>
part is entirely redundant. This part is no longer included when reifyingC
. It’s possible that this may break some code which assumes the existence offorall a. C a =>
.Template Haskell has been updated to support visible kind applications and explicit
foralls
in type family instances andRULES
. These required a couple of backwards-incompatible changes to thetemplate-haskell
API. Please refer to the GHC 8.8 Migration Guide for more details.Template Haskell now supports implicit parameters and recursive do.
Template Haskell splices can now embed assembler source (Trac #16180)
3.2.5. ghc-prim
library¶
- GHC now exposes a new primop,
traceBinaryEvent#
. This primop writes eventlog events similar totraceBinaryEvent#
but allows the user to pass the event payload as a binary blob instead of aString
. - The
StableName#
type parameter now has a phantom role instead of a representational one. There is really no reason to care about the type of the underlying object.
3.2.6. ghc
library¶
3.2.7. base
library¶
The final phase of the
MonadFail
proposal has been implemented. As a result of this change:- The
fail
method ofMonad
has been removed in favor of the method of the same name in theMonadFail
class. MonadFail(fail)
is now re-exported from thePrelude
andControl.Monad
modules.
These are breaking changes that may require you to update your code. Please refer to the GHC 8.8 Migration Guide for more details.
- The
- Support the characters from recent versions of Unicode (up to v. 12) in literals
(see Trac #5518).
The
StableName
type parameter now has a phantom role instead of a representational one. There is really no reason to care about the type of the underlying object.The functions
zipWith3
andzip3
inPrelude
can now fuse, together withzipWith4
tozipWith7
as well as their tuple counterparts inData.List
.
3.2.8. Build system¶
- Configure: Add ALEX and HAPPY variables to explicitly set the alex and happy programs to use.
- Configure: Deprecate –with-ghc=ARG in favour of the GHC variable.
3.3. Included libraries¶
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.8.0.20190613 | The compiler itself |
Cabal | 3.0.0.0 | Dependency of ghc-pkg utility |
Win32 | 2.6.1.0 | Dependency of ghc library |
array | 0.5.4.0 | Dependency of ghc library |
base | 4.13.0.0 | Core library |
binary | 0.8.7.0 | Dependency of ghc library |
bytestring | 0.10.9.0 | Dependency 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.2 | Dependency of ghc library |
filepath | 1.4.2.1 | Dependency of ghc library |
ghc-boot-th | 8.8.0.20190613 | Internal compiler library |
ghc-boot | 8.8.0.20190613 | Internal compiler library |
ghc-compact | 0.1.0.0 | Core library |
ghc-heap | 8.8.0.20190613 | GHC heap-walking library |
ghc-prim | 0.5.3 | Core library |
ghci | 8.8.0.20190613 | The REPL interface |
haskeline | 0.7.5.0 | Dependency of ghci executable |
hpc | 0.6.0.3 | Dependency of hpc executable |
integer-gmp | 1.0.2.0 | Core library |
libiserv | 8.8.0.20190613 | Internal compiler library |
mtl | 2.2.2 | Dependency of Cabal library |
parsec | 3.1.13.0 | Dependency of Cabal library |
pretty | 1.1.3.6 | Dependency of ghc library |
process | 1.6.5.1 | Dependency of ghc library |
stm | 2.5.0.0 | Dependency of haskeline library |
template-haskell | 2.15.0.0 | Core library |
terminfo | 0.4.1.4 | Dependency of haskeline library |
text | 1.2.3.1 | Dependency of Cabal library |
time | 1.9.3 | 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 |