Skip to content

Commit 27ac40a

Browse files
authored
Merge pull request #121 from dolio/master
Fix Traversable use for createT on older GHCs.
2 parents 0cf1ae4 + 117cf17 commit 27ac40a

File tree

6 files changed

+19
-1
lines changed

6 files changed

+19
-1
lines changed

Data/Vector.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -703,7 +703,7 @@ create :: (forall s. ST s (MVector s a)) -> Vector a
703703
create p = G.create p
704704

705705
-- | Execute the monadic action and freeze the resulting vectors.
706-
createT :: Traversable f => (forall s. ST s (f (MVector s a))) -> f (Vector a)
706+
createT :: Traversable.Traversable f => (forall s. ST s (f (MVector s a))) -> f (Vector a)
707707
{-# INLINE createT #-}
708708
createT p = G.createT p
709709

Data/Vector/Generic.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -217,6 +217,10 @@ mkNoRepType :: String -> DataType
217217
mkNoRepType = mkNorepType
218218
#endif
219219

220+
#if !MIN_VERSION_base(4,8,0)
221+
import Data.Traversable (Traversable, traverse)
222+
#endif
223+
220224
-- Length information
221225
-- ------------------
222226

Data/Vector/Primitive.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -169,6 +169,7 @@ import Data.Semigroup ( Semigroup(..) )
169169

170170
#if !MIN_VERSION_base(4,8,0)
171171
import Data.Monoid ( Monoid(..) )
172+
import Data.Traversable ( Traversable )
172173
#endif
173174

174175
#if __GLASGOW_HASKELL__ >= 708

Data/Vector/Storable.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -174,6 +174,7 @@ import Data.Semigroup ( Semigroup(..) )
174174

175175
#if !MIN_VERSION_base(4,8,0)
176176
import Data.Monoid ( Monoid(..) )
177+
import Data.Traversable ( Traversable )
177178
#endif
178179

179180
#if __GLASGOW_HASKELL__ >= 708

Data/Vector/Unboxed.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -191,6 +191,7 @@ import Data.Semigroup ( Semigroup(..) )
191191

192192
#if !MIN_VERSION_base(4,8,0)
193193
import Data.Monoid ( Monoid(..) )
194+
import Data.Traversable ( Traversable )
194195
#endif
195196

196197
#if __GLASGOW_HASKELL__ >= 708

tests/Tests/Vector.hs

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,9 @@ module Tests.Vector (tests) where
33
import Boilerplater
44
import Utilities as Util
55

6+
import Data.Traversable (Traversable(..))
7+
import Data.Foldable (Foldable(foldMap))
8+
69
import qualified Data.Vector.Generic as V
710
import qualified Data.Vector
811
import qualified Data.Vector.Primitive
@@ -66,6 +69,14 @@ import Control.Monad.Trans.Writer
6669

6770
-- TODO: test non-IVector stuff?
6871

72+
#if !MIN_VERSION_base(4,7,0)
73+
instance Foldable ((,) a) where
74+
foldMap f (_, b) = f b
75+
76+
instance Traversable ((,) a) where
77+
traverse f (a, b) = fmap ((,) a) $ f b
78+
#endif
79+
6980
testSanity :: forall a v. (COMMON_CONTEXT(a, v)) => v a -> [Test]
7081
testSanity _ = [
7182
testProperty "fromList.toList == id" prop_fromList_toList,

0 commit comments

Comments
 (0)