1 patch for repository http://code.haskell.org/vector:

Wed Nov 28 14:55:19 GMT Standard Time 2012  jpm@cs.ox.ac.uk
  * Derive Typeable instances

New patches:

[Derive Typeable instances
jpm@cs.ox.ac.uk**20121128145519
 Ignore-this: ab50ca93bdf25e1570f694dcab2d840b
] {
hunk ./Data/Vector/Generic.hs 199
                         showsPrec )
 
 import qualified Text.Read as Read
+
+#if __GLASGOW_HASKELL__ >= 707
+import Data.Typeable ( Typeable, gcast1 )
+#else
 import Data.Typeable ( Typeable1, gcast1 )
hunk ./Data/Vector/Generic.hs 204
+#endif
 
 #include "vector.h"
 
hunk ./Data/Vector/Generic.hs 2029
 {-# INLINE mkType #-}
 mkType = mkNoRepType
 
+#if __GLASGOW_HASKELL__ >= 707
+dataCast :: (Vector v a, Data a, Typeable v, Typeable t)
+#else
 dataCast :: (Vector v a, Data a, Typeable1 v, Typeable1 t)
hunk ./Data/Vector/Generic.hs 2033
+#endif
          => (forall d. Data  d => c (t d)) -> Maybe  (c (v a))
 {-# INLINE dataCast #-}
 dataCast f = gcast1 f
hunk ./Data/Vector/Unboxed/Base.hs 2
 {-# LANGUAGE MultiParamTypeClasses, TypeFamilies, FlexibleContexts #-}
+#if __GLASGOW_HASKELL__ >= 707
+{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
+#endif
 {-# OPTIONS_HADDOCK hide #-}
 
 -- |
hunk ./Data/Vector/Unboxed/Base.hs 37
 import Data.Int  ( Int8, Int16, Int32, Int64 )
 import Data.Complex
 
+#if __GLASGOW_HASKELL__ >= 707
+import Data.Typeable ( Typeable )
+#else
 import Data.Typeable ( Typeable1(..), Typeable2(..), mkTyConApp,
 #if MIN_VERSION_base(4,4,0)
                        mkTyCon3
hunk ./Data/Vector/Unboxed/Base.hs 47
                        mkTyCon
 #endif
                      )
+#endif
+
 import Data.Data     ( Data(..) )
 
 #include "vector.h"
hunk ./Data/Vector/Unboxed/Base.hs 69
 -- -----------------
 -- Data and Typeable
 -- -----------------
-
+#if __GLASGOW_HASKELL__ >= 707
+deriving instance Typeable Vector
+deriving instance Typeable MVector
+#else
 #if MIN_VERSION_base(4,4,0)
 vectorTyCon = mkTyCon3 "vector"
 #else
hunk ./Data/Vector/Unboxed/Base.hs 84
 
 instance Typeable2 MVector where
   typeOf2 _ = mkTyConApp (vectorTyCon "Data.Vector.Unboxed.Mutable" "MVector") []
+#endif
 
 instance (Data a, Unbox a) => Data (Vector a) where
   gfoldl       = G.gfoldl
}

Context:

[Resolve conflict
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20121010222123
 Ignore-this: a979066440b0d0a6b174d13ece9865db
] 
[TAG 0.10.0.1
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20121010222017
 Ignore-this: d57b460b1d13938c4036f4c6fbe45805
] 
[Require primitive >= 0.5.0.1
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20121010221948
 Ignore-this: dc4f770f952bb71a985a5749a38c9ab
] 
[Make inplace fusion work on Streams rather than Bundles
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20121007204842
 Ignore-this: 8c561f1383dc42818fea1dca9525ed5a
] 
[Readd Fusion.Stream.Monadic and use it Bundle.Monadic
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20121007120950
 Ignore-this: 984b6e01e21a8133d1b311fb15d41c9f
] 
[Add internal checks
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20121006214817
 Ignore-this: 84845e263b6dc20993fb90581bda566c
] 
[Adapt tests to new names and modules
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20121005194435
 Ignore-this: b8aaed091a79d8e37e91cd3a10db81b9
] 
[Finish Stream -> Bundle renaming
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20121004191113
 Ignore-this: 293f0971af184cdc8d45cda2fecd09b7
] 
[Rename Facets to Bundle
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20121003222143
 Ignore-this: 569dfd7a06ef70c2f7352f8bf3d4382d
] 
[Work around bug in ghc-7.6.1
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120928231021
 Ignore-this: f68e9090339216883bf77536be562141
] 
[Bump version number
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120928223340
 Ignore-this: 6b5f74114030b821f7282c2cca1ac3a8
] 
[Resolve conflict
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120928223207
 Ignore-this: 4365b9dd18af8cf4415bb80173e2976f
] 
[liftStream -> lift
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120131234133
 Ignore-this: b2d34ac008bd828c9bf4f0cb702e4c7c
] 
[INLINE_STREAM -> INLINE_FUSED
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120131233432
 Ignore-this: 584d9b0ca2399d3327fcbfe8ba3f6075
] 
[fromVectorStream -> concatVectors
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120131232247
 Ignore-this: 5611343838e2855865e42c78e00d9cc9
] 
[Rename Stream -> Facets
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120131231412
 Ignore-this: bc127674894ba5de50f8c6d38aa7b6b4
] 
[TAG 0.10
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120928202555
 Ignore-this: c50cd5461a8fa2ec1ee06b2643b6a6db
] 
[Add missing file
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120928202546
 Ignore-this: 5ef739adf565d61eb6f771d70e621d2d
] 
[Changelog
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120927225949
 Ignore-this: 4bddb6a64b0dbbc45b9d12054eb7f4e1
] 
[Remove Safe Haskell support
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120927223636
 Ignore-this: 46d32132f3a454b91b6308cdb1c26848
] 
[Bump versions and dependencies
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120927223243
 Ignore-this: 1064cbaa8853864febf18aa8c2f0a7eb
] 
[Remove outdated Changelog file
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120927223155
 Ignore-this: c548cafc6ea4a816b00e549791b7fac8
] 
[Add type signatures for GHC >= 7.4
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120927212743
 Ignore-this: 856f6046bc1436d7b3cd5a88cf2d5c38
] 
[Move eq and cmp to monadic streams
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120129131954
 Ignore-this: 731869deb00ab66bfcaf1fa064387b60
] 
[Comment out the NFData instance for mutable boxed vectors for now
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120129121429
 Ignore-this: 660c999e4020dfcef117ce58ccefb17e
] 
[Resolve conflict
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120129113249
 Ignore-this: 611d1f1ed63e7bd2b6cee4b4a1a8c4e8
] 
[Added NFData instances for all vectors
Bas van Dijk <v.dijk.bas@gmail.com>**20120107160949
 Ignore-this: 7def955f95e5af88790e772a0373c0c6
] 
[Improve length and null
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120129110308
 Ignore-this: fec36f9bd984234ab29b5f947ec67cd1
] 
[Use new Stream in length and null
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120129105346
 Ignore-this: f751ead0f5e8ca6571d4b67bef8fd12
] 
[Add Maybe (v a) to Stream representations
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120129105027
 Ignore-this: 1cafdffc87c44d98e1f8649b53585c61
] 
[Whitespace
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120129005750
 Ignore-this: 4d254ad63e51a7e32e09c5a58bda57c1
] 
[Faster concatMap
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120129005702
 Ignore-this: 49f2fdb23d884e1d9ed985981c003ea6
] 
[Relax package upper bounds
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120129002810
 Ignore-this: d18883c66c2a2616f71dc63d782f8e7d
] 
[Delete dead code
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120128094405
 Ignore-this: e88744f3d9e3328741c6d0a1032cf110
] 
[Switch to record syntax for streams
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120128092814
 Ignore-this: fdad04881b4858c29105c191ecf13ede
] 
[Improve basicSet for primitive vectors
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120127234426
 Ignore-this: 21eae1c4c8c2c03ae44282e66d30be8
] 
[Improve basicSet for Storable vectors
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120127233842
 Ignore-this: 1baa8a0010123ceb1101946fda04dcb5
] 
[Require dev version of primitive
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120127233830
 Ignore-this: 97ba1b53fd58c783f73e3134169a4af2
] 
[Fix docs
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120125233010
 Ignore-this: 3889c922035c970094500a83bf5be7af
] 
[Have streams carry chunk initialisers rather than vectors
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120124181931
 Ignore-this: 3a79767cf8a413df4635a4aed211b0d8
] 
[Reimplement concat
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120108105916
 Ignore-this: 9b215a5101c810536aeb5cb7be440516
] 
[Allow streams to produce entire vectors as well as individual elements
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120107110600
 Ignore-this: 727e51c5d236ecb0d1021c5b740b983
 
 This is a signficant extension to the stream fusion mechanism. A Stream is now
 parametrised with a vector type and offers two iteration modes: individual
 elements and individual elements + vectors. This supports significantly more
 efficient implementations of block operations. For instance, (++) will now use
 memcpy where possible rather than iterating through the elements in a loop.
 
 Comments are sorely lacking at the moment.
] 
[Change version number again
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120107104052
 Ignore-this: d52e18bc0bbf221385cc59cfccdabfba
] 
[Use SPEC in stream comparisons
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120107103044
 Ignore-this: 59ff46e5b834400450af94e425d025ab
] 
[Export SPEC
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120107103031
 Ignore-this: 7e2a7f45ba99ad62eea28de474bbdd83
] 
[Bump version
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120107102613
 Ignore-this: d4ff3ccc4c17210317f430fcd4cd4fb7
] 
[Strictness fix
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20120107102518
 Ignore-this: 904948491a2e1a5a21cbabda0ada5706
] 
[Documentation
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20111231134323
 Ignore-this: 6f836ae502f1b072a851a3bc9fccc625
] 
[Bump version
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20111231134314
 Ignore-this: dac62c46a54308d64912d15865f25bbd
] 
[TAG 0.9.1
Roman Leshchinskiy <rl@cse.unsw.edu.au>**20111231003141
 Ignore-this: ee19d3940a3827eefe4cb13b99a863bf
] 
Patch bundle hash:
610dcdfed2916b93deec7ffc3def6558d6cd42a9
