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

4.1. Highlights

The highlights, since the 8.6.1 release, are:

  • Many, many bug fixes.
  • A new code layout algorithm for x86.

4.2. Full details

4.2.1. Language

  • 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 in f, since it is impossible to construct a terminating value of type Void. Accordingly, GHC will not warn about K2 (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 for Numeric.Natural.

4.2.2. Compiler

4.2.3. Runtime system

  • Add and document new FFI functions hs_lock_stable_ptr_table and hs_unlock_stable_ptr_table. These replace the undocumented functions hs_lock_stable_tables and hs_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.

4.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 reifying C. It’s possible that this may break some code which assumes the existence of forall a. C a =>.

  • Template Haskell now supports implicit parameters and recursive do.

  • Template Haskell splices can now embed assembler source (Trac #16180)

4.2.5. ghc-prim library

  • GHC now exposes a new primop, traceBinaryEvent#. This primop writes eventlog events similar to traceBinaryEvent# but allows the user to pass the event payload as a binary blob instead of a String.
  • 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.

4.2.6. ghc library

4.2.7. base library

  • 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 and zip3 in Prelude can now fuse, together with zipWith4 to zipWith7 as well as their tuple counterparts in Data.List.

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

4.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.20190424 The compiler itself
Cabal 2.5.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.6.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.20190424 Internal compiler library
ghc-boot 8.8.0.20190424 Internal compiler library
ghc-compact 0.1.0.0 Core library
ghc-heap 8.8.0.20190424 GHC heap-walking library
ghc-prim 0.5.3 Core library
ghci 8.8.0.20190424 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.20190424 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.0 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.3 Dependency of haskeline library
text 1.2.3.1 Dependency of Cabal library
time 1.9.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