| Safe Haskell | Trustworthy |
|---|---|
| Language | Haskell2010 |
Data.Vector.Unboxed.Mutable.Bit
Synopsis
- module Data.Bit
- unzip6 :: (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => MVector s (a, b, c, d, e, f) -> (MVector s a, MVector s b, MVector s c, MVector s d, MVector s e, MVector s f)
- zip6 :: (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => MVector s a -> MVector s b -> MVector s c -> MVector s d -> MVector s e -> MVector s f -> MVector s (a, b, c, d, e, f)
- unzip5 :: (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => MVector s (a, b, c, d, e) -> (MVector s a, MVector s b, MVector s c, MVector s d, MVector s e)
- zip5 :: (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => MVector s a -> MVector s b -> MVector s c -> MVector s d -> MVector s e -> MVector s (a, b, c, d, e)
- unzip4 :: (Unbox a, Unbox b, Unbox c, Unbox d) => MVector s (a, b, c, d) -> (MVector s a, MVector s b, MVector s c, MVector s d)
- zip4 :: (Unbox a, Unbox b, Unbox c, Unbox d) => MVector s a -> MVector s b -> MVector s c -> MVector s d -> MVector s (a, b, c, d)
- unzip3 :: (Unbox a, Unbox b, Unbox c) => MVector s (a, b, c) -> (MVector s a, MVector s b, MVector s c)
- zip3 :: (Unbox a, Unbox b, Unbox c) => MVector s a -> MVector s b -> MVector s c -> MVector s (a, b, c)
- unzip :: (Unbox a, Unbox b) => MVector s (a, b) -> (MVector s a, MVector s b)
- zip :: (Unbox a, Unbox b) => MVector s a -> MVector s b -> MVector s (a, b)
- nextPermutation :: (PrimMonad m, Ord e, Unbox e) => MVector (PrimState m) e -> m Bool
- unsafeMove :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
- move :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
- unsafeCopy :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
- copy :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
- set :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> a -> m ()
- unsafeSwap :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> Int -> m ()
- unsafeModify :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> (a -> a) -> Int -> m ()
- unsafeWrite :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> a -> m ()
- unsafeRead :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m a
- swap :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> Int -> m ()
- modify :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> (a -> a) -> Int -> m ()
- write :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> a -> m ()
- read :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m a
- clear :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> m ()
- unsafeGrow :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a)
- grow :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a)
- clone :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> m (MVector (PrimState m) a)
- replicateM :: (PrimMonad m, Unbox a) => Int -> m a -> m (MVector (PrimState m) a)
- replicate :: (PrimMonad m, Unbox a) => Int -> a -> m (MVector (PrimState m) a)
- unsafeNew :: (PrimMonad m, Unbox a) => Int -> m (MVector (PrimState m) a)
- new :: (PrimMonad m, Unbox a) => Int -> m (MVector (PrimState m) a)
- overlaps :: Unbox a => MVector s a -> MVector s a -> Bool
- unsafeTail :: Unbox a => MVector s a -> MVector s a
- unsafeInit :: Unbox a => MVector s a -> MVector s a
- unsafeDrop :: Unbox a => Int -> MVector s a -> MVector s a
- unsafeTake :: Unbox a => Int -> MVector s a -> MVector s a
- unsafeSlice :: Unbox a => Int -> Int -> MVector s a -> MVector s a
- tail :: Unbox a => MVector s a -> MVector s a
- init :: Unbox a => MVector s a -> MVector s a
- splitAt :: Unbox a => Int -> MVector s a -> (MVector s a, MVector s a)
- drop :: Unbox a => Int -> MVector s a -> MVector s a
- take :: Unbox a => Int -> MVector s a -> MVector s a
- slice :: Unbox a => Int -> Int -> MVector s a -> MVector s a
- null :: Unbox a => MVector s a -> Bool
- length :: Unbox a => MVector s a -> Int
- data family MVector s a :: Type
- data family Vector a :: Type
- type IOVector = MVector RealWorld
- type STVector s = MVector s
- class (Vector Vector a, MVector MVector a) => Unbox a
- wordSize :: Int
- wordLength :: MVector s Bit -> Int
- cloneFromWords :: PrimMonad m => Int -> MVector (PrimState m) Word -> m (MVector (PrimState m) Bit)
- cloneToWords :: PrimMonad m => MVector (PrimState m) Bit -> m (MVector (PrimState m) Word)
- readWord :: PrimMonad m => MVector (PrimState m) Bit -> Int -> m Word
- writeWord :: PrimMonad m => MVector (PrimState m) Bit -> Int -> Word -> m ()
- mapMInPlaceWithIndex :: PrimMonad m => (Int -> Word -> m Word) -> MVector (PrimState m) Bit -> m ()
- mapInPlaceWithIndex :: PrimMonad m => (Int -> Word -> Word) -> MVector (PrimState m) Bit -> m ()
- mapMInPlace :: PrimMonad m => (Word -> m Word) -> MVector (PrimState m) Bit -> m ()
- mapInPlace :: PrimMonad m => (Word -> Word) -> MVector (PrimState m) Bit -> m ()
- zipInPlace :: PrimMonad m => (Word -> Word -> Word) -> MVector (PrimState m) Bit -> Vector Bit -> m ()
- unionInPlace :: PrimMonad m => MVector (PrimState m) Bit -> Vector Bit -> m ()
- intersectionInPlace :: PrimMonad m => MVector (PrimState m) Bit -> Vector Bit -> m ()
- differenceInPlace :: PrimMonad m => MVector (PrimState m) Bit -> Vector Bit -> m ()
- symDiffInPlace :: PrimMonad m => MVector (PrimState m) Bit -> Vector Bit -> m ()
- invertInPlace :: PrimMonad m => MVector (PrimState m) Bit -> m ()
- selectBitsInPlace :: PrimMonad m => Vector Bit -> MVector (PrimState m) Bit -> m Int
- excludeBitsInPlace :: PrimMonad m => Vector Bit -> MVector (PrimState m) Bit -> m Int
- countBits :: PrimMonad m => MVector (PrimState m) Bit -> m Int
- listBits :: PrimMonad m => MVector (PrimState m) Bit -> m [Int]
- and :: PrimMonad m => MVector (PrimState m) Bit -> m Bool
- or :: PrimMonad m => MVector (PrimState m) Bit -> m Bool
- any :: PrimMonad m => (Bit -> Bool) -> MVector (PrimState m) Bit -> m Bool
- anyBits :: PrimMonad m => Bit -> MVector (PrimState m) Bit -> m Bool
- all :: PrimMonad m => (Bit -> Bool) -> MVector (PrimState m) Bit -> m Bool
- allBits :: PrimMonad m => Bit -> MVector (PrimState m) Bit -> m Bool
- reverseInPlace :: PrimMonad m => MVector (PrimState m) Bit -> m ()
Documentation
module Data.Bit
unzip6 :: (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => MVector s (a, b, c, d, e, f) -> (MVector s a, MVector s b, MVector s c, MVector s d, MVector s e, MVector s f) #
O(1) Unzip 6 vectors
zip6 :: (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => MVector s a -> MVector s b -> MVector s c -> MVector s d -> MVector s e -> MVector s f -> MVector s (a, b, c, d, e, f) #
O(1) Zip 6 vectors
unzip5 :: (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => MVector s (a, b, c, d, e) -> (MVector s a, MVector s b, MVector s c, MVector s d, MVector s e) #
O(1) Unzip 5 vectors
zip5 :: (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => MVector s a -> MVector s b -> MVector s c -> MVector s d -> MVector s e -> MVector s (a, b, c, d, e) #
O(1) Zip 5 vectors
unzip4 :: (Unbox a, Unbox b, Unbox c, Unbox d) => MVector s (a, b, c, d) -> (MVector s a, MVector s b, MVector s c, MVector s d) #
O(1) Unzip 4 vectors
zip4 :: (Unbox a, Unbox b, Unbox c, Unbox d) => MVector s a -> MVector s b -> MVector s c -> MVector s d -> MVector s (a, b, c, d) #
O(1) Zip 4 vectors
unzip3 :: (Unbox a, Unbox b, Unbox c) => MVector s (a, b, c) -> (MVector s a, MVector s b, MVector s c) #
O(1) Unzip 3 vectors
zip3 :: (Unbox a, Unbox b, Unbox c) => MVector s a -> MVector s b -> MVector s c -> MVector s (a, b, c) #
O(1) Zip 3 vectors
nextPermutation :: (PrimMonad m, Ord e, Unbox e) => MVector (PrimState m) e -> m Bool #
Compute the next (lexicographically) permutation of given vector in-place. Returns False when input is the last permtuation
Arguments
| :: (PrimMonad m, Unbox a) | |
| => MVector (PrimState m) a | target |
| -> MVector (PrimState m) a | source |
| -> m () |
Move the contents of a vector. The two vectors must have the same length, but this is not checked.
If the vectors do not overlap, then this is equivalent to unsafeCopy.
Otherwise, the copying is performed as if the source vector were
copied to a temporary vector and then the temporary vector was copied
to the target vector.
move :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> MVector (PrimState m) a -> m () #
Move the contents of a vector. The two vectors must have the same length.
If the vectors do not overlap, then this is equivalent to copy.
Otherwise, the copying is performed as if the source vector were
copied to a temporary vector and then the temporary vector was copied
to the target vector.
Arguments
| :: (PrimMonad m, Unbox a) | |
| => MVector (PrimState m) a | target |
| -> MVector (PrimState m) a | source |
| -> m () |
Copy a vector. The two vectors must have the same length and may not overlap. This is not checked.
Arguments
| :: (PrimMonad m, Unbox a) | |
| => MVector (PrimState m) a | target |
| -> MVector (PrimState m) a | source |
| -> m () |
Copy a vector. The two vectors must have the same length and may not overlap.
set :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> a -> m () #
Set all elements of the vector to the given value.
unsafeSwap :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> Int -> m () #
Swap the elements at the given positions. No bounds checks are performed.
unsafeModify :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> (a -> a) -> Int -> m () #
Modify the element at the given position. No bounds checks are performed.
unsafeWrite :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> a -> m () #
Replace the element at the given position. No bounds checks are performed.
unsafeRead :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m a #
Yield the element at the given position. No bounds checks are performed.
swap :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> Int -> m () #
Swap the elements at the given positions.
modify :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> (a -> a) -> Int -> m () #
Modify the element at the given position.
write :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> a -> m () #
Replace the element at the given position.
read :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m a #
Yield the element at the given position.
clear :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> m () #
Reset all elements of the vector to some undefined value, clearing all references to external objects. This is usually a noop for unboxed vectors.
unsafeGrow :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a) #
Grow a vector by the given number of elements. The number must be positive but this is not checked.
grow :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a) #
Grow a vector by the given number of elements. The number must be positive.
clone :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> m (MVector (PrimState m) a) #
Create a copy of a mutable vector.
replicateM :: (PrimMonad m, Unbox a) => Int -> m a -> m (MVector (PrimState m) a) #
Create a mutable vector of the given length (0 if the length is negative) and fill it with values produced by repeatedly executing the monadic action.
replicate :: (PrimMonad m, Unbox a) => Int -> a -> m (MVector (PrimState m) a) #
Create a mutable vector of the given length (0 if the length is negative) and fill it with an initial value.
unsafeNew :: (PrimMonad m, Unbox a) => Int -> m (MVector (PrimState m) a) #
Create a mutable vector of the given length. The memory is not initialized.
new :: (PrimMonad m, Unbox a) => Int -> m (MVector (PrimState m) a) #
Create a mutable vector of the given length.
unsafeTail :: Unbox a => MVector s a -> MVector s a #
unsafeInit :: Unbox a => MVector s a -> MVector s a #
Yield a part of the mutable vector without copying it. No bounds checks are performed.
slice :: Unbox a => Int -> Int -> MVector s a -> MVector s a #
Yield a part of the mutable vector without copying it.
data family MVector s a :: Type #
Instances
data family Vector a :: Type #
Instances
class (Vector Vector a, MVector MVector a) => Unbox a #
Instances
wordLength :: MVector s Bit -> Int Source #
Get the length of the vector that would be created by cloneToWords
cloneFromWords :: PrimMonad m => Int -> MVector (PrimState m) Word -> m (MVector (PrimState m) Bit) Source #
Clone a specified number of bits from a vector of words into a new vector of bits (interpreting the words in little-endian order, as described at indexWord). If there are not enough words for the number of bits requested, the vector will be zero-padded.
cloneToWords :: PrimMonad m => MVector (PrimState m) Bit -> m (MVector (PrimState m) Word) Source #
clone a vector of bits to a new unboxed vector of words. If the bits don't completely fill the words, the last word will be zero-padded.
readWord :: PrimMonad m => MVector (PrimState m) Bit -> Int -> m Word Source #
read a word at the given bit offset in little-endian order (i.e., the LSB will correspond to the bit at the given address, the 2's bit will correspond to the address + 1, etc.). If the offset is such that the word extends past the end of the vector, the result is zero-padded.
writeWord :: PrimMonad m => MVector (PrimState m) Bit -> Int -> Word -> m () Source #
write a word at the given bit offset in little-endian order (i.e., the LSB will correspond to the bit at the given address, the 2's bit will correspond to the address + 1, etc.). If the offset is such that the word extends past the end of the vector, the word is truncated and as many low-order bits as possible are written.
mapMInPlaceWithIndex :: PrimMonad m => (Int -> Word -> m Word) -> MVector (PrimState m) Bit -> m () Source #
Map a function over a bit vector one Word at a time (wordSize bits at a time). The function will be passed the bit index (which will always be wordSize-aligned) and the current value of the corresponding word. The returned word will be written back to the vector. If there is a partial word at the end of the vector, it will be zero-padded when passed to the function and truncated when the result is written back to the array.
mapInPlaceWithIndex :: PrimMonad m => (Int -> Word -> Word) -> MVector (PrimState m) Bit -> m () Source #
mapMInPlace :: PrimMonad m => (Word -> m Word) -> MVector (PrimState m) Bit -> m () Source #
Same as mapMInPlaceWithIndex but without the index.
zipInPlace :: PrimMonad m => (Word -> Word -> Word) -> MVector (PrimState m) Bit -> Vector Bit -> m () Source #
invertInPlace :: PrimMonad m => MVector (PrimState m) Bit -> m () Source #
Flip every bit in the given vector
countBits :: PrimMonad m => MVector (PrimState m) Bit -> m Int Source #
return the number of ones in a bit vector
and :: PrimMonad m => MVector (PrimState m) Bit -> m Bool Source #
Returns True if all bits in the vector are set