sdp-0.2: Simple Data Processing
Copyright(c) Andrey Mulik 2019
LicenseBSD-style
Maintainerwork.a.mulik@gmail.com
Portabilitynon-portable (GHC extensions)
Safe HaskellSafe
LanguageHaskell2010

SDP.IndexedM

Description

SDP.IndexedM provides IndexedM and Thaw classes.

Synopsis

Exports

module SDP.MapM

IndexedM

class (LinearM m v e, BorderedM m v i, MapM m v i e) => IndexedM m v i e where Source #

Class for work with mutable indexed structures.

Minimal complete definition

fromIndexed', fromIndexedM

Methods

fromAssocs :: (i, i) -> [(i, e)] -> m v Source #

fromAssocs bnds ascs creates 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).

fromAssocs' :: (i, i) -> e -> [(i, e)] -> m v Source #

fromAssocs' bnds defvalue 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).

writeM' :: v -> i -> e -> m () Source #

writeM map key e writes element e to key position safely (if key is out of map range, do nothing). The writeM function is intended to overwrite only existing values, so its behavior is identical for structures with both static and dynamic boundaries.

swapM' :: v -> i -> i -> m () Source #

Just swap two elements.

fromIndexed' :: Indexed v' j e => v' -> m v Source #

fromIndexed' is overloaded version of thaw.

fromIndexedM :: IndexedM m v' j e => v' -> m v Source #

fromIndexed converts one mutable structure to other.

reshaped :: IndexedM m v' j e => (i, i) -> v' -> (i -> j) -> m v Source #

reshaped creates new indexed structure from old with reshaping function.

fromAccum :: (e -> e' -> e) -> v -> [(i, e')] -> m v Source #

fromAccum f es ies create a new structure from es elements selectively updated by function f and ies associations list.

updateM' :: v -> (e -> e) -> i -> m () Source #

Update element by given function.

Instances

Instances details
IndexedM STM (TArray# e) Int e Source # 
Instance details

Defined in SDP.Prim.TArray

Methods

fromAssocs :: (Int, Int) -> [(Int, e)] -> STM (TArray# e) Source #

fromAssocs' :: (Int, Int) -> e -> [(Int, e)] -> STM (TArray# e) Source #

writeM' :: TArray# e -> Int -> e -> STM () Source #

swapM' :: TArray# e -> Int -> Int -> STM () Source #

fromIndexed' :: Indexed v' j e => v' -> STM (TArray# e) Source #

fromIndexedM :: IndexedM STM v' j e => v' -> STM (TArray# e) Source #

reshaped :: IndexedM STM v' j e => (Int, Int) -> v' -> (Int -> j) -> STM (TArray# e) Source #

fromAccum :: (e -> e' -> e) -> TArray# e -> [(Int, e')] -> STM (TArray# e) Source #

updateM' :: TArray# e -> (e -> e) -> Int -> STM () Source #

(MonadIO io, Unboxed e) => IndexedM io (MIOBytes# io e) Int e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

fromAssocs :: (Int, Int) -> [(Int, e)] -> io (MIOBytes# io e) Source #

fromAssocs' :: (Int, Int) -> e -> [(Int, e)] -> io (MIOBytes# io e) Source #

writeM' :: MIOBytes# io e -> Int -> e -> io () Source #

swapM' :: MIOBytes# io e -> Int -> Int -> io () Source #

fromIndexed' :: Indexed v' j e => v' -> io (MIOBytes# io e) Source #

fromIndexedM :: IndexedM io v' j e => v' -> io (MIOBytes# io e) Source #

reshaped :: IndexedM io v' j e => (Int, Int) -> v' -> (Int -> j) -> io (MIOBytes# io e) Source #

fromAccum :: (e -> e' -> e) -> MIOBytes# io e -> [(Int, e')] -> io (MIOBytes# io e) Source #

updateM' :: MIOBytes# io e -> (e -> e) -> Int -> io () Source #

MonadIO io => IndexedM io (MIOArray# io e) Int e Source # 
Instance details

Defined in SDP.Prim.SArray

Methods

fromAssocs :: (Int, Int) -> [(Int, e)] -> io (MIOArray# io e) Source #

fromAssocs' :: (Int, Int) -> e -> [(Int, e)] -> io (MIOArray# io e) Source #

writeM' :: MIOArray# io e -> Int -> e -> io () Source #

swapM' :: MIOArray# io e -> Int -> Int -> io () Source #

fromIndexed' :: Indexed v' j e => v' -> io (MIOArray# io e) Source #

fromIndexedM :: IndexedM io v' j e => v' -> io (MIOArray# io e) Source #

reshaped :: IndexedM io v' j e => (Int, Int) -> v' -> (Int -> j) -> io (MIOArray# io e) Source #

fromAccum :: (e -> e' -> e) -> MIOArray# io e -> [(Int, e')] -> io (MIOArray# io e) Source #

updateM' :: MIOArray# io e -> (e -> e) -> Int -> io () Source #

(SplitM1 m rep e, IndexedM1 m rep Int e) => IndexedM m (AnyChunks rep e) Int e Source # 
Instance details

Defined in SDP.Templates.AnyChunks

Methods

fromAssocs :: (Int, Int) -> [(Int, e)] -> m (AnyChunks rep e) Source #

fromAssocs' :: (Int, Int) -> e -> [(Int, e)] -> m (AnyChunks rep e) Source #

writeM' :: AnyChunks rep e -> Int -> e -> m () Source #

swapM' :: AnyChunks rep e -> Int -> Int -> m () Source #

fromIndexed' :: Indexed v' j e => v' -> m (AnyChunks rep e) Source #

fromIndexedM :: IndexedM m v' j e => v' -> m (AnyChunks rep e) Source #

reshaped :: IndexedM m v' j e => (Int, Int) -> v' -> (Int -> j) -> m (AnyChunks rep e) Source #

fromAccum :: (e -> e' -> e) -> AnyChunks rep e -> [(Int, e')] -> m (AnyChunks rep e) Source #

updateM' :: AnyChunks rep e -> (e -> e) -> Int -> m () Source #

(Index i, IndexedM1 m rep Int e) => IndexedM m (AnyBorder rep i e) i e Source # 
Instance details

Defined in SDP.Templates.AnyBorder

Methods

fromAssocs :: (i, i) -> [(i, e)] -> m (AnyBorder rep i e) Source #

fromAssocs' :: (i, i) -> e -> [(i, e)] -> m (AnyBorder rep i e) Source #

writeM' :: AnyBorder rep i e -> i -> e -> m () Source #

swapM' :: AnyBorder rep i e -> i -> i -> m () Source #

fromIndexed' :: Indexed v' j e => v' -> m (AnyBorder rep i e) Source #

fromIndexedM :: IndexedM m v' j e => v' -> m (AnyBorder rep i e) Source #

reshaped :: IndexedM m v' j e => (i, i) -> v' -> (i -> j) -> m (AnyBorder rep i e) Source #

fromAccum :: (e -> e' -> e) -> AnyBorder rep i e -> [(i, e')] -> m (AnyBorder rep i e) Source #

updateM' :: AnyBorder rep i e -> (e -> e) -> i -> m () Source #

Unboxed e => IndexedM (ST s) (STBytes# s e) Int e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

fromAssocs :: (Int, Int) -> [(Int, e)] -> ST s (STBytes# s e) Source #

fromAssocs' :: (Int, Int) -> e -> [(Int, e)] -> ST s (STBytes# s e) Source #

writeM' :: STBytes# s e -> Int -> e -> ST s () Source #

swapM' :: STBytes# s e -> Int -> Int -> ST s () Source #

fromIndexed' :: Indexed v' j e => v' -> ST s (STBytes# s e) Source #

fromIndexedM :: IndexedM (ST s) v' j e => v' -> ST s (STBytes# s e) Source #

reshaped :: IndexedM (ST s) v' j e => (Int, Int) -> v' -> (Int -> j) -> ST s (STBytes# s e) Source #

fromAccum :: (e -> e' -> e) -> STBytes# s e -> [(Int, e')] -> ST s (STBytes# s e) Source #

updateM' :: STBytes# s e -> (e -> e) -> Int -> ST s () Source #

IndexedM (ST s) (STArray# s e) Int e Source # 
Instance details

Defined in SDP.Prim.SArray

Methods

fromAssocs :: (Int, Int) -> [(Int, e)] -> ST s (STArray# s e) Source #

fromAssocs' :: (Int, Int) -> e -> [(Int, e)] -> ST s (STArray# s e) Source #

writeM' :: STArray# s e -> Int -> e -> ST s () Source #

swapM' :: STArray# s e -> Int -> Int -> ST s () Source #

fromIndexed' :: Indexed v' j e => v' -> ST s (STArray# s e) Source #

fromIndexedM :: IndexedM (ST s) v' j e => v' -> ST s (STArray# s e) Source #

reshaped :: IndexedM (ST s) v' j e => (Int, Int) -> v' -> (Int -> j) -> ST s (STArray# s e) Source #

fromAccum :: (e -> e' -> e) -> STArray# s e -> [(Int, e')] -> ST s (STArray# s e) Source #

updateM' :: STArray# s e -> (e -> e) -> Int -> ST s () Source #

type IndexedM1 m v i e = IndexedM m (v e) i e Source #

Kind (* -> *) IndexedM.

type IndexedM2 m v i e = IndexedM m (v i e) i e Source #

Kind (* -> * -> *) IndexedM.

Thaw

class Monad m => Thaw m v v' | v' -> m where Source #

Service class of immutable to mutable conversions.

Minimal complete definition

thaw

Methods

thaw :: v -> m v' Source #

thaw is safe way to convert a immutable structure to a mutable. thaw should copy the old structure or ensure that it will not be used after the procedure calling.

unsafeThaw :: v -> m v' Source #

unsafeThaw is unsafe version of thaw. unsafeThaw 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

Instances details
(Index i, Thaw m imm (rep e), Bordered1 rep Int e) => Thaw m imm (AnyBorder rep i e) Source # 
Instance details

Defined in SDP.Templates.AnyBorder

Methods

thaw :: imm -> m (AnyBorder rep i e) Source #

unsafeThaw :: imm -> m (AnyBorder rep i e) Source #

Thaw STM (SArray# e) (TArray# e) Source # 
Instance details

Defined in SDP.Prim.TArray

(Storable e, Unboxed e) => Thaw IO (SBytes# e) (Int, Ptr e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

thaw :: SBytes# e -> IO (Int, Ptr e) Source #

unsafeThaw :: SBytes# e -> IO (Int, Ptr e) Source #

Storable e => Thaw IO (SArray# e) (Int, Ptr e) Source # 
Instance details

Defined in SDP.Prim.SArray

Methods

thaw :: SArray# e -> IO (Int, Ptr e) Source #

unsafeThaw :: SArray# e -> IO (Int, Ptr e) Source #

(MonadIO io, Unboxed e) => Thaw io (SBytes# e) (MIOBytes# io e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

thaw :: SBytes# e -> io (MIOBytes# io e) Source #

unsafeThaw :: SBytes# e -> io (MIOBytes# io e) Source #

MonadIO io => Thaw io (SArray# e) (MIOArray# io e) Source # 
Instance details

Defined in SDP.Prim.SArray

Methods

thaw :: SArray# e -> io (MIOArray# io e) Source #

unsafeThaw :: SArray# e -> io (MIOArray# io e) Source #

Thaw1 m imm mut e => Thaw m (imm e) (AnyChunks mut e) Source #

Creates one-chunk mutable stream, may be memory inefficient.

Instance details

Defined in SDP.Templates.AnyChunks

Methods

thaw :: imm e -> m (AnyChunks mut e) Source #

unsafeThaw :: imm e -> m (AnyChunks mut e) Source #

(Linear1 imm e, Thaw1 m imm mut e) => Thaw m (AnyChunks imm e) (mut e) Source #

Creates new local immutable structure and thaw it as fast, as possible.

Instance details

Defined in SDP.Templates.AnyChunks

Methods

thaw :: AnyChunks imm e -> m (mut e) Source #

unsafeThaw :: AnyChunks imm e -> m (mut e) Source #

Thaw1 m imm mut e => Thaw m (AnyChunks imm e) (AnyChunks mut e) Source # 
Instance details

Defined in SDP.Templates.AnyChunks

Methods

thaw :: AnyChunks imm e -> m (AnyChunks mut e) Source #

unsafeThaw :: AnyChunks imm e -> m (AnyChunks mut e) Source #

(Index i, Thaw m (rep e) mut) => Thaw m (AnyBorder rep i e) mut Source # 
Instance details

Defined in SDP.Templates.AnyBorder

Methods

thaw :: AnyBorder rep i e -> m mut Source #

unsafeThaw :: AnyBorder rep i e -> m mut Source #

(Index i, Thaw1 m imm mut e) => Thaw m (AnyBorder imm i e) (AnyBorder mut i e) Source # 
Instance details

Defined in SDP.Templates.AnyBorder

Methods

thaw :: AnyBorder imm i e -> m (AnyBorder mut i e) Source #

unsafeThaw :: AnyBorder imm i e -> m (AnyBorder mut i e) Source #

Unboxed e => Thaw (ST s) (SBytes# e) (STBytes# s e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

thaw :: SBytes# e -> ST s (STBytes# s e) Source #

unsafeThaw :: SBytes# e -> ST s (STBytes# s e) Source #

Thaw (ST s) (SArray# e) (STArray# s e) Source # 
Instance details

Defined in SDP.Prim.SArray

Methods

thaw :: SArray# e -> ST s (STArray# s e) Source #

unsafeThaw :: SArray# e -> ST s (STArray# s e) Source #

type Thaw1 m v v' e = Thaw m (v e) (v' e) Source #

Kind (* -> *) Thaw.