Copyright | (c) Sergey Vinokurov 2023 |
---|---|
License | Apache-2.0 (see LICENSE) |
Maintainer | serg.foo@gmail.com |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
This module defines how quicksort is parallelised using the Fork2
class.
Synopsis
- class Fork2 a x m | a -> x where
- data Sequential = Sequential
- data Parallel
- mkParallel :: Int -> IO Parallel
- waitParallel :: Parallel -> IO ()
- data ParStrategies
- defaultParStrategies :: ParStrategies
- setParStrategiesCutoff :: Int -> ParStrategies -> ParStrategies
- class HasLength a
- getLength :: HasLength a => a -> Int
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
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.
:: (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 |
-> 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
Fork2 ParStrategies () IO Source # | |
Monad m => Fork2 Sequential () m Source # | |
Defined in Data.Vector.Algorithms.Quicksort.Fork2 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 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
|
Fork2 Parallel (Bool, Bool) IO Source # | |
Defined in Data.Vector.Algorithms.Quicksort.Fork2 |
No parallelisation
data Sequential Source #
Trivial parallelisation strategy that executes everything sequentially in current thread. Good default overall.
Instances
Monad m => Fork2 Sequential () m Source # | |
Defined in Data.Vector.Algorithms.Quicksort.Fork2 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
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.
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
Fork2 ParStrategies () 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 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
|
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
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.