The significant changes to the various parts of the compiler are listed in the following sections.
The new QuasiQuotes language extension adds general quasi-quotation, as described in "Nice to be Quoted: Quasiquoting for Haskell" (Geoffrey Mainland, Haskell Workshop 2007). See Section 7.9.5, “ Template Haskell Quasi-quotation ” for more information.
The new ViewPatterns language extension allows
"view patterns". The syntax for view patterns
is expression -> pattern in a pattern.
For more information, see Section 7.3.5, “View patterns
”.
GHC already supported (e op) postfix operators, but this support was enabled by default. Now you need to use the PostfixOperators language extension if you want it. See Section 7.3.10, “Postfix operators” for more information on postfix operators.
The new TransformListComp language extension enables implements generalised list comprehensions, as described in the paper "Comprehensive comprehensions" (Peyton Jones & Wadler, Haskell Workshop 2007). For more information see Section 7.3.8, “Generalised (SQL-Like) List Comprehensions”.
If you want to use impredicative types then you now need to enable the ImpredicativeTypes language extension. See Section 7.8.5, “Impredicative polymorphism ” for more information.
FFI change: header files are now not
used when compiling via C.
The -#include flag,
the includes field
in .cabal files, and header files
specified in a foreign import
declaration all have no effect when compiling Haskell
source code.
This change has important ramifications if you are
calling FFI functions that are defined by macros (or renamed
by macros). If you need to call one of these functions,
then write a C wrapper for the function and call the wrapper
using the FFI instead. In this way, your code will work
with GHC 6.10.1, and will also work
with -fasm in older GHCs.
This change was made for several reasons.
Firstly, -fvia-C now behaves consistently
with -fasm, which is important because we
intend to stop compiling via C in the future. Also, we
don't need to worry about the interactions between header
files, or CPP options necessary to expose certain functions
from the system header files (this was becoming quite a
headache). We don't need to worry about needing header
files when inlining FFI calls across module or package
boundaries; calls can now be inlined freely. One downside
is that you don't get a warning from the C compiler when you
call a function via the FFI at the wrong type.
Another consequence of this change is that
calling varargs functions (such
as printf) via the FFI no longer works.
It has never been officially supported (the FFI spec outlaws
it), but in GHC 6.10.1 it may now really cause a crash on
certain platforms. Again, to call one of these functions
use appropriate fixed-argument C wrappers.
There is a new languages extension PackageImports which allows imports to be qualified with the package they should come from, e.g.
import "network" Network.Socket
Note that this feature is not intended for general use, it
was added for constructing backwards-compatibility packages
such as the base-3.0.3.0 package. See
Section 7.3.15, “Package-qualified imports” for more details.
In earlier versions of GHC, the recompilation checker didn't notice changes in other packages meant that recompilation is needed. This is now handled properly, using MD5 checksums of the interface ABIs.
GHC now treats the Unicode "Letter, Other" class as lowercase letters. This is an arbitrary choice, but better than not allowing them in identifiers at all. This may be revisited by Haskell'.
In addition to the DEPRECATED pragma, you
can now attach arbitrary warnings to declarations with the new
WARNING pragma. See
Section 7.13.4, “WARNING and DEPRECATED pragmas” for more details.
If GHC is failing due to -Werror, then it
now emits a message telling you so.
GHC now warns about unrecognised pragmas, as they are often
caused by a typo. The
-fwarn-unrecognised-pragmas controls
whether this warning is emitted.
The warning is enabled by default.
There is a new flag
-fwarn-dodgy-foreign-imports which controls
a new warning about FFI delcarations of the form
foreign import "f" f :: FunPtr t
on the grounds that it is probably meant to be
foreign import "&f" f :: FunPtr t
The warning is enabled by default.
External core (output only) is working again.
There is a new flag -dsuppress-uniques that
makes GHC's intermediate core easier to read. This flag cannot
be used when actually generating code.
There is a new flag -dno-debug-output that
suppresses all of the debug information when running a
compiler built with the DEBUG option.
A bug in earlier versions of GHC meant that sections didn't
always need to be parenthesised, e.g.
(+ 1, 2) was accepted. This has now been
fixed.
The -fspec-threshold flag has been replaced
by -fspec-constr-threshold and
-fliberate-case-threshold flags.
The thresholds can be disabled by
-fno-spec-constr-threshold and
-fno-liberate-case-threshold.
The new flag -fsimplifier-phases
controls the number of simplifier phases run during
optimisation. These are numbered from n to 1 (by default, n=2).
Phase 0 is always run regardless of this flag.
Simplifier phases can have an arbitrary number of tags
assigned to them, and multiple phases can share the same tags.
The tags can be used as arguments to the new flag
-ddump-simpl-phases
to specify which phases are to be dumped.
For example,
-ddump-simpl-phases=main will dump the
output of phases 2, 1 and 0 of the initial simplifier run
(they all share the "main" tag) while
-ddump-simpl-phases=main:0
will dump only the output of phase 0 of that run.
At the moment, the supported tags are main (the main, staged simplifier run (before strictness)), post-worker-wrapper (after the w/w split), post-liberate-case (after LiberateCase), and final (final clean-up run)
The names are somewhat arbitrary and will change in the future.
The -fno-method-sharing flag is now
dynamic (it used to be static).
The new flag -fwarn-deprecated-flags,
controls whether we warn about deprecated flags and language
extensions. The warning is on by default.
The following language extensions are now marked as deprecated; expect them to be removed in a future release:
RecordPuns
(use NamedFieldPuns instead)
PatternSignatures
(use ScopedTypeVariables instead)
The following flags are now marked as deprecated; expect them to be removed in a future release:
-Onot
(use -O0 instead)
-Wnot
(use -w instead)
-frewrite-rules
(use -fenable-rewrite-rules instead)
-no-link
(use -c instead)
-recomp
(use -fno-force-recomp instead)
-no-recomp
(use -fforce-recomp instead)
-syslib
(use -package instead)
-fth
(use the TemplateHaskell language
extension instead)
-ffi, -fffi
(use the ForeignFunctionInterface
extension instead)
-farrows
(use the Arrows language
extension instead)
-fgenerics
(use the Generics language
extension instead)
-fno-implicit-prelude
(use the NoImplicitPrelude language
extension instead)
-fbang-patterns
(use the BangPatterns language
extension instead)
-fno-monomorphism-restriction
(use the NoMonomorphismRestriction language
extension instead)
-fmono-pat-binds
(use the MonoPatBinds language
extension instead)
-fextended-default-rules
(use the ExtendedDefaultRules language
extension instead)
-fimplicit-params
(use the ImplicitParams language
extension instead)
-fscoped-type-variables
(use the ScopedTypeVariables language
extension instead)
-fparr
(use the PArr language
extension instead)
-fallow-overlapping-instances
(use the OverlappingInstances language
extension instead)
-fallow-undecidable-instances
(use the UndecidableInstances language
extension instead)
-fallow-incoherent-instances
(use the IncoherentInstances language
extension instead)
-optdep-s
(use -dep-suffix instead)
-optdep-f
(use -dep-makefile instead)
-optdep-w
(has no effect)
-optdep--include-prelude
(use -include-pkg-deps instead)
-optdep--include-pkg-deps
(use -include-pkg-deps instead)
-optdep--exclude-module
(use -exclude-module instead)
-optdep-x
(use -exclude-module instead)
The following flags have been removed:
-no-link-chk
(has been a no-op since at least 6.0)
-fruntime-types
(has not been used for years)
-fhardwire-lib-paths
(use -dynload sysdep)
The -unreg flag, which was used to build
unregisterised code with a registerised compiler, has been
removed. Now you need to build an unregisterised compiler
if you want to build unregisterised code.
There is now a Ghc Monad used to carry around GHC's Session data. This Monad also provides exception handling functions.
It is now possible to get the raw characters corresponding to each token the lexer outputs, and thus to reconstruct the original file.
GHCi implicitly brings all exposed modules into scope with
qualified module names. There is a new flag
-fimplicit-import-qualified
that controls this behaviour, so other GHC API clients can
specify whether or not they want it.
There is now haddock documentation for much of the GHC API.
You can now force GHCi to interpret a module, rather than loading its compiled code, by prepending a * character to its name, e.g.
Prelude> :load *A Compiling A ( A.hs, interpreted ) *A>
By default, GHCi will not print bind results, e.g.
Prelude> c <- return 'c' Prelude>
does not print 'c'. Use
-fprint-bind-result if you want the old
behaviour.
GHCi now uses editline, rather than readline, for input. This shouldn't affect its behaviour.
The GHCi prompt history is now saved in
~/.ghc/ghci_history.
GHCi now uses libffi to make FFI calls, which means that the FFI now works in GHCi on a much wider range of platforms (all those platforms that libffi supports).
The garbage collector can now use multiple threads in parallel.
The new -g RTS
flag controls it, e.g. run your program with
n+RTS -g2 -RTS to use 2 threads.
The -g option is implied by the
usual -N option, so normally there will be
no need to specify it separately, although occasionally it
is useful to turn it off with -g1.
Do let us know if you experience strange effects,
especially an increase in GC time when using the parallel GC
(use +RTS -s -RTS to measure GC time).
See Section 4.14.3, “RTS options to control the garbage collector” for more details.
It is now possible to generate a heap profile without
recompiling your program for profiling. Run the program
with +RTS -hT to generate a basic heap
profile, and use hp2ps as usual to
convert the heap profile into a .ps file
for viewing. See Section 4.14.5, “RTS options for profiling” for more
details.
If the user presses control-C while running a Haskell program then the program gets an asynchronous UserInterrupt exception.
We now ignore SIGPIPE by default.
The -S and -s RTS flags
now send their output to stderr, rather than
,
by default.
prog.stat
The new -vg RTS flag provides some RTS trace
messages even in the non-debug RTS variants.
runghc now uses the compiler that it came with to run the code, rather than the first compiler that it finds on the PATH.
If the program to run does not have a .lhs
extension then runghc now treats it as a .hs
file. In particular, this means that programs without an
extension now work.
runghc foo will now work if
foo.hs or foo.lhs exists.
runghc can now take the code to run from stdin.
ghc-pkg will refuse to unregister a package on which
other packages depend, unless
the ––force option is also
supplied.
ghc-pkg now has a -no-user-package-conf
flag which instructs it to ignore the user's personal
package.conf.
ghc-pkg no longer allows you to register two packages that differ in case only.
ghc-pkg no longer allows you to register packages which have unversioned dependencies.
There is a new command dump which is
similar to describe '*', but in a format
that is designed to be parsable by other tools.
DPH is now an extralib.
There is a new flag -Odph that sets the
flags recommended when using DPH. Currently it is equivalent
to
-O2 -fno-method-sharing -fdicts-cheap
-fmax-simplifier-iterations20 -fno-spec-constr-threshold
There are now flags -fdph-seq and
-fdph-par for selecting which DPH backend
to use.
The -fflatten flag has been removed. It
never worked and has now been superceded by vectorisation.
Version number 4.0.0.0 (was 3.0.2.0)
We also ship a base version 3.0.3.0, so legacy code should continue to work.
The Show instance
for Ratio now puts spaces around
the %, as required by Haskell 98.
There is a new module Control.Category.
>>> is no longer a method of the
Arrow class; instead
Category is a superclass of
Arrow.
pure is no longer a method of the
Arrow class; use arr
instead.
Control.Exception now uses extensible
exceptions. The old style of exceptions are still available
in Control.OldException, but we expect to
remove them in a future release.
There is a new function
System.Exit.exitSuccess :: IO a
analogous to the existing
System.Exit.exitFailure :: IO a.
There are new functions
Data.Either.lefts :: [Either a b] -> [a],
Data.Either.rights :: [Either a b] -> [b]
and
Data.Either.partitionEithers :: [Either a b] -> ([a], [b])
.
The new function
Data.List.subsequences :: [a] -> [[a]]
gives all sublists of a list, e.g.
subsequences "abc" ==
["","a","b","ab","c","ac","bc","abc"]
.
The new function
Data.List.permutations :: [a] -> [[a]]
gives all permutations of a list, e.g.
permutations "abc" ==
["abc","bac","cba","bca","cab","acb"]
.
The new functions
Data.Traversable.mapAccumL and
Data.Traversable.mapAccumR generalise their
Data.List counterparts to work on any
Traversable type.
The new function
Control.Exception.blocked :: IO Bool
tells you whether or not exceptions are blocked (as controlled
by Control.Exception.(un)block).
There is a new function
traceShow :: Show a => a -> b -> b in
Debug.Trace.
The type of Control.Monad.forever has
been generalised from
Monad m => m a -> m () to
Monad m => m a -> m b.
The new value GHC.Exts.maxTupleSize
tells you the largest tuple size that can be used. This is
mostly of use in Template Haskell programs.
GHC.Exts now exports
Down(..),
groupWith,
sortWith and
the which are used in the desugaring of
generalised comprehensions.
GHC.Exts no longer exports the
Integer internals. If you want them then
you need to get them directly from the
new integer package.
The new function GHC.Conc.threadStatus
allows you to ask whether a thread is running, blocked on
an MVar, etc.
The Data.Generics hierarchy has been
moved to a new package syb.
The GHC.Prim and
GHC.PrimopWrappers modules have been
moved into a new ghc-prim package.
Version number 1.6.0.1 (was 1.2.4.0)
Many API changes. See the Cabal docs for more information.
Version number 0.2.0.0 (was 0.1.0.2)
Various result type now use Maybe rather
than allowing any Monad.
Version number 1.0.0.2 (was 1.0.0.1)
No longer defines the UNICODE CPP symbol for packages that use it.
Version number 1.0.1.0 (was 1.0.0.0)
There is a new combinator
zeroWidthText :: String -> Doc
for printing things like ANSI escape sequences.
Version number 1.0.1.0 (was 1.0.0.1)
The System.Process API has been overhauled.
The new API is a superset of the old API, however.
Version number 2.3.0.0 (was 2.2.0.0)
The datatypes now have support for Word primitives.
currentModule :: Q String has been
replaced with
location :: Q Loc, where
Loc is a new datatype.
Version number 2.3.1.0 (was 2.3.0.1)
The System.Posix.Terminal.BaudRate type
now includes B57600 and
B115200 constructors.