vector-quicksort-0.1: Fast and flexible quicksort implementation for mutable vectors
Copyright(c) Sergey Vinokurov 2023
LicenseApache-2.0 (see LICENSE)
Maintainerserg.foo@gmail.com
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Vector.Algorithms.Quicksort

Description

This module provides reasonable default sorting algorithm with no parallelisation. To get parallelisation please use Parameterised.

Example

Vanilla vectors:

>>> import Data.Vector.Unboxed qualified as U
>>> sort $ U.fromList @Int [20, 19 .. 0]
[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20]

Mutable vectors:

>>> import Control.Monad.ST (runST)
>>> import Data.Vector.Unboxed qualified as U
>>> :{
runST $ do
  xs <- U.unsafeThaw $ U.fromList @Int [20, 19 .. 0]
  sortInplace xs
  U.unsafeFreeze xs
:}
[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20]

With modify:

>>> import Data.Vector.Unboxed qualified as U
>>> U.modify sortInplace $ U.fromList @Int [20, 19 .. 0]
[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20]

Performance considerations

For best performance it's recommended to keep a close eye on core to make sure that this function doesn't take any class dictionaries. If it does then performance will be very bad since either comparisons will go via indirection, vector reads/writes, monadic bind, or any combinatior of those will go through dictionary indirection. This can be avoided either by compiling with -fspecialise-aggressively flag or by using via SPECIALIZE pragmas, like so:

-- Either use the flag to specialize everything, ...
{-# OPTIONS_GHC -fspecialise-aggressively #-}

-- ... or the pragmas for specific functions
import Data.Vector.Algorithms.FixedSort
import Data.Vector.Algorithms.Heapsort
import Data.Vector.Algorithms.Quicksort
import Data.Vector.Unboxed qualified as U

-- If sorting in ST
-- These are fallback sorts and their performance is important
{-# SPECIALIZE heapSort    :: U.MVector s Int -> ST s ()        #-}
{-# SPECIALIZE bitonicSort :: Int -> U.MVector s Int -> ST s () #-}
-- Main sort entry point
{-# SPECIALIZE sort        :: U.MVector s Int -> ST s ()        #-}

-- If sorting in IO
{-# SPECIALIZE heapSort    :: U.MVector RealWorld Int -> IO ()        #-}
{-# SPECIALIZE bitonicSort :: Int -> U.MVector RealWorld Int -> IO () #-}
{-# SPECIALIZE sort        :: U.MVector RealWorld Int -> IO ()        #-}
Synopsis

Documentation

sort :: forall a v. (Ord a, Vector v a) => v a -> v a Source #

Good default sort. Returns sorted copy.

This function takes generic vectors so will work with any vectors from the vector package.

sortInplace :: forall m a v. (PrimMonad m, Ord a, MVector v a) => v (PrimState m) a -> m () Source #

Good default sort for mutable vectors.

This function takes generic mutable vectors so will work with any vectors from the vector package.

Could be run on immutable vectors with modify.