Safe Haskell | None |
---|---|
Language | Haskell2010 |
SubHask.Algebra.Parallel
Contents
Description
Every monoid homomorphism from a Container can be parallelized.
And if you believe that NC /= P
, then every parallel algorithm is induced by a monoid in this manner.
- parallel :: (Partitionable domain, Monoid range, NFData range) => (domain -> range) -> domain -> range
- disableMultithreading :: IO a -> IO a
- class (Monoid t, Foldable t, Constructible t) => Partitionable t where
- partition :: Int -> t -> [t]
- partitionInterleaved :: Int -> t -> [t]
- law_Partitionable_length :: (ClassicalLogic t, Partitionable t) => Int -> t -> Bool
- law_Partitionable_monoid :: (ClassicalLogic t, Eq_ t, Partitionable t) => Int -> t -> Bool
- parallelBlockedN :: (Partitionable domain, Monoid range, NFData range) => Int -> (domain -> range) -> domain -> range
- parallelBlocked :: (Partitionable domain, Monoid range, NFData range) => (domain -> range) -> domain -> range
- unsafeParallelInterleavedN :: (Partitionable domain, Monoid range, NFData range) => Int -> (domain -> range) -> domain -> range
- unsafeParallelInterleaved :: (Partitionable domain, Monoid range, NFData range) => (domain -> range) -> domain -> range
- parallelInterleaved :: (Partitionable domain, Abelian range, Monoid range, NFData range) => (domain -> range) -> domain -> range
Documentation
Arguments
:: (Partitionable domain, Monoid range, NFData range) | |
=> (domain -> range) | sequential monoid homomorphism |
-> domain -> range | parallel monoid homomorphism |
Converts any monoid homomorphism into an efficient parallelized function. This is the only function you should have to care about. It uses rewrite rules to select the most cache-efficient parallelization method for the particular data types called.
disableMultithreading :: IO a -> IO a Source
This forces a function to be run with only a single thread.
That is, the function is executed as if -N1
was passed into the program rather than whatever value was actually used.
Subsequent functions are not affected.
Why is this useful?
The GHC runtime system can make non-threaded code run really slow when many threads are enabled.
For example, I have found instances of sequential code taking twice as long when the -N16
flag is passed to the run time system.
By wrapping those function calls in "disableMultithreading", we restore the original performance.
class (Monoid t, Foldable t, Constructible t) => Partitionable t where Source
A Partitionable container can be split up into an arbitrary number of subcontainers of roughly equal size.
Minimal complete definition
Nothing
Methods
partition :: Int -> t -> [t] Source
The Int must be >0
partitionInterleaved :: Int -> t -> [t] Source
Instances
Partitionable [a] Source | |
ValidLogic e => Partitionable (BArray e) Source | |
Unboxable e => Partitionable (UArray e) Source | |
ValidEq a => Partitionable (Seq a) Source | |
Partitionable (ByteString Char) Source | |
((~) * a (ByteString Char), Partitionable a) => Partitionable (PartitionOnNewline a) Source |
law_Partitionable_length :: (ClassicalLogic t, Partitionable t) => Int -> t -> Bool Source
law_Partitionable_monoid :: (ClassicalLogic t, Eq_ t, Partitionable t) => Int -> t -> Bool Source
parallel helpers
Arguments
:: (Partitionable domain, Monoid range, NFData range) | |
=> Int | number of parallel threads |
-> (domain -> range) | sequential monoid homomorphism |
-> domain -> range | parallel monoid homomorphism |
Let's you specify the exact number of threads to parallelize over.
Arguments
:: (Partitionable domain, Monoid range, NFData range) | |
=> (domain -> range) | sequential monoid homomorphism |
-> domain -> range | parallel monoid homomorphism |
unsafeParallelInterleavedN Source
Arguments
:: (Partitionable domain, Monoid range, NFData range) | |
=> Int | number of parallel threads |
-> (domain -> range) | sequential monoid homomorphism |
-> domain -> range | parallel monoid homomorphism |
Let's you specify the exact number of threads to parallelize over.
This function is unsafe because if our range
is not Abelian, this function changes the results.
unsafeParallelInterleaved Source
Arguments
:: (Partitionable domain, Monoid range, NFData range) | |
=> (domain -> range) | sequential monoid homomorphism |
-> domain -> range | parallel monoid homomorphism |
This function automatically detects the number of available processors and parallelizes the function accordingly.
This function is unsafe because if our range
is not Abelian, this function changes the results.
Arguments
:: (Partitionable domain, Abelian range, Monoid range, NFData range) | |
=> (domain -> range) | sequential monoid homomorphism |
-> domain -> range | parallel monoid homomorphism |
This function automatically detects the number of available processors and parallelizes the function accordingly. This function is safe (i.e. it won't affect the output) because it requires the Abelian constraint.