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

Description

This module defines how quicksort is parallelised using the Fork2 class.

Synopsis

Main interface

class Fork2 a x m | a -> x where Source #

Parallelization strategy for the quicksort algorithm with single-pivot partitioning. Specifies how to apply a pair of functions to their respective inputs (which will be recursive quicksort calls).

NB the name Fork2 suggests that two threads will be only forked.

Parameter meaning; - a - the parallelisation we're defining instance for - x - type of tokens that strategy can pass around to track recursive calls - m - monad the strategy operates in. Some strategies only make sense in a particular monad, e.g. parellelisation via forkIO

Methods

startWork :: a -> m x Source #

Will get called only once by quicksort when sorting starts, returns token to be passed around. Other tokens, e.g. for new spawned threads, are created by the strategy in the corresponding class instance.

endWork :: a -> x -> m () Source #

Will get called by quicksort when it finishes sorting its array. Will receive previously created token.

fork2 Source #

Arguments

:: (HasLength b, HasLength d) 
=> a

Parallelisation algorithm that can carry extra info, e.g. for synchronization

-> x

Token for current execution thread, will be passed to endWork when done

-> Int

Recursion depth

-> (x -> b -> m ())

One recursive quicksort call

-> (x -> d -> m ())

The other recursive quicksort call

-> b

One of the subarrays after partitioning to be sorted

-> d

The other subarray to be sorted

-> m () 

Instances

Instances details
Fork2 ParStrategies () IO Source # 
Instance details

Defined in Data.Vector.Algorithms.Quicksort.Fork2

Methods

startWork :: ParStrategies -> IO () Source #

endWork :: ParStrategies -> () -> IO () Source #

fork2 :: (HasLength b, HasLength d) => ParStrategies -> () -> Int -> (() -> b -> IO ()) -> (() -> d -> IO ()) -> b -> d -> IO () Source #

Monad m => Fork2 Sequential () m Source # 
Instance details

Defined in Data.Vector.Algorithms.Quicksort.Fork2

Methods

startWork :: Sequential -> m () Source #

endWork :: Sequential -> () -> m () Source #

fork2 :: (HasLength b, HasLength d) => Sequential -> () -> Int -> (() -> b -> m ()) -> (() -> d -> m ()) -> b -> d -> m () Source #

Fork2 ParStrategies () (ST s) Source #

This instance is a bit surprising - ST monad, after all, doesn’t have concurrency and threads everywhere its s parameter to signal, among other things, that it’s single execution thread.

Still, quicksort in this package hopefully doesn’t do anything funny that may break under parallelism. Use of this instance for other purposes has at least the same caveats as use of unsafeInterleaveST (i.e. not recommended, especially considering that the instance may change).

Instance details

Defined in Data.Vector.Algorithms.Quicksort.Fork2

Methods

startWork :: ParStrategies -> ST s () Source #

endWork :: ParStrategies -> () -> ST s () Source #

fork2 :: (HasLength b, HasLength d) => ParStrategies -> () -> Int -> (() -> b -> ST s ()) -> (() -> d -> ST s ()) -> b -> d -> ST s () Source #

Fork2 Parallel (Bool, Bool) IO Source # 
Instance details

Defined in Data.Vector.Algorithms.Quicksort.Fork2

Methods

startWork :: Parallel -> IO (Bool, Bool) Source #

endWork :: Parallel -> (Bool, Bool) -> IO () Source #

fork2 :: (HasLength b, HasLength d) => Parallel -> (Bool, Bool) -> Int -> ((Bool, Bool) -> b -> IO ()) -> ((Bool, Bool) -> d -> IO ()) -> b -> d -> IO () Source #

No parallelisation

data Sequential Source #

Trivial parallelisation strategy that executes everything sequentially in current thread. Good default overall.

Constructors

Sequential 

Instances

Instances details
Monad m => Fork2 Sequential () m Source # 
Instance details

Defined in Data.Vector.Algorithms.Quicksort.Fork2

Methods

startWork :: Sequential -> m () Source #

endWork :: Sequential -> () -> m () Source #

fork2 :: (HasLength b, HasLength d) => Sequential -> () -> Int -> (() -> b -> m ()) -> (() -> d -> m ()) -> b -> d -> m () Source #

Parallelisation with threads

data Parallel Source #

At most N concurrent jobs will be spawned to evaluate recursive calls after quicksort partitioning.

Warning: currently not as fast as sparks-based ParStrategies strategy, take care to benchmark before using.

Instances

Instances details
Fork2 Parallel (Bool, Bool) IO Source # 
Instance details

Defined in Data.Vector.Algorithms.Quicksort.Fork2

Methods

startWork :: Parallel -> IO (Bool, Bool) Source #

endWork :: Parallel -> (Bool, Bool) -> IO () Source #

fork2 :: (HasLength b, HasLength d) => Parallel -> (Bool, Bool) -> Int -> ((Bool, Bool) -> b -> IO ()) -> ((Bool, Bool) -> d -> IO ()) -> b -> d -> IO () Source #

mkParallel :: Int -> IO Parallel Source #

Make parallelisation strategy with at most N threads.

waitParallel :: Parallel -> IO () Source #

Wait until all threads related to a particular Parallel instance finish.

Parallelisation with sparks

data ParStrategies Source #

Parallelise with sparks. After partitioning, if sides are sufficiently big then spark will be created to evaluate one of the parts while another will continue to be evaluated in current execution thread.

This strategy works in both IO and ST monads (see docs for relevant instance for some discussion on how that works).

Sparks will seamlessly use all available RTS capabilities (configured with +RTS -N flag) and according to benchmarks in this package have pretty low synchronization overhead as opposed to thread-based parallelisation that Parallel offers. These benefits allow sparks to work on much smaller chunks and exercise more parallelism.

Instances

Instances details
Fork2 ParStrategies () IO Source # 
Instance details

Defined in Data.Vector.Algorithms.Quicksort.Fork2

Methods

startWork :: ParStrategies -> IO () Source #

endWork :: ParStrategies -> () -> IO () Source #

fork2 :: (HasLength b, HasLength d) => ParStrategies -> () -> Int -> (() -> b -> IO ()) -> (() -> d -> IO ()) -> b -> d -> IO () Source #

Fork2 ParStrategies () (ST s) Source #

This instance is a bit surprising - ST monad, after all, doesn’t have concurrency and threads everywhere its s parameter to signal, among other things, that it’s single execution thread.

Still, quicksort in this package hopefully doesn’t do anything funny that may break under parallelism. Use of this instance for other purposes has at least the same caveats as use of unsafeInterleaveST (i.e. not recommended, especially considering that the instance may change).

Instance details

Defined in Data.Vector.Algorithms.Quicksort.Fork2

Methods

startWork :: ParStrategies -> ST s () Source #

endWork :: ParStrategies -> () -> ST s () Source #

fork2 :: (HasLength b, HasLength d) => ParStrategies -> () -> Int -> (() -> b -> ST s ()) -> (() -> d -> ST s ()) -> b -> d -> ST s () Source #

defaultParStrategies :: ParStrategies Source #

Parallelise with sparks for reasonably big vectors.

setParStrategiesCutoff :: Int -> ParStrategies -> ParStrategies Source #

Adjust length of vectors for which parallelisation will be performed.

Helpers

class HasLength a Source #

Helper that can be used to estimatae sizes of subproblems.

For inscance, too small array will not benefit from sorting it in parallel because parallelisation overhead will likely trump any time savings.

Minimal complete definition

getLength

Instances

Instances details
MVector v a => HasLength (v s a) Source # 
Instance details

Defined in Data.Vector.Algorithms.Quicksort.Fork2

Methods

getLength :: v s a -> Int Source #

getLength :: HasLength a => a -> Int Source #

Length of item