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.6 branch.
The highlights, since the 7.6 branch, are:
OS X Mavericks with XCode 5 is now properly supported by GHC. As a result of this, GHC now uses Clang to preprocess Haskell code by default for Mavericks builds.
Note that normally, GHC used gcc
as
the preprocessor for Haskell code (as it was the
default everywhere,) which implements
-traditional
behavior. However,
Clang is not 100% compatible with GCC's
-traditional
as it is rather
implementation specified and does not match any
specification. Clang is also more strict.
As a result of this, when using Clang as the
preprocessor, some programs which previously used
-XCPP
and the preprocessor will now
fail to compile. Users who wish to retain the previous
behavior are better off using cpphs as an external
preprocessor for the time being.
In the future, we hope to fix this by adopting a better preprocessor implementation independent of the C compiler (perhaps cpphs itself,) and ship that instead.
By default, GHC has a new warning enabled,
-fwarn-typed-holes
, which causes the
compiler to respond with the types of unbound
variables it encounters in the source code. (It is
reminiscient of the "holes" feature in languages such
as Agda.)
For more information, see Section 7.14, “Typed Holes”.
GHC can now perform simple evaluation of type-level
natural numbers, when using the
DataKinds
extension. For example,
given a type-level constraint such as (x + 3)
~ 5
, GHC is able to infer that
x
is 2. Similarly, GHC can now
understand type-level identities such as x +
0 ~ x
.
Note that the solving of these equations is only used to resolve unification variables - it does not generate new facts in the type checker. This is similar to how functional dependencies work.
It is now possible to declare a 'closed' type
family
when using the
TypeFamilies
extension. A closed
type family
cannot have any
instances created other than the ones in its
definition.
For more information, see Section 7.7.2.3, “Closed type families”.
Use of the GeneralizedNewtypeDeriving
extension is now subject to role checking,
to ensure type safety of the derived instances. As this change
increases the type safety of GHC, it is possible that some code
that previously compiled will no longer work.
For more information, see Section 7.25, “Roles
”.
GHC now supports overloading list literals using the new
OverloadedLists
extension.
For more information, see Section 7.6.5, “Overloaded lists”.
GHC now supports pattern synonyms, enabled by the
-XPatternSynonyms
extension,
allowing you to name and abstract over patterns more
easily.
For more information, see Section 7.3.8, “Pattern synonyms
”.
Note: For the GHC 7.8.1 version, this language feature should be regarded as a preview.
There has been significant overhaul of the type inference engine and constraint solver, meaning it should be faster and use less memory.
By default, GHC will now unbox all "small" strict
fields in a data type. A "small" data type is one
whose size is equivalent to or smaller than the native
word size of the machine. This means you no longer
have to specify UNPACK
pragmas for
e.g. strict Int
fields. This also
applies to floating-point values.
GHC now has a brand-new I/O manager that scales significantly better for larger workloads compared to the previous one. It should scale linearly up to approximately 32 cores.
The LLVM backend now supports 128- and 256-bit SIMD operations.
Note carefully: this is only available with the LLVM backend, and should be considered experimental.
The new code generator, after significant work by many individuals over the past several years, is now enabled by default. This is a complete rewrite of the STG to Cmm transformation. In general, your programs may get slightly faster.
The old code generator has been removed completely.
GHC now has substantially better support for cross compilation. In particular, GHC now has all the necessary patches to support cross compilation to Apple iOS, using the LLVM backend.
PrimOps for comparing unboxed values now return
Int#
instead of Bool
.
This change is backwards incompatible. See
this GHC wiki page for instructions how to update your
existing code. See
here for motivation and discussion of implementation details.
New PrimOps for atomic memory operations.
The casMutVar#
PrimOp was introduced in
GHC 7.2 (debugged in 7.4). This release also includes additional
PrimOps for compare-and-swap (casArray#
and
casIntArray#
) and one for fetch-and-add
(fetchAddIntArray#
).
On Linux, FreeBSD and Mac OS X, GHCi now uses the system dynamic linker by default, instead of its built in (static) object linker. This is more robust cross-platform, and fixes many long-standing bugs (for example: constructors and destructors, weak symbols, etc work correctly, and several edge cases in the RTS are fixed.)
As a result of this, GHCi (and Template Haskell) must
now load dynamic object files, not static
ones. To assist this, there is a new compilation flag,
-dynamic-too
, which when used
during compilation causes GHC to emit both static and
dynamic object files at the same time. GHC itself
still defaults to static linking.
Note that Cabal will correctly handle
-dynamic-too
for you automatically,
especially when -XTemplateHaskell
is needed - but you must tell Cabal you are
using the TemplateHaskell
extension.
Note that you must be using Cabal and Cabal-install 1.18 for it to correctly build dynamic shared libraries for you.
Currently, Dynamic GHCi and
-dynamic-too
are not supported on
Windows (32bit or 64bit.)
Typeable
is now poly-kinded, making
Typeable1
, Typeable2
,
etc., obsolete, deprecated, and relegated to
Data.OldTypeable
. Furthermore, user-written
instances of Typeable
are now disallowed:
use deriving
or the new extension
-XAutoDeriveTypeable
, which will create
Typeable
instances for every datatype
declared in the module.
GHC now has a parallel compilation driver. When
compiling with --make
(which is on
by default,) you may also specify
-jN
in order to compile
N
modules in
parallel. (Note: this will automatically scale on
multicore machines without specifying +RTS
-N
to the compiler.)
GHC now has support for a new pragma,
{-# MINIMAL #-}
, allowing you to
explicitly declare the minimal complete definition of
a class. Should an instance not provide the minimal
required definitions, a warning will be emitted.
See Section 7.20.5, “MINIMAL pragma” for details.
In GHC 7.10, Applicative
will
become a superclass of Monad
,
potentially breaking a lot of user code. To ease this
transition, GHC now generates warnings when
definitions conflict with the Applicative-Monad
Proposal (AMP).
A warning is emitted if a type is an instance of
Monad
but not of
Applicative
,
MonadPlus
but not
Alternative
, and when a local
function named join
,
<*>
or pure
is
defined.
The warnings are enabled by default, and can be controlled
using the new flag -f[no-]warn-amp
.
Using the new InterruptibleFFI
extension, it's possible to now declare a foreign
import as interruptible
, as opposed
to only safe
or
unsafe
. An
interruptible
foreign call is the
same as a safe
call, but may be
interrupted by asynchronous Haskell
exceptions, such as those generated by
throwTo
or
timeout
.
For more information (including the exact details on how the foreign thread is interrupted,) see Section 8.1.4, “Interruptible foreign calls”.
GHC's internal compiler pipeline is now exposed
through a Hooks
module inside the
GHC API. These hooks allow you to control most of the
internal compiler phase machinery, including compiling
expressions, phase control, and linking.
Note: this interface will likely see continuous refinement and API changes in future releases, so it should be considered a preview.
The LLVM code generator has been fixed to support dynamic linking. This enables runtime-linking (e.g. GHCi) support for architectures without support in GHC's own runtime linker (e.g. ARM).
Note: Tables-next-to-code is disabled when building on ARM with binutil's ld due to a bug in ld.
GHC now uses Unicode left/right single quotation marks (i.e. U+2018 and U+2019) in compiler messages if the current locale supports Unicode characters.
There is a new extension,
NullaryTypeClasses
, which
allows you to declare a type class without any
parameters.
There is a new extension,
NumDecimals
, which allows you
to specify an integer using compact "floating
literal" syntax. This lets you say things like
1.2e6 :: Integer
instead of
1200000
There is a new extension,
NegativeLiterals
, which will
cause GHC to interpret the expression
-123
as fromIntegral
(-123)
. Haskell 98 and Haskell 2010 both
specify that it should instead desugar to
negate (fromIntegral 123)
There is a new extension,
EmptyCase
, which allows
to write a case expression with no alternatives
case ... of {}
.
The IncoherentInstances
extension has seen a behavioral change, and is
now 'liberated' and less conservative during
instance resolution. This allows more programs to
compile than before.
Now, IncoherentInstances
will
always pick an arbitrary matching instance, if
multiple ones exist.
A new built-in function coerce
is
provided that allows to safely coerce values between types
that have the same run-time-presentation, such as
newtypes, but also newtypes inside containers. See the
haddock documentation of
coerce
and of the class
Coercible
for more details.
This feature is included in this release as a technology preview, and may change its syntax and/or semantics in the next release.
The new pragma, {-# MINIMAL #-}
,
allows to explicitly declare the minimal complete
definition of a class. Should an instance not provide
the minimal required definitions, a warning will be
emitted.
See Section 7.20.5, “MINIMAL pragma” for more details.
GHC can now build both static and dynamic object
files at the same time in a single compilation
pass, when given the
-dynamic-too
flag. This will
produce both a statically-linkable
.o
object file, and a
dynamically-linkable .dyn_o
file. The output suffix of the dynamic objects can
be controlled by the flag
-dynosuf
.
Note that GHC still builds statically by default.
GHC now supports a
--show-options
flag, which will
dump all of the flags it supports to standard out.
GHC now supports warning about overflow of integer
literals, enabled by
-fwarn-overflowed-literals
. It
is enabled by default.
It's now possible to switch the system linker on Linux (between GNU gold and GNU ld) at runtime without problem.
The -fwarn-dodgy-imports
flag now warns
in the case an import
statement hides an
entity which is not exported.
The LLVM backend was overhauled and rewritten, and should hopefully be easier to maintain and work on in the future.
GHC now detects annotation changes during recompilation, and correctly persists new annotations.
There is a new set of primops for utilizing hardware-based prefetch instructions, to help guide the processor's caching decisions.
Currently, the primops get translated into the associated hardware supported prefetch instructions only with the LLVM backend and x86/amd64 backends. On all other backends, the prefetch primops are currently erased at code generation time.
GHCi now supports a prompt2
setting, which allows you to customize the
continuation prompt of multi-line input.
For more information, see Section 2.7, “GHCi commands”.
The new :shows paths
command
shows the current working directory and the
current search path for Haskell modules.
On Linux, the static GHCi linker now supports weak symbols.
The (static) GHCi linker (except 64-bit Windows) now runs
constructors for linked libraries. This means for example
that C code using
__attribute__((constructor))
can now properly be loaded into GHCi.
Note: destructors are not supported.
Template Haskell now supports Roles.
Template Haskell now supports annotation pragmas.
Typed Template Haskell expressions are now supported. See Section 7.16, “Template Haskell” for more details.
Template Haskell declarations, types, patterns, and untyped expressions are no longer typechecked at all. This is a backwards-compatible change since it allows strictly more programs to be typed.
The RTS linker can now unload object code at
runtime (when using the GHC API
ObjLink
module.) Previously,
GHC would not unload the old object file, causing
a gradual memory leak as more objects were loaded
over time.
Note that this change in unloading behavior only affects statically linked binaries, and not dynamic ones.
The performance of StablePtr
s and
StableName
s has been improved.
The default maximum stack size has
increased. Previously, it defaulted to 8m
(equivalent to passing +RTS
-K8m
. Now, GHC will use up-to 80% of the
physical memory available at
runtime.
GHC >= 7.4 is now required for bootstrapping.
GHC can now be built with Clang, and use Clang as the preprocessor for Haskell code. Only Clang version 3.4 (or Apple LLVM Clang 5.0) or beyond is reliably supported.
Note that normally, GHC uses
gcc
as the preprocessor for
Haskell code, which implements
-traditional
behavior. However,
Clang is not 100% compatible with GCC's
-traditional
as it is rather
implementation specified, and is more strict.
As a result of this, when using Clang as the
preprocessor, some programs which previously used
-XCPP
and the preprocessor will
now fail to compile. Users who wish to retain the
previous behavior are better off using cpphs.
Version number 4.7.0.0 (was 4.6.0.1)
The Control.Category
module now has the
PolyKinds
extension enabled, meaning
that instances of Category
no longer
need be of kind * -> * -> *
.
There are now Foldable
and Traversable
instances for Either a
, Const r
, and (,) a
.
There is now a Monoid
instance for Const
.
There is now a Data
instance for Data.Version
.
There are now Data
,
Typeable
, and
Generic
instances for the types
in Data.Monoid
and
Control.Applicative
There are now Num
instances for Data.Monoid.Product
and Data.Monoid.Sum
There are now Eq
, Ord
, Show
and Read
instances for ZipList
.
There are now Eq
, Ord
, Show
and Read
instances for Down
.
There are now Eq
, Ord
, Show
, Read
and Generic
instances for types in GHC.Generics (U1
, Par1
, Rec1
, K1
, M1
, (:+:)
, (:*:)
, (:.:)
).
A zero-width unboxed poly-kinded Proxy#
was added to GHC.Prim
. It can be used to make it so
that there is no the operational overhead for passing around proxy
arguments to model type application.
Control.Concurrent.MVar
has a new
implementation of readMVar
, which
fixes a long-standing bug where
readMVar
is only atomic if there
are no other threads running
putMVar
.
readMVar
now is atomic, and is
guaranteed to return the value from the first
putMVar
. There is also a new tryReadMVar
which is a non-blocking version.
There are now byte endian-swapping primitives
available in Data.Word
, which
use optimized machine instructions when available.
Data.Bool
now exports
bool :: a -> a -> Bool -> a
, analogously
to maybe
and either
in their respective modules.
Rewrote portions of Text.Printf
, and
made changes to Numeric
(added
Numeric.showFFloatAlt
and
Numeric.showGFloatAlt
) and
GHC.Float
(added
formatRealFloatAlt
) to support it.
The rewritten version is extensible to user types, adds a
"generic" format specifier "%v
",
extends the printf
spec
to support much of C's printf(3)
functionality, and fixes the spurious warnings about
using Text.Printf.printf
at
(IO a)
while ignoring the return value.
These changes were contributed by Bart Massey.
The minimal complete definitions for all
type-classes with cyclic default implementations
have been explicitly annotated with the new
{-# MINIMAL #-}
pragma.
Control.Applicative.WrappedMonad
,
which can be used to convert a Monad
to an Applicative
, has now
a Monad m => Monad (WrappedMonad m)
instance.
Version number 1.2.0.2 (was 1.2.0.1)
The function findExecutables
now correctly checks to see if the execute bit is
set on Linux, rather than just looking in
$PATH
.
There are several new functions for finding files,
including findFiles
and
findFilesWith
, which allow you
to search for a file given a set of filepaths, and
run a predicate over them.
Version number 0.3.1.0 (was 0.3.0.0)
The type-classes Eq
and
Ord
have been annotated with
the new {-# MINIMAL #-}
pragma.
There is a new type exposed by
GHC.Types
, called
SPEC
, which can be used to
inform GHC to perform call-pattern specialisation
extremely aggressively. See Section 4.10, “Optimisation (code improvement)” for more details
concerning -fspec-constr
.
Version number 1.2.0.0 (was 1.1.0.2)
Several bugs have been fixed, including deadlocks
in readProcess
and
readProcessWithExitCode
.
Version number 2.9.0.0 (was 2.8.0.0)
Typed Template Haskell expressions are now supported. See Section 7.16, “Template Haskell” for more details.
There is now support for roles.
There is now support for annotation pragmas.
Version number 2.7.0.0 (was 2.6.0.0)
A crash in getGroupEntryForID
(and related functions like
getUserEntryForID
and
getUserEntryForName
) in
multi-threaded applications has been fixed.
The functions getGroupEntryForID
and getUserEntryForID
now fail
with a isDoesNotExist
error when
the specified ID cannot be found.
On OS X Mavericks, when using Clang as the C preprocessor, Haddock has a bug that causes it to fail to generate documentation, with an error similar to the following:
<no location info>: module 'xhtml-3000.2.1:Main' is defined in multiple files: dist-bindist/build/tmp-72252/Text/XHtml.hs dist-bindist/build/tmp-72252/Text/XHtml/Frameset.hs dist-bindist/build/tmp-72252/Text/XHtml/Strict.hs dist-bindist/build/tmp-72252/Text/XHtml/Transitional.hs ...
This only affects certain packages. This is due to a bad interaction with Clang, which we hope to resolve soon.
Note that when using cabal-install
,
this only effects the package documentation, not
installation or building.
On OS X 10.7 and beyond, with default build settings,
the runtime system currently suffers from a fairly
large (approx. 30%) performance regression in the
parallel garbage collector when using
-threaded
.
This is due to the fact that the OS X 10.7+ toolchain
does not (by default) support register variables, or a
fast __thread
implementation. Note
that this can be worked around by building GHC using
GCC instead on OS X platforms, but the binary
distribution then requires GCC later.
On Windows, -dynamic-too
is unsupported.
On Windows, we currently don't ship dynamic libraries or use a dynamic GHCi, unlike Linux, FreeBSD or OS X.