diff --git a/patches/vector-algorithms-0.8.0.4.patch b/patches/vector-algorithms-0.8.0.4.patch new file mode 100644 index 0000000000000000000000000000000000000000..51b7e584e4a7af97a307ec5f5522f88937c66028 --- /dev/null +++ b/patches/vector-algorithms-0.8.0.4.patch @@ -0,0 +1,153 @@ +diff --git a/bench/simple/Main.hs b/bench/simple/Main.hs +index 04028bc..67d541f 100644 +--- a/bench/simple/Main.hs ++++ b/bench/simple/Main.hs +@@ -12,7 +12,8 @@ import Data.Char + import Data.Ord (comparing) + import Data.List (maximumBy) + +-import Data.Vector.Unboxed.Mutable ++import qualified Data.Vector.Unboxed.Mutable as U ++import Data.Vector.Unboxed.Mutable (MVector, Unbox) + + import qualified Data.Vector.Algorithms.Insertion as INS + import qualified Data.Vector.Algorithms.Intro as INT +@@ -35,8 +36,8 @@ noalgo _ = return () + -- Allocates a temporary buffer, like mergesort for similar purposes as noalgo. + alloc :: (Unbox e) => MVector RealWorld e -> IO () + alloc arr | len <= 4 = arr `seq` return () +- | otherwise = (new (len `div` 2) :: IO (MVector RealWorld Int)) >> return () +- where len = length arr ++ | otherwise = (U.new (len `div` 2) :: IO (MVector RealWorld Int)) >> return () ++ where len = U.length arr + + displayTime :: String -> Integer -> IO () + displayTime s elapsed = putStrLn $ +@@ -47,7 +48,7 @@ run s t = t >>= displayTime s + + sortSuite :: String -> GenIO -> Int -> (MVector RealWorld Int -> IO ()) -> IO () + sortSuite str g n sort = do +- arr <- new n ++ arr <- U.new n + putStrLn $ "Testing: " ++ str + run "Random " $ speedTest arr n (rand g >=> modulo n) sort + run "Sorted " $ speedTest arr n ascend sort +diff --git a/src/Data/Vector/Algorithms/Optimal.hs b/src/Data/Vector/Algorithms/Optimal.hs +index a6a72d4..42a4f07 100644 +--- a/src/Data/Vector/Algorithms/Optimal.hs ++++ b/src/Data/Vector/Algorithms/Optimal.hs +@@ -40,6 +40,13 @@ import Data.Vector.Generic.Mutable + + import Data.Vector.Algorithms.Common (Comparison) + ++#if MIN_VERSION_vector(0,13,0) ++import qualified Data.Vector.Internal.Check as Ck ++# define CHECK_INDEX(name, i, n) Ck.checkIndex Ck.Unsafe (i) (n) ++#else ++# define CHECK_INDEX(name, i, n) UNSAFE_CHECK(checkIndex) name (i) (n) ++#endif ++ + #include "vector.h" + + -- | Sorts the elements at the positions 'off' and 'off + 1' in the given +@@ -54,8 +61,8 @@ sort2ByOffset cmp a off = sort2ByIndex cmp a off (off + 1) + -- be the 'lower' of the two. + sort2ByIndex :: (PrimMonad m, MVector v e) + => Comparison e -> v (PrimState m) e -> Int -> Int -> m () +-sort2ByIndex cmp a i j = UNSAFE_CHECK(checkIndex) "sort2ByIndex" i (length a) +- $ UNSAFE_CHECK(checkIndex) "sort2ByIndex" j (length a) $ do ++sort2ByIndex cmp a i j = CHECK_INDEX("sort2ByIndex", i, length a) ++ $ CHECK_INDEX("sort2ByIndex", j, length a) $ do + a0 <- unsafeRead a i + a1 <- unsafeRead a j + case cmp a0 a1 of +@@ -75,9 +82,9 @@ sort3ByOffset cmp a off = sort3ByIndex cmp a off (off + 1) (off + 2) + -- lowest position in the array. + sort3ByIndex :: (PrimMonad m, MVector v e) + => Comparison e -> v (PrimState m) e -> Int -> Int -> Int -> m () +-sort3ByIndex cmp a i j k = UNSAFE_CHECK(checkIndex) "sort3ByIndex" i (length a) +- $ UNSAFE_CHECK(checkIndex) "sort3ByIndex" j (length a) +- $ UNSAFE_CHECK(checkIndex) "sort3ByIndex" k (length a) $ do ++sort3ByIndex cmp a i j k = CHECK_INDEX("sort3ByIndex", i, length a) ++ $ CHECK_INDEX("sort3ByIndex", j, length a) ++ $ CHECK_INDEX("sort3ByIndex", k, length a) $ do + a0 <- unsafeRead a i + a1 <- unsafeRead a j + a2 <- unsafeRead a k +@@ -114,10 +121,10 @@ sort4ByOffset cmp a off = sort4ByIndex cmp a off (off + 1) (off + 2) (off + 3) + -- it can be used to sort medians into particular positions and so on. + sort4ByIndex :: (PrimMonad m, MVector v e) + => Comparison e -> v (PrimState m) e -> Int -> Int -> Int -> Int -> m () +-sort4ByIndex cmp a i j k l = UNSAFE_CHECK(checkIndex) "sort4ByIndex" i (length a) +- $ UNSAFE_CHECK(checkIndex) "sort4ByIndex" j (length a) +- $ UNSAFE_CHECK(checkIndex) "sort4ByIndex" k (length a) +- $ UNSAFE_CHECK(checkIndex) "sort4ByIndex" l (length a) $ do ++sort4ByIndex cmp a i j k l = CHECK_INDEX("sort4ByIndex", i, length a) ++ $ CHECK_INDEX("sort4ByIndex", j, length a) ++ $ CHECK_INDEX("sort4ByIndex", k, length a) ++ $ CHECK_INDEX("sort4ByIndex", l, length a) $ do + a0 <- unsafeRead a i + a1 <- unsafeRead a j + a2 <- unsafeRead a k +diff --git a/tests/properties/Optimal.hs b/tests/properties/Optimal.hs +index 2db2eda..9007a4a 100644 +--- a/tests/properties/Optimal.hs ++++ b/tests/properties/Optimal.hs +@@ -8,7 +8,7 @@ module Optimal where + import Control.Arrow + import Control.Monad + +-import Data.List ++import qualified Data.List as List + import Data.Function + + import Data.Vector.Generic hiding (map, zip, concatMap, (++), replicate, foldM) +@@ -32,18 +32,18 @@ monotones k = atLeastOne 0 + stability :: (Vector v (Int,Int)) => Int -> [v (Int, Int)] + stability n = concatMap ( map fromList + . foldM interleavings [] +- . groupBy ((==) `on` fst) ++ . List.groupBy ((==) `on` fst) + . flip zip [0..]) + $ monotones (n-2) n + + sort2 :: (Vector v Int) => [v Int] +-sort2 = map fromList $ permutations [0,1] ++sort2 = map fromList $ List.permutations [0,1] + + stability2 :: (Vector v (Int,Int)) => [v (Int, Int)] + stability2 = [fromList [(0, 0), (0, 1)]] + + sort3 :: (Vector v Int) => [v Int] +-sort3 = map fromList $ permutations [0..2] ++sort3 = map fromList $ List.permutations [0..2] + + {- + stability3 :: [UArr (Int :*: Int)] +@@ -58,5 +58,5 @@ stability3 = map toU [ [0:*:0, 0:*:1, 0:*:2] + -} + + sort4 :: (Vector v Int) => [v Int] +-sort4 = map fromList $ permutations [0..3] ++sort4 = map fromList $ List.permutations [0..3] + +diff --git a/vector-algorithms.cabal b/vector-algorithms.cabal +index 44f7544..1723ec1 100644 +--- a/vector-algorithms.cabal ++++ b/vector-algorithms.cabal +@@ -1,5 +1,6 @@ + name: vector-algorithms + version: 0.8.0.4 ++x-revision: 2 + license: BSD3 + license-file: LICENSE + author: Dan Doel +@@ -57,7 +58,7 @@ library + default-language: Haskell2010 + + build-depends: base >= 4.5 && < 5, +- vector >= 0.6 && < 0.13, ++ vector >= 0.6 && < 0.14, + primitive >=0.3 && <0.8, + bytestring >= 0.9 && < 1.0 + diff --git a/patches/vector-th-unbox-0.2.2.patch b/patches/vector-th-unbox-0.2.2.patch new file mode 100644 index 0000000000000000000000000000000000000000..fffc06a9fc9ea9611ebc53b0ecab673b8007c5bd --- /dev/null +++ b/patches/vector-th-unbox-0.2.2.patch @@ -0,0 +1,23 @@ +diff --git a/vector-th-unbox.cabal b/vector-th-unbox.cabal +index 84b5241..964b584 100644 +--- a/vector-th-unbox.cabal ++++ b/vector-th-unbox.cabal +@@ -1,5 +1,6 @@ + name: vector-th-unbox + version: 0.2.2 ++x-revision: 1 + synopsis: Deriver for Data.Vector.Unboxed using Template Haskell + description: + A Template Haskell deriver for unboxed vectors, given a pair of coercion +@@ -35,9 +36,9 @@ library + Data.Vector.Unboxed.Deriving + + build-depends: +- base >= 4.5 && < 4.17, ++ base >= 4.9 && < 4.17, + template-haskell >= 2.5 && <2.19, +- vector >= 0.7.1 && <0.13 ++ vector >= 0.7.1 && <0.14 + + test-suite sanity + default-language: Haskell2010