1.6. Release notes for version 7.0.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 6.12 branch.

1.6.1. Highlights

  • GHC now defaults to the Haskell 2010 language standard.

    Libraries are not quite so straightforward. By default, GHC provides access to the base package, which includes the Haskell 2010 libraries, albeit with a few minor differences. For those who want to write strictly standards-conforming code we also provide the haskell2010 package which provides the precise APIs specified by Haskell 2010, but because the module names in this package overlap with those in the base package it is not possible to use both haskell2010 and base at the same time (this also applies to the array package). Hence to use the Haskell 2010 libraries you should hide the base and array packages, for example with GHCi:

    $ ghci -package haskell2010 -hide-package base -hide-package array
    

    If you are using Cabal it isn't necessary to hide base and array explicitly, just don't include them in your build-depends.

  • The -fglasgow-exts flag has been deprecated. Individual extensions should be enabled instead.

    The GADTs and TypeFamilies exntensions are no longer enabled by -fglasgow-exts.

  • On POSIX platforms, there is a new I/O manager based on epoll/kqueue/poll, which allows multithreaded I/O code to scale to a much larger number (100k+) of threads.

  • GHC now includes an LLVM code generator. For certain code, particularly arithmetic heavy code, using the LLVM code generator can bring some nice performance improvements.

  • The type checker has been overhauled, which means it is now able to correctly handle interactions between the type system extensions.

  • The inliner has been overhauled, which should in general give better performance while reducing unnecessary code-size explosion.

  • Large parts of the runtime system have been overhauled, in particular the machinery related to blocking and wakeup of threads and exception throwing (throwTo). Several instances of pathological performance have been fixed, especially where large numbers of threads are involved.

  • Due to changes in the runtime system, if you are using Control.Parallel.Strategies from the parallel package, please upgrade to at least version 2 (preferably version 3). The implementation of Strategies in parallel-1.x will lose parallelism with GHC 7.0.1.

  • The full Haskell import syntax can now been used to bring modules into scope in GHCi, e.g.

    Prelude> import Data.List as L
    Prelude Data.List> L.length "foo"
    3
    
  • GHC now comes with a more recent mingw bundled on Windows, which includes a fix for windres on Windows 7.

  • There is a new -fno-ghci-sandbox flag, which stops GHCi running computations in a separate thread. In particular, this is useful for GLUT on OS X, which only works if being run on the main thread.

1.6.2. Language changes

  • GHC now understands the Haskell98 and Haskell2010 languages.

    These get processed before the language extension pragmas, and define the default sets of extensions that are enabled. If neither is specified, then the default is Haskell2010 plus the MonoPatBinds extension.

  • GHC now supports the DoAndIfThenElse extension, which is part of the Haskell 2010 standard.

  • Rebinadble syntax now has its own extension, RebindableSyntax, and thus is no longer enabled by NoImplicitPrelude.

  • Datatype contexts, such as the Eq a in

    data Eq a => Set a = NilSet | ConsSet a (Set a)
    

    are now treated as an extension DatatypeContexts (on by default) by GHC.

  • GHC's support for unicode source has been improved, including removing support for U+22EF for the .. symbol. See Section 7.3.1, “Unicode syntax” for more details.

  • Pragmas are now reread after preprocessing. In particular, this means that if a pragma is used to turn CPP on, then other pragmas can be put in CPP conditionals.

  • The TypeOperators extension now allows instance heads to use infix syntax.

  • The PackageImports extension now understands this to mean the current package.

  • The INLINE and NOINLINE pragmas can now take a CONLIKE modifier, which indicates that the right hand side is cheap to compute, and can thus be duplicated more freely. See Section 7.14.3, “How rules interact with INLINE/NOINLINE and CONLIKE pragmas” for more details.

  • A ForceSpecConstr annotation on a type, e.g.

    import SpecConstr
    {-# ANN type SPEC ForceSpecConstr #-}
    

    can be used to force GHC to fully specialise argument of that type.

  • A NoSpecConstr annotation on a type, e.g.

    import SpecConstr
    {-# ANN type T NoSpecConstr #-}
    

    can be used to prevent SpecConstr from specialising on arguments of that type.

  • There is are two experimental new extensions AlternativeLayoutRule and AlternativeLayoutRuleTransitional, which are for exploring alternative layout rules in Haskell'. The details are subject to change, so we advise against using them in real code for now.

  • The NewQualifiedOperators extension has been deprecated, as it was rejected by the Haskell' committee.

1.6.3. Warnings

  • There is now a warning for missing type signatures for polymorphic local bindings, controlled by the new -fwarn-missing-local-sigs flag.

  • There is now a warning for missing import lists, controlled by the new -fwarn-missing-import-lists flag.

  • GHC will now warn about SPECIALISE and UNPACK pragmas that have no effect.

  • The -fwarn-simple-patterns flag has been removed. The warnings have been merged into the -fwarn-incomplete-patterns flag.

1.6.4. DLLs

  • Shared libraries are once again supported on Windows.

  • Shared libraries are now supported on OS X, both on x86 and on PowerPC. The new -dylib-install-name GHC flag is used to set the location of the dynamic library. See Section 4.12.4, “Finding shared libraries at runtime” for more details.

1.6.5. Runtime system

  • For security reasons, by default, the only RTS flag that programs accept is +RTS --info. If you want the full range of RTS flags then you need to link with the new -rtsopts flag. See Section 4.11.6, “Options affecting linking” for more details.

  • The RTS now exports a function setKeepCAFs which is important when loading Haskell DLLs dynamically, as a DLL may refer to CAFs that hae already been GCed.

  • The garbage collector no longer allows you to specify a number of steps; there are now always 2. The -T RTS flag has thus been removed.

  • A new RTS flag -H causes the RTS to use a larger nursery, but without exceeding the amount of memory that the application is already using. It makes some programs go slower, but others go faster.

  • GHC now returns memory to the OS, if memory usage peaks and then drops again. This is mainly useful for long running processes which normally use very little memory, but occasionally need a lot of memory for a short period of time.

  • On OS X, eventLog events are now available as DTrace probes.

  • The PAPI support has been improved. The new RTS flag -a#0x40000000 can be used to tell the RTS to collect the native PAPI event 0x40000000.

1.6.6. Compiler

  • GHC now defaults to --make mode, i.e. GHC will chase dependencies for you automatically by default.

  • GHC now includes an LLVM code generator.

    This includes a number of new flags: a flag to tell GHC to use LLVM, -fllvm; a flag to dump the LLVM input ,-ddump-llvm; flags to keep the LLVM intermediate files, -keep-llvm-file and -keep-llvm-files; flags to set the location and options for the LLVM optimiser and compiler, -pgmlo, -pgmlc, -optlo and -optlc. The LLVM code generator requires LLVM version 2.7 or later on your path.

  • It is now possible to use -fno-code with --make.

  • The new flag -dsuppress-coercions controls whether GHC prints coercions in core dumps.

  • The new flag -dsuppress-module-prefixes controls whether GHC prints module qualification prefixes in core dumps.

  • The inliner has been overhauled. The most significant user-visible change is that only saturated functions are inlined, e.g.

    (.) f g x = f (g x)
    

    would only be inlined if (.) is applied to 3 arguments, while

    (.) f g = \x -> f (g x)
    

    will be inlined if only applied to 2 arguments.

  • The -finline-if-enough-args flag is no longer supported.

  • Column numbers in warnings and error messages now start at 1, as is more standard, rather than 0.

  • GHCi now understands most linker scripts. In particular, this means that GHCi is able to load the C pthread library.

  • The ghc --info output has been updated:

    It now includes the location of the global package database, in the Global Package DB field.

    It now includes the build, host and target platforms, in the Build platform, Host platform and Target platform fields.

    It now includes a Have llvm code generator field.

    The Win32 DLLs field has been removed.

  • The registerised via-C backend, and the -fvia-C flag, have been deprecated. The poor floating-point performance in the x86 native code generator has now been fixed, so we don't believe there is still any reason to use the via-C backend.

  • There is now a new flag --supported-extensions, which currently behaves the same as --supported-languages.

  • GHC progress output such as

    [ 1 of 5] Compiling Foo              ( Foo.hs, Foo.o )
    

    is now sent to stdout rather than stderr.

  • The new flag -fexpose-all-unfoldings makes GHC put unfoldings for everything in the interface file.

  • There are two new flags, -fno-specialise and -fno-float-in, for disabling the specialise and float-in passes.

  • The new flag -fstrictness-before=n tells GHC to run an additional strictness analysis pass before simplifier phase n.

  • There is a new flag -funfolding-dict-discount for tweaking the optimiser's behaviour.

  • The -fspec-inline-join-points flag has been removed.

  • The -dynload wrapper flag has been removed.

  • The __HASKELL1__, __HASKELL98__ and __CONCURRENT_HASKELL__ symbols are no longer defined by default when CPPing.

1.6.7. GHCi

  • GHCi now understands layout in multi-line commands, so this now works:

    Prelude> :{
    Prelude| let x = 1
    Prelude|     y = 2 in x + y
    Prelude| :}
    3
    

1.6.8. Template Haskell and Quasi-Quoters

  • It is now possible to quasi-quote patterns with [p| ... |].

  • It is no longer necessary to use a $ before the name of a quasi-quoter, e.g. one can now say [expr| ... |] rather than [$expr| ... |].

  • It is now possible to use a quasi-quoter for types, e.g. f :: [$qq| ... |]

  • It is now possible to quasi-quote existentials and GADTs.

1.6.9. GHC API

  • There are now Data and Typeable instances for the HsSyn typed.

1.6.10. Libraries

1.6.10.1. array

  • Version number 0.3.0.2 (was 0.3.0.1)

1.6.10.2. base

  • Version number 4.3.0.0 (was 4.2.0.2)

  • There is a new asynchronous exception control API in Control.Exception, using the new functions mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b and mask_ :: IO a -> IO a rather than the old block and unblock. There are also functions uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b and getMaskingState :: IO MaskingState, and a type MaskingState, as well as forkIOUnmasked :: IO () -> IO ThreadId in Control.Concurrent.

  • Control.Monad exports a new function void :: Functor f => f a -> f ().

  • Data.Tuple exports a new function swap :: (a,b) -> (b,a).

  • System.IO exports a new function hGetBufSome :: Handle -> Ptr a -> Int -> IO Int which is like hGetBuf but can return short reads.

  • There is a new function mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a in Control.Monad.

  • The Foreign.Marshal module now exports unsafeLocalState :: IO a -> a as specified by Haskell 2010.

  • The module now exports four new functions specified by Haskell 2010: castCUCharToChar :: CUChar -> Char, castCharToCUChar :: Char -> CUChar, castCSCharToChar :: CSChar -> Char and castCharToCSChar :: Char -> CSChar.

  • The Foreign.Marshal.Alloc module now exports allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b for allocating memory with a particular alignment.

  • There is a new function numSparks :: IO Int in GHC.Conc.

  • Data.Either.partitionEithers in now lazier.

  • There is now a Typeable instance for Data.Unique.Unique.

  • Control.Concurrent.SampleVar.SampleVar is now an abstract type.

  • There are now Applicative, Alternative and MonadPlus instances for STM.

  • There are now Applicative, Monad and MonadFix instances for Either.

  • There are now Ord, Read and Show instances for Newline and NewlineMode.

  • There is now a Show instance for TextEncoding.

  • The unGetChan and isEmptyChan functions in Control.Concurrent.Chan are now deprecated. Control.Concurrent.STM.TChan should be used instead if you need that functionality.

  • The Read Integer instance now matches the standard definition.

1.6.10.3. base 3 compat

  • We no longer ship a base 3 compat package

1.6.10.4. bin-package-db

  • This is an internal package, and should not be used.

1.6.10.5. bytestring

  • Version number 0.9.1.8 (was 0.9.1.7)

1.6.10.6. Cabal

  • Version number 1.10.0.0 (was 1.8.0.6)

  • Many API changes. See the Cabal docs for more information.

1.6.10.7. containers

  • Version number 0.4.0.0 (was 0.3.0.0)

  • Strictness is now more consistent, with containers being strict in their elements even in singleton cases.

  • There is a new function insertLookupWithKey' in Data.Map.

  • The foldWithKey function in Data.Map has been deprecated in favour of foldrWithKey.

1.6.10.8. directory

  • Version number 1.1.0.0 (was 1.0.1.1)

  • The System.Directory module now exports the Permissions type abstractly. There are also new functions setOwnerReadable, setOwnerWritable, setOwnerExecutable and setOwnerSearchable, and a new value emptyPermissions.

1.6.10.9.  dph (dph-base, dph-par, dph-prim-interface, dph-prim-par, dph-prim-seq, dph-seq)

  • The dph packages are no longer shipped with GHC.

1.6.10.10. extensible-exceptions

  • Version number 0.1.1.2 (was 0.1.1.1)

1.6.10.11. filepath

  • Version number 1.2.0.0 (was 1.1.0.4)

  • The current directory is now "." rather than "".

1.6.10.12. ghc-binary

  • This is an internal package, and should not be used.

1.6.10.13. ghc-prim

  • This is an internal package, and should not be used.

1.6.10.14. haskell98

  • Version number 1.1.0.0 (was 1.0.1.1)

  • In the Directory module, the Permissions type and the getPermissions and setPermissions functions are now different to their equivalents in base:System.Directory.

1.6.10.15. haskell2010

  • This is a new boot package, version 1.0.0.0. It is not exposed by default.

1.6.10.16. hpc

  • Version number 0.5.0.6 (was 0.5.0.5)

1.6.10.17. integer-gmp

  • Version number 0.2.0.2 (was 0.2.0.1)

1.6.10.18. old-locale

  • No change (version 1.0.0.2)

1.6.10.19. old-time

  • Version number 1.0.0.6 (was 1.0.0.5)

1.6.10.20. pretty

  • Version number 1.0.1.2 (was 1.0.1.1)

1.6.10.21. process

  • Version number 1.0.1.4 (was 1.0.1.3)

1.6.10.22. random

  • Version number 1.0.0.3 (was 1.0.0.2)

1.6.10.23. syb

  • The syb package is no longer included with GHC.

1.6.10.24. template-haskell

  • Version number 2.5.0.0 (was 2.4.0.1)

  • There is a new type synonym DecsQ in Language.Haskell.TH.Lib.

  • There is a new StringPrimL constructor in Language.Haskell.TH.Syntax.Lit, and a new helper function stringPrimL for it in Language.Haskell.TH.Lib.

  • There is a new function quoteFile in Language.Haskell.TH.Quote.

  • The Language.Haskell.TH.Quote.QuasiQuoter type has two new fields: quoteType and quoteDec.

  • There is a new ClassInstance type in Language.Haskell.TH.Syntax. The Language.Haskell.TH.Syntax.Info.ClassI constructor now includes a value of this type, which allows instance information to be queried via the new isClassInstance and classInstances functions. There is also a new method qClassInstances in the Quasi class.

1.6.10.25. time

  • Version number 1.2.0.3 (was 1.1.4)

  • The types provided by the time package now include Data instances.

1.6.10.26. unix

  • Version number 2.4.1.0 (was 2.4.0.2)

  • There are three new helper function in System.Posix.Error: throwErrnoPathIfRetry, throwErrnoPathIfNullRetry and throwErrnoPathIfMinus1Retry.

  • There are three new functions in System.Posix.User: setEffectiveUserID, setEffectiveGroupID and setGroups.