Copyright | (c) Andrey Mulik 2019 |
---|---|
License | BSD-style |
Maintainer | work.a.mulik@gmail.com |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
SDP.Vector
provides Vector
- immutable lazy boxed vector.
Synopsis
- module SDP.Indexed
- module SDP.Sort
- module SDP.Scan
- data Vector a
Exports
module SDP.Indexed
module SDP.Sort
module SDP.Scan
Vector
Boxed vectors, supporting efficient slicing.
Instances
Monad Vector | |
Functor Vector | |
MonadFix Vector | Instance has same semantics as one for lists Since: vector-0.12.2.0 |
Defined in Data.Vector | |
MonadFail Vector | Since: vector-0.12.1.0 |
Defined in Data.Vector | |
Applicative Vector | |
Foldable Vector | |
Defined in Data.Vector fold :: Monoid m => Vector m -> m # foldMap :: Monoid m => (a -> m) -> Vector a -> m # foldMap' :: Monoid m => (a -> m) -> Vector a -> m # foldr :: (a -> b -> b) -> b -> Vector a -> b # foldr' :: (a -> b -> b) -> b -> Vector a -> b # foldl :: (b -> a -> b) -> b -> Vector a -> b # foldl' :: (b -> a -> b) -> b -> Vector a -> b # foldr1 :: (a -> a -> a) -> Vector a -> a # foldl1 :: (a -> a -> a) -> Vector a -> a # elem :: Eq a => a -> Vector a -> Bool # maximum :: Ord a => Vector a -> a # minimum :: Ord a => Vector a -> a # | |
Traversable Vector | |
Eq1 Vector | |
Ord1 Vector | |
Defined in Data.Vector | |
Read1 Vector | |
Defined in Data.Vector | |
Show1 Vector | |
MonadZip Vector | |
Alternative Vector | |
MonadPlus Vector | |
NFData1 Vector | Since: vector-0.12.1.0 |
Defined in Data.Vector | |
Zip Vector Source # | |
Defined in SDP.Vector zap :: Vector (a -> b) -> Vector a -> Vector b # all2 :: (a -> b -> Bool) -> Vector a -> Vector b -> Bool # all3 :: (a -> b -> c -> Bool) -> Vector a -> Vector b -> Vector c -> Bool # all4 :: (a -> b -> c -> d -> Bool) -> Vector a -> Vector b -> Vector c -> Vector d -> Bool # all5 :: (a -> b -> c -> d -> e -> Bool) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Bool # all6 :: (a -> b -> c -> d -> e -> f -> Bool) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f -> Bool # any2 :: (a -> b -> Bool) -> Vector a -> Vector b -> Bool # any3 :: (a -> b -> c -> Bool) -> Vector a -> Vector b -> Vector c -> Bool # any4 :: (a -> b -> c -> d -> Bool) -> Vector a -> Vector b -> Vector c -> Vector d -> Bool # any5 :: (a -> b -> c -> d -> e -> Bool) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Bool # any6 :: (a -> b -> c -> d -> e -> f -> Bool) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f -> Bool # zip :: Vector a -> Vector b -> Vector (a, b) # zip3 :: Vector a -> Vector b -> Vector c -> Vector (a, b, c) # zip4 :: Vector a -> Vector b -> Vector c -> Vector d -> Vector (a, b, c, d) # zip5 :: Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector (a, b, c, d, e) # zip6 :: Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f -> Vector (a, b, c, d, e, f) # zipWith :: (a -> b -> c) -> Vector a -> Vector b -> Vector c # zipWith3 :: (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d # zipWith4 :: (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e # zipWith5 :: (a -> b -> c -> d -> e -> f) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f # zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f -> Vector g # | |
Vector Vector a | |
Defined in Data.Vector basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) a -> m (Vector a) # basicUnsafeThaw :: PrimMonad m => Vector a -> m (Mutable Vector (PrimState m) a) # basicLength :: Vector a -> Int # basicUnsafeSlice :: Int -> Int -> Vector a -> Vector a # basicUnsafeIndexM :: Monad m => Vector a -> Int -> m a # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) a -> Vector a -> m () # | |
MonadIO io => Thaw io (Vector e) (MIOUnlist io e) Source # | |
Defined in SDP.Vector | |
MonadIO io => Thaw io (Vector e) (MIOArray# io e) Source # | |
Defined in SDP.Vector | |
MonadIO io => Freeze io (MIOUnlist io e) (Vector e) Source # | |
Defined in SDP.Vector | |
MonadIO io => Freeze io (MIOArray# io e) (Vector e) Source # | |
Defined in SDP.Vector | |
IsList (Vector a) | |
Eq a => Eq (Vector a) | |
Data a => Data (Vector a) | |
Defined in Data.Vector gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector a -> c (Vector a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector a) # toConstr :: Vector a -> Constr # dataTypeOf :: Vector a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector a)) # gmapT :: (forall b. Data b => b -> b) -> Vector a -> Vector a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQ :: (forall d. Data d => d -> u) -> Vector a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # | |
Ord a => Ord (Vector a) | |
Defined in Data.Vector | |
Read a => Read (Vector a) | |
Show a => Show (Vector a) | |
Semigroup (Vector a) | |
Monoid (Vector a) | |
NFData a => NFData (Vector a) | |
Defined in Data.Vector | |
Nullable (Vector e) Source # | |
Estimate (Vector e) Source # | |
Defined in SDP.Vector (<.=>) :: Vector e -> Int -> Ordering # (<==>) :: Compare (Vector e) # (.==) :: Vector e -> Int -> Bool # (./=) :: Vector e -> Int -> Bool # (.<=) :: Vector e -> Int -> Bool # (.>=) :: Vector e -> Int -> Bool # (.<) :: Vector e -> Int -> Bool # (.>) :: Vector e -> Int -> Bool # (.<.) :: Vector e -> Vector e -> Bool # (.>.) :: Vector e -> Vector e -> Bool # (.<=.) :: Vector e -> Vector e -> Bool # (.>=.) :: Vector e -> Vector e -> Bool # | |
Scan (Vector e) e Source # | |
Defined in SDP.Vector | |
Bordered (Vector e) Int Source # | |
Defined in SDP.Vector | |
Linear (Vector e) e Source # | |
Defined in SDP.Vector uncons :: Vector e -> (e, Vector e) # uncons' :: Vector e -> Maybe (e, Vector e) # toHead :: e -> Vector e -> Vector e # tail :: Vector e -> Vector e # unsnoc :: Vector e -> (Vector e, e) # unsnoc' :: Vector e -> Maybe (Vector e, e) # toLast :: Vector e -> e -> Vector e # init :: Vector e -> Vector e # (++) :: Vector e -> Vector e -> Vector e # replicate :: Int -> e -> Vector e # fromListN :: Int -> [e] -> Vector e # fromFoldable :: Foldable f => f e -> Vector e # (!^) :: Vector e -> Int -> e # write :: Vector e -> Int -> e -> Vector e # concat :: Foldable f => f (Vector e) -> Vector e # concatMap :: Foldable f => (a -> Vector e) -> f a -> Vector e # intersperse :: e -> Vector e -> Vector e # filter :: (e -> Bool) -> Vector e -> Vector e # except :: (e -> Bool) -> Vector e -> Vector e # partition :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # partitions :: Foldable f => f (e -> Bool) -> Vector e -> [Vector e] # select :: (e -> Maybe a) -> Vector e -> [a] # select' :: (t e ~ Vector e, Linear1 t a) => (e -> Maybe a) -> Vector e -> t a # extract :: (e -> Maybe a) -> Vector e -> ([a], Vector e) # extract' :: (t e ~ Vector e, Linear1 t a) => (e -> Maybe a) -> Vector e -> (t a, Vector e) # selects :: Foldable f => f (e -> Maybe a) -> Vector e -> ([[a]], Vector e) # selects' :: (Foldable f, t e ~ Vector e, Linear1 t a) => f (e -> Maybe a) -> Vector e -> ([t a], Vector e) # isSubseqOf :: Vector e -> Vector e -> Bool # reverse :: Vector e -> Vector e # force :: Vector e -> Vector e # subsequences :: Vector e -> [Vector e] # iterate :: Int -> (e -> e) -> e -> Vector e # nubBy :: Equal e -> Vector e -> Vector e # ofoldr :: (Int -> e -> b -> b) -> b -> Vector e -> b # ofoldl :: (Int -> b -> e -> b) -> b -> Vector e -> b # ofoldr' :: (Int -> e -> b -> b) -> b -> Vector e -> b # ofoldl' :: (Int -> b -> e -> b) -> b -> Vector e -> b # o_foldr :: (e -> b -> b) -> b -> Vector e -> b # o_foldl :: (b -> e -> b) -> b -> Vector e -> b # | |
Split (Vector e) e Source # | |
Defined in SDP.Vector take :: Int -> Vector e -> Vector e # drop :: Int -> Vector e -> Vector e # keep :: Int -> Vector e -> Vector e # sans :: Int -> Vector e -> Vector e # save :: Int -> Vector e -> Vector e # skip :: Int -> Vector e -> Vector e # split :: Int -> Vector e -> (Vector e, Vector e) # divide :: Int -> Vector e -> (Vector e, Vector e) # splits :: Foldable f => f Int -> Vector e -> [Vector e] # divides :: Foldable f => f Int -> Vector e -> [Vector e] # parts :: Foldable f => f Int -> Vector e -> [Vector e] # chunks :: Int -> Vector e -> [Vector e] # splitBy :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # divideBy :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # splitsBy :: (e -> Bool) -> Vector e -> [Vector e] # splitsOn :: Vector e -> Vector e -> [Vector e] # replaceBy :: Vector e -> Vector e -> Vector e -> Vector e # removeAll :: Vector e -> Vector e -> Vector e # combo :: Equal e -> Vector e -> Int # justifyL :: Int -> e -> Vector e -> Vector e # justifyR :: Int -> e -> Vector e -> Vector e # each :: Int -> Vector e -> Vector e # eachFrom :: Int -> Int -> Vector e -> Vector e # isPrefixOf :: Vector e -> Vector e -> Bool # isSuffixOf :: Vector e -> Vector e -> Bool # isInfixOf :: Vector e -> Vector e -> Bool # prefix :: (e -> Bool) -> Vector e -> Int # suffix :: (e -> Bool) -> Vector e -> Int # infixes :: Vector e -> Vector e -> [Int] # dropSide :: (e -> Bool) -> Vector e -> Vector e # takeWhile :: (e -> Bool) -> Vector e -> Vector e # dropWhile :: (e -> Bool) -> Vector e -> Vector e # takeEnd :: (e -> Bool) -> Vector e -> Vector e # dropEnd :: (e -> Bool) -> Vector e -> Vector e # spanl :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # breakl :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # spanr :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # breakr :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # selectWhile :: (e -> Maybe a) -> Vector e -> [a] # selectEnd :: (e -> Maybe a) -> Vector e -> [a] # extractWhile :: (e -> Maybe a) -> Vector e -> ([a], Vector e) # extractEnd :: (e -> Maybe a) -> Vector e -> (Vector e, [a]) # selectWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> Vector e -> t a # selectEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> Vector e -> t a # extractWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> Vector e -> (t a, Vector e) # extractEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> Vector e -> (Vector e, t a) # | |
Sort (Vector e) e Source # | |
Indexed (Vector e) Int e Source # | |
Defined in SDP.Vector assoc :: (Int, Int) -> [(Int, e)] -> Vector e # assoc' :: (Int, Int) -> e -> [(Int, e)] -> Vector e # fromIndexed :: Indexed m j e => m -> Vector e # write' :: Vector e -> Int -> e -> Vector e # accum :: (e -> e' -> e) -> Vector e -> [(Int, e')] -> Vector e # imap :: Map m j e => (Int, Int) -> m -> (Int -> j) -> Vector e # | |
Map (Vector e) Int e Source # | |
Defined in SDP.Vector assocs :: Vector e -> [(Int, e)] # toMap :: [(Int, e)] -> Vector e # toMap' :: e -> [(Int, e)] -> Vector e # insert' :: Int -> e -> Vector e -> Vector e # delete' :: Int -> Vector e -> Vector e # member' :: Int -> Vector e -> Bool # (//) :: Vector e -> [(Int, e)] -> Vector e # (.!) :: Vector e -> Int -> e # (!?) :: Vector e -> Int -> Maybe e # filter' :: (Int -> e -> Bool) -> Vector e -> Vector e # union' :: (e -> e -> e) -> Vector e -> Vector e -> Vector e # difference' :: (e -> e -> Maybe e) -> Vector e -> Vector e -> Vector e # intersection' :: (e -> e -> e) -> Vector e -> Vector e -> Vector e # update :: Vector e -> (Int -> e -> e) -> Vector e # lookupLT' :: Int -> Vector e -> Maybe (Int, e) # lookupGT' :: Int -> Vector e -> Maybe (Int, e) # lookupLE' :: Int -> Vector e -> Maybe (Int, e) # lookupGE' :: Int -> Vector e -> Maybe (Int, e) # (.$) :: (e -> Bool) -> Vector e -> Maybe Int # (*$) :: (e -> Bool) -> Vector e -> [Int] # kfoldr :: (Int -> e -> b -> b) -> b -> Vector e -> b # kfoldl :: (Int -> b -> e -> b) -> b -> Vector e -> b # | |
Thaw (ST s) (Vector e) (STUnlist s e) Source # | |
Thaw (ST s) (Vector e) (STArray# s e) Source # | |
Freeze (ST s) (STUnlist s e) (Vector e) Source # | |
Freeze (ST s) (STArray# s e) (Vector e) Source # | |
type Mutable Vector | |
Defined in Data.Vector | |
type Item (Vector a) | |
Defined in Data.Vector |
Orphan instances
Zip Vector Source # | |
zap :: Vector (a -> b) -> Vector a -> Vector b # all2 :: (a -> b -> Bool) -> Vector a -> Vector b -> Bool # all3 :: (a -> b -> c -> Bool) -> Vector a -> Vector b -> Vector c -> Bool # all4 :: (a -> b -> c -> d -> Bool) -> Vector a -> Vector b -> Vector c -> Vector d -> Bool # all5 :: (a -> b -> c -> d -> e -> Bool) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Bool # all6 :: (a -> b -> c -> d -> e -> f -> Bool) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f -> Bool # any2 :: (a -> b -> Bool) -> Vector a -> Vector b -> Bool # any3 :: (a -> b -> c -> Bool) -> Vector a -> Vector b -> Vector c -> Bool # any4 :: (a -> b -> c -> d -> Bool) -> Vector a -> Vector b -> Vector c -> Vector d -> Bool # any5 :: (a -> b -> c -> d -> e -> Bool) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Bool # any6 :: (a -> b -> c -> d -> e -> f -> Bool) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f -> Bool # zip :: Vector a -> Vector b -> Vector (a, b) # zip3 :: Vector a -> Vector b -> Vector c -> Vector (a, b, c) # zip4 :: Vector a -> Vector b -> Vector c -> Vector d -> Vector (a, b, c, d) # zip5 :: Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector (a, b, c, d, e) # zip6 :: Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f -> Vector (a, b, c, d, e, f) # zipWith :: (a -> b -> c) -> Vector a -> Vector b -> Vector c # zipWith3 :: (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d # zipWith4 :: (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e # zipWith5 :: (a -> b -> c -> d -> e -> f) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f # zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f -> Vector g # | |
MonadIO io => Thaw io (Vector e) (MIOUnlist io e) Source # | |
MonadIO io => Thaw io (Vector e) (MIOArray# io e) Source # | |
MonadIO io => Freeze io (MIOUnlist io e) (Vector e) Source # | |
MonadIO io => Freeze io (MIOArray# io e) (Vector e) Source # | |
Nullable (Vector e) Source # | |
Estimate (Vector e) Source # | |
(<.=>) :: Vector e -> Int -> Ordering # (<==>) :: Compare (Vector e) # (.==) :: Vector e -> Int -> Bool # (./=) :: Vector e -> Int -> Bool # (.<=) :: Vector e -> Int -> Bool # (.>=) :: Vector e -> Int -> Bool # (.<) :: Vector e -> Int -> Bool # (.>) :: Vector e -> Int -> Bool # (.<.) :: Vector e -> Vector e -> Bool # (.>.) :: Vector e -> Vector e -> Bool # (.<=.) :: Vector e -> Vector e -> Bool # (.>=.) :: Vector e -> Vector e -> Bool # | |
Scan (Vector e) e Source # | |
Bordered (Vector e) Int Source # | |
Linear (Vector e) e Source # | |
uncons :: Vector e -> (e, Vector e) # uncons' :: Vector e -> Maybe (e, Vector e) # toHead :: e -> Vector e -> Vector e # tail :: Vector e -> Vector e # unsnoc :: Vector e -> (Vector e, e) # unsnoc' :: Vector e -> Maybe (Vector e, e) # toLast :: Vector e -> e -> Vector e # init :: Vector e -> Vector e # (++) :: Vector e -> Vector e -> Vector e # replicate :: Int -> e -> Vector e # fromListN :: Int -> [e] -> Vector e # fromFoldable :: Foldable f => f e -> Vector e # (!^) :: Vector e -> Int -> e # write :: Vector e -> Int -> e -> Vector e # concat :: Foldable f => f (Vector e) -> Vector e # concatMap :: Foldable f => (a -> Vector e) -> f a -> Vector e # intersperse :: e -> Vector e -> Vector e # filter :: (e -> Bool) -> Vector e -> Vector e # except :: (e -> Bool) -> Vector e -> Vector e # partition :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # partitions :: Foldable f => f (e -> Bool) -> Vector e -> [Vector e] # select :: (e -> Maybe a) -> Vector e -> [a] # select' :: (t e ~ Vector e, Linear1 t a) => (e -> Maybe a) -> Vector e -> t a # extract :: (e -> Maybe a) -> Vector e -> ([a], Vector e) # extract' :: (t e ~ Vector e, Linear1 t a) => (e -> Maybe a) -> Vector e -> (t a, Vector e) # selects :: Foldable f => f (e -> Maybe a) -> Vector e -> ([[a]], Vector e) # selects' :: (Foldable f, t e ~ Vector e, Linear1 t a) => f (e -> Maybe a) -> Vector e -> ([t a], Vector e) # isSubseqOf :: Vector e -> Vector e -> Bool # reverse :: Vector e -> Vector e # force :: Vector e -> Vector e # subsequences :: Vector e -> [Vector e] # iterate :: Int -> (e -> e) -> e -> Vector e # nubBy :: Equal e -> Vector e -> Vector e # ofoldr :: (Int -> e -> b -> b) -> b -> Vector e -> b # ofoldl :: (Int -> b -> e -> b) -> b -> Vector e -> b # ofoldr' :: (Int -> e -> b -> b) -> b -> Vector e -> b # ofoldl' :: (Int -> b -> e -> b) -> b -> Vector e -> b # o_foldr :: (e -> b -> b) -> b -> Vector e -> b # o_foldl :: (b -> e -> b) -> b -> Vector e -> b # | |
Split (Vector e) e Source # | |
take :: Int -> Vector e -> Vector e # drop :: Int -> Vector e -> Vector e # keep :: Int -> Vector e -> Vector e # sans :: Int -> Vector e -> Vector e # save :: Int -> Vector e -> Vector e # skip :: Int -> Vector e -> Vector e # split :: Int -> Vector e -> (Vector e, Vector e) # divide :: Int -> Vector e -> (Vector e, Vector e) # splits :: Foldable f => f Int -> Vector e -> [Vector e] # divides :: Foldable f => f Int -> Vector e -> [Vector e] # parts :: Foldable f => f Int -> Vector e -> [Vector e] # chunks :: Int -> Vector e -> [Vector e] # splitBy :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # divideBy :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # splitsBy :: (e -> Bool) -> Vector e -> [Vector e] # splitsOn :: Vector e -> Vector e -> [Vector e] # replaceBy :: Vector e -> Vector e -> Vector e -> Vector e # removeAll :: Vector e -> Vector e -> Vector e # combo :: Equal e -> Vector e -> Int # justifyL :: Int -> e -> Vector e -> Vector e # justifyR :: Int -> e -> Vector e -> Vector e # each :: Int -> Vector e -> Vector e # eachFrom :: Int -> Int -> Vector e -> Vector e # isPrefixOf :: Vector e -> Vector e -> Bool # isSuffixOf :: Vector e -> Vector e -> Bool # isInfixOf :: Vector e -> Vector e -> Bool # prefix :: (e -> Bool) -> Vector e -> Int # suffix :: (e -> Bool) -> Vector e -> Int # infixes :: Vector e -> Vector e -> [Int] # dropSide :: (e -> Bool) -> Vector e -> Vector e # takeWhile :: (e -> Bool) -> Vector e -> Vector e # dropWhile :: (e -> Bool) -> Vector e -> Vector e # takeEnd :: (e -> Bool) -> Vector e -> Vector e # dropEnd :: (e -> Bool) -> Vector e -> Vector e # spanl :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # breakl :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # spanr :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # breakr :: (e -> Bool) -> Vector e -> (Vector e, Vector e) # selectWhile :: (e -> Maybe a) -> Vector e -> [a] # selectEnd :: (e -> Maybe a) -> Vector e -> [a] # extractWhile :: (e -> Maybe a) -> Vector e -> ([a], Vector e) # extractEnd :: (e -> Maybe a) -> Vector e -> (Vector e, [a]) # selectWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> Vector e -> t a # selectEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> Vector e -> t a # extractWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> Vector e -> (t a, Vector e) # extractEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> Vector e -> (Vector e, t a) # | |
Sort (Vector e) e Source # | |
Indexed (Vector e) Int e Source # | |
assoc :: (Int, Int) -> [(Int, e)] -> Vector e # assoc' :: (Int, Int) -> e -> [(Int, e)] -> Vector e # fromIndexed :: Indexed m j e => m -> Vector e # write' :: Vector e -> Int -> e -> Vector e # accum :: (e -> e' -> e) -> Vector e -> [(Int, e')] -> Vector e # imap :: Map m j e => (Int, Int) -> m -> (Int -> j) -> Vector e # | |
Map (Vector e) Int e Source # | |
assocs :: Vector e -> [(Int, e)] # toMap :: [(Int, e)] -> Vector e # toMap' :: e -> [(Int, e)] -> Vector e # insert' :: Int -> e -> Vector e -> Vector e # delete' :: Int -> Vector e -> Vector e # member' :: Int -> Vector e -> Bool # (//) :: Vector e -> [(Int, e)] -> Vector e # (.!) :: Vector e -> Int -> e # (!?) :: Vector e -> Int -> Maybe e # filter' :: (Int -> e -> Bool) -> Vector e -> Vector e # union' :: (e -> e -> e) -> Vector e -> Vector e -> Vector e # difference' :: (e -> e -> Maybe e) -> Vector e -> Vector e -> Vector e # intersection' :: (e -> e -> e) -> Vector e -> Vector e -> Vector e # update :: Vector e -> (Int -> e -> e) -> Vector e # lookupLT' :: Int -> Vector e -> Maybe (Int, e) # lookupGT' :: Int -> Vector e -> Maybe (Int, e) # lookupLE' :: Int -> Vector e -> Maybe (Int, e) # lookupGE' :: Int -> Vector e -> Maybe (Int, e) # (.$) :: (e -> Bool) -> Vector e -> Maybe Int # (*$) :: (e -> Bool) -> Vector e -> [Int] # kfoldr :: (Int -> e -> b -> b) -> b -> Vector e -> b # kfoldl :: (Int -> b -> e -> b) -> b -> Vector e -> b # | |
Thaw (ST s) (Vector e) (STUnlist s e) Source # | |
Thaw (ST s) (Vector e) (STArray# s e) Source # | |
Freeze (ST s) (STUnlist s e) (Vector e) Source # | |
Freeze (ST s) (STArray# s e) (Vector e) Source # | |