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.Parameterised

Contents

Description

This module provides fully generic quicksort for now allowing caller to decide how to parallelize and how to select median. More things may be parameterised in the future, likely by introducing new functions taking more arguments.

Example

This is how you’d define parallel sort that uses sparks on unboxed vectors of integers:

>>> import Control.Monad.ST
>>> import Data.Int
>>> import Data.Vector.Algorithms.Quicksort.Parameterised
>>> import Data.Vector.Unboxed qualified as U
>>> :{
let myParallelSort :: U.MVector s Int64 -> ST s ()
    myParallelSort = sortInplaceFM defaultParStrategies (Median3or5 @Int64)
in U.modify myParallelSort $ U.fromList @Int64 [20, 19 .. 0]
:}
[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20]

Design considerations

Because of reliance on specialisation, this package doesn't provide sort functions that take comparator function as argument. They rely on the Ord instance instead. While somewhat limiting, this allows to offload optimization to the SPECIALIZE pragmas even if compiler wasn't smart enough to monomorphise automatically.

Performance considerations

Compared to the default sort this one is even more sensitive to specialisation. Users caring about performance are advised to dump core and ensure that sort is monomorphised. The GHC 9.6.1 was seen to specialize automatically but 9.4 wasn't as good and required pragmas both for the main sort function and for its helpers, like this:

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

-- ... or the pragmas for specific functions
import Control.Monad.ST
import Data.Int
import Data.Vector.Algorithms.FixedSort
import Data.Vector.Algorithms.Heapsort
import Data.Vector.Algorithms.Quicksort.Parameterised
import Data.Vector.Unboxed qualified as U

{-# SPECIALIZE heapSort      :: U.MVector s Int64 -> ST s ()        #-}
{-# SPECIALIZE bitonicSort   :: Int -> U.MVector s Int64 -> ST s () #-}
{-# SPECIALIZE sortInplaceFM :: Sequential -> Median3 Int64 -> U.MVector s Int64 -> ST s () #-}

Speeding up compilation

In order to speed up compilations it's a good idea to introduce dedicated module where all the sorts will reside and import it instead of calling sort or sortInplaceFM in moduler with other logic. This way the sort functions, which can take a while to compile, will be recompiled rarely.

module MySorts (mySequentialSort) where

import Control.Monad.ST
import Data.Int
import Data.Vector.Unboxed qualified as U

import Data.Vector.Algorithms.Quicksort.Parameterised

{-# NOINLINE mySequentialSort #-}
mySequentialSort :: U.MVector s Int64 -> ST s ()
mySequentialSort = sortInplaceFM Sequential (Median3or5 @Int64)

Reducing code bloat

Avoid using sorts with both ST and IO monads. Stick to the ST monad as much as possible because it can be easily converted to IO via safe stToIO function. Using same sort in both IO and ST monads will compile two versions of it along with all it’s helper sorts which can be pretty big (especially the bitonic sort).

Synopsis

Documentation

sortInplaceFM :: forall p med x m a v. (Fork2 p x m, Median med a m (PrimState m), PrimMonad m, Ord a, MVector v a) => p -> med -> v (PrimState m) a -> m () Source #

Quicksort parameterised by median selection method and parallelisation strategy.

Reexports