Copyright | (c) Andrey Mulik 2019 |
---|---|
License | BSD-style |
Maintainer | work.a.mulik@gmail.com |
Portability | non-portable (GHC extensions) |
Safe Haskell | Safe |
Language | Haskell2010 |
SDP.Indexed provides Indexed
and Freeze
classes.
Synopsis
- module SDP.Linear
- module SDP.Map
- class (Linear v e, Bordered v i, Map v i e) => Indexed v i e | v -> i, v -> e where
- type Indexed1 v i e = Indexed (v e) i e
- type Indexed2 v i e = Indexed (v i e) i e
- binaryContain :: (Linear v e, Bordered v i) => Compare e -> e -> v -> Bool
- class Monad m => Freeze m v' v | v' -> m where
- freeze :: v' -> m v
- unsafeFreeze :: v' -> m v
- type Freeze1 m v' v e = Freeze m (v' e) (v e)
Exports
module SDP.Linear
module SDP.Map
Indexed
class (Linear v e, Bordered v i, Map v i e) => Indexed v i e | v -> i, v -> e where Source #
Indexed
is class of ordered associative arrays with static bounds.
assoc :: (i, i) -> [(i, e)] -> v Source #
assoc bnds ascs
create new structure from list of associations, without
default element. Note that bnds
is ascs
bounds and may not match with
the result bounds (not always possible).
assoc' :: (i, i) -> e -> [(i, e)] -> v Source #
assoc' bnds def ascs
creates new structure from list of associations
with default element. Note that bnds
is ascs
bounds and may not match
with the result bounds (not always possible).
fromIndexed :: Indexed m j e => m -> v Source #
fromIndexed
converts this indexed structure to another one.
write' :: v -> i -> e -> v Source #
Safe index-based immutable writer.
accum :: (e -> e' -> e) -> v -> [(i, e')] -> v Source #
create a new structure from accum
f es ieses
elements selectively
updated by function f
and ies
associations list.
imap :: Map m j e => (i, i) -> m -> (i -> j) -> v Source #
imap
creates new indexed structure from old with reshaping.
update' :: v -> (e -> e) -> i -> v Source #
Update element by given function.
updates' :: v -> (i -> e -> e) -> v Source #
Create new structure from old by mapping with index.
Instances
Indexed [e] Int e Source # | |
Defined in SDP.Indexed assoc :: (Int, Int) -> [(Int, e)] -> [e] Source # assoc' :: (Int, Int) -> e -> [(Int, e)] -> [e] Source # fromIndexed :: Indexed m j e => m -> [e] Source # write' :: [e] -> Int -> e -> [e] Source # accum :: (e -> e' -> e) -> [e] -> [(Int, e')] -> [e] Source # imap :: Map m j e => (Int, Int) -> m -> (Int -> j) -> [e] Source # | |
Unboxed e => Indexed (SBytes# e) Int e Source # | |
Defined in SDP.Prim.SBytes assoc :: (Int, Int) -> [(Int, e)] -> SBytes# e Source # assoc' :: (Int, Int) -> e -> [(Int, e)] -> SBytes# e Source # fromIndexed :: Indexed m j e => m -> SBytes# e Source # write' :: SBytes# e -> Int -> e -> SBytes# e Source # accum :: (e -> e' -> e) -> SBytes# e -> [(Int, e')] -> SBytes# e Source # imap :: Map m j e => (Int, Int) -> m -> (Int -> j) -> SBytes# e Source # update' :: SBytes# e -> (e -> e) -> Int -> SBytes# e Source # updates' :: SBytes# e -> (Int -> e -> e) -> SBytes# e Source # | |
Indexed (SArray# e) Int e Source # | |
Defined in SDP.Prim.SArray assoc :: (Int, Int) -> [(Int, e)] -> SArray# e Source # assoc' :: (Int, Int) -> e -> [(Int, e)] -> SArray# e Source # fromIndexed :: Indexed m j e => m -> SArray# e Source # write' :: SArray# e -> Int -> e -> SArray# e Source # accum :: (e -> e' -> e) -> SArray# e -> [(Int, e')] -> SArray# e Source # imap :: Map m j e => (Int, Int) -> m -> (Int -> j) -> SArray# e Source # update' :: SArray# e -> (e -> e) -> Int -> SArray# e Source # updates' :: SArray# e -> (Int -> e -> e) -> SArray# e Source # | |
Indexed1 rep Int e => Indexed (AnyChunks rep e) Int e Source # | |
Defined in SDP.Templates.AnyChunks assoc :: (Int, Int) -> [(Int, e)] -> AnyChunks rep e Source # assoc' :: (Int, Int) -> e -> [(Int, e)] -> AnyChunks rep e Source # fromIndexed :: Indexed m j e => m -> AnyChunks rep e Source # write' :: AnyChunks rep e -> Int -> e -> AnyChunks rep e Source # accum :: (e -> e' -> e) -> AnyChunks rep e -> [(Int, e')] -> AnyChunks rep e Source # imap :: Map m j e => (Int, Int) -> m -> (Int -> j) -> AnyChunks rep e Source # update' :: AnyChunks rep e -> (e -> e) -> Int -> AnyChunks rep e Source # updates' :: AnyChunks rep e -> (Int -> e -> e) -> AnyChunks rep e Source # | |
(Index i, Indexed1 rep Int e) => Indexed (AnyBorder rep i e) i e Source # | |
Defined in SDP.Templates.AnyBorder assoc :: (i, i) -> [(i, e)] -> AnyBorder rep i e Source # assoc' :: (i, i) -> e -> [(i, e)] -> AnyBorder rep i e Source # fromIndexed :: Indexed m j e => m -> AnyBorder rep i e Source # write' :: AnyBorder rep i e -> i -> e -> AnyBorder rep i e Source # accum :: (e -> e' -> e) -> AnyBorder rep i e -> [(i, e')] -> AnyBorder rep i e Source # imap :: Map m j e => (i, i) -> m -> (i -> j) -> AnyBorder rep i e Source # update' :: AnyBorder rep i e -> (e -> e) -> i -> AnyBorder rep i e Source # updates' :: AnyBorder rep i e -> (i -> e -> e) -> AnyBorder rep i e Source # |
binaryContain :: (Linear v e, Bordered v i) => Compare e -> e -> v -> Bool Source #
binaryContain checks that sorted structure has equal element.
Freeze
class Monad m => Freeze m v' v | v' -> m where Source #
Service class of mutable to immutable conversions.
freeze
is a safe way to convert a mutable structure to a immutable.
freeze
should copy the old structure or ensure that it will not be used
after calling the procedure.
unsafeFreeze :: v' -> m v Source #
unsafeFreeze
is unsafe version of freeze
. unsafeFreeze
doesn't
guarantee that the structure will be copied or locked. It only guarantees
that if the old structure isn't used, no error will occur.
Instances
(Index i, Freeze m mut (rep e), Bordered1 rep Int e) => Freeze m mut (AnyBorder rep i e) Source # | |
Defined in SDP.Templates.AnyBorder | |
Freeze STM (TArray# e) (SArray# e) Source # | |
Freeze1 m mut imm e => Freeze m (mut e) (AnyChunks imm e) Source # | Creates one-chunk immutable stream, may be memory inefficient. |
Defined in SDP.Templates.AnyChunks | |
(Storable e, Unboxed e) => Freeze IO (Int, Ptr e) (SBytes# e) Source # | |
Storable e => Freeze IO (Int, Ptr e) (SArray# e) Source # | |
(MonadIO io, Unboxed e) => Freeze io (MIOBytes# io e) (SBytes# e) Source # | |
MonadIO io => Freeze io (MIOArray# io e) (SArray# e) Source # | |
(LinearM1 m mut e, Freeze1 m mut imm e) => Freeze m (AnyChunks mut e) (imm e) Source # | Creates new immutable structure using |
Defined in SDP.Templates.AnyChunks | |
Freeze1 m mut imm e => Freeze m (AnyChunks mut e) (AnyChunks imm e) Source # | |
(Index i, Freeze m (rep e) imm) => Freeze m (AnyBorder rep i e) imm Source # | |
Defined in SDP.Templates.AnyBorder | |
(Index i, Freeze1 m mut imm e) => Freeze m (AnyBorder mut i e) (AnyBorder imm i e) Source # | |
Unboxed e => Freeze (ST s) (STBytes# s e) (SBytes# e) Source # | |
Freeze (ST s) (STArray# s e) (SArray# e) Source # | |