1.5. Release notes for version 7.2.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.0 branch. The 7.2 branch is intended to be more of a "technology preview" than normal GHC stable branches.

1.5.1. Highlights

1.5.2. Language changes

  • It is now possible to give classes equality superclasses, i.e. you can write something like class (F a ~ b) => C a b where { ... }. See Section 7.7.2.3, “Equality constraints” for more details.

  • The TypeSynonymInstances extension now correctly requires that instances are valid once the type synonym is expanded. For example, in order to have

    instance SomeClass String where
        ...
    

    you need both TypeSynonymInstances and FlexibleInstances enabled, as the latter is necessary for

    instance SomeClass [Char] where
        ...
    
  • The DatatypeContexts extension (which will not be in the next Haskell language standard) is now off by default, and deprecated. It is still enabled by the Haskell98 and Haskell2010 languages. See Section 7.4.2, “Data type contexts” for more details.

  • There is a new extension NondecreasingIndentation, which controls an extension to the layout rule that was previously always enabled. It is now on by default, and (incorrectly, but for backwards compatibility) on in Haskell98, but off in Haskell2010.

  • The new RelaxedLayout extension now controls a small extension to the layout rule that GHC has supported unconditionally for some time. It allows explicit braces to be less indented than implicit braces, without closing the implicit braces, e.g.:

    f x = case x of
         False -> do
        { return x; }
    

    parses as

    f x = case x of
         {False -> do
        { return x; }}
    
  • There is a new family of language extensions, collectively known as "Safe Haskell". This includes notions of "safe modules", "trusted modules" and "trusted packages". See Section 7.20, “Safe Haskell” for more details.

    The new SafeImports extension extends the import declaration syntax to take an optional safe keyword after the import keyword, e.g. with

    import safe Network.Socket
    

    compilation will only succeed if Network.Socket is a "trusted" module. See Section 7.3.19, “Safe imports” for more details.

    The new Trustworthy extension means that users of the package are able to declare that this module is to be trusted, even though GHC can't infer that it is safe. It implies the SafeImports extension. See Section 7.20.4, “Trust” for more details.

    The new Safe extension means GHC will check that a module's code is safe, and that all its imports are trusted. It implies the SafeImports extension, although all imports are required to be trusted anyway. See Section 7.20.2, “Safe Language” for more details.

  • The new extension MonadComprehensions allows comprehension syntax to be usde with any Monad, not just lists. e.g.

    [ x + y | x <- Just 1, y <- Just 2 ]
    

    evaluates to Just 3. See Section 7.3.10, “Monad comprehensions” for more details.

  • The new DefaultSignatures extension allows you to define a default implementation for a class method that isn't as general as the method's type. For example,

    class DefaultValue a where
        defaultValue :: a
        default defaultValue :: Num a => a
        defaultValue = 3
    
    instance DefaultValue Int
    instance DefaultValue Float
    instance DefaultValue Char where
        defaultValue = 'x'
    

    See Section 7.6.1.4, “Default signatures” for more details.

  • The new DeriveGeneric extension allows instances of the new GHC.Generics.Generic class to be derived. Together with the DefaultSignatures extension this allows generic programming. See Section 7.17, “Generic programming” for more details.

  • The Generics extension has now been removed. Use the new DefaultSignatures and DeriveGeneric extensions instead. The {| curly-pipe bracket |} syntax is thus no longer recognised.

    The -XGenerics flag will give a warning, but the -fgenerics flag is no longer accepted.

  • When the new InterruptibleFFI extension is enabled, it is now possible to annotate FFI imports as interruptible, e.g.

    foreign import ccall interruptible
        "sleep" :: CUint -> IO CUint
    

    in which case for most foreign calls it is possible to interrupt the foreign call by using throwTo to throw an exception to the thread making the call. See Section 8.1.4, “Interruptible foreign calls” for more details.

  • The threadsafe FFI annotation is no longer supported. Use safe instead.

  • The OverlappingInstances extension used to allow overlapping instances only when all but the most specific instance were compiled with OverlappingInstances. Now overlap is allowed if either all but the most specific instance were compiled with OverlappingInstances, or if the most specific instance was compiled with OverlappingInstances.

  • There is a new extension GADTSyntax, off by default, which permits generalised algebraic data type syntax for declaring traditional Haskell datatypes. It is enabled by the GADTs extension. See Section 7.4.6, “Declaring data types with explicit constructor signatures” for more details.

  • The NewQualifiedOperators extension, which was deprecated, has now been removed.

  • There are new pragmas VECTORISE, VECTORISE_SCALAR and NOVECTORISE for controlling the behaviour of the vectoriser.

  • Characters in the unicode OtherNumber category are now treated as being 'digit's, rather than 'other graphical' characters.

1.5.3. Warnings

  • The new -fwarn-identities flag warns about uses of toInteger, toRational, fromIntegral and realToFrac which are the identity.

  • The new -fwarn-incomplete-uni-patterns flag warns about pattern matches in a lambda expression or pattern binding which could fail, e.g.

    h = \[] -> 2
    Just k = f y
    
  • The new -fwarn-missing-local-sigs flag warns about polymorphic local bindings without type signatures. The warning includes the inferred type.

  • The new -fwarn-missing-import-lists flag warns if you use an unqualified import declaration that does not explicitly list the entities brought into scope. For example,

    import X (f)
    import Y
    import qualified Z
    

    will warn about the import of Y, but not X or Z. The rationale is that if module Y is later changed to export something called f, then any references to f will become ambiguous.

1.5.4. Dumps

  • The previously-undocumented flag -ddump-to-file causes the output from the other -ddump-* flags to be put in appropriately-named files, rather than printed on stdout.

    This now also includes the -ddump-simpl flag, whose output is put in file_base_name.dump-simpl.

  • The new -dppr-noprags flag omits the pragma info in dumps.

  • The new -ddump-rule-rewrites flag dumps detailed information about all rules that fired in this module.

  • The new -ddump-vect flag dumps the output of the vectoriser.

  • The new -ddump-vt-trace flag makes the vectoriser be very chatty about what it is up to.

  • The new -ddump-core-stats flag prints a one-line summary of the size of the Core program at the end of the optimisation pipeline.

  • The new -dppr-case-as-let flag prints single-alternative case expressions as though they were strict let expressions. This is helpful when your code does a lot of unboxing.

  • The new -dsuppress-all flag suppresses everything that can be suppressed, except for unique ids (as this often makes the printout ambiguous). If you just want to see the overall structure of the code, then start here.

  • The new -dsuppress-idinfo flag suppresses extended information about identifiers where they are bound. This includes strictness information and inliner templates. Using this flag can cut the size of the core dump in half, due to the lack of inliner templates.

  • The new -dsuppress-type-signatures flag suppresses the printing of type signatures.

  • The new -dsuppress-type-applications flag suppresses the printing of type applications.

  • The new -dppr-colsNNN flag sets the width of debugging output. Use this if your code is wrapping too much. For example, -dppr-cols200.

1.5.5. Runtime system

  • The -k RTS flag, which sets the initial thread stack size (default 1k), has been renamed -ki. The old name still works, but may be removed in a future version of GHC.

    There are also new flags -kc, which sets the stack chunk size (default 32k), and -kb, which sets the stack chunk buffer size (default 1k).

  • Profiling reports now use constant width columns, so large values don't cause the layout to go wrong.

  • The -L RTS flag, which sets the width of the labels in heap profile graphs, can now also be used when retainer profiling.

  • The -qw RTS flag is now deprecated. It does nothing, and will be removed in a future version of GHC.

  • We now keep copies of the argument lists we are passed, so it is safe for callers of hs_init() to free the pointers they pass.

  • The archive loader now supports Darwin "fat archives".

  • Linker scripts using INPUT are now supported.

  • The RtsFlags.h header file has finally been removed; use Rts.h instead.

  • There are some new threadscope event types:

    EVENT_CAPSET_CREATECreate capability set
    EVENT_CAPSET_DELETEDelete capability set
    EVENT_CAPSET_ASSIGN_CAPAdd capability to capability set
    EVENT_CAPSET_REMOVE_CAPRemove capability from capability set
    EVENT_RTS_IDENTIFIERRTS name and version
    EVENT_PROGRAM_ARGSProgram arguments
    EVENT_PROGRAM_ENVProgram environment variables
    EVENT_OSPROCESS_PIDProcess ID
    EVENT_OSPROCESS_PPIDParent process ID

  • The linker now supports kfreebsdgnu.

1.5.6. Compiler

  • When using Haskell code as a library, and calling it from another language, it is no longer necessary to call the hs_add_root function.

  • The "evil mangler" has been removed, and registerised compilation via C is no longer supported. This means that the -fvia-c, -fvia-C, -keep-raw-s-file, -keep-raw-s-files, -pgmm, -optm, -monly-2-regs, -monly-3-regs and -monly-4-regs flags are now deprecated, and have no effect. The -fasm-mangling and -fno-asm-mangling flags have been removed.

    Unregisterised compilation, for architectures for which there is no native code generator, is still possible, and still compiles via C.

  • Compiling Objective-C (.m) files is now supported, assuming your gcc is capable of compiling them.

  • The new "Safe Haskell" extensions introduce three new GHC flags: -trust P exposes package P if it was hidden and considers it a trusted package; -distrust P exposes package P if it was hidden and considers it an untrusted package; -distrust-all-packages considers all packages distrusted unless they are explicitly set to be trusted by subsequent command-line options.

  • Significant progress has been made on the new code generator, but it is not yet ready for prime-time. If you want to try it out, use the -fnew-codegen flag.

  • The Alpha native code generator had bitrotted, so has now been removed.

  • Running ghc -v ... will no longer pass -v to gcc. You now need to use ghc -v4 ... (or higher) instead.

  • The -Odph flag is now equivalent to -O2 -fsimplifier-phases=3 -fsimplifier-iterations=20.

  • There is a new -fdph-none flag can be used to specify that no DPH backend should be used. It is now the default, i.e. -fdph-par or -fdph-seq need to be explicitly specified if required.

  • The -n flag has been removed.

  • The -fmethod-sharing flag has been removed.

1.5.7. GHCi

  • GHCi now has a multiline-input mode, enabled with :set +m. For example,

    Prelude> :set +m
    Prelude> let x = 3
    Prelude|     y = 4
    Prelude| in x + y
    7
    Prelude>
    
  • The new :script command takes a filename as an argument, and executes each line in that file. It supports multiline statements if the +m mode is set.

  • The new :issafe command tells you whether a module is considered to be trusted or not.

  • When resolving abbreviated GHCi commands, we now prefer built-in commands to user defined commands. This makes things more consistent, e.g. :i will always mean :info, unless :i itself is defined by the user.

  • The :m +M and import M GHCi commands now do exactly the same thing.

  • With a new flag -ghci-script you can specify additional files to be read on startup, in the same way that .ghci is.

1.5.8. ghc-pkg

  • There are new ghc-pkg commands trust and distrust, used for setting the trustworthiness of packages for Safe Haskell. See Section 4.9.6, “Package management (the ghc-pkg command)” for more details.

  • The new flags -expand-env-vars, -expand-pkgroot and -no-expand-pkgroot control whether the ${pkgroot}, ${pkgrooturl} and ${topdir} variables are expanded when printing information.

  • The --auto-ghci-libs flag is deprecated, and will be removed in a future version.

1.5.9. hsc2hs

  • Cross-compilation is now supported by hsc2hs, for most features. The new --cross-compile (or -x) flag enables cross-compilation, while --cross-safe checks that only features for which cross-compilation works are used. See Section 11.2.4, “Cross-compilation” for more details.

  • The new --keep-files (or -k) flag makes hsc2hs keep the intermediate files that it generates.

1.5.10. GHC API

  • GHC now has support for "plugins". This feature allows you to write a Core-to-Core pass and have it dynamically linked into an otherwise-unmodified GHC, and run at a place you specify in the Core optimisation pipeline.

    The new -fplugin=module flag specifies that module is to be used as a plugin, and -fplugin-opt=module:args allows arguments to be passed to the plugin.

    See Section 9.3, “Compiler Plugins” for more details.

  • Coercions now have their own datatype rather than being represented as types. They are now value-level things, rather than type-level things, although the value is zero bits wide (like the State token).

  • The StmtLR datatype has a new constructor LastStmt, which holds the final (expression) statement of all comprehensions and do-blocks.

  • The printExceptionAndWarnings function has been deprecated, in favour of the new printException function.

  • The SrcSpan and SrcLoc types have been refactored so that the new RealSrcSpan and RealSrcLoc types are used when we have a real location, rather than an "unhelpful" location.

  • The type of defaultErrorHandler has changed. In particular, this means that you will normally want to pass it defaultLogAction instead of defaultDynFlags.

  • Calling withFlattenedDynflags is no longer necessary, and the function has been removed.

  • Several of the old native code generator modules gained an Old prefix, when their names clashed with modules in the new native code generator.

1.5.11. Build System and Infrastructure

  • GHC development now uses git repositories, rather than darcs repositories. Instructions for getting source trees are on the GHC wiki.

    The sync-all script, rather than the darcs-all script, is now used for dealing with repositories.

  • GHC >= 6.12 is now required to build GHC.

  • Building with gcc 4.6 now works.

  • On Windows, we now bundle gcc 4.5.2-1 (was 4.5.0-1).

  • GHC now works with LLVM 3.0.

  • The location of gcc, and various other settings, is now in a settings file. The extra-gcc-opts file is no longer used.

  • It is no longer necessary to set GhcWithLlvmCodeGen = YES in order to get llvm support: llvm support is now always enabled.

  • The new code generator is not yet ready for prime-time, but if you want to experiment with it you can make it the default by setting

    GhcStage1DefaultNewCodegen=YES
    GhcStage2DefaultNewCodegen=YES
    GhcStage3DefaultNewCodegen=YES
    

    in your mk/build.mk.

  • Platforms with a vendor of softfloat, such as armv5tel-softfloat-linux-gnueabi, are now supported.

1.5.12. Libraries

  • Unicode support has generally been improved across the core libraries. This has a few consequences:

    Code that has been using the *CString functions may need to be corrected to use the *CAString functions.

    Users may now observe strings — particularly those from the commandline — containing private-use characters, i.e. those in the range 0xEF00 to 0xEFFF inclusive.

    Programs may now get exceptions when writing strings in the wrong encoding to (for example) stdout.

1.5.12.1. array

  • Version number 0.3.0.3 (was 0.3.0.2)

1.5.12.2. base

  • Version number 4.4.0.0 (was 4.3.1.0)

  • The Typeable module has been overhauled. The mkTyCon function has been deprecated; the preferable fix is to derive Typeable instead (see Section 7.5.3, “Deriving clause for extra classes (Typeable, Data, etc)”), although there is also a replacement for mkTyCon in the form of a new function mkTyCon3, which takes separate strings for the package, module and name of the type constructor. Also, typeRepKey is deprecated, and both TypeRep and TyCon now have Ord instances which means they can be used as Map keys.

  • The result of gcd 0 0 is now 0, rather than throwing an exception.

  • The result of minBound `rem` -1 and minBound `div` -1 is now 0, rather than throwing an overflow exception.

  • Control.Concurrent now exports new functions forkIOWithUnmask, forkOn, forkOnWithUnmask, getNumCapabilities and threadCapability. The forkIOUnmasked function has been deprecated in favour of forkIOWithUnmask.

    The same changes have been made to GHC.Conc and GHC.Conc.Sync.

  • Control.Exception exports a new function allowInterrupt which, when invoked inside mask, allows a blocked asynchronous exception to be raised, if one exists.

  • System.IO.Unsafe now exports the new function unsafeDupablePerformIO. This is a more efficient version of unsafePerformIO, but may run the IO action multiple times (currently, in GHC, only when multiple threads try to evaluate it simultaneously).

  • System.IO.Error now exports new functions catchIOError and tryIOError. The try and catch functions are now deprecated.

  • GHC.IO.Encoding now exports three new TextEncodings:

    The fileSystemEncoding encoding is the Unicode encoding of the current locale, but allows arbitrary undecodable bytes to be round-tripped through it. It is used to decode and encode command line arguments and environment variables on non-Windows platforms.

    The foreignEncoding encoding is the Unicode encoding of the current locale, but undecodable bytes are replaced with their closest visual match. It's used for the CString marshalling functions in Foreign.C.String.

    In the char8 encoding Unicode code points are translated to bytes by taking the code point modulo 256. When decoding, bytes are translated directly into the equivalent code point. This encoding is also exported by System.IO.

  • The functions to make TextEncodings now have mk* variants which take a CodingFailureMode argument. The new functions, together with what they generalise, are:

    GHC.IO.Encoding.Latin1latin1mkLatin1
    GHC.IO.Encoding.Latin1latin1_checkedmkLatin1_checked
    GHC.IO.Encoding.UTF8utf8mkUTF8
    GHC.IO.Encoding.UTF8utf8_bommkUTF8_bom
    GHC.IO.Encoding.UTF16utf16mkUTF16
    GHC.IO.Encoding.UTF16utf16bemkUTF16be
    GHC.IO.Encoding.UTF16utf16lemkUTF16le
    GHC.IO.Encoding.UTF32utf32mkUTF32
    GHC.IO.Encoding.UTF32utf32bemkUTF32be
    GHC.IO.Encoding.UTF32utf32lemkUTF32le

    Similarly, there are new mkCodePageEncoding and mkLocaleEncoding generalisations of codePageEncoding and localeEncoding in GHC.IO.Encoding.CodePage.

    GHC.IO.Encoding.Iconv has been similarly altered, and now only exports iconvEncoding, mkIconvEncoding, localeEncoding and mkLocaleEncoding.

  • GHC.IO.Encoding.Types and GHC.IO.Encoding now export a new type CodingProgress which describes the state of a text encoder. The BufferCodec, DecodeBuffer and EncodeBuffer types have also changed.

  • GHC.IO now exports bracket.

  • GHC.IO.blocked is now deprecated in favour of Control.Exception.getMaskingState.

  • GHC.Show now exports two new helpers, showLitString (analogous to showLitChar) and showMultiLineString (which breaks a string containing newlines characters up into multiple strings).

  • The type of GHC.IO.FD.openFile has changed to include a flag for whether to open the file in non-blocking mode.

  • GHC.IO.Handle.FD now exports a variant openFileBlocking of openFile, which opens the file in blocking mode.

  • The type of Foreign.Marshal.Utils.maybeNew has been generalised to (a -> IO (Ptr b)) -> (Maybe a -> IO (Ptr b))

  • Foreign.C.Types now exports new types CUSeconds and CSUSeconds, corresponding to the C types useconds_t and suseconds_t respectively.

  • System.Posix.Internals new exports new functions peekFilePath and, on non-Windows platforms, peekFilePathLen and c_safe_open.

  • Data.List.inits, Data.List.tails, Data.List.intersperse and Data.List.intersectBy are now lazier.

  • Data.Char no longer exports String.

  • Data.String now re-exports String, lines, unlines, words and unwords.

  • There is now a Read instance for Data.Fixed.Fixed a.

  • There are now Eq instances for Control.Concurrent.Chan.Chan, Control.Concurrent.QSem.QSem and Control.Concurrent.QSemN.QSemN.

  • There are now Applicative instances for Control.Monad.ST.ST and Control.Monad.ST.Lazy.ST.

  • There is now a Typeable instance for Control.Concurrent.SampleVar.SampleVar.

  • Most of GHC.PArr has been moved into the dph package. Only the [::] datatype remains.

  • There is a new module Control.Monad.Group for monadic grouping (used for monad comprehensions).

  • There is a new module Control.Monad.Zip for monadic zipping (used for monad comprehensions).

  • There is a new internal module GHC.Foreign which provides versions of some C string functions generalised to be usable with any encoding.

  • There is a new internal module GHC.IO.Encoding.Failure which provides functionality for specifying how text encoding and decoding fails.

  • On Windows, there is a new internal module GHC.Windows which duplicates part of System.Win32.Types.

  • Some functions have been moved from GHC.Base down into GHC.Classes.

  • There are now new internal modules GHC.Float.ConversionUtils and GHC.Float.RealFracMethods.

  • The safe parts of the Foreign module are now in a new module Foreign.Safe. Foreign now reexports all the safe code it used to, as well as deprecated copies of the unsafe functions.

  • The Foreign.ForeignPtr module has been split into Foreign.ForeignPtr.Safe and Foreign.ForeignPtr.Unsafe. Foreign.ForeignPtr now reexports Foreign.ForeignPtr.Safe and a deprecated copy of the unsafe function (unsafeForeignPtrToPtr).

  • The Foreign.Marshal module has been split into Foreign.Marshal.Safe and Foreign.Marshal.Unsafe. Foreign.Marshal now reexports Foreign.Marshal.Safe and a deprecated copy of the unsafe function (unsafeLocalState).

  • The Control.Monad.ST module has been split into Control.Monad.ST.Safe and Control.Monad.ST.Unsafe. Control.Monad.ST now reexports Control.Monad.ST.Safe and deprecated copies of the unsafe functions (unsafeInterleaveST, unsafeIOToST and unsafeSTToIO).

  • The Control.Monad.ST.Lazy module has been split into Control.Monad.ST.Lazy.Safe and Control.Monad.ST.Lazy.Unsafe. Control.Monad.ST.Lazy now reexports Control.Monad.ST.Lazy.Safe and deprecated copies of the unsafe functions (unsafeInterleaveST and unsafeIOToST).

  • The System.Event module has been renamed GHC.Event.

  • Following the removal of DatatypeContexts from the language, the definitions of Control.Arrow.ArrowMonad, Array and Complex and Ratio have had their datatype contexts removed.

  • Many modules have been marked Trustworthy.

  • System.Posix.Internals now exports a function puts, for debugging within the base package.

  • The Unicode data is now based on version 6.0.0 (was 5.1.0) of the Unicode spec.

1.5.12.3. bin-package-db

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

1.5.12.4. binary

  • New package, version 0.5.1.0. TODO: Bump version It is not exposed by default.

1.5.12.5. bytestring

  • Version number 0.9.2.0 (was 0.9.1.10)

  • There is now an hPutNonBlocking function in Data.ByteString, Data.ByteString.Char8, Data.ByteString.Lazy and Data.ByteString.Lazy.Char8.

  • There are now hPutStrLn and putStrLn functions in Data.ByteString.Char8 and Data.ByteString.Lazy.Char8.

    The functions in Data.ByteString and Data.ByteString.Lazy are now deprecated.

1.5.12.6. Cabal

  • Version number 1.12.0.0 (was 1.10.2.0) TODO: Currently we have 1.11.0. The branch needs to be created.

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

1.5.12.7. containers

  • Version number 0.4.1.0 (was 0.4.0.0) TODO: Bump version

  • Data.Map now exports new functions foldrWithKey' and foldlWithKey', which are strict variants of foldrWithKey and foldlWithKey respectively.

  • Data.IntMap now exports new functions insertWith' and insertWithKey', which are strict variants of insertWith and insertWithKey respectively.

1.5.12.8. directory

  • Version number 1.1.0.1 (was 1.1.0.0)

1.5.12.9. extensible-exceptions

  • Version number 0.1.1.3 (was 0.1.1.2)

1.5.12.10. filepath

  • Version number 1.2.0.1 (was 1.2.0.0)

  • The handling of "." as a component in a FilePath is now more consistent. See #3975 for more information.

1.5.12.11. ghc-binary

  • GHC no longer includes this internal package.

1.5.12.12. ghc-prim

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

1.5.12.13. haskell98

  • Version number 2.0.0.0 (was 1.1.0.1)

  • It is no longer possible to use the haskell98 package with the base package, as it now includes the Prelude and Numeric modules. The haskell98 package is therefore now hidden by default.

1.5.12.14. haskell2010

  • Version number 1.1.0.0 (was 1.0.0.0)

  • The splitAt function now has the correct strictness, as defined by the report.

1.5.12.15. hoopl

  • This is a new package, version 3.8.7.2. TODO: Bump version number. 3.8.7.1 is on hackage.

1.5.12.16. hpc

  • Version number 0.5.1.0 (was 0.5.0.6)

  • A new function catchIO is now exported by Trace.Hpc.Util.

1.5.12.17. integer-gmp

  • Version number 0.3.0.0 (was 0.2.0.2)

  • Now exposes two new modules, GHC.Integer.Logarithms and GHC.Integer.Logarithms.Internals.

  • The toInt# function has been renamed to integerToInt.

1.5.12.18. old-locale

  • Version number 1.0.0.3 (was 1.0.0.2)

1.5.12.19. old-time

  • Version number 1.0.0.7 (was 1.0.0.6)

1.5.12.20. pretty

  • Version number 1.1.0.0 (was 1.0.1.2)

  • There is a new function sizedText, which allows you to specify the width that a string should be considered to have.

  • The Doc type is now an instance of IsString and Monoid.

1.5.12.21. process

  • Version number 1.1.0.0 (was 1.0.1.4)

  • There is a new function showCommandForUser in System.Process which, given a program and its arguments, returns a string suitable for pasting into sh (on POSIX OSs) or cmd.exe (on Windows).

  • There is a new function interruptProcessGroupOf in System.Process which sends an interrupt signal to the process group of the given process. On Unix systems, it sends the group the SIGINT signal. On Windows systems, it generates a CTRL_BREAK_EVENT and will only work for processes created using createProcess with the create_group flag set.

  • The CreateProcess constructor, exported by System.Process.Internals and System.Process, has a new Bool field create_group which specifies whether a process group should be created.

  • The type of withCEnvironment on Windows is now more consistent with other platforms, as the action now takes a Ptr CWString rather than Ptr ().

1.5.12.22. random

  • GHC no longer includes the random library

1.5.12.23. template-haskell

  • Version number 2.6.0.0 (was 2.5.0.0)

  • In Language.Haskell.TH.Syntax the Exp, Pat and Type datatypes have new constructors UnboxedTupE, UnboxedTupP and UnboxedTupleT respectively. There are also new helper functions unboxedTupleTypeName and unboxedTupleDataName.

    There are corresponding helper functions unboxedTupE, unboxedTupP and unboxedTupleT in Language.Haskell.TH.Lib.

  • In Language.Haskell.TH.Syntax the Safety type has a new constructor Interruptible.

    There is a corresponding new value interruptible :: Safety in Language.Haskell.TH.Lib.

    However, the Threadsafe constructor and threadsafe helper have been removed, following the removal of the feature from GHC.

  • In Language.Haskell.TH.Syntax, the classInstances function now has type Name -> [Type] -> Q [ClassInstance], and the qClassInstances instance of the Quasi class now has type Name -> [Type] -> m [ClassInstance].

  • There are now helper functions pprString and hashParens exported from Language.Haskell.TH.Ppr.

  • The helper functions combine, rename, genpat, alpha and simpleMatch have been removed from Language.Haskell.TH.Lib.

1.5.12.24. time

  • Version number 1.2.0.5 (was 1.2.0.3)

  • The %-, %_ and %0 specifiers can now be used. For example,

    > parseTime defaultTimeLocale "%-m/%e/%Y" "3/9/2011" :: Maybe Day
    Just 2011-03-09
    
  • The default year is now correctly in the range 1969-2068, rather than 1900-1999.

  • Some cases in which an exception was thrown now correctly return Nothing.

1.5.12.25. unix

  • Version number 2.5.0.0 (was 2.4.2.0)

  • In System.Posix.Process the createProcessGroup and setProcessGroupID functions have been deprecated.

    There are new functions, which subsume their functionality, called createProcessGroupFor, getProcessGroupIDOf and setProcessGroupIDOf.

  • In System.Posix.Error, there is a new variant of throwErrnoPathIfMinus1Retry called throwErrnoPathIfMinus1Retry_, which returns IO ().

1.5.12.26. Win32

  • Version number 2.2.1.0 (was 2.2.0.2)

  • There are new functions getProcessId and c_GetProcessId in System.Win32.Process.