Skip to content

Commit

Permalink
Fix to use INLINE for sort and sortUniq
Browse files Browse the repository at this point in the history
  • Loading branch information
toyboot4e committed Feb 3, 2025
1 parent 80bb471 commit 05296e7
Show file tree
Hide file tree
Showing 7 changed files with 13 additions and 13 deletions.
4 changes: 2 additions & 2 deletions src/Data/Vector/Algorithms/AmericanFlag.hs
Original file line number Diff line number Diff line change
Expand Up @@ -244,15 +244,15 @@ sort :: forall e m v. (PrimMonad m, MVector v e, Lexicographic e, Ord e)
sort v = sortBy compare terminate (size p) index v
where p :: Proxy e
p = Proxy
{-# INLINABLE sort #-}
{-# INLINE sort #-}

-- | A variant on `sort` that returns a vector of unique elements.
sortUniq :: forall e m v. (PrimMonad m, MVector v e, Lexicographic e, Ord e)
=> v (PrimState m) e -> m (v (PrimState m) e)
sortUniq v = sortUniqBy compare terminate (size p) index v
where p :: Proxy e
p = Proxy
{-# INLINABLE sortUniq #-}
{-# INLINE sortUniq #-}

-- | A fully parameterized version of the sorting algorithm. Again, this
-- function takes both radix information and a comparison, because the
Expand Down
4 changes: 2 additions & 2 deletions src/Data/Vector/Algorithms/Heap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,12 +56,12 @@ import qualified Data.Vector.Algorithms.Optimal as O
-- | Sorts an entire array using the default ordering.
sort :: (PrimMonad m, MVector v e, Ord e) => v (PrimState m) e -> m ()
sort = sortBy compare
{-# INLINABLE sort #-}
{-# INLINE sort #-}

-- | A variant on `sort` that returns a vector of unique elements.
sortUniq :: (PrimMonad m, MVector v e, Ord e) => v (PrimState m) e -> m (v (PrimState m) e)
sortUniq = sortUniqBy compare
{-# INLINABLE sortUniq #-}
{-# INLINE sortUniq #-}

-- | Sorts an entire array using a custom ordering.
sortBy :: (PrimMonad m, MVector v e) => Comparison e -> v (PrimState m) e -> m ()
Expand Down
4 changes: 2 additions & 2 deletions src/Data/Vector/Algorithms/Insertion.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,12 +36,12 @@ import qualified Data.Vector.Algorithms.Optimal as O
-- | Sorts an entire array using the default comparison for the type
sort :: (PrimMonad m, MVector v e, Ord e) => v (PrimState m) e -> m ()
sort = sortBy compare
{-# INLINABLE sort #-}
{-# INLINE sort #-}

-- | A variant on `sort` that returns a vector of unique elements.
sortUniq :: (PrimMonad m, MVector v e, Ord e) => v (PrimState m) e -> m (v (PrimState m) e)
sortUniq = sortUniqBy compare
{-# INLINABLE sortUniq #-}
{-# INLINE sortUniq #-}

-- | Sorts an entire array using a given comparison
sortBy :: (PrimMonad m, MVector v e) => Comparison e -> v (PrimState m) e -> m ()
Expand Down
4 changes: 2 additions & 2 deletions src/Data/Vector/Algorithms/Intro.hs
Original file line number Diff line number Diff line change
Expand Up @@ -67,12 +67,12 @@ import qualified Data.Vector.Algorithms.Heap as H
-- | Sorts an entire array using the default ordering.
sort :: (PrimMonad m, MVector v e, Ord e) => v (PrimState m) e -> m ()
sort = sortBy compare
{-# INLINABLE sort #-}
{-# INLINE sort #-}

-- | A variant on `sort` that returns a vector of unique elements.
sortUniq :: (PrimMonad m, MVector v e, Ord e) => v (PrimState m) e -> m (v (PrimState m) e)
sortUniq = sortUniqBy compare
{-# INLINABLE sortUniq #-}
{-# INLINE sortUniq #-}

-- | A variant on `sortBy` which returns a vector of unique elements.
sortBy :: (PrimMonad m, MVector v e) => Comparison e -> v (PrimState m) e -> m ()
Expand Down
4 changes: 2 additions & 2 deletions src/Data/Vector/Algorithms/Merge.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,12 +37,12 @@ import qualified Data.Vector.Algorithms.Insertion as I
-- | Sorts an array using the default comparison.
sort :: (PrimMonad m, MVector v e, Ord e) => v (PrimState m) e -> m ()
sort = sortBy compare
{-# INLINABLE sort #-}
{-# INLINE sort #-}

-- | A variant on `sort` that returns a vector of unique elements.
sortUniq :: (PrimMonad m, MVector v e, Ord e) => v (PrimState m) e -> m (v (PrimState m) e)
sortUniq = sortUniqBy compare
{-# INLINABLE sortUniq #-}
{-# INLINE sortUniq #-}

-- | Sorts an array using a custom comparison.
sortBy :: (PrimMonad m, MVector v e) => Comparison e -> v (PrimState m) e -> m ()
Expand Down
2 changes: 1 addition & 1 deletion src/Data/Vector/Algorithms/Radix.hs
Original file line number Diff line number Diff line change
Expand Up @@ -186,7 +186,7 @@ sort arr = sortBy (passes e) (size e) radix arr
where
e :: e
e = undefined
{-# INLINABLE sort #-}
{-# INLINE sort #-}

-- | Radix sorts an array using custom radix information
-- requires the number of passes to fully sort the array,
Expand Down
4 changes: 2 additions & 2 deletions src/Data/Vector/Algorithms/Tim.hs
Original file line number Diff line number Diff line change
Expand Up @@ -113,12 +113,12 @@ import Data.Vector.Algorithms.Common (uniqueMutableBy)
-- | Sorts an array using the default comparison.
sort :: (PrimMonad m, MVector v e, Ord e) => v (PrimState m) e -> m ()
sort = sortBy compare
{-# INLINABLE sort #-}
{-# INLINE sort #-}

-- | A variant on `sort` that returns a vector of unique elements.
sortUniq :: (PrimMonad m, MVector v e, Ord e) => v (PrimState m) e -> m (v (PrimState m) e)
sortUniq = sortUniqBy compare
{-# INLINABLE sortUniq #-}
{-# INLINE sortUniq #-}

-- | Sorts an array using a custom comparison.
sortBy :: (PrimMonad m, MVector v e)
Expand Down

0 comments on commit 05296e7

Please sign in to comment.