31ac6099d07b0bf57a6d84a9b012b0d0b0b7a446
[ghc-hetmet.git] / docs / users_guide / 7.0.1-notes.xml
1 <?xml version="1.0" encoding="iso-8859-1"?>
2 <sect1 id="release-7-0-1">
3   <title>Release notes for version 7.0.1</title>
4
5   <para>
6     The significant changes to the various parts of the compiler are
7     listed in the following sections. There have also been numerous bug
8     fixes and performance improvements over the 6.12 branch.
9   </para>
10
11   <sect2>
12     <title>Highlights</title>
13     <itemizedlist>
14       <listitem>
15         <para>
16           GHC now defaults to the Haskell 2010 language standard.
17         </para>
18
19         <para>
20           Libraries are not quite so straightforward.  By default, GHC
21           provides access to the <literal>base</literal> package,
22           which includes the Haskell 2010 libraries, albeit with a few
23           minor differences.  For those who want to write strictly
24           standards-conforming code we also provide
25           the <literal>haskell2010</literal> package which provides
26           the precise APIs specified by Haskell 2010, but because the
27           module names in this package overlap with those in
28           the <literal>base</literal> package it is not possible to
29           use both <literal>haskell2010</literal>
30           and <literal>base</literal> at the same time (this also
31           applies to the <literal>array</literal> package).  Hence to use
32           the Haskell 2010 libraries you should hide
33           the <literal>base</literal> and <literal>array</literal>
34           packages, for example with GHCi:
35 <screen>
36 $ ghci -package haskell2010 -hide-package base -hide-package array
37 </screen>
38           If you are using Cabal it isn't necessary to
39           hide <literal>base</literal> and <literal>array</literal>
40           explicitly, just don't include them in your <literal>build-depends</literal>.
41         </para>
42       </listitem>
43
44       <listitem>
45         <para>
46           On POSIX platforms, there is a new I/O manager based on
47           epoll/kqueue/poll, which allows multithreaded I/O code to
48           scale to a much larger number (100k+) of threads.
49         </para>
50       </listitem>
51
52       <listitem>
53         <para>
54                                         GHC now includes an LLVM code generator. For certain code,
55                                         particularly arithmetic heavy code, using the LLVM code
56                                         generator can bring some nice performance improvements.
57         </para>
58       </listitem>
59
60       <listitem>
61         <para>
62           The inliner has been overhauled, which should in general
63           give better performance while reducing unnecessary code-size
64           explosion.
65         </para>
66       </listitem>
67
68       <listitem>
69         <para>
70           Large parts of the runtime system have been overhauled, in
71           particular the machinery related to blocking and wakeup of
72           threads and exception throwing (<literal>throwTo</literal>).
73           Several instances of pathological performance have been
74           fixed, especially where large numbers of threads are
75           involved.
76         </para>
77       </listitem>
78
79       <listitem>
80         <para>
81           Due to changes in the runtime system, if you are
82           using <literal>Control.Parallel.Strategies</literal> from
83           the <literal>parallel</literal> package, please upgrade to
84           at least version 2 (preferably version 3).  The
85           implementation of Strategies
86           in <literal>parallel-1.x</literal> will lose parallelism
87           with GHC 7.0.1.
88         </para>
89       </listitem>
90
91       <listitem>
92         <para>
93           The full Haskell <literal>import</literal> syntax can now been
94           used to bring modules into scope in GHCi, e.g.
95         </para>
96 <programlisting>
97 Prelude> import Data.List as L
98 Prelude Data.List> L.length "foo"
99 3
100 </programlisting>
101       </listitem>
102
103       <listitem>
104         <para>
105           GHC now comes with a more recent mingw bundled on Windows,
106           which includes a fix for windres on Windows 7.
107         </para>
108       </listitem>
109     </itemizedlist>
110   </sect2>
111
112   <sect2>
113     <title>Language changes</title>
114     <itemizedlist>
115       <listitem>
116         <para>
117           GHC now understands the <literal>Haskell98</literal> and
118           <literal>Haskell2010</literal> languages.
119         </para>
120
121         <para>
122           These get processed before the language extension pragmas,
123           and define the default sets of extensions that are enabled.
124           If neither is specified, then the default is
125           <literal>Haskell2010</literal> plus the
126           <literal>MonoPatBinds</literal> extension.
127         </para>
128       </listitem>
129
130       <listitem>
131         <para>
132           GHC now supports the <literal>DoAndIfThenElse</literal>
133           extension, which is part of the Haskell 2010 standard.
134         </para>
135       </listitem>
136
137       <listitem>
138         <para>
139           Datatype contexts, such as the <literal>Eq a</literal> in
140         </para>
141 <programlisting>
142 data Eq a => Set a = NilSet | ConsSet a (Set a)
143 </programlisting>
144         <para>
145           are now treated as an extension
146           <literal>DatatypeContexts</literal> (on by default) by GHC.
147         </para>
148       </listitem>
149
150       <listitem>
151         <para>
152           GHC's support for unicode source has been improved, including
153           removing support for U+22EF for the <literal>..</literal>
154           symbol. See <xref linkend="unicode-syntax" /> for more details.
155         </para>
156       </listitem>
157
158       <listitem>
159         <para>
160           Pragmas are now reread after preprocessing. In particular,
161           this means that if a pragma is used to turn CPP on, then other
162           pragmas can be put in CPP conditionals.
163         </para>
164       </listitem>
165
166       <listitem>
167         <para>
168           The <literal>TypeOperators</literal> extension now allows
169           instance heads to use infix syntax.
170         </para>
171       </listitem>
172
173       <listitem>
174         <para>
175           The <literal>PackageImports</literal> extension now understands
176           <literal>this</literal> to mean the current package.
177         </para>
178       </listitem>
179
180       <listitem>
181         <para>
182           The <literal>INLINE</literal> and <literal>NOINLINE</literal>
183           pragmas can now take a <literal>CONLIKE</literal> modifier,
184           which indicates that the right hand side is cheap to compute,
185           and can thus be duplicated more freely.
186           See <xref linkend="conlike" /> for more details.
187         </para>
188       </listitem>
189
190       <listitem>
191         <para>
192           A <literal>ForceSpecConstr</literal> annotation on a type, e.g.
193         </para>
194 <programlisting>
195 import SpecConstr
196 {-# ANN type SPEC ForceSpecConstr #-}
197 </programlisting>
198         <para>
199           can be used to force GHC to fully specialise argument of that
200           type.
201         </para>
202       </listitem>
203
204       <listitem>
205         <para>
206           A <literal>NoSpecConstr</literal> annotation on a type, e.g.
207         </para>
208 <programlisting>
209 import SpecConstr
210 {-# ANN type T NoSpecConstr #-}
211 </programlisting>
212         <para>
213           can be used to prevent SpecConstr from specialising on
214           arguments of that type.
215         </para>
216       </listitem>
217
218       <listitem>
219         <para>
220           There is are two experimental new extensions
221           <literal>AlternativeLayoutRule</literal> and
222           <literal>AlternativeLayoutRuleTransitional</literal>,
223           which are for exploring alternative layout rules in Haskell'.
224           The details are subject to change, so we advise against using
225           them in real code for now.
226         </para>
227       </listitem>
228
229       <listitem>
230         <para>
231           The <literal>NewQualifiedOperators</literal> extension has
232           been deprecated, as it was rejected by the Haskell' committee.
233         </para>
234       </listitem>
235     </itemizedlist>
236   </sect2>
237
238   <sect2>
239     <title>Warnings</title>
240     <itemizedlist>
241       <listitem>
242         <para>
243           There is now a warning for missing import lists, controlled
244           by the new <literal>-fwarn-missing-import-lists</literal> flag.
245         </para>
246       </listitem>
247
248       <listitem>
249         <para>
250           GHC will now warn about <literal>SPECIALISE</literal> and
251           <literal>UNPACK</literal> pragmas that have no effect.
252         </para>
253       </listitem>
254     </itemizedlist>
255   </sect2>
256
257   <sect2>
258     <title>DLLs</title>
259     <itemizedlist>
260       <listitem>
261         <para>
262           Shared libraries are once again supported on Windows.
263         </para>
264       </listitem>
265
266       <listitem>
267         <para>
268           Shared libraries are now supported on OS X, both on x86 and on
269           PowerPC. The new <literal>-dylib-install-name</literal> GHC
270           flag is used to set the location of the dynamic library.
271           See <xref linkend="finding-shared-libs" /> for more details.
272         </para>
273       </listitem>
274     </itemizedlist>
275   </sect2>
276
277   <sect2>
278     <title>Runtime system</title>
279
280     <itemizedlist>
281       <listitem>
282         <para>
283           For security reasons, by default, the only RTS flag that
284           programs accept is <literal>+RTS --info</literal>. If you want
285           the full range of RTS flags then you need to link with the new
286           <literal>-rtsopts</literal> flag. See
287           <xref linkend="options-linker" /> for more details.
288         </para>
289       </listitem>
290
291       <listitem>
292         <para>
293           The RTS now exports a function <literal>setKeepCAFs</literal>
294           which is important when loading Haskell DLLs dynamically, as
295           a DLL may refer to CAFs that hae already been GCed.
296         </para>
297       </listitem>
298
299       <listitem>
300         <para>
301           The garbage collector no longer allows you to specify a number
302           of steps; there are now always 2. The <literal>-T</literal>
303           RTS flag has thus been removed.
304         </para>
305       </listitem>
306
307       <listitem>
308         <para>
309           A new RTS flag <literal>-H</literal> causes the RTS to use a
310           larger nursery, but without exceeding the amount of memory
311           that the application is already using. It makes some programs
312           go slower, but others go faster.
313         </para>
314       </listitem>
315
316       <listitem>
317         <para>
318           GHC now returns memory to the OS, if memory usage peaks and
319           then drops again. This is mainly useful for long running
320           processes which normally use very little memory, but
321           occasionally need a lot of memory for a short period of time.
322         </para>
323       </listitem>
324
325       <listitem>
326         <para>
327           On OS X, eventLog events are now available as DTrace probes.
328         </para>
329       </listitem>
330
331       <listitem>
332         <para>
333           The PAPI support has been improved. The new RTS flag
334           <literal>-a#0x40000000</literal> can be used to tell the RTS
335           to collect the native PAPI event <literal>0x40000000</literal>.
336         </para>
337       </listitem>
338     </itemizedlist>
339   </sect2>
340
341   <sect2>
342     <title>Compiler</title>
343     <itemizedlist>
344       <listitem>
345         <para>
346           GHC now defaults to <literal>--make</literal> mode, i.e. GHC
347           will chase dependencies for you automatically by default.
348         </para>
349       </listitem>
350
351       <listitem>
352         <para>
353           GHC now includes an LLVM code generator.
354         </para>
355         <para>
356           This includes a number of new flags:
357           a flag to tell GHC to use LLVM, <literal>-fllvm</literal>;
358           a flag to dump the LLVM input ,<literal>-ddump-llvm</literal>;
359           flags to keep the LLVM intermediate files,
360           <literal>-keep-llvm-file</literal> and
361           <literal>-keep-llvm-files</literal>;
362                                         flags to set the location and options for the LLVM optimiser
363                                         and compiler,
364           <literal>-pgmlo</literal>,
365           <literal>-pgmlc</literal>,
366           <literal>-optlo</literal> and
367           <literal>-optlc</literal>.
368                                         The LLVM code generator requires LLVM version 2.7 or later on
369                                         your path.
370         </para>
371       </listitem>
372
373       <listitem>
374         <para>
375           It is now possible to use <literal>-fno-code</literal> with
376           <literal>--make</literal>.
377         </para>
378       </listitem>
379
380       <listitem>
381         <para>
382           The new flag <literal>-dsuppress-coercions</literal> controls
383           whether GHC prints coercions in core dumps.
384         </para>
385       </listitem>
386
387       <listitem>
388         <para>
389           The new flag <literal>-dsuppress-module-prefixes</literal>
390           controls whether GHC prints module qualification prefixes
391           in core dumps.
392         </para>
393       </listitem>
394
395       <listitem>
396         <para>
397           The inliner has been overhauled. The most significant
398           user-visible change is that only saturated functions are
399           inlined, e.g.
400         </para>
401 <programlisting>
402 (.) f g x = f (g x)
403 </programlisting>
404         <para>
405           would only be inlined if <literal>(.)</literal> is applied to 3
406           arguments, while
407         </para>
408 <programlisting>
409 (.) f g = \x -> f (g x)
410 </programlisting>
411         <para>
412           will be inlined if only applied to 2 arguments.
413         </para>
414       </listitem>
415
416       <listitem>
417         <para>
418           The <literal>-finline-if-enough-args</literal> flag is no
419           longer supported.
420         </para>
421       </listitem>
422
423       <listitem>
424         <para>
425           Column numbers in warnings and error messages now start at 1,
426           as is more standard, rather than 0.
427         </para>
428       </listitem>
429
430       <listitem>
431         <para>
432           GHCi now understands most linker scripts. In particular, this
433           means that GHCi is able to load the C pthread library.
434         </para>
435       </listitem>
436
437       <listitem>
438         <para>
439           The <literal>ghc --info</literal> output has been updated:
440         </para>
441         <para>
442           It now includes the
443           location of the global package database, in the
444           <literal>Global Package DB</literal> field.
445         </para>
446         <para>
447           It now includes the build, host and target platforms, in the
448           <literal>Build platform</literal>,
449           <literal>Host platform</literal> and
450           <literal>Target platform</literal> fields.
451         </para>
452         <para>
453           It now includes a <literal>Have llvm code generator</literal>
454           field.
455         </para>
456         <para>
457           The <literal>Win32 DLLs</literal> field has been removed.
458         </para>
459       </listitem>
460
461       <listitem>
462         <para>
463           The registerised via-C backend, and the
464           <literal>-fvia-C</literal> flag, have been deprecated. The poor
465           floating-point performance in the x86 native code generator
466           has now been fixed, so we don't believe there is still any
467           reason to use the via-C backend.
468         </para>
469       </listitem>
470
471       <listitem>
472         <para>
473           There is now a new flag <literal>--supported-extensions</literal>,
474           which currently behaves the same as
475           <literal>--supported-languages</literal>.
476         </para>
477       </listitem>
478
479       <listitem>
480         <para>
481           GHC progress output such as
482         </para>
483 <programlisting>
484 [ 1 of 5] Compiling Foo              ( Foo.hs, Foo.o )
485 </programlisting>
486         <para>
487           is now sent to stdout rather than stderr.
488         </para>
489       </listitem>
490
491       <listitem>
492         <para>
493           The new flag <literal>-fexpose-all-unfoldings</literal>
494           makes GHC put unfoldings for <emphasis>everything</emphasis>
495           in the interface file.
496         </para>
497       </listitem>
498
499       <listitem>
500         <para>
501           There are two new flags, <literal>-fno-specialise</literal>
502           and <literal>-fno-float-in</literal>, for disabling the
503           specialise and float-in passes.
504         </para>
505       </listitem>
506
507       <listitem>
508         <para>
509           The new flag <literal>-fstrictness-before=<replaceable>n</replaceable></literal> tells
510           GHC to run an additional strictness analysis pass
511           before simplifier phase <replaceable>n</replaceable>.
512         </para>
513       </listitem>
514
515       <listitem>
516         <para>
517           There is a new flag
518           <literal>-funfolding-dict-discount</literal>
519           for tweaking the optimiser's behaviour.
520         </para>
521       </listitem>
522
523       <listitem>
524         <para>
525           The <literal>-fspec-inline-join-points</literal> flag has been
526           removed.
527         </para>
528       </listitem>
529
530       <listitem>
531         <para>
532           The <literal>-dynload wrapper</literal> flag has been
533           removed.
534         </para>
535       </listitem>
536     </itemizedlist>
537   </sect2>
538
539   <sect2>
540     <title>GHCi</title>
541     <itemizedlist>
542       <listitem>
543         <para>
544           GHCi now understands layout in multi-line commands, so
545           this now works:
546         </para>
547 <programlisting>
548 Prelude> :{
549 Prelude| let x = 1
550 Prelude|     y = 2 in x + y
551 Prelude| :}
552 3
553 </programlisting>
554       </listitem>
555     </itemizedlist>
556   </sect2>
557
558   <sect2>
559     <title>Template Haskell and Quasi-Quoters</title>
560     <itemizedlist>
561       <listitem>
562         <para>
563           It is now possible to quasi-quote patterns with
564           <literal>[p| ... |]</literal>.
565         </para>
566       </listitem>
567
568       <listitem>
569         <para>
570           It is no longer to use a <literal>$</literal> before the
571           name of a quasi-quoter, e.g. one can now say
572           <literal>[expr| ... |]</literal> rather than
573           <literal>[$expr| ... |]</literal>.
574         </para>
575       </listitem>
576
577       <listitem>
578         <para>
579           It is now possible to use a quasi-quoter for types, e.g.
580           <literal>f :: [$qq| ... |]</literal>
581         </para>
582       </listitem>
583
584       <listitem>
585         <para>
586           It is now possible to quasi-quote existentials and GADTs.
587         </para>
588       </listitem>
589     </itemizedlist>
590   </sect2>
591
592   <sect2>
593     <title>GHC API</title>
594     <itemizedlist>
595       <listitem>
596         <para>
597           There are now <literal>Data</literal> and
598           <literal>Typeable</literal> instances for the
599           HsSyn typed.
600         </para>
601       </listitem>
602
603       <listitem>
604         <para>
605           As language extensions are not applied until after the base
606           language (Haskell98, Haskell2010 or the default) has been
607           selected, it is now necessary to tell the GHC API the point
608           at which the extension flags should be processed. Normally
609           this is done by calling
610           <literal>DynFlags.flattenExtensionFlags</literal> once all
611           the flags and pragmas have been read.
612         </para>
613       </listitem>
614     </itemizedlist>
615   </sect2>
616
617   <sect2>
618     <title>Libraries</title>
619
620     <sect3>
621         <title>array</title>
622         <itemizedlist>
623             <listitem>
624                 <para>
625                     Version number 0.3.0.2 (was 0.3.0.1)
626                 </para>
627             </listitem>
628         </itemizedlist>
629     </sect3>
630
631     <sect3>
632         <title>base</title>
633         <itemizedlist>
634             <listitem>
635                 <para>
636                     Version number 4.3.0.0 (was 4.2.0.2)
637                 </para>
638             </listitem>
639
640             <listitem>
641                 <para>
642                     There is a new asynchronous exception control API
643                     in <literal>Control.Exception</literal>, using the
644                     new functions
645                     <literal>mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b</literal>
646                     and <literal>mask_ :: IO a -> IO a</literal>
647                     rather than the old
648                     <literal>block</literal> and <literal>unblock</literal>.
649                     There are also functions
650                     <literal>uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b</literal>
651                     and
652                     <literal>getMaskingState :: IO MaskingState</literal>,
653                     and a type
654                     <literal>MaskingState</literal>, as well as
655                     <literal>forkIOUnmasked :: IO () -> IO ThreadId</literal>
656                     in <literal>Control.Concurrent</literal>.
657                 </para>
658             </listitem>
659
660             <listitem>
661                 <para>
662                     <literal>Control.Monad</literal> exports a new function
663                     <literal>void :: Functor f => f a -> f ()</literal>.
664                 </para>
665             </listitem>
666
667             <listitem>
668                 <para>
669                     <literal>Data.Tuple</literal> exports a new function
670                     <literal>swap :: (a,b) -> (b,a)</literal>.
671                 </para>
672             </listitem>
673
674             <listitem>
675                 <para>
676                     <literal>System.IO</literal> exports a new function
677                     <literal>hGetBufSome :: Handle -> Ptr a -> Int -> IO Int</literal>
678                     which is like <literal>hGetBuf</literal> but can
679                     return short reads.
680                 </para>
681             </listitem>
682
683             <listitem>
684                 <para>
685                     There is a new function
686                     <literal>mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a</literal>
687                     in
688                     <literal>Control.Monad</literal>.
689                 </para>
690             </listitem>
691
692             <listitem>
693                 <para>
694                     The <literal>Foreign.Marshal</literal> module now
695                     exports
696                     <literal>unsafeLocalState :: IO a -> a</literal>
697                     as specified by Haskell 2010.
698                 </para>
699             </listitem>
700
701             <listitem>
702                 <para>
703                     The <literal></literal>
704                     module now exports four new functions specified by
705                     Haskell 2010:
706                     <literal>castCUCharToChar :: CUChar -> Char</literal>,
707                     <literal>castCharToCUChar :: Char -> CUChar</literal>,
708                     <literal>castCSCharToChar :: CSChar -> Char</literal> and
709                     <literal>castCharToCSChar :: Char -> CSChar</literal>.
710                 </para>
711             </listitem>
712
713             <listitem>
714                 <para>
715                     The <literal>Foreign.Marshal.Alloc</literal>
716                     module now exports
717                     <literal>allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b</literal>
718                     for allocating memory with a particular alignment.
719                 </para>
720             </listitem>
721
722             <listitem>
723                 <para>
724                     There is a new function
725                     <literal>numSparks :: IO Int</literal>
726                     in <literal>GHC.Conc</literal>.
727                 </para>
728             </listitem>
729
730             <listitem>
731                 <para>
732                     <literal>Data.Either.partitionEithers</literal>
733                     in now lazier.
734                 </para>
735             </listitem>
736
737             <listitem>
738                 <para>
739                     There is now a <literal>Typeable</literal> instance for
740                     <literal>Data.Unique.Unique</literal>.
741                 </para>
742             </listitem>
743
744             <listitem>
745                 <para>
746                     <literal>Control.Concurrent.SampleVar.SampleVar</literal>
747                     is now an abstract type.
748                 </para>
749             </listitem>
750
751             <listitem>
752                 <para>
753                     There are now
754                     <literal>Applicative</literal>,
755                     <literal>Alternative</literal> and
756                     <literal>MonadPlus</literal>
757                     instances for <literal>STM</literal>.
758                 </para>
759             </listitem>
760
761             <listitem>
762                 <para>
763                     There are now <literal>Applicative</literal>,
764                     <literal>Monad</literal> and
765                     <literal>MonadFix</literal>
766                     instances for <literal>Either</literal>.
767                 </para>
768             </listitem>
769
770             <listitem>
771                 <para>
772                     There are now
773                     <literal>Ord</literal>,
774                     <literal>Read</literal> and
775                     <literal>Show</literal> instances for
776                     <literal>Newline</literal> and
777                     <literal>NewlineMode</literal>.
778                 </para>
779             </listitem>
780
781             <listitem>
782                 <para>
783                     There is now a <literal>Show</literal> instance for
784                     <literal>TextEncoding</literal>.
785                 </para>
786             </listitem>
787
788             <listitem>
789                 <para>
790                     The <literal>unGetChan</literal> and
791                     <literal>isEmptyChan</literal> functions in
792                     <literal>Control.Concurrent.Chan</literal> are now
793                     deprecated.
794                     <literal>Control.Concurrent.STM.TChan</literal>
795                     should be used instead if you need that
796                     functionality.
797                 </para>
798             </listitem>
799
800             <listitem>
801                 <para>
802                     The <literal>Read Integer</literal> instance now
803                     matches the standard definition.
804                 </para>
805             </listitem>
806         </itemizedlist>
807     </sect3>
808
809     <sect3>
810         <title>base 3 compat</title>
811         <itemizedlist>
812             <listitem>
813                 <para>
814                     We no longer ship a base 3 compat package
815                 </para>
816             </listitem>
817         </itemizedlist>
818     </sect3>
819
820     <sect3>
821         <title>bin-package-db</title>
822         <itemizedlist>
823             <listitem>
824                 <para>
825                     This is an internal package, and should not be used.
826                 </para>
827             </listitem>
828         </itemizedlist>
829     </sect3>
830
831     <sect3>
832         <title>bytestring</title>
833         <itemizedlist>
834             <listitem>
835                 <para>
836                     Version number 0.9.1.8 (was 0.9.1.7)
837                 </para>
838             </listitem>
839         </itemizedlist>
840     </sect3>
841
842     <sect3>
843         <title>Cabal</title>
844         <itemizedlist>
845             <listitem>
846                 <para>
847                     Version number 1.9.2 (was 1.8.0.6)
848                 </para>
849             </listitem>
850
851             <listitem>
852                 <para>
853                     Many API changes. See the Cabal docs for more information.
854                 </para>
855             </listitem>
856         </itemizedlist>
857     </sect3>
858
859     <sect3>
860         <title>containers</title>
861         <itemizedlist>
862             <listitem>
863                 <para>
864                     Version number 0.4.0.0 (was 0.3.0.0)
865                 </para>
866             </listitem>
867
868             <listitem>
869                 <para>
870                     Strictness is now more consistent, with containers
871                     being strict in their elements even in singleton
872                     cases.
873                 </para>
874             </listitem>
875
876             <listitem>
877                 <para>
878                     There is a new function
879                     <literal>insertLookupWithKey'</literal> in
880                     <literal>Data.Map</literal>.
881                 </para>
882             </listitem>
883
884             <listitem>
885                 <para>
886                     The <literal>foldWithKey</literal> function in
887                     <literal>Data.Map</literal> has been deprecated in
888                     favour of <literal>foldrWithKey</literal>.
889                 </para>
890             </listitem>
891         </itemizedlist>
892     </sect3>
893
894     <sect3>
895         <title>directory</title>
896         <itemizedlist>
897             <listitem>
898                 <para>
899                     Version number 1.1.0.0 (was 1.0.1.1)
900                 </para>
901             </listitem>
902
903             <listitem>
904                 <para>
905                     The <literal>System.Directory</literal> module
906                     now exports the <literal>Permissions</literal> type
907                     abstractly. There are also new functions
908                     <literal>setOwnerReadable</literal>,
909                     <literal>setOwnerWritable</literal>,
910                     <literal>setOwnerExecutable</literal> and
911                     <literal>setOwnerSearchable</literal>, and
912                     a new value <literal>emptyPermissions</literal>.
913                 </para>
914             </listitem>
915         </itemizedlist>
916     </sect3>
917
918     <sect3>
919         <title>
920             dph
921             (dph-base, dph-par, dph-prim-interface, dph-prim-par,
922             dph-prim-seq, dph-seq)
923         </title>
924         <itemizedlist>
925             <listitem>
926                 <para>
927                     All the dph packages are version 0.4.0.
928                 </para>
929             </listitem>
930         </itemizedlist>
931     </sect3>
932
933     <sect3>
934         <title>extensible-exceptions</title>
935         <itemizedlist>
936             <listitem>
937                 <para>
938                     Version number 0.1.1.2 (was 0.1.1.1)
939                 </para>
940             </listitem>
941         </itemizedlist>
942     </sect3>
943
944     <sect3>
945         <title>filepath</title>
946         <itemizedlist>
947             <listitem>
948                 <para>
949                     Version number 1.2.0.0 (was 1.1.0.4)
950                 </para>
951             </listitem>
952
953             <listitem>
954                 <para>
955                     The current directory is now <literal>"."</literal>
956                     rather than <literal>""</literal>.
957                 </para>
958             </listitem>
959         </itemizedlist>
960     </sect3>
961
962     <sect3>
963         <title>ghc-binary</title>
964         <itemizedlist>
965             <listitem>
966                 <para>
967                     This is an internal package, and should not be used.
968                 </para>
969             </listitem>
970         </itemizedlist>
971     </sect3>
972
973     <sect3>
974         <title>ghc-prim</title>
975         <itemizedlist>
976             <listitem>
977                 <para>
978                     This is an internal package, and should not be used.
979                 </para>
980             </listitem>
981         </itemizedlist>
982     </sect3>
983
984     <sect3>
985         <title>haskell98</title>
986         <itemizedlist>
987             <listitem>
988                 <para>
989                     Version number 1.1.0.0 (was 1.0.1.1)
990                 </para>
991             </listitem>
992
993             <listitem>
994                 <para>
995                     In the <literal>Directory</literal> module, the
996                     <literal>Permissions</literal> type and the
997                     <literal>getPermissions</literal> and
998                     <literal>setPermissions</literal> functions are now
999                     different to their equivalents in
1000                     <literal>base:System.Directory</literal>.
1001                 </para>
1002             </listitem>
1003         </itemizedlist>
1004     </sect3>
1005
1006     <sect3>
1007         <title>haskell2010</title>
1008         <itemizedlist>
1009             <listitem>
1010                 <para>
1011                     This is a new boot package, version 1.0.0.0.
1012                     It is not exposed by default.
1013                 </para>
1014             </listitem>
1015         </itemizedlist>
1016     </sect3>
1017
1018     <sect3>
1019         <title>hpc</title>
1020         <itemizedlist>
1021             <listitem>
1022                 <para>
1023                     Version number 0.5.0.6 (was 0.5.0.5)
1024                 </para>
1025             </listitem>
1026         </itemizedlist>
1027     </sect3>
1028
1029     <sect3>
1030         <title>integer-gmp</title>
1031         <itemizedlist>
1032             <listitem>
1033                 <para>
1034                     Version number 0.2.0.2 (was 0.2.0.1)
1035                 </para>
1036             </listitem>
1037         </itemizedlist>
1038     </sect3>
1039
1040     <sect3>
1041         <title>old-locale</title>
1042         <itemizedlist>
1043             <listitem>
1044                 <para>
1045                     No change (version 1.0.0.2)
1046                 </para>
1047             </listitem>
1048         </itemizedlist>
1049     </sect3>
1050
1051     <sect3>
1052         <title>old-time</title>
1053         <itemizedlist>
1054             <listitem>
1055                 <para>
1056                     Version number 1.0.0.6 (was 1.0.0.5)
1057                 </para>
1058             </listitem>
1059         </itemizedlist>
1060     </sect3>
1061
1062     <sect3>
1063         <title>pretty</title>
1064         <itemizedlist>
1065             <listitem>
1066                 <para>
1067                     Version number 1.0.1.2 (was 1.0.1.1)
1068                 </para>
1069             </listitem>
1070         </itemizedlist>
1071     </sect3>
1072
1073     <sect3>
1074         <title>process</title>
1075         <itemizedlist>
1076             <listitem>
1077                 <para>
1078                     Version number 1.0.1.4 (was 1.0.1.3)
1079                 </para>
1080             </listitem>
1081         </itemizedlist>
1082     </sect3>
1083
1084     <sect3>
1085         <title>random</title>
1086         <itemizedlist>
1087             <listitem>
1088                 <para>
1089                     Version number 1.0.0.3 (was 1.0.0.2)
1090                 </para>
1091             </listitem>
1092         </itemizedlist>
1093     </sect3>
1094
1095     <sect3>
1096         <title>syb</title>
1097         <itemizedlist>
1098             <listitem>
1099                 <para>
1100                     The syb package is no longer included with GHC.
1101                 </para>
1102             </listitem>
1103         </itemizedlist>
1104     </sect3>
1105
1106     <sect3>
1107         <title>template-haskell</title>
1108         <itemizedlist>
1109             <listitem>
1110                 <para>
1111                     Version number 2.5.0.0 (was 2.4.0.1)
1112                 </para>
1113             </listitem>
1114
1115             <listitem>
1116                 <para>
1117                     There is a new type synonym <literal>DecsQ</literal>
1118                     in <literal>Language.Haskell.TH.Lib</literal>.
1119                 </para>
1120             </listitem>
1121
1122             <listitem>
1123                 <para>
1124                     There is a new <literal>StringPrimL</literal>
1125                     constructor in
1126                     <literal>Language.Haskell.TH.Syntax.Lit</literal>,
1127                     and a new helper function
1128                     <literal>stringPrimL</literal> for it in
1129                     <literal>Language.Haskell.TH.Lib</literal>.
1130                 </para>
1131             </listitem>
1132
1133             <listitem>
1134                 <para>
1135                     There is a new function <literal>quoteFile</literal>
1136                     in <literal>Language.Haskell.TH.Quote</literal>.
1137                 </para>
1138             </listitem>
1139
1140             <listitem>
1141                 <para>
1142                     The
1143                     <literal>Language.Haskell.TH.Quote.QuasiQuoter</literal>
1144                     type has two new fields:
1145                     <literal>quoteType</literal> and
1146                     <literal>quoteDec</literal>.
1147                 </para>
1148             </listitem>
1149
1150             <listitem>
1151                 <para>
1152                     There is a new <literal>ClassInstance</literal>
1153                     type in <literal>Language.Haskell.TH.Syntax</literal>.
1154                     The
1155                     <literal>Language.Haskell.TH.Syntax.Info.ClassI</literal>
1156                     constructor now includes a value of this type, which
1157                     allows instance information to be queried via the
1158                     new <literal>isClassInstance</literal>
1159                     and <literal>classInstances</literal> functions.
1160                     There is also a new method
1161                     <literal>qClassInstances</literal> in the
1162                     <literal>Quasi</literal> class.
1163                 </para>
1164             </listitem>
1165         </itemizedlist>
1166     </sect3>
1167
1168     <sect3>
1169         <title>time</title>
1170         <itemizedlist>
1171             <listitem>
1172                 <para>
1173                     Version number 1.2.0.3 (was 1.1.4)
1174                 </para>
1175             </listitem>
1176
1177             <listitem>
1178                 <para>
1179                     The types provided by the time package now include
1180                     <literal>Data</literal> instances.
1181                 </para>
1182             </listitem>
1183         </itemizedlist>
1184     </sect3>
1185
1186     <sect3>
1187         <title>unix</title>
1188         <itemizedlist>
1189             <listitem>
1190                 <para>
1191                     Version number 2.4.1.0 (was 2.4.0.2)
1192                 </para>
1193             </listitem>
1194
1195             <listitem>
1196                 <para>
1197                     There are three new helper function in
1198                     <literal>System.Posix.Error</literal>:
1199                     <literal>throwErrnoPathIfRetry</literal>,
1200                     <literal>throwErrnoPathIfNullRetry</literal> and
1201                     <literal>throwErrnoPathIfMinus1Retry</literal>.
1202                 </para>
1203             </listitem>
1204
1205             <listitem>
1206                 <para>
1207                     There are three new functions in
1208                     <literal>System.Posix.User</literal>:
1209                     <literal>setEffectiveUserID</literal>,
1210                     <literal>setEffectiveGroupID</literal> and
1211                     <literal>setGroups</literal>.
1212                 </para>
1213             </listitem>
1214         </itemizedlist>
1215     </sect3>
1216   </sect2>
1217 </sect1>
1218