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.4 branch.
There is a new extension
ExplicitNamespacesthat allows to qualify the export of a type with thetypekeyword.The behavior of the
TypeOperatorextension has changed: previously, only type operators starting with ":" were considered type constructors, and other operators were treated as type variables. Now type operators are always constructors.It is now possible to explicitly annotate types with kind variables (#5862). You can now write, for example:
class Category (c :: k -> k -> *) where type Ob c :: k -> Constraint id :: Ob c a => c a a (.) :: (Ob c a, Ob c b, Ob c c) => c b c -> c a b -> c a c
and the variable
k, ranging over kinds, is in scope within the class declaration.It is now possible to derive instances of
Generic1automatically. See Section�7.22, “Generic programming” for more information.There is a new FFI calling convention
capi, enabled by theCApiFFIextension. For example, given the following declaration:foreign import capi "header.h f" f :: CInt -> IO CInt
GHC will generate code to call
fusing the C API defined in the headerheader.h. Thusfcan be called even if it may be defined as a CPP#define, rather than a proper function.There is a new pragma
CTYPE, which can be used to specify the C type that a Haskell type corresponds to, when it is used with thecapicalling convention.Generic default methods are now allowed for multi-parameter type classes.
A constructor of a GADT is now considered infix (by a derived
Showinstance) if it is a two-argument operator with a fixity declaration (#5712).There is a new extension
InstanceSigs, which allows type signatures to be specified in instance declarations.GHC now supports numeric and string type literals (enabled by
DataKinds), of kindNatandSymbolrespectively (see Section�7.9.5, “Promoted Literals”).The type
Anycan now be used as an argument forforeign primfunctions.The
mdokeyword has been reintroduced. This keyword can be used to createdoexpressions with recursive bindings. The behavior of thereckeyword has been changed, so that it does not perform automatic segmentation in adoexpression anymore.There is a new syntactic construct (enabled by the
LambdaCaseextension) for creating an anonymous function out of acaseexpression. For example, the following expression:\case Nothing -> 0 Just n -> nis equivalent to:
\x -> case x of Nothing -> 0 Just n -> nSee Section�7.3.15, “Lambda-case” for more details.
There is a new syntactic construct (enabled by the
MultiWayIfextension) to create conditional expressions with multiple branches. For example, you can now write:if | x == 0 -> [...] | x > 1 -> [...] | x < 0 -> [...] | otherwise -> [...]
See Section�7.3.16, “Multi-way if-expressions” for more information.
Some limitations on the usage of unboxed tuples have been lifted. For example, when the
UnboxedTuplesextension is on, an unboxed tuple can now be used as the type of a constructor, function argument, or variable:data Foo = Foo (# Int, Int #) f :: (# Int, Int #) -> (# Int, Int #) f x = x g :: (# Int, Int #) -> Int g (# a,b #) = a h x = let y = (# x,x #) in ...
Unboxed tuple can now also be nested:
f :: (# Int, (# Int, Int #), Bool #)
The
-packageflag now correctly loads only the most recent version of a package (#7030).In
--makemode, GHC now gives an indication of why a module is being recompiled.There is a new flag
-freg-livenessflag to control if STG liveness information is used for optimisation. The flag is enabled by default.Package database flags have been renamed from
-package-conf*to-package-db*.It is now possible to hide the global package db, and specify the order of the user and global package databases in the stack (see Section�4.9.4, “Package Databases”).
Commands defined later have now precedence in the resolution of abbreviated commands (#3858).
It is now possible to specify a custom pretty-printing function for expressions evaluated at the prompt using the
-interactive-printflag.GHCi now supports loading additional
.ghcifiles via the-ghci-scriptflag (#5265).A new
:seticommand has been introduced, which sets an option that applies only at the prompt.Files are now reloaded after having been edited with the
:editcommand.defaultdeclarations can now be entered at the GHCi prompt.
The presentation of parallel GC work balance in
+RTS -sis now expressed as a percentage value (with 100% being "perfect") instead of a number from 1 to N, with N being the number of capabilities.The RTS now supports changing the number of capabilities at runtime with
Control.Concurrent.setNumCapabilities: Section�4.15.2, “RTS options for SMP parallelism”.The internal timer is now based on a monotonic clock in both the threaded and non-threaded RTS, on all tier-1 platforms.
There have been some changes that have effected multiple libraries:
The deprecated function
catchhas been removed fromPrelude.
The following libraries have been removed from the GHC tree:
extensible-exceptions
mtl
The following libraries have been added to the GHC tree:
tranformers (version 0.3.0.0)
Version number 4.6.0.0 (was 4.5.1.0)
The
Text.Readmodule now exports functionsreadEither :: Read a => String -> Either String a readMaybe :: Read a => String -> Maybe a
An infix alias for
mappendinData.Monoidhas been introduced:(<>) :: Monoid m => m -> m -> m
The
Bitsclass does not have aNumsuperclass anymore.You can make code that works with both Haskell98/Haskell2010 and GHC by:
Whenever you make a
Bitsinstance of a type, also makeNuminstance, andWhenever you give a function, instance or class a
Bits tconstraint, also give it aNum tconstraint.
ApplicativeandAlternativeinstances for theReadPandReadPrecmonads have been added.foldl'andfoldr'inData.Foldableare now methods of theFoldableclass.The deprecated
Control.OldExceptionmodule has now been removed.Strict versions of
modifyIORefandatomicModifyIORefhave been added to theData.IORefmodule:modifyIORef' :: IORef a -> (a -> a) -> IO () atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b
Similarly, a strict version of
modifySTRefhas been added toData.STRef.A bug in the fingerprint calculation for
TypeRep(#5962) has been fixed.A new function
lookupEnvhas been added toSystem.Environment, which behaves likegetEnv, but returnsNothingwhen the environment variable is not defined, instead of throwing an exception.There is a new function
getGCStatsEnabledinGHC.Stats, which checks whether GC stats have been enabled (for example, via the-TRTS flag).QSeminControl.Concurrentis now deprecated, and will be removed in GHC 7.8. Please use an alternative, e.g. the SafeSemaphore package, instead.A new function
getExecutablePathhas been added toSystem.Environment. This function returns the full path of the current executable, as opposed togetProgName, which only returns the base name.The
Data.HashTablemodule is now deprecated, and will be removed in GHC 7.8. Please use an alternative, e.g. the hashtables package, instead.The
Data.Ordmodule now exports theDownnewtype, which reverses the sort order of its argument.
Version number 0.10.0.0 (was 0.9.2.1)
A new module
Data.ByteString.Lazy.Builderhas been added.The new module defines a
Buildermonoid, which allows to efficiently construct bytestrings by concatenation. Possible applications include binary serialization, targets for efficient pretty-printers, etc.
Version number 1.16.0 (was 1.14.0)
For details of the changes to the Cabal library, please see the Cabal changelog.
Version number 0.5.0.0 (was 0.4.2.1)
See the announcement for details of the changes to the containers library.
Version number 1.2.0.0 (was 1.1.0.2)
The dependency on the old-time package has been changed to time.
Version number 3.9.0.0 (was 3.8.7.3)
Compiler.Hoopl.Blocknow contains the Block datatype and all the operations on blocks.Compiler.Hoopl.Graphnow has the operations on Graphs.Compiler.Hoopl.UtilandCompiler.Hoopl.GraphUtilhave been removed; their contents have been moved to other modules.The Dataflow algorithms have been optimized.
Numerous other API changes.
Version number 0.6.0.0 (was 0.5.1.1)
The dependency on the old-time package has been changed to time.
Version number 1.1.0.2 (was 1.1.0.1)
Asynchronous exception bugs in
readProcessandreadProcessWithExitCodehave been fixed.
Version number 2.8.0.0 (was 2.7.0.0)
Promoted kinds and kind polymorphism are now supported in Template Haskell.
Fixity declarations have been added to Template Haskell.
The
StringPrimLconstructor forLitnow takes aWord8array, instead of aString.
Version number 2.6.0.0 (was 2.5.1.1)
Bindings for
mkdtempandmkstempshave been added.New functions
setEnvironmentandcleanEnvhave been added.Bindings for functions to access high resolution timestamps have been added.