1.5. Release notes for version 7.6.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 7.4 branch.

1.5.1. Highlights

The highlights, since the 7.4 branch, are:

1.5.2. Full details

1.5.2.1. Language

  • There is a new extension ExplicitNamespaces that allows to qualify the export of a type with the type keyword.

  • The behavior of the TypeOperator extension 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 Generic1 automatically. See Section 7.22, “Generic programming” for more information.

  • There is a new FFI calling convention capi, enabled by the CApiFFI extension. For example, given the following declaration:

    foreign import capi "header.h f" f :: CInt -> IO CInt
    

    GHC will generate code to call f using the C API defined in the header header.h. Thus f can 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 the capi calling convention.

  • Generic default methods are now allowed for multi-parameter type classes.

  • A constructor of a GADT is now considered infix (by a derived Show instance) 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 kind Nat and Symbol respectively (see Section 7.9.5, “Promoted Literals”).

  • The type Any can now be used as an argument for foreign prim functions.

  • The mdo keyword has been reintroduced. This keyword can be used to create do expressions with recursive bindings. The behavior of the rec keyword has been changed, so that it does not perform automatic segmentation in a do expression anymore.

  • There is a new syntactic construct (enabled by the LambdaCase extension) for creating an anonymous function out of a case expression. For example, the following expression:

    \case
        Nothing -> 0
        Just n  -> n
    

    is equivalent to:

    \x -> case x of
        Nothing -> 0
        Just n  -> n
    

    See Section 7.3.15, “Lambda-case” for more details.

  • There is a new syntactic construct (enabled by the MultiWayIf extension) 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 UnboxedTuples extension 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 #)
    

1.5.2.2. Compiler

  • The -package flag now correctly loads only the most recent version of a package (#7030).

  • In --make mode, GHC now gives an indication of why a module is being recompiled.

  • There is a new flag -freg-liveness flag 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”).

1.5.2.3. GHCi

  • 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-print flag.

  • GHCi now supports loading additional .ghci files via the -ghci-script flag (#5265).

  • A new :seti command has been introduced, which sets an option that applies only at the prompt.

  • Files are now reloaded after having been edited with the :edit command.

  • default declarations can now be entered at the GHCi prompt.

1.5.2.4. Template Haskell

  • Promoted kinds and kind polymorphism are now supported in Template Haskell.

  • It is now possible to create fixity declarations in Template Haskell (#1541).

  • Primitive byte-array literals can now be created with Template Haskell (#5877).

1.5.2.5. Runtime system

  • The presentation of parallel GC work balance in +RTS -s is 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.

1.5.2.6. Build system

  • GHC >= 7.0 is now required for bootstrapping.

  • Windows 64bit is now a supported platform.

1.5.3. Libraries

There have been some changes that have effected multiple libraries:

  • The deprecated function catch has been removed from Prelude.

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)

1.5.3.1. array

  • Version number 0.4.0.1 (was 0.4.0.0)

1.5.3.2. base

  • Version number 4.6.0.0 (was 4.5.1.0)

  • The Text.Read module now exports functions

    readEither :: Read a => String -> Either String a
    readMaybe :: Read a => String -> Maybe a
    

  • An infix alias for mappend in Data.Monoid has been introduced:

    (<>) :: Monoid m => m -> m -> m
    

  • The Bits class does not have a Num superclass anymore.

    You can make code that works with both Haskell98/Haskell2010 and GHC by:

    • Whenever you make a Bits instance of a type, also make Num instance, and

    • Whenever you give a function, instance or class a Bits t constraint, also give it a Num t constraint.

  • Applicative and Alternative instances for the ReadP and ReadPrec monads have been added.

  • foldl' and foldr' in Data.Foldable are now methods of the Foldable class.

  • The deprecated Control.OldException module has now been removed.

  • Strict versions of modifyIORef and atomicModifyIORef have been added to the Data.IORef module:

    modifyIORef' :: IORef a -> (a -> a) -> IO ()
    atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b
    

    Similarly, a strict version of modifySTRef has been added to Data.STRef.

  • A bug in the fingerprint calculation for TypeRep (#5962) has been fixed.

  • A new function lookupEnv has been added to System.Environment, which behaves like getEnv, but returns Nothing when the environment variable is not defined, instead of throwing an exception.

  • There is a new function getGCStatsEnabled in GHC.Stats, which checks whether GC stats have been enabled (for example, via the -T RTS flag).

  • QSem in Control.Concurrent is now deprecated, and will be removed in GHC 7.8. Please use an alternative, e.g. the SafeSemaphore package, instead.

  • A new function getExecutablePath has been added to System.Environment. This function returns the full path of the current executable, as opposed to getProgName, which only returns the base name.

  • The Data.HashTable module is now deprecated, and will be removed in GHC 7.8. Please use an alternative, e.g. the hashtables package, instead.

  • The Data.Ord module now exports the Down newtype, which reverses the sort order of its argument.

1.5.3.3. bin-package-db

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

1.5.3.4. binary

  • Version number 0.5.1.1 (was 0.5.1.0)

1.5.3.5. bytestring

  • Version number 0.10.0.0 (was 0.9.2.1)

  • A new module Data.ByteString.Lazy.Builder has been added.

    The new module defines a Builder monoid, which allows to efficiently construct bytestrings by concatenation. Possible applications include binary serialization, targets for efficient pretty-printers, etc.

1.5.3.6. Cabal

  • Version number 1.16.0 (was 1.14.0)

  • For details of the changes to the Cabal library, please see the Cabal changelog.

1.5.3.7. containers

  • Version number 0.5.0.0 (was 0.4.2.1)

  • See the announcement for details of the changes to the containers library.

1.5.3.8. deepseq

  • Version number 1.3.0.1 (was 1.3.0.0)

1.5.3.9. directory

  • Version number 1.2.0.0 (was 1.1.0.2)

  • The dependency on the old-time package has been changed to time.

1.5.3.10. filepath

  • Version number 1.3.0.1 (was 1.3.0.0)

1.5.3.11. ghc-prim

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

1.5.3.12. haskell98

  • Version number 2.0.0.2 (was 2.0.0.1)

1.5.3.13. haskell2010

  • Version number 1.1.1.0 (was 1.1.0.1)

1.5.3.14. hoopl

  • Version number 3.9.0.0 (was 3.8.7.3)

  • Compiler.Hoopl.Block now contains the Block datatype and all the operations on blocks.

  • Compiler.Hoopl.Graph now has the operations on Graphs.

  • Compiler.Hoopl.Util and Compiler.Hoopl.GraphUtil have been removed; their contents have been moved to other modules.

  • The Dataflow algorithms have been optimized.

  • Numerous other API changes.

1.5.3.15. hpc

  • Version number 0.6.0.0 (was 0.5.1.1)

  • The dependency on the old-time package has been changed to time.

1.5.3.16. integer-gmp

  • Version number 0.5.0.0 (was 0.4.0.0)

1.5.3.17. old-locale

  • Version number 1.0.0.5 (was 1.0.0.4)

1.5.3.18. old-time

  • Version number 1.1.0.1 (was 1.1.0.0)

1.5.3.19. process

  • Version number 1.1.0.2 (was 1.1.0.1)

  • Asynchronous exception bugs in readProcess and readProcessWithExitCode have been fixed.

1.5.3.20. template-haskell

  • 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 StringPrimL constructor for Lit now takes a Word8 array, instead of a String.

1.5.3.21. time

  • Version number 1.4.1 (was 1.4)

1.5.3.22. unix

  • Version number 2.6.0.0 (was 2.5.1.1)

  • Bindings for mkdtemp and mkstemps have been added.

  • New functions setEnvironment and cleanEnv have been added.

  • Bindings for functions to access high resolution timestamps have been added.

1.5.3.23. Win32

  • Version number 2.3.0.0 (was 2.2.2.0)