Skip to content

Commit 95394f8

Browse files
committed
Merge pull request #53: Replace macros with ConstraintKinds
- This really only affected the test suite, but we have taken the opportunity to drop support for GHCs less than 7.4. This obviated some CPP, and the cabal file and travis config have been updated to match. - Also, instead of deleting the 7.2.2 travis config, switched it to a 7.4.2 config, as it had previously been omitted mistakenly.
2 parents 640b4c6 + 228d2dd commit 95394f8

File tree

5 files changed

+35
-59
lines changed

5 files changed

+35
-59
lines changed

.travis.yml

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -13,12 +13,9 @@ before_cache:
1313

1414
matrix:
1515
include:
16-
- env: CABALVER=1.16 GHCVER=7.0.4
17-
compiler: ": #GHC 7.0.4"
18-
addons: {apt: {packages: [cabal-install-1.16,ghc-7.0.4], sources: [hvr-ghc]}}
19-
- env: CABALVER=1.16 GHCVER=7.2.2
20-
compiler: ": #GHC 7.2.2"
21-
addons: {apt: {packages: [cabal-install-1.16,ghc-7.2.2], sources: [hvr-ghc]}}
16+
- env: CABALVER=1.16 GHCVER=7.4.2
17+
compiler: ": #GHC 7.4.2"
18+
addons: {apt: {packages: [cabal-install-1.16,ghc-7.4.2], sources: [hvr-ghc]}}
2219
- env: CABALVER=1.16 GHCVER=7.6.3
2320
compiler: ": #GHC 7.6.3"
2421
addons: {apt: {packages: [cabal-install-1.16,ghc-7.6.3], sources: [hvr-ghc]}}

Data/Vector.hs

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -175,9 +175,7 @@ import Control.Monad.ST ( ST )
175175
import Control.Monad.Primitive
176176

177177

178-
#if MIN_VERSION_base(4,4,0)
179178
import Control.Monad.Zip
180-
#endif
181179

182180
import Prelude hiding ( length, null,
183181
replicate, (++), concat,
@@ -333,8 +331,6 @@ instance MonadPlus Vector where
333331
{-# INLINE mplus #-}
334332
mplus = (++)
335333

336-
-- MonadZip was added in base-4.4.0
337-
#if MIN_VERSION_base(4,4,0)
338334
instance MonadZip Vector where
339335
{-# INLINE mzip #-}
340336
mzip = zip
@@ -344,7 +340,6 @@ instance MonadZip Vector where
344340

345341
{-# INLINE munzip #-}
346342
munzip = unzip
347-
#endif
348343

349344

350345
instance Applicative.Applicative Vector where

Data/Vector/Unboxed/Base.hs

Lines changed: 0 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -42,11 +42,7 @@ import Data.Word ( Word )
4242
import Data.Typeable ( Typeable )
4343
#else
4444
import Data.Typeable ( Typeable1(..), Typeable2(..), mkTyConApp,
45-
#if MIN_VERSION_base(4,4,0)
4645
mkTyCon3
47-
#else
48-
mkTyCon
49-
#endif
5046
)
5147
#endif
5248

@@ -76,11 +72,7 @@ instance NFData (MVector s a) where rnf !_ = ()
7672
deriving instance Typeable Vector
7773
deriving instance Typeable MVector
7874
#else
79-
#if MIN_VERSION_base(4,4,0)
8075
vectorTyCon = mkTyCon3 "vector"
81-
#else
82-
vectorTyCon m s = mkTyCon $ m ++ "." ++ s
83-
#endif
8476

8577
instance Typeable1 Vector where
8678
typeOf1 _ = mkTyConApp (vectorTyCon "Data.Vector.Unboxed" "Vector") []

tests/Tests/Vector.hs

Lines changed: 28 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE ConstraintKinds #-}
12
module Tests.Vector (tests) where
23

34
import Boilerplater
@@ -28,18 +29,13 @@ import System.Random (Random)
2829
import Data.Functor.Identity
2930
import Control.Monad.Trans.Writer
3031

31-
#if MIN_VERSION_base(4,4,0)
3232
import Control.Monad.Zip
33-
#endif
34-
35-
#define COMMON_CONTEXT(a, v) \
36-
VANILLA_CONTEXT(a, v), VECTOR_CONTEXT(a, v)
37-
38-
#define VANILLA_CONTEXT(a, v) \
39-
Eq a, Show a, Arbitrary a, CoArbitrary a, TestData a, Model a ~ a, EqTest a ~ Property
4033

41-
#define VECTOR_CONTEXT(a, v) \
42-
Eq (v a), Show (v a), Arbitrary (v a), CoArbitrary (v a), TestData (v a), Model (v a) ~ [a], EqTest (v a) ~ Property, V.Vector v a
34+
type CommonContext a v = (VanillaContext a, VectorContext a v)
35+
type VanillaContext a = ( Eq a , Show a, Arbitrary a, CoArbitrary a
36+
, TestData a, Model a ~ a, EqTest a ~ Property)
37+
type VectorContext a v = ( Eq (v a), Show (v a), Arbitrary (v a), CoArbitrary (v a)
38+
, TestData (v a), Model (v a) ~ [a], EqTest (v a) ~ Property, V.Vector v a)
4339

4440
-- TODO: implement Vector equivalents of list functions for some of the commented out properties
4541

@@ -82,7 +78,7 @@ instance T.Traversable ((,) a) where
8278
traverse f (a, b) = fmap ((,) a) $ f b
8379
#endif
8480

85-
testSanity :: forall a v. (COMMON_CONTEXT(a, v)) => v a -> [Test]
81+
testSanity :: forall a v. (CommonContext a v) => v a -> [Test]
8682
testSanity _ = [
8783
testProperty "fromList.toList == id" prop_fromList_toList,
8884
testProperty "toList.fromList == id" prop_toList_fromList,
@@ -95,7 +91,7 @@ testSanity _ = [
9591
prop_unstream_stream (v :: v a) = (V.unstream . V.stream) v == v
9692
prop_stream_unstream (s :: S.Bundle v a) = ((V.stream :: v a -> S.Bundle v a) . V.unstream) s == s
9793

98-
testPolymorphicFunctions :: forall a v. (COMMON_CONTEXT(a, v), VECTOR_CONTEXT(Int, v)) => v a -> [Test]
94+
testPolymorphicFunctions :: forall a v. (CommonContext a v, VectorContext Int v) => v a -> [Test]
9995
testPolymorphicFunctions _ = $(testProperties [
10096
'prop_eq,
10197

@@ -471,26 +467,22 @@ testPolymorphicFunctions _ = $(testProperties [
471467
constructrN xs 0 _ = xs
472468
constructrN xs n f = constructrN (f xs : xs) (n-1) f
473469

474-
testTuplyFunctions:: forall a v. (COMMON_CONTEXT(a, v), VECTOR_CONTEXT((a, a), v), VECTOR_CONTEXT((a, a, a), v)) => v a -> [Test]
470+
testTuplyFunctions:: forall a v. (CommonContext a v, VectorContext (a, a) v, VectorContext (a, a, a) v) => v a -> [Test]
475471
testTuplyFunctions _ = $(testProperties [ 'prop_zip, 'prop_zip3
476472
, 'prop_unzip, 'prop_unzip3
477-
#if MIN_VERSION_base(4,4,0)
478473
, 'prop_mzip, 'prop_munzip
479-
#endif
480474
])
481475
where
482476
prop_zip :: P (v a -> v a -> v (a, a)) = V.zip `eq` zip
483477
prop_zip3 :: P (v a -> v a -> v a -> v (a, a, a)) = V.zip3 `eq` zip3
484478
prop_unzip :: P (v (a, a) -> (v a, v a)) = V.unzip `eq` unzip
485479
prop_unzip3 :: P (v (a, a, a) -> (v a, v a, v a)) = V.unzip3 `eq` unzip3
486-
#if MIN_VERSION_base(4,4,0)
487480
prop_mzip :: P (Data.Vector.Vector a -> Data.Vector.Vector a -> Data.Vector.Vector (a, a))
488481
= mzip `eq` zip
489482
prop_munzip :: P (Data.Vector.Vector (a, a) -> (Data.Vector.Vector a, Data.Vector.Vector a))
490483
= munzip `eq` unzip
491-
#endif
492484

493-
testOrdFunctions :: forall a v. (COMMON_CONTEXT(a, v), Ord a, Ord (v a)) => v a -> [Test]
485+
testOrdFunctions :: forall a v. (CommonContext a v, Ord a, Ord (v a)) => v a -> [Test]
494486
testOrdFunctions _ = $(testProperties
495487
['prop_compare,
496488
'prop_maximum, 'prop_minimum,
@@ -502,7 +494,7 @@ testOrdFunctions _ = $(testProperties
502494
prop_minIndex :: P (v a -> Int) = not . V.null ===> V.minIndex `eq` minIndex
503495
prop_maxIndex :: P (v a -> Int) = not . V.null ===> V.maxIndex `eq` maxIndex
504496

505-
testEnumFunctions :: forall a v. (COMMON_CONTEXT(a, v), Enum a, Ord a, Num a, Random a) => v a -> [Test]
497+
testEnumFunctions :: forall a v. (CommonContext a v, Enum a, Ord a, Num a, Random a) => v a -> [Test]
506498
testEnumFunctions _ = $(testProperties
507499
[ 'prop_enumFromN, 'prop_enumFromThenN,
508500
'prop_enumFromTo, 'prop_enumFromThenTo])
@@ -533,28 +525,28 @@ testEnumFunctions _ = $(testProperties
533525
where
534526
d = abs (j-i)
535527

536-
testMonoidFunctions :: forall a v. (COMMON_CONTEXT(a, v), Monoid (v a)) => v a -> [Test]
528+
testMonoidFunctions :: forall a v. (CommonContext a v, Monoid (v a)) => v a -> [Test]
537529
testMonoidFunctions _ = $(testProperties
538530
[ 'prop_mempty, 'prop_mappend, 'prop_mconcat ])
539531
where
540532
prop_mempty :: P (v a) = mempty `eq` mempty
541533
prop_mappend :: P (v a -> v a -> v a) = mappend `eq` mappend
542534
prop_mconcat :: P ([v a] -> v a) = mconcat `eq` mconcat
543535

544-
testFunctorFunctions :: forall a v. (COMMON_CONTEXT(a, v), Functor v) => v a -> [Test]
536+
testFunctorFunctions :: forall a v. (CommonContext a v, Functor v) => v a -> [Test]
545537
testFunctorFunctions _ = $(testProperties
546538
[ 'prop_fmap ])
547539
where
548540
prop_fmap :: P ((a -> a) -> v a -> v a) = fmap `eq` fmap
549541

550-
testMonadFunctions :: forall a v. (COMMON_CONTEXT(a, v), Monad v) => v a -> [Test]
542+
testMonadFunctions :: forall a v. (CommonContext a v, Monad v) => v a -> [Test]
551543
testMonadFunctions _ = $(testProperties
552544
[ 'prop_return, 'prop_bind ])
553545
where
554546
prop_return :: P (a -> v a) = return `eq` return
555547
prop_bind :: P (v a -> (a -> v a) -> v a) = (>>=) `eq` (>>=)
556548

557-
testApplicativeFunctions :: forall a v. (COMMON_CONTEXT(a, v), V.Vector v (a -> a), Applicative.Applicative v) => v a -> [Test]
549+
testApplicativeFunctions :: forall a v. (CommonContext a v, V.Vector v (a -> a), Applicative.Applicative v) => v a -> [Test]
558550
testApplicativeFunctions _ = $(testProperties
559551
[ 'prop_applicative_pure, 'prop_applicative_appl ])
560552
where
@@ -563,27 +555,27 @@ testApplicativeFunctions _ = $(testProperties
563555
prop_applicative_appl :: [a -> a] -> P (v a -> v a)
564556
= \fs -> (Applicative.<*>) (V.fromList fs) `eq` (Applicative.<*>) fs
565557

566-
testAlternativeFunctions :: forall a v. (COMMON_CONTEXT(a, v), Applicative.Alternative v) => v a -> [Test]
558+
testAlternativeFunctions :: forall a v. (CommonContext a v, Applicative.Alternative v) => v a -> [Test]
567559
testAlternativeFunctions _ = $(testProperties
568560
[ 'prop_alternative_empty, 'prop_alternative_or ])
569561
where
570562
prop_alternative_empty :: P (v a) = Applicative.empty `eq` Applicative.empty
571563
prop_alternative_or :: P (v a -> v a -> v a)
572564
= (Applicative.<|>) `eq` (Applicative.<|>)
573565

574-
testBoolFunctions :: forall v. (COMMON_CONTEXT(Bool, v)) => v Bool -> [Test]
566+
testBoolFunctions :: forall v. (CommonContext Bool v) => v Bool -> [Test]
575567
testBoolFunctions _ = $(testProperties ['prop_and, 'prop_or])
576568
where
577569
prop_and :: P (v Bool -> Bool) = V.and `eq` and
578570
prop_or :: P (v Bool -> Bool) = V.or `eq` or
579571

580-
testNumFunctions :: forall a v. (COMMON_CONTEXT(a, v), Num a) => v a -> [Test]
572+
testNumFunctions :: forall a v. (CommonContext a v, Num a) => v a -> [Test]
581573
testNumFunctions _ = $(testProperties ['prop_sum, 'prop_product])
582574
where
583575
prop_sum :: P (v a -> a) = V.sum `eq` sum
584576
prop_product :: P (v a -> a) = V.product `eq` product
585577

586-
testNestedVectorFunctions :: forall a v. (COMMON_CONTEXT(a, v)) => v a -> [Test]
578+
testNestedVectorFunctions :: forall a v. (CommonContext a v) => v a -> [Test]
587579
testNestedVectorFunctions _ = $(testProperties [])
588580
where
589581
-- Prelude
@@ -595,7 +587,7 @@ testNestedVectorFunctions _ = $(testProperties [])
595587
--prop_inits = V.inits `eq1` (inits :: v a -> [v a])
596588
--prop_tails = V.tails `eq1` (tails :: v a -> [v a])
597589

598-
testGeneralBoxedVector :: forall a. (COMMON_CONTEXT(a, Data.Vector.Vector), Ord a) => Data.Vector.Vector a -> [Test]
590+
testGeneralBoxedVector :: forall a. (CommonContext a Data.Vector.Vector, Ord a) => Data.Vector.Vector a -> [Test]
599591
testGeneralBoxedVector dummy = concatMap ($ dummy) [
600592
testSanity,
601593
testPolymorphicFunctions,
@@ -615,7 +607,7 @@ testBoolBoxedVector dummy = concatMap ($ dummy)
615607
, testBoolFunctions
616608
]
617609

618-
testNumericBoxedVector :: forall a. (COMMON_CONTEXT(a, Data.Vector.Vector), Ord a, Num a, Enum a, Random a) => Data.Vector.Vector a -> [Test]
610+
testNumericBoxedVector :: forall a. (CommonContext a Data.Vector.Vector, Ord a, Num a, Enum a, Random a) => Data.Vector.Vector a -> [Test]
619611
testNumericBoxedVector dummy = concatMap ($ dummy)
620612
[
621613
testGeneralBoxedVector
@@ -624,15 +616,15 @@ testNumericBoxedVector dummy = concatMap ($ dummy)
624616
]
625617

626618

627-
testGeneralPrimitiveVector :: forall a. (COMMON_CONTEXT(a, Data.Vector.Primitive.Vector), Data.Vector.Primitive.Prim a, Ord a) => Data.Vector.Primitive.Vector a -> [Test]
619+
testGeneralPrimitiveVector :: forall a. (CommonContext a Data.Vector.Primitive.Vector, Data.Vector.Primitive.Prim a, Ord a) => Data.Vector.Primitive.Vector a -> [Test]
628620
testGeneralPrimitiveVector dummy = concatMap ($ dummy) [
629621
testSanity,
630622
testPolymorphicFunctions,
631623
testOrdFunctions,
632624
testMonoidFunctions
633625
]
634626

635-
testNumericPrimitiveVector :: forall a. (COMMON_CONTEXT(a, Data.Vector.Primitive.Vector), Data.Vector.Primitive.Prim a, Ord a, Num a, Enum a, Random a) => Data.Vector.Primitive.Vector a -> [Test]
627+
testNumericPrimitiveVector :: forall a. (CommonContext a Data.Vector.Primitive.Vector, Data.Vector.Primitive.Prim a, Ord a, Num a, Enum a, Random a) => Data.Vector.Primitive.Vector a -> [Test]
636628
testNumericPrimitiveVector dummy = concatMap ($ dummy)
637629
[
638630
testGeneralPrimitiveVector
@@ -641,15 +633,15 @@ testNumericPrimitiveVector dummy = concatMap ($ dummy)
641633
]
642634

643635

644-
testGeneralStorableVector :: forall a. (COMMON_CONTEXT(a, Data.Vector.Storable.Vector), Data.Vector.Storable.Storable a, Ord a) => Data.Vector.Storable.Vector a -> [Test]
636+
testGeneralStorableVector :: forall a. (CommonContext a Data.Vector.Storable.Vector, Data.Vector.Storable.Storable a, Ord a) => Data.Vector.Storable.Vector a -> [Test]
645637
testGeneralStorableVector dummy = concatMap ($ dummy) [
646638
testSanity,
647639
testPolymorphicFunctions,
648640
testOrdFunctions,
649641
testMonoidFunctions
650642
]
651643

652-
testNumericStorableVector :: forall a. (COMMON_CONTEXT(a, Data.Vector.Storable.Vector), Data.Vector.Storable.Storable a, Ord a, Num a, Enum a, Random a) => Data.Vector.Storable.Vector a -> [Test]
644+
testNumericStorableVector :: forall a. (CommonContext a Data.Vector.Storable.Vector, Data.Vector.Storable.Storable a, Ord a, Num a, Enum a, Random a) => Data.Vector.Storable.Vector a -> [Test]
653645
testNumericStorableVector dummy = concatMap ($ dummy)
654646
[
655647
testGeneralStorableVector
@@ -658,7 +650,7 @@ testNumericStorableVector dummy = concatMap ($ dummy)
658650
]
659651

660652

661-
testGeneralUnboxedVector :: forall a. (COMMON_CONTEXT(a, Data.Vector.Unboxed.Vector), Data.Vector.Unboxed.Unbox a, Ord a) => Data.Vector.Unboxed.Vector a -> [Test]
653+
testGeneralUnboxedVector :: forall a. (CommonContext a Data.Vector.Unboxed.Vector, Data.Vector.Unboxed.Unbox a, Ord a) => Data.Vector.Unboxed.Vector a -> [Test]
662654
testGeneralUnboxedVector dummy = concatMap ($ dummy) [
663655
testSanity,
664656
testPolymorphicFunctions,
@@ -677,15 +669,15 @@ testBoolUnboxedVector dummy = concatMap ($ dummy)
677669
, testBoolFunctions
678670
]
679671

680-
testNumericUnboxedVector :: forall a. (COMMON_CONTEXT(a, Data.Vector.Unboxed.Vector), Data.Vector.Unboxed.Unbox a, Ord a, Num a, Enum a, Random a) => Data.Vector.Unboxed.Vector a -> [Test]
672+
testNumericUnboxedVector :: forall a. (CommonContext a Data.Vector.Unboxed.Vector, Data.Vector.Unboxed.Unbox a, Ord a, Num a, Enum a, Random a) => Data.Vector.Unboxed.Vector a -> [Test]
681673
testNumericUnboxedVector dummy = concatMap ($ dummy)
682674
[
683675
testGeneralUnboxedVector
684676
, testNumFunctions
685677
, testEnumFunctions
686678
]
687679

688-
testTupleUnboxedVector :: forall a. (COMMON_CONTEXT(a, Data.Vector.Unboxed.Vector), Data.Vector.Unboxed.Unbox a, Ord a) => Data.Vector.Unboxed.Vector a -> [Test]
680+
testTupleUnboxedVector :: forall a. (CommonContext a Data.Vector.Unboxed.Vector, Data.Vector.Unboxed.Unbox a, Ord a) => Data.Vector.Unboxed.Vector a -> [Test]
689681
testTupleUnboxedVector dummy = concatMap ($ dummy)
690682
[
691683
testGeneralUnboxedVector

vector.cabal

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ Description:
3737
Tested-With:
3838
GHC == 7.0.4,
3939
GHC == 7.2.2,
40-
GHC == 7.4.3,
40+
GHC == 7.4.2,
4141
GHC == 7.6.3,
4242
GHC == 7.8.4,
4343
GHC == 7.10.3,
@@ -151,7 +151,7 @@ Library
151151
Install-Includes:
152152
vector.h
153153

154-
Build-Depends: base >= 4.3 && < 4.10
154+
Build-Depends: base >= 4.5 && < 4.10
155155
, primitive >= 0.5.0.1 && < 0.7
156156
, ghc-prim >= 0.2 && < 0.6
157157
, deepseq >= 1.1 && < 1.5
@@ -186,7 +186,7 @@ test-suite vector-tests-O0
186186
type: exitcode-stdio-1.0
187187
Main-Is: Main.hs
188188
hs-source-dirs: tests
189-
Build-Depends: base >= 4 && < 5, template-haskell, vector,
189+
Build-Depends: base >= 4.5 && < 5, template-haskell, vector,
190190
random,
191191
QuickCheck >= 2.9 && < 2.10 , test-framework, test-framework-quickcheck2,
192192
transformers >= 0.2.0.0
@@ -215,7 +215,7 @@ test-suite vector-tests-O2
215215
type: exitcode-stdio-1.0
216216
Main-Is: Main.hs
217217
hs-source-dirs: tests
218-
Build-Depends: base >= 4 && < 5, template-haskell, vector,
218+
Build-Depends: base >= 4.5 && < 5, template-haskell, vector,
219219
random,
220220
QuickCheck >= 2.9 && < 2.10 , test-framework, test-framework-quickcheck2,
221221
transformers >= 0.2.0.0

0 commit comments

Comments
 (0)