From 481b2e2f3f4484f589157accfc17cf11cbf7dbd6 Mon Sep 17 00:00:00 2001 From: Preetham Gujjula Date: Wed, 22 May 2024 16:51:51 -0400 Subject: [PATCH 1/6] Warn when there are unused imports --- pqueue.cabal | 3 --- 1 file changed, 3 deletions(-) diff --git a/pqueue.cabal b/pqueue.cabal index f006f9d..db6a922 100644 --- a/pqueue.cabal +++ b/pqueue.cabal @@ -74,9 +74,6 @@ library -fspec-constr -fdicts-strict -Wall - if impl(ghc >= 8.0) - ghc-options: - -fno-warn-unused-imports test-suite test hs-source-dirs: src, tests From c14f33613f8a160e1e3eb4b03891f4fe4c1835e4 Mon Sep 17 00:00:00 2001 From: Preetham Gujjula Date: Wed, 22 May 2024 14:47:08 -0400 Subject: [PATCH 2/6] Remove unused imports --- benchmarks/HeapSort.hs | 1 - benchmarks/KWay/PrioMergeAlg.hs | 1 - benchmarks/KWay/RandomIncreasing.hs | 1 - benchmarks/PHeapSort.hs | 1 - src/BinomialQueue/Max.hs | 15 +-------------- src/BinomialQueue/Min.hs | 14 +------------- src/Data/PQueue/Internals.hs | 3 --- src/Data/PQueue/Min.hs | 14 +------------- src/Data/PQueue/Prio/Internals.hs | 6 +++++- src/Data/PQueue/Prio/Min.hs | 4 ---- 10 files changed, 8 insertions(+), 52 deletions(-) diff --git a/benchmarks/HeapSort.hs b/benchmarks/HeapSort.hs index 7179e87..89bd6fe 100644 --- a/benchmarks/HeapSort.hs +++ b/benchmarks/HeapSort.hs @@ -1,6 +1,5 @@ module HeapSort where -import Data.PQueue.Min (MinQueue) import qualified Data.PQueue.Min as P import System.Random diff --git a/benchmarks/KWay/PrioMergeAlg.hs b/benchmarks/KWay/PrioMergeAlg.hs index 9ccb7ca..fef8dd9 100644 --- a/benchmarks/KWay/PrioMergeAlg.hs +++ b/benchmarks/KWay/PrioMergeAlg.hs @@ -7,7 +7,6 @@ module KWay.PrioMergeAlg ) where import qualified Data.PQueue.Prio.Min as P -import System.Random (StdGen) import Data.Word import Data.List (unfoldr) import KWay.RandomIncreasing diff --git a/benchmarks/KWay/RandomIncreasing.hs b/benchmarks/KWay/RandomIncreasing.hs index bb6d6a2..40354a2 100644 --- a/benchmarks/KWay/RandomIncreasing.hs +++ b/benchmarks/KWay/RandomIncreasing.hs @@ -5,7 +5,6 @@ module KWay.RandomIncreasing where import System.Random import Data.Word -import Data.List (unfoldr) data Stream = Stream !Word64 {-# UNPACK #-} !StdGen diff --git a/benchmarks/PHeapSort.hs b/benchmarks/PHeapSort.hs index 6c4b9a5..66a93b6 100644 --- a/benchmarks/PHeapSort.hs +++ b/benchmarks/PHeapSort.hs @@ -1,6 +1,5 @@ module PHeapSort where -import Data.PQueue.Prio.Min (MinPQueue) import qualified Data.PQueue.Prio.Min as P import System.Random diff --git a/src/BinomialQueue/Max.hs b/src/BinomialQueue/Max.hs index c379579..f21c0cc 100644 --- a/src/BinomialQueue/Max.hs +++ b/src/BinomialQueue/Max.hs @@ -88,26 +88,13 @@ module BinomialQueue.Max ( import Prelude hiding (null, take, drop, takeWhile, dropWhile, splitAt, span, break, (!!), filter, map) import Data.Coerce (coerce) -import Data.Foldable (foldl') -import Data.Maybe (fromMaybe) import Data.Bifunctor (bimap) - -#if MIN_VERSION_base(4,9,0) -import Data.Semigroup (Semigroup((<>))) -#endif - import qualified Data.List as List +import Data.Maybe (fromMaybe) import qualified BinomialQueue.Min as MinQ import Data.PQueue.Internals.Down -#ifdef __GLASGOW_HASKELL__ -import GHC.Exts (build) -#else -build :: ((a -> [a] -> [a]) -> [a] -> [a]) -> [a] -build f = f (:) [] -#endif - newtype MaxQueue a = MaxQueue { unMaxQueue :: MinQ.MinQueue (Down a) } -- | \(O(\log n)\). Returns the minimum element. Throws an error on an empty queue. diff --git a/src/BinomialQueue/Min.hs b/src/BinomialQueue/Min.hs index 2eee2b7..fd6910d 100644 --- a/src/BinomialQueue/Min.hs +++ b/src/BinomialQueue/Min.hs @@ -89,23 +89,11 @@ module BinomialQueue.Min ( import Prelude hiding (null, take, drop, takeWhile, dropWhile, splitAt, span, break, (!!), filter, map) import Data.Foldable (foldl') -import Data.Maybe (fromMaybe) - -#if MIN_VERSION_base(4,9,0) -import Data.Semigroup (Semigroup((<>))) -#endif - import qualified Data.List as List +import Data.Maybe (fromMaybe) import BinomialQueue.Internals -#ifdef __GLASGOW_HASKELL__ -import GHC.Exts (build) -#else -build :: ((a -> [a] -> [a]) -> [a] -> [a]) -> [a] -build f = f (:) [] -#endif - -- | \(O(\log n)\). Returns the minimum element. Throws an error on an empty queue. findMin :: Ord a => MinQueue a -> a findMin = fromMaybe (error "Error: findMin called on empty queue") . getMin diff --git a/src/Data/PQueue/Internals.hs b/src/Data/PQueue/Internals.hs index 78d0d1d..a4ce5b1 100644 --- a/src/Data/PQueue/Internals.hs +++ b/src/Data/PQueue/Internals.hs @@ -45,8 +45,6 @@ import BinomialQueue.Internals , BinomTree (..) , Succ (..) , Zero (..) - , Extract (..) - , MExtract (..) ) import qualified BinomialQueue.Internals as BQ import Control.DeepSeq (NFData(rnf), deepseq) @@ -55,7 +53,6 @@ import Data.Foldable (foldl') import Data.Semigroup (Semigroup(..), stimesMonoid) #endif -import Data.PQueue.Internals.Foldable #ifdef __GLASGOW_HASKELL__ import Data.Data import Text.Read (Lexeme(Ident), lexP, parens, prec, diff --git a/src/Data/PQueue/Min.hs b/src/Data/PQueue/Min.hs index 02b6e35..1fbea31 100644 --- a/src/Data/PQueue/Min.hs +++ b/src/Data/PQueue/Min.hs @@ -95,13 +95,8 @@ module Data.PQueue.Min ( import Prelude hiding (null, take, drop, takeWhile, dropWhile, splitAt, span, break, (!!), filter, map) import Data.Foldable (foldl') -import Data.Maybe (fromMaybe) - -#if MIN_VERSION_base(4,9,0) -import Data.Semigroup (Semigroup((<>))) -#endif - import qualified Data.List as List +import Data.Maybe (fromMaybe) import Data.PQueue.Internals hiding (MinQueue (..)) import Data.PQueue.Internals (MinQueue (MinQueue)) @@ -109,13 +104,6 @@ import qualified Data.PQueue.Internals as Internals import qualified BinomialQueue.Internals as BQ import qualified Data.PQueue.Prio.Internals as Prio -#ifdef __GLASGOW_HASKELL__ -import GHC.Exts (build) -#else -build :: ((a -> [a] -> [a]) -> [a] -> [a]) -> [a] -build f = f (:) [] -#endif - #ifdef __GLASGOW_HASKELL__ -- | A bidirectional pattern synonym for an empty priority queue. -- diff --git a/src/Data/PQueue/Prio/Internals.hs b/src/Data/PQueue/Prio/Internals.hs index 4afaede..85c1dde 100644 --- a/src/Data/PQueue/Prio/Internals.hs +++ b/src/Data/PQueue/Prio/Internals.hs @@ -52,7 +52,11 @@ module Data.PQueue.Prio.Internals ( unions ) where -import Control.Applicative (liftA2, liftA3, Const (..)) +#if MIN_VERSION_base(4,18,0) +import Control.Applicative (Const (..)) +#else +import Control.Applicative (liftA2, Const (..)) +#endif import Control.DeepSeq (NFData(rnf), deepseq) import Data.Coerce (coerce) import Data.Functor.Identity (Identity(Identity, runIdentity)) diff --git a/src/Data/PQueue/Prio/Min.hs b/src/Data/PQueue/Prio/Min.hs index ca026ca..5db11ee 100644 --- a/src/Data/PQueue/Prio/Min.hs +++ b/src/Data/PQueue/Prio/Min.hs @@ -132,10 +132,6 @@ module Data.PQueue.Prio.Min ( import qualified Data.List as List import Data.Maybe (fromMaybe) -#if MIN_VERSION_base(4,9,0) -import Data.Semigroup (Semigroup((<>))) -#endif - import Data.PQueue.Prio.Internals hiding (MinPQueue (..)) import Data.PQueue.Prio.Internals (MinPQueue) import qualified Data.PQueue.Prio.Internals as Internals From a5b9e46d3670cbdef2e13fa28b89b70977a80e37 Mon Sep 17 00:00:00 2001 From: Preetham Gujjula Date: Wed, 22 May 2024 16:02:21 -0400 Subject: [PATCH 3/6] Only import foldl' when base < 4.20 --- src/BinomialQueue/Internals.hs | 2 ++ src/BinomialQueue/Min.hs | 2 ++ src/Data/PQueue/Internals.hs | 2 ++ src/Data/PQueue/Max.hs | 6 +++--- src/Data/PQueue/Min.hs | 2 ++ 5 files changed, 11 insertions(+), 3 deletions(-) diff --git a/src/BinomialQueue/Internals.hs b/src/BinomialQueue/Internals.hs index aa4dcd4..0168c70 100644 --- a/src/BinomialQueue/Internals.hs +++ b/src/BinomialQueue/Internals.hs @@ -46,7 +46,9 @@ module BinomialQueue.Internals ( ) where import Control.DeepSeq (NFData(rnf), deepseq) +#if !MIN_VERSION_base(4,20,0) import Data.Foldable (foldl') +#endif import Data.Function (on) #if MIN_VERSION_base(4,9,0) import Data.Semigroup (Semigroup(..), stimesMonoid) diff --git a/src/BinomialQueue/Min.hs b/src/BinomialQueue/Min.hs index fd6910d..4885fd7 100644 --- a/src/BinomialQueue/Min.hs +++ b/src/BinomialQueue/Min.hs @@ -88,7 +88,9 @@ module BinomialQueue.Min ( import Prelude hiding (null, take, drop, takeWhile, dropWhile, splitAt, span, break, (!!), filter, map) +#if !MIN_VERSION_base(4,20,0) import Data.Foldable (foldl') +#endif import qualified Data.List as List import Data.Maybe (fromMaybe) diff --git a/src/Data/PQueue/Internals.hs b/src/Data/PQueue/Internals.hs index a4ce5b1..0e5ed51 100644 --- a/src/Data/PQueue/Internals.hs +++ b/src/Data/PQueue/Internals.hs @@ -48,7 +48,9 @@ import BinomialQueue.Internals ) import qualified BinomialQueue.Internals as BQ import Control.DeepSeq (NFData(rnf), deepseq) +#if !MIN_VERSION_base(4,20,0) import Data.Foldable (foldl') +#endif #if MIN_VERSION_base(4,9,0) import Data.Semigroup (Semigroup(..), stimesMonoid) #endif diff --git a/src/Data/PQueue/Max.hs b/src/Data/PQueue/Max.hs index fe98ae1..53986d3 100644 --- a/src/Data/PQueue/Max.hs +++ b/src/Data/PQueue/Max.hs @@ -86,14 +86,14 @@ module Data.PQueue.Max ( import Control.DeepSeq (NFData(rnf)) import Data.Coerce (coerce) +#if !MIN_VERSION_base(4,20,0) +import Data.Foldable (foldl') +#endif import Data.Maybe (fromMaybe) - #if MIN_VERSION_base(4,9,0) import Data.Semigroup (Semigroup(..), stimesMonoid) #endif -import Data.Foldable (foldl') - import qualified Data.PQueue.Min as Min import qualified Data.PQueue.Prio.Max.Internals as Prio import Data.PQueue.Internals.Down (Down(..)) diff --git a/src/Data/PQueue/Min.hs b/src/Data/PQueue/Min.hs index 1fbea31..5b668de 100644 --- a/src/Data/PQueue/Min.hs +++ b/src/Data/PQueue/Min.hs @@ -94,7 +94,9 @@ module Data.PQueue.Min ( import Prelude hiding (null, take, drop, takeWhile, dropWhile, splitAt, span, break, (!!), filter, map) +#if !MIN_VERSION_base(4,20,0) import Data.Foldable (foldl') +#endif import qualified Data.List as List import Data.Maybe (fromMaybe) From 4112883e2b6e61471d6a9ed0dc13a3d468a716d0 Mon Sep 17 00:00:00 2001 From: Preetham Gujjula Date: Wed, 22 May 2024 16:06:51 -0400 Subject: [PATCH 4/6] Only import unsafeCoerce when necessary --- src/Nattish.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Nattish.hs b/src/Nattish.hs index 925f8b3..a52c4fe 100644 --- a/src/Nattish.hs +++ b/src/Nattish.hs @@ -18,7 +18,9 @@ module Nattish ( Nattish (Zeroy, Succy) ) where +#if __GLASGOW_HASKELL__ >= 904 import Unsafe.Coerce (unsafeCoerce) +#endif #if __GLASGOW_HASKELL__ >= 800 import Data.Kind (Type) #endif From 0b38aebd3598f3749f6b4faea5cacdf2d131303d Mon Sep 17 00:00:00 2001 From: Preetham Gujjula Date: Wed, 22 May 2024 16:17:42 -0400 Subject: [PATCH 5/6] Only use Type when it's defined --- src/Nattish.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Nattish.hs b/src/Nattish.hs index a52c4fe..c782e72 100644 --- a/src/Nattish.hs +++ b/src/Nattish.hs @@ -40,7 +40,11 @@ import Data.Kind (Type) -- it is very fast to work with. #if __GLASGOW_HASKELL__ < 904 +#if __GLASGOW_HASKELL__ >= 800 +data Nattish :: k -> (k -> k) -> k -> Type where +#else data Nattish :: k -> (k -> k) -> k -> * where +#endif Zeroy :: Nattish zero succ zero Succy :: !(Nattish zero succ n) -> Nattish zero succ (succ n) From 45f128e45e6818b0bb7a26947820abc02ad0bfe5 Mon Sep 17 00:00:00 2001 From: Preetham Gujjula Date: Wed, 22 May 2024 16:35:08 -0400 Subject: [PATCH 6/6] Use COMPLETE pragma only when ghc >= 8.2 --- src/Data/PQueue/Min.hs | 2 ++ src/Data/PQueue/Prio/Min.hs | 2 ++ 2 files changed, 4 insertions(+) diff --git a/src/Data/PQueue/Min.hs b/src/Data/PQueue/Min.hs index 5b668de..c824457 100644 --- a/src/Data/PQueue/Min.hs +++ b/src/Data/PQueue/Min.hs @@ -136,7 +136,9 @@ pattern a :< q <- (minView -> Just (a, q)) {-# INLINE (:<) #-} # endif +# if __GLASGOW_HASKELL__ >= 820 {-# COMPLETE Empty, (:<) #-} +# endif #endif -- | \(O(1)\). Returns the minimum element. Throws an error on an empty queue. diff --git a/src/Data/PQueue/Prio/Min.hs b/src/Data/PQueue/Prio/Min.hs index 5db11ee..bf39e3e 100644 --- a/src/Data/PQueue/Prio/Min.hs +++ b/src/Data/PQueue/Prio/Min.hs @@ -168,7 +168,9 @@ pattern ka :< q <- (minViewWithKey -> Just (ka, q)) {-# INLINE (:<) #-} # endif +# if __GLASGOW_HASKELL__ >= 820 {-# COMPLETE Empty, (:<) #-} +# endif #endif (.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d