
New patches:

[Add the necessary FFI declarations and imports for building on Windows
Neil Mitchell**20080911104821] {
hunk ./src/Main.hs 1
+{-# LANGUAGE ForeignFunctionInterface #-}
hunk ./src/Main.hs 61
+
+#if defined(mingw32_HOST_OS)
+import Foreign
+import Foreign.C.String
+#endif
}

[Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better
Neil Mitchell**20080911104855] {
hunk ./src/Main.hs 46
+#else
+import GHC.Paths
hunk ./src/Main.hs 51
-#ifdef GHC_PATHS
-import GHC.Paths
-#endif
}

Context:

[bindist fixes
Ian Lynagh <igloo@earth.li>**20080907185251] 
[follow library changes
Ian Lynagh <igloo@earth.li>**20080903223553] 
[Fix in-tree haddock on Windows
Ian Lynagh <igloo@earth.li>**20080829000742] 
[Don't use Cabal wrappers on Windows
Ian Lynagh <igloo@earth.li>**20080828211427] 
[Fixes for using haddock in a GHC build tree
Ian Lynagh <igloo@earth.li>**20080828142229] 
[Fix some warnings
Ian Lynagh <igloo@earth.li>**20080827213222] 
[Increase the upper bound on the GHC version number
Ian Lynagh <igloo@earth.li>**20080827204155] 
[Update extensions in Cabal file
Ian Lynagh <igloo@earth.li>**20080827204127
 Use ScopedTypeVariables instead of PatternSignatures
] 
[Add a manual Cabal flag to control the ghc-paths dependency
Ian Lynagh <igloo@earth.li>**20080827180702] 
[Add haddock.wrapper
Ian Lynagh <igloo@earth.li>**20080827180646] 
[Add a Makefile for GHC's build system. Still won't work yet, but we're closer
Ian Lynagh <igloo@earth.li>**20080814104914] 
[In the hoogle back end, markup definition lists using <i>, not <b>
Neil Mitchell**20080821182024] 
[Simplify the code by removing not-to-important use of <.> in the Hoogle back end
Neil Mitchell**20080820075913] 
[Remove Explicit top-level forall's when pretty-printing signatures
Neil Mitchell**20080818125304] 
[Use the same method to put out signatures as class methods in the Hoogle backend
Neil Mitchell**20080818125243] 
[Make Hoogle add documentation to a package
Neil Mitchell**20080813140346] 
[Generalise Hoogle.doc and add a docWith
Neil Mitchell**20080813140324] 
[Add support for type synonyms to Hoogle, was accidentally missing before (woops!)
Neil Mitchell**20080812213732] 
[Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base
Neil Mitchell**20080812160253] 
[Change ghc version dependency to >= 6.8.2 && <= 6.9
David Waern <david.waern@gmail.com>**20080813215017] 
[Follow changes to Binary in GHC 6.9
David Waern <david.waern@gmail.com>**20080813214736] 
[Follow changes to parseDynamic- parseStaticFlags in GHC
David Waern <david.waern@gmail.com>**20080813214654] 
[Update test following Haddock version change
David Waern <david.waern@gmail.com>**20080813214620] 
[Follow extensible exceptions changes
David Waern <david.waern@gmail.com>**20080813214529] 
[Follow move of package string functions from PackageConfig to Module
David Waern <david.waern@gmail.com>**20080813214417] 
[Add __GHC_PATCHLEVEL__ symbol also when building the library
David Waern <david.waern@gmail.com>**20080813214358] 
[Follow changes to parseDynamic/StaticFlags
David Waern <david.waern@gmail.com>**20080812231112] 
[Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3
David Waern <david.waern@gmail.com>**20080812230358] 
[Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9
David Waern <david.waern@gmail.com>**20080812230202] 
[Remove matching on NoteTy in AttachInstances, it has been removed
David Waern <david.waern@gmail.com>**20080812224957] 
[Make our .haddock file version number depend on the GHC version
David Waern <david.waern@gmail.com>**20080812224039
 
 We need to do this, since our .haddock format can potentially
 change whenever GHC's version changes (even when only the patchlevel
 changes).
] 
[Import Control.OldException instead of C.Exception when using ghc >= 6.9
David Waern <david.waern@gmail.com>**20080811194154
 
 We should really test for base version instead, but I don't currently
 know which version to test for.
] 
[Make H.GHC.Utils build with GHC HEAD
David Waern <david.waern@gmail.com>**20080810224205] 
[Change ghc version dependency to >= 6.8.2
David Waern <david.waern@gmail.com>**20080805192608] 
[Doc: say that the --hoogle option is functional
David Waern <david.waern@gmail.com>**20080811185637] 
[invoking haddock clarification and help
Luke Plant <L.Plant.98@cantab.net>**20080811152059] 
[Fix CHANGES
David Waern <david.waern@gmail.com>**20080805191649] 
[TAG 2.2.2
David Waern <david.waern@gmail.com>**20080805191453] 
Patch bundle hash:
a54a1caad90f8ef1090b5859abe8ce0648f4feec
