Copyright | (c) Alexey Kuleshevich 2019-2022 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- quicksortM_ :: (Ord e, Manifest r e, MonadPrimBase s m) => Scheduler s () -> MVector s r e -> m ()
- quicksortByM_ :: (Manifest r e, MonadPrimBase s m) => (e -> e -> m Ordering) -> Scheduler s () -> MVector s r e -> m ()
- unstablePartitionM :: forall r e m. (Manifest r e, PrimMonad m) => MVector (PrimState m) r e -> (e -> m Bool) -> m Ix1
- iterateUntilM :: (Load r' ix e, Manifest r e, MonadIO m) => (Int -> Array r ix e -> MArray RealWorld r ix e -> m Bool) -> (Int -> Array r ix e -> m (Array r' ix e)) -> Array r ix e -> m (Array r ix e)
Documentation
quicksortM_ :: (Ord e, Manifest r e, MonadPrimBase s m) => Scheduler s () -> MVector s r e -> m () Source #
Manifest version of quicksort
Since: 0.3.2
quicksortByM_ :: (Manifest r e, MonadPrimBase s m) => (e -> e -> m Ordering) -> Scheduler s () -> MVector s r e -> m () Source #
Same as quicksortM_
, but instead of Ord
constraint expects a custom Ordering
.
Since: 0.6.1
:: forall r e m. (Manifest r e, PrimMonad m) | |
=> MVector (PrimState m) r e | |
-> (e -> m Bool) | Predicate |
-> m Ix1 |
Partition elements of the supplied mutable vector according to the predicate.
Example
>>>
import Data.Massiv.Array as A
>>>
import Data.Massiv.Array.Mutable.Algorithms
>>>
:set -XOverloadedLists
>>>
m <- thaw ([2,1,50,10,20,8] :: Array P Ix1 Int)
>>>
unstablePartitionM m (pure . (<= 10))
4>>>
freeze Seq m
Array P Seq (Sz1 6) [ 2, 1, 8, 10, 20, 50 ]
Since: 1.0.0
:: (Load r' ix e, Manifest r e, MonadIO m) | |
=> (Int -> Array r ix e -> MArray RealWorld r ix e -> m Bool) | Convergence condition. Accepts current iteration counter, pure array at previous state and a mutable at the current state, therefore after each iteration its contents can be modifed if necessary. |
-> (Int -> Array r ix e -> m (Array r' ix e)) | A modifying function to apply at each iteration. The size of resulting array may differ if necessary. |
-> Array r ix e | Initial source array |
-> m (Array r ix e) |
Monadic version of iterateUntil
where at each iteration mutable version
of an array is available. However it is less efficient then the pure
alternative, because an intermediate array must be copied at each
iteration.
Since: 0.3.6