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

SDP.LinearM

Description

SDP.LinearM is a module that provides BorderedM and LinearM classes.

Synopsis

Exports

module SDP.Linear

BorderedM class

class (Monad m, Index i) => BorderedM m b i | b -> m, b -> i where Source #

BorderedM is Bordered version for mutable data structures.

Minimal complete definition

(getBounds | getLower, getUpper)

Methods

getBounds :: b -> m (i, i) Source #

getBounds returns bounds of mutable data structure.

getLower :: b -> m i Source #

getLower returns lower bound of mutable data structure.

getUpper :: b -> m i Source #

getUpper returns upper bound of mutable data structure.

getSizeOf :: b -> m Int Source #

getSizeOf returns size of mutable data structure.

getSizesOf :: b -> m [Int] Source #

getSizesOf returns sizes of mutable data structure.

nowIndexIn :: b -> i -> m Bool Source #

nowIndexIn is indexIn version for mutable structures.

getOffsetOf :: b -> i -> m Int Source #

getOffsetOf is offsetOf version for mutable structures.

getIndexOf :: b -> Int -> m i Source #

getIndexOf is indexOf version for mutable structures.

getIndices :: b -> m [i] Source #

getIndices returns indices of mutable data structure.

Instances

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

Defined in SDP.Prim.TArray

MonadIO io => BorderedM io (MIOBytes# io e) Int Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

getBounds :: MIOBytes# io e -> io (Int, Int) Source #

getLower :: MIOBytes# io e -> io Int Source #

getUpper :: MIOBytes# io e -> io Int Source #

getSizeOf :: MIOBytes# io e -> io Int Source #

getSizesOf :: MIOBytes# io e -> io [Int] Source #

nowIndexIn :: MIOBytes# io e -> Int -> io Bool Source #

getOffsetOf :: MIOBytes# io e -> Int -> io Int Source #

getIndexOf :: MIOBytes# io e -> Int -> io Int Source #

getIndices :: MIOBytes# io e -> io [Int] Source #

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

Defined in SDP.Prim.SArray

Methods

getBounds :: MIOArray# io e -> io (Int, Int) Source #

getLower :: MIOArray# io e -> io Int Source #

getUpper :: MIOArray# io e -> io Int Source #

getSizeOf :: MIOArray# io e -> io Int Source #

getSizesOf :: MIOArray# io e -> io [Int] Source #

nowIndexIn :: MIOArray# io e -> Int -> io Bool Source #

getOffsetOf :: MIOArray# io e -> Int -> io Int Source #

getIndexOf :: MIOArray# io e -> Int -> io Int Source #

getIndices :: MIOArray# io e -> io [Int] Source #

BorderedM1 m rep Int e => BorderedM m (AnyChunks rep e) Int Source # 
Instance details

Defined in SDP.Templates.AnyChunks

Methods

getBounds :: AnyChunks rep e -> m (Int, Int) Source #

getLower :: AnyChunks rep e -> m Int Source #

getUpper :: AnyChunks rep e -> m Int Source #

getSizeOf :: AnyChunks rep e -> m Int Source #

getSizesOf :: AnyChunks rep e -> m [Int] Source #

nowIndexIn :: AnyChunks rep e -> Int -> m Bool Source #

getOffsetOf :: AnyChunks rep e -> Int -> m Int Source #

getIndexOf :: AnyChunks rep e -> Int -> m Int Source #

getIndices :: AnyChunks rep e -> m [Int] Source #

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

Defined in SDP.Templates.AnyBorder

Methods

getBounds :: AnyBorder rep i e -> m (i, i) Source #

getLower :: AnyBorder rep i e -> m i Source #

getUpper :: AnyBorder rep i e -> m i Source #

getSizeOf :: AnyBorder rep i e -> m Int Source #

getSizesOf :: AnyBorder rep i e -> m [Int] Source #

nowIndexIn :: AnyBorder rep i e -> i -> m Bool Source #

getOffsetOf :: AnyBorder rep i e -> i -> m Int Source #

getIndexOf :: AnyBorder rep i e -> Int -> m i Source #

getIndices :: AnyBorder rep i e -> m [i] Source #

BorderedM (ST s) (STBytes# s e) Int Source # 
Instance details

Defined in SDP.Prim.SBytes

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

Defined in SDP.Prim.SArray

type BorderedM1 m l i e = BorderedM m (l e) i Source #

BorderedM contraint for (Type -> Type)-kind types.

type BorderedM2 m l i e = BorderedM m (l i e) i Source #

BorderedM contraint for (Type -> Type -> Type)-kind types.

LinearM class

class Monad m => LinearM m l e | l -> m, l -> e where Source #

LinearM is Linear version for mutable data structures. This class is designed with the possibility of in-place implementation, so many operations from Linear have no analogues here.

Minimal complete definition

(newLinear | fromFoldableM), (getLeft | getRight), (!#>), writeM, copyTo

Methods

newNull :: m l Source #

Monadic single.

nowNull :: l -> m Bool Source #

Monadic isNull.

singleM :: e -> m l Source #

Monadic single.

getHead :: l -> m e Source #

getHead is monadic version of head. This procedure mustn't modify the source structure or return references to its mutable fields.

getLast :: l -> m e Source #

getLast is monadic version of last. This procedure mustn't modify the source structure or return references to its mutable fields.

prepend :: e -> l -> m l Source #

Prepends new element to the start of the structure (monadic toHead). Like most size-changing operations, prepend doesn't guarantee the correctness of the original structure after conversion.

append :: l -> e -> m l Source #

Appends new element to the end of the structure (monadic toLast). Like most size-changing operations, append doesn't guarantee the correctness of the original structure after conversion.

newLinear :: [e] -> m l Source #

Monadic fromList.

newLinearN :: Int -> [e] -> m l Source #

Monadic fromListN.

fromFoldableM :: Foldable f => f e -> m l Source #

Monadic fromFoldable.

getLeft :: l -> m [e] Source #

Left view of line.

getRight :: l -> m [e] Source #

Right view of line.

(!#>) :: l -> Int -> m e infixl 5 Source #

(!#>) is unsafe monadic offset-based reader.

writeM :: l -> Int -> e -> m () Source #

Unsafe monadic offset-based writer.

copied :: l -> m l Source #

Create copy.

copied' :: l -> Int -> Int -> m l Source #

copied' es l n returns the slice of es from l of length n.

reversed :: l -> m l Source #

Monadic reverse, returns new structure.

reversed' :: l -> m () Source #

Monadic in-place reverse, reverse elements of given structure.

Since: 0.2.1

merged :: Foldable f => f l -> m l Source #

Monadic concat.

filled :: Int -> e -> m l Source #

Monadic version of replicate.

removed :: Int -> l -> m l Source #

removed n es removes element with offset n from es.

Since: 0.2.1

lshiftM :: l -> Int -> Int -> m () Source #

lshiftM es i j cyclically shifts the elements with offsets between i and j (i < j) one position to the left (the j-th element is in the i-th position, the i-th in the (i+1)th, etc.) If i >= j, does nothing.

Since: 0.2.1

copyTo :: l -> Int -> l -> Int -> Int -> m () Source #

copyTo source soff target toff count writes count elements of source from soff to target starting with toff.

ofoldrM :: (Int -> e -> r -> m r) -> r -> l -> m r Source #

ofoldrM is right monadic fold with offset.

ofoldlM :: (Int -> r -> e -> m r) -> r -> l -> m r Source #

ofoldlM is left monadic fold with offset.

ofoldrM' :: (Int -> e -> r -> m r) -> r -> l -> m r Source #

ofoldrM' is strict version of ofoldrM.

ofoldlM' :: (Int -> r -> e -> m r) -> r -> l -> m r Source #

ofoldrM' is strict version of ofoldrM.

foldrM :: (e -> r -> m r) -> r -> l -> m r Source #

foldrM is just ofoldrM in Linear context.

foldlM :: (r -> e -> m r) -> r -> l -> m r Source #

foldlM is just ofoldlM in Linear context.

foldrM' :: (e -> r -> m r) -> r -> l -> m r Source #

foldrM' is strict version of foldrM.

foldlM' :: (r -> e -> m r) -> r -> l -> m r Source #

foldlM' is strict version of foldlM.

foldrM1 :: (e -> e -> m e) -> l -> m e Source #

foldrM1 is foldrM version with last element as base.

Since: 0.2.1

foldlM1 :: (e -> e -> m e) -> l -> m e Source #

foldlM1 is foldlM version with head element as base.

Since: 0.2.1

swapM :: l -> Int -> Int -> m () Source #

Just swap two elements.

Instances

Instances details
LinearM STM (TArray# e) e Source # 
Instance details

Defined in SDP.Prim.TArray

Methods

newNull :: STM (TArray# e) Source #

nowNull :: TArray# e -> STM Bool Source #

singleM :: e -> STM (TArray# e) Source #

getHead :: TArray# e -> STM e Source #

getLast :: TArray# e -> STM e Source #

prepend :: e -> TArray# e -> STM (TArray# e) Source #

append :: TArray# e -> e -> STM (TArray# e) Source #

newLinear :: [e] -> STM (TArray# e) Source #

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

fromFoldableM :: Foldable f => f e -> STM (TArray# e) Source #

getLeft :: TArray# e -> STM [e] Source #

getRight :: TArray# e -> STM [e] Source #

(!#>) :: TArray# e -> Int -> STM e Source #

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

copied :: TArray# e -> STM (TArray# e) Source #

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

reversed :: TArray# e -> STM (TArray# e) Source #

reversed' :: TArray# e -> STM () Source #

merged :: Foldable f => f (TArray# e) -> STM (TArray# e) Source #

filled :: Int -> e -> STM (TArray# e) Source #

removed :: Int -> TArray# e -> STM (TArray# e) Source #

lshiftM :: TArray# e -> Int -> Int -> STM () Source #

copyTo :: TArray# e -> Int -> TArray# e -> Int -> Int -> STM () Source #

ofoldrM :: (Int -> e -> r -> STM r) -> r -> TArray# e -> STM r Source #

ofoldlM :: (Int -> r -> e -> STM r) -> r -> TArray# e -> STM r Source #

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

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

foldrM :: (e -> r -> STM r) -> r -> TArray# e -> STM r Source #

foldlM :: (r -> e -> STM r) -> r -> TArray# e -> STM r Source #

foldrM' :: (e -> r -> STM r) -> r -> TArray# e -> STM r Source #

foldlM' :: (r -> e -> STM r) -> r -> TArray# e -> STM r Source #

foldrM1 :: (e -> e -> STM e) -> TArray# e -> STM e Source #

foldlM1 :: (e -> e -> STM e) -> TArray# e -> STM e Source #

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

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

Defined in SDP.Prim.SBytes

Methods

newNull :: io (MIOBytes# io e) Source #

nowNull :: MIOBytes# io e -> io Bool Source #

singleM :: e -> io (MIOBytes# io e) Source #

getHead :: MIOBytes# io e -> io e Source #

getLast :: MIOBytes# io e -> io e Source #

prepend :: e -> MIOBytes# io e -> io (MIOBytes# io e) Source #

append :: MIOBytes# io e -> e -> io (MIOBytes# io e) Source #

newLinear :: [e] -> io (MIOBytes# io e) Source #

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

fromFoldableM :: Foldable f => f e -> io (MIOBytes# io e) Source #

getLeft :: MIOBytes# io e -> io [e] Source #

getRight :: MIOBytes# io e -> io [e] Source #

(!#>) :: MIOBytes# io e -> Int -> io e Source #

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

copied :: MIOBytes# io e -> io (MIOBytes# io e) Source #

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

reversed :: MIOBytes# io e -> io (MIOBytes# io e) Source #

reversed' :: MIOBytes# io e -> io () Source #

merged :: Foldable f => f (MIOBytes# io e) -> io (MIOBytes# io e) Source #

filled :: Int -> e -> io (MIOBytes# io e) Source #

removed :: Int -> MIOBytes# io e -> io (MIOBytes# io e) Source #

lshiftM :: MIOBytes# io e -> Int -> Int -> io () Source #

copyTo :: MIOBytes# io e -> Int -> MIOBytes# io e -> Int -> Int -> io () Source #

ofoldrM :: (Int -> e -> r -> io r) -> r -> MIOBytes# io e -> io r Source #

ofoldlM :: (Int -> r -> e -> io r) -> r -> MIOBytes# io e -> io r Source #

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

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

foldrM :: (e -> r -> io r) -> r -> MIOBytes# io e -> io r Source #

foldlM :: (r -> e -> io r) -> r -> MIOBytes# io e -> io r Source #

foldrM' :: (e -> r -> io r) -> r -> MIOBytes# io e -> io r Source #

foldlM' :: (r -> e -> io r) -> r -> MIOBytes# io e -> io r Source #

foldrM1 :: (e -> e -> io e) -> MIOBytes# io e -> io e Source #

foldlM1 :: (e -> e -> io e) -> MIOBytes# io e -> io e Source #

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

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

Defined in SDP.Prim.SArray

Methods

newNull :: io (MIOArray# io e) Source #

nowNull :: MIOArray# io e -> io Bool Source #

singleM :: e -> io (MIOArray# io e) Source #

getHead :: MIOArray# io e -> io e Source #

getLast :: MIOArray# io e -> io e Source #

prepend :: e -> MIOArray# io e -> io (MIOArray# io e) Source #

append :: MIOArray# io e -> e -> io (MIOArray# io e) Source #

newLinear :: [e] -> io (MIOArray# io e) Source #

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

fromFoldableM :: Foldable f => f e -> io (MIOArray# io e) Source #

getLeft :: MIOArray# io e -> io [e] Source #

getRight :: MIOArray# io e -> io [e] Source #

(!#>) :: MIOArray# io e -> Int -> io e Source #

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

copied :: MIOArray# io e -> io (MIOArray# io e) Source #

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

reversed :: MIOArray# io e -> io (MIOArray# io e) Source #

reversed' :: MIOArray# io e -> io () Source #

merged :: Foldable f => f (MIOArray# io e) -> io (MIOArray# io e) Source #

filled :: Int -> e -> io (MIOArray# io e) Source #

removed :: Int -> MIOArray# io e -> io (MIOArray# io e) Source #

lshiftM :: MIOArray# io e -> Int -> Int -> io () Source #

copyTo :: MIOArray# io e -> Int -> MIOArray# io e -> Int -> Int -> io () Source #

ofoldrM :: (Int -> e -> r -> io r) -> r -> MIOArray# io e -> io r Source #

ofoldlM :: (Int -> r -> e -> io r) -> r -> MIOArray# io e -> io r Source #

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

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

foldrM :: (e -> r -> io r) -> r -> MIOArray# io e -> io r Source #

foldlM :: (r -> e -> io r) -> r -> MIOArray# io e -> io r Source #

foldrM' :: (e -> r -> io r) -> r -> MIOArray# io e -> io r Source #

foldlM' :: (r -> e -> io r) -> r -> MIOArray# io e -> io r Source #

foldrM1 :: (e -> e -> io e) -> MIOArray# io e -> io e Source #

foldlM1 :: (e -> e -> io e) -> MIOArray# io e -> io e Source #

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

(BorderedM1 m rep Int e, SplitM1 m rep e) => LinearM m (AnyChunks rep e) e Source # 
Instance details

Defined in SDP.Templates.AnyChunks

Methods

newNull :: m (AnyChunks rep e) Source #

nowNull :: AnyChunks rep e -> m Bool Source #

singleM :: e -> m (AnyChunks rep e) Source #

getHead :: AnyChunks rep e -> m e Source #

getLast :: AnyChunks rep e -> m e Source #

prepend :: e -> AnyChunks rep e -> m (AnyChunks rep e) Source #

append :: AnyChunks rep e -> e -> m (AnyChunks rep e) Source #

newLinear :: [e] -> m (AnyChunks rep e) Source #

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

fromFoldableM :: Foldable f => f e -> m (AnyChunks rep e) Source #

getLeft :: AnyChunks rep e -> m [e] Source #

getRight :: AnyChunks rep e -> m [e] Source #

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

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

copied :: AnyChunks rep e -> m (AnyChunks rep e) Source #

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

reversed :: AnyChunks rep e -> m (AnyChunks rep e) Source #

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

merged :: Foldable f => f (AnyChunks rep e) -> m (AnyChunks rep e) Source #

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

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

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

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

ofoldrM :: (Int -> e -> r -> m r) -> r -> AnyChunks rep e -> m r Source #

ofoldlM :: (Int -> r -> e -> m r) -> r -> AnyChunks rep e -> m r Source #

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

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

foldrM :: (e -> r -> m r) -> r -> AnyChunks rep e -> m r Source #

foldlM :: (r -> e -> m r) -> r -> AnyChunks rep e -> m r Source #

foldrM' :: (e -> r -> m r) -> r -> AnyChunks rep e -> m r Source #

foldlM' :: (r -> e -> m r) -> r -> AnyChunks rep e -> m r Source #

foldrM1 :: (e -> e -> m e) -> AnyChunks rep e -> m e Source #

foldlM1 :: (e -> e -> m e) -> AnyChunks rep e -> m e Source #

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

(Index i, LinearM1 m rep e, BorderedM1 m rep Int e) => LinearM m (AnyBorder rep i e) e Source # 
Instance details

Defined in SDP.Templates.AnyBorder

Methods

newNull :: m (AnyBorder rep i e) Source #

nowNull :: AnyBorder rep i e -> m Bool Source #

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

getHead :: AnyBorder rep i e -> m e Source #

getLast :: AnyBorder rep i e -> m e Source #

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

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

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

newLinearN :: Int -> [e] -> m (AnyBorder rep i e) Source #

fromFoldableM :: Foldable f => f e -> m (AnyBorder rep i e) Source #

getLeft :: AnyBorder rep i e -> m [e] Source #

getRight :: AnyBorder rep i e -> m [e] Source #

(!#>) :: AnyBorder rep i e -> Int -> m e Source #

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

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

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

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

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

merged :: Foldable f => f (AnyBorder rep i e) -> m (AnyBorder rep i e) Source #

filled :: Int -> e -> m (AnyBorder rep i e) Source #

removed :: Int -> AnyBorder rep i e -> m (AnyBorder rep i e) Source #

lshiftM :: AnyBorder rep i e -> Int -> Int -> m () Source #

copyTo :: AnyBorder rep i e -> Int -> AnyBorder rep i e -> Int -> Int -> m () Source #

ofoldrM :: (Int -> e -> r -> m r) -> r -> AnyBorder rep i e -> m r Source #

ofoldlM :: (Int -> r -> e -> m r) -> r -> AnyBorder rep i e -> m r Source #

ofoldrM' :: (Int -> e -> r -> m r) -> r -> AnyBorder rep i e -> m r Source #

ofoldlM' :: (Int -> r -> e -> m r) -> r -> AnyBorder rep i e -> m r Source #

foldrM :: (e -> r -> m r) -> r -> AnyBorder rep i e -> m r Source #

foldlM :: (r -> e -> m r) -> r -> AnyBorder rep i e -> m r Source #

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

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

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

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

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

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

Defined in SDP.Prim.SBytes

Methods

newNull :: ST s (STBytes# s e) Source #

nowNull :: STBytes# s e -> ST s Bool Source #

singleM :: e -> ST s (STBytes# s e) Source #

getHead :: STBytes# s e -> ST s e Source #

getLast :: STBytes# s e -> ST s e Source #

prepend :: e -> STBytes# s e -> ST s (STBytes# s e) Source #

append :: STBytes# s e -> e -> ST s (STBytes# s e) Source #

newLinear :: [e] -> ST s (STBytes# s e) Source #

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

fromFoldableM :: Foldable f => f e -> ST s (STBytes# s e) Source #

getLeft :: STBytes# s e -> ST s [e] Source #

getRight :: STBytes# s e -> ST s [e] Source #

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

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

copied :: STBytes# s e -> ST s (STBytes# s e) Source #

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

reversed :: STBytes# s e -> ST s (STBytes# s e) Source #

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

merged :: Foldable f => f (STBytes# s e) -> ST s (STBytes# s e) Source #

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

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

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

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

ofoldrM :: (Int -> e -> r -> ST s r) -> r -> STBytes# s e -> ST s r Source #

ofoldlM :: (Int -> r -> e -> ST s r) -> r -> STBytes# s e -> ST s r Source #

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

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

foldrM :: (e -> r -> ST s r) -> r -> STBytes# s e -> ST s r Source #

foldlM :: (r -> e -> ST s r) -> r -> STBytes# s e -> ST s r Source #

foldrM' :: (e -> r -> ST s r) -> r -> STBytes# s e -> ST s r Source #

foldlM' :: (r -> e -> ST s r) -> r -> STBytes# s e -> ST s r Source #

foldrM1 :: (e -> e -> ST s e) -> STBytes# s e -> ST s e Source #

foldlM1 :: (e -> e -> ST s e) -> STBytes# s e -> ST s e Source #

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

LinearM (ST s) (STArray# s e) e Source # 
Instance details

Defined in SDP.Prim.SArray

Methods

newNull :: ST s (STArray# s e) Source #

nowNull :: STArray# s e -> ST s Bool Source #

singleM :: e -> ST s (STArray# s e) Source #

getHead :: STArray# s e -> ST s e Source #

getLast :: STArray# s e -> ST s e Source #

prepend :: e -> STArray# s e -> ST s (STArray# s e) Source #

append :: STArray# s e -> e -> ST s (STArray# s e) Source #

newLinear :: [e] -> ST s (STArray# s e) Source #

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

fromFoldableM :: Foldable f => f e -> ST s (STArray# s e) Source #

getLeft :: STArray# s e -> ST s [e] Source #

getRight :: STArray# s e -> ST s [e] Source #

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

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

copied :: STArray# s e -> ST s (STArray# s e) Source #

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

reversed :: STArray# s e -> ST s (STArray# s e) Source #

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

merged :: Foldable f => f (STArray# s e) -> ST s (STArray# s e) Source #

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

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

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

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

ofoldrM :: (Int -> e -> r -> ST s r) -> r -> STArray# s e -> ST s r Source #

ofoldlM :: (Int -> r -> e -> ST s r) -> r -> STArray# s e -> ST s r Source #

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

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

foldrM :: (e -> r -> ST s r) -> r -> STArray# s e -> ST s r Source #

foldlM :: (r -> e -> ST s r) -> r -> STArray# s e -> ST s r Source #

foldrM' :: (e -> r -> ST s r) -> r -> STArray# s e -> ST s r Source #

foldlM' :: (r -> e -> ST s r) -> r -> STArray# s e -> ST s r Source #

foldrM1 :: (e -> e -> ST s e) -> STArray# s e -> ST s e Source #

foldlM1 :: (e -> e -> ST s e) -> STArray# s e -> ST s e Source #

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

type LinearM1 m l e = LinearM m (l e) e Source #

LinearM contraint for (Type -> Type)-kind types.

type LinearM2 m l i e = LinearM m (l i e) e Source #

LinearM contraint for (Type -> Type -> Type)-kind types.

pattern (:+=) :: (Typeable record, Typeable field, Typeable m, Typeable l, Typeable e, LinearM m l e, FieldGet field, FieldSet field) => e -> field m record l -> Prop m field record Source #

(:+=) is fmr-compatible prepend element pattern for LinearM fields.

Since: 0.2.1

pattern (:=+) :: (Typeable record, Typeable field, Typeable m, Typeable l, Typeable e, LinearM m l e, FieldGet field, FieldSet field) => field m record l -> e -> Prop m field record Source #

(:=+) is fmr-compatible append element pattern for LinearM fields.

Since: 0.2.1

pattern (:~=) :: (Typeable record, Typeable field, Typeable m, Typeable l, Typeable e, LinearM m l e, FieldGet field, FieldSet field) => Int -> field m record l -> Prop m field record Source #

(:~=) is fmr-compatible delete element pattern for LinearM fields, see removed.

Since: 0.2.1

Rank 2 quantified constraints

GHC 8.6.1+ only

type BorderedM' m l i = forall e. BorderedM m (l e) i Source #

BorderedM contraint for (Type -> Type)-kind types.

type BorderedM'' m l = forall i e. BorderedM m (l i e) i Source #

BorderedM contraint for (Type -> Type -> Type)-kind types.

type LinearM' m l = forall e. LinearM m (l e) e Source #

LinearM contraint for (Type -> Type)-kind types.

type LinearM'' m l = forall i e. LinearM m (l i e) e Source #

LinearM contraint for (Type -> Type -> Type)-kind types.

SplitM class

class LinearM m s e => SplitM m s e where Source #

SplitM is Split version for mutable data structures. This class is designed with the possibility of in-place implementation, so many operations from Split have no analogues here.

Minimal complete definition

(takeM | sansM), (dropM | keepM)

Methods

takeM :: Int -> s -> m s Source #

takeM n es returns a reference to the es, keeping first n elements. Changes in the source and result must be synchronous.

default takeM :: BorderedM m s i => Int -> s -> m s Source #

dropM :: Int -> s -> m s Source #

dropM n es returns a reference to the es, discarding first n elements. Changes in the source and result must be synchronous.

default dropM :: BorderedM m s i => Int -> s -> m s Source #

keepM :: Int -> s -> m s Source #

keepM n es returns a reference to the es, keeping last n elements. Changes in the source and result must be synchronous.

default keepM :: BorderedM m s i => Int -> s -> m s Source #

sansM :: Int -> s -> m s Source #

sansM n es returns a reference to the es, discarding last n elements. Changes in the source and result must be synchronous.

default sansM :: BorderedM m s i => Int -> s -> m s Source #

splitM :: Int -> s -> m (s, s) Source #

splitM n es returns pair of references to the es: keeping and discarding first n elements. Changes in the source and result must be synchronous.

divideM :: Int -> s -> m (s, s) Source #

divideM n es returns pair of references to the es: discarding and keeping last n elements. Changes in the source and results must be synchronous.

splitsM :: Foldable f => f Int -> s -> m [s] Source #

splitM ns es returns the sequence of es prefix references of length n <- ns. Changes in the source and results must be synchronous.

dividesM :: Foldable f => f Int -> s -> m [s] Source #

dividesM ns es returns the sequence of es suffix references of length n <- ns. Changes in the source and results must be synchronous.

partsM :: Foldable f => f Int -> s -> m [s] Source #

partsM n es returns the sequence of es prefix references, splitted by offsets in es. Changes in the source and results must be synchronous.

chunksM :: Int -> s -> m [s] Source #

chunksM n es returns the sequence of es prefix references of length n. Changes in the source and results must be synchronous.

eachM :: Int -> s -> m s Source #

eachM n es returns new sequence of es elements with step n. eachM shouldn't return references to es.

prefixM :: (e -> Bool) -> s -> m Int Source #

prefixM p es returns the longest es prefix size, satisfying p.

suffixM :: (e -> Bool) -> s -> m Int Source #

suffixM p es returns the longest es suffix size, satisfying p.

mprefix :: (e -> m Bool) -> s -> m Int Source #

mprefix p es returns the longest es prefix size, satisfying p.

msuffix :: (e -> m Bool) -> s -> m Int Source #

msuffix p es returns the longest es suffix size, satisfying p.

Instances

Instances details
SplitM STM (TArray# e) e Source # 
Instance details

Defined in SDP.Prim.TArray

Methods

takeM :: Int -> TArray# e -> STM (TArray# e) Source #

dropM :: Int -> TArray# e -> STM (TArray# e) Source #

keepM :: Int -> TArray# e -> STM (TArray# e) Source #

sansM :: Int -> TArray# e -> STM (TArray# e) Source #

splitM :: Int -> TArray# e -> STM (TArray# e, TArray# e) Source #

divideM :: Int -> TArray# e -> STM (TArray# e, TArray# e) Source #

splitsM :: Foldable f => f Int -> TArray# e -> STM [TArray# e] Source #

dividesM :: Foldable f => f Int -> TArray# e -> STM [TArray# e] Source #

partsM :: Foldable f => f Int -> TArray# e -> STM [TArray# e] Source #

chunksM :: Int -> TArray# e -> STM [TArray# e] Source #

eachM :: Int -> TArray# e -> STM (TArray# e) Source #

prefixM :: (e -> Bool) -> TArray# e -> STM Int Source #

suffixM :: (e -> Bool) -> TArray# e -> STM Int Source #

mprefix :: (e -> STM Bool) -> TArray# e -> STM Int Source #

msuffix :: (e -> STM Bool) -> TArray# e -> STM Int Source #

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

Defined in SDP.Prim.SBytes

Methods

takeM :: Int -> MIOBytes# io e -> io (MIOBytes# io e) Source #

dropM :: Int -> MIOBytes# io e -> io (MIOBytes# io e) Source #

keepM :: Int -> MIOBytes# io e -> io (MIOBytes# io e) Source #

sansM :: Int -> MIOBytes# io e -> io (MIOBytes# io e) Source #

splitM :: Int -> MIOBytes# io e -> io (MIOBytes# io e, MIOBytes# io e) Source #

divideM :: Int -> MIOBytes# io e -> io (MIOBytes# io e, MIOBytes# io e) Source #

splitsM :: Foldable f => f Int -> MIOBytes# io e -> io [MIOBytes# io e] Source #

dividesM :: Foldable f => f Int -> MIOBytes# io e -> io [MIOBytes# io e] Source #

partsM :: Foldable f => f Int -> MIOBytes# io e -> io [MIOBytes# io e] Source #

chunksM :: Int -> MIOBytes# io e -> io [MIOBytes# io e] Source #

eachM :: Int -> MIOBytes# io e -> io (MIOBytes# io e) Source #

prefixM :: (e -> Bool) -> MIOBytes# io e -> io Int Source #

suffixM :: (e -> Bool) -> MIOBytes# io e -> io Int Source #

mprefix :: (e -> io Bool) -> MIOBytes# io e -> io Int Source #

msuffix :: (e -> io Bool) -> MIOBytes# io e -> io Int Source #

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

Defined in SDP.Prim.SArray

Methods

takeM :: Int -> MIOArray# io e -> io (MIOArray# io e) Source #

dropM :: Int -> MIOArray# io e -> io (MIOArray# io e) Source #

keepM :: Int -> MIOArray# io e -> io (MIOArray# io e) Source #

sansM :: Int -> MIOArray# io e -> io (MIOArray# io e) Source #

splitM :: Int -> MIOArray# io e -> io (MIOArray# io e, MIOArray# io e) Source #

divideM :: Int -> MIOArray# io e -> io (MIOArray# io e, MIOArray# io e) Source #

splitsM :: Foldable f => f Int -> MIOArray# io e -> io [MIOArray# io e] Source #

dividesM :: Foldable f => f Int -> MIOArray# io e -> io [MIOArray# io e] Source #

partsM :: Foldable f => f Int -> MIOArray# io e -> io [MIOArray# io e] Source #

chunksM :: Int -> MIOArray# io e -> io [MIOArray# io e] Source #

eachM :: Int -> MIOArray# io e -> io (MIOArray# io e) Source #

prefixM :: (e -> Bool) -> MIOArray# io e -> io Int Source #

suffixM :: (e -> Bool) -> MIOArray# io e -> io Int Source #

mprefix :: (e -> io Bool) -> MIOArray# io e -> io Int Source #

msuffix :: (e -> io Bool) -> MIOArray# io e -> io Int Source #

(BorderedM1 m rep Int e, SplitM1 m rep e) => SplitM m (AnyChunks rep e) e Source # 
Instance details

Defined in SDP.Templates.AnyChunks

Methods

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

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

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

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

splitM :: Int -> AnyChunks rep e -> m (AnyChunks rep e, AnyChunks rep e) Source #

divideM :: Int -> AnyChunks rep e -> m (AnyChunks rep e, AnyChunks rep e) Source #

splitsM :: Foldable f => f Int -> AnyChunks rep e -> m [AnyChunks rep e] Source #

dividesM :: Foldable f => f Int -> AnyChunks rep e -> m [AnyChunks rep e] Source #

partsM :: Foldable f => f Int -> AnyChunks rep e -> m [AnyChunks rep e] Source #

chunksM :: Int -> AnyChunks rep e -> m [AnyChunks rep e] Source #

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

prefixM :: (e -> Bool) -> AnyChunks rep e -> m Int Source #

suffixM :: (e -> Bool) -> AnyChunks rep e -> m Int Source #

mprefix :: (e -> m Bool) -> AnyChunks rep e -> m Int Source #

msuffix :: (e -> m Bool) -> AnyChunks rep e -> m Int Source #

(Index i, BorderedM1 m rep Int e, SplitM1 m rep e) => SplitM m (AnyBorder rep i e) e Source # 
Instance details

Defined in SDP.Templates.AnyBorder

Methods

takeM :: Int -> AnyBorder rep i e -> m (AnyBorder rep i e) Source #

dropM :: Int -> AnyBorder rep i e -> m (AnyBorder rep i e) Source #

keepM :: Int -> AnyBorder rep i e -> m (AnyBorder rep i e) Source #

sansM :: Int -> AnyBorder rep i e -> m (AnyBorder rep i e) Source #

splitM :: Int -> AnyBorder rep i e -> m (AnyBorder rep i e, AnyBorder rep i e) Source #

divideM :: Int -> AnyBorder rep i e -> m (AnyBorder rep i e, AnyBorder rep i e) Source #

splitsM :: Foldable f => f Int -> AnyBorder rep i e -> m [AnyBorder rep i e] Source #

dividesM :: Foldable f => f Int -> AnyBorder rep i e -> m [AnyBorder rep i e] Source #

partsM :: Foldable f => f Int -> AnyBorder rep i e -> m [AnyBorder rep i e] Source #

chunksM :: Int -> AnyBorder rep i e -> m [AnyBorder rep i e] Source #

eachM :: Int -> AnyBorder rep i e -> m (AnyBorder rep i e) Source #

prefixM :: (e -> Bool) -> AnyBorder rep i e -> m Int Source #

suffixM :: (e -> Bool) -> AnyBorder rep i e -> m Int Source #

mprefix :: (e -> m Bool) -> AnyBorder rep i e -> m Int Source #

msuffix :: (e -> m Bool) -> AnyBorder rep i e -> m Int Source #

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

Defined in SDP.Prim.SBytes

Methods

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

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

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

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

splitM :: Int -> STBytes# s e -> ST s (STBytes# s e, STBytes# s e) Source #

divideM :: Int -> STBytes# s e -> ST s (STBytes# s e, STBytes# s e) Source #

splitsM :: Foldable f => f Int -> STBytes# s e -> ST s [STBytes# s e] Source #

dividesM :: Foldable f => f Int -> STBytes# s e -> ST s [STBytes# s e] Source #

partsM :: Foldable f => f Int -> STBytes# s e -> ST s [STBytes# s e] Source #

chunksM :: Int -> STBytes# s e -> ST s [STBytes# s e] Source #

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

prefixM :: (e -> Bool) -> STBytes# s e -> ST s Int Source #

suffixM :: (e -> Bool) -> STBytes# s e -> ST s Int Source #

mprefix :: (e -> ST s Bool) -> STBytes# s e -> ST s Int Source #

msuffix :: (e -> ST s Bool) -> STBytes# s e -> ST s Int Source #

SplitM (ST s) (STArray# s e) e Source # 
Instance details

Defined in SDP.Prim.SArray

Methods

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

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

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

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

splitM :: Int -> STArray# s e -> ST s (STArray# s e, STArray# s e) Source #

divideM :: Int -> STArray# s e -> ST s (STArray# s e, STArray# s e) Source #

splitsM :: Foldable f => f Int -> STArray# s e -> ST s [STArray# s e] Source #

dividesM :: Foldable f => f Int -> STArray# s e -> ST s [STArray# s e] Source #

partsM :: Foldable f => f Int -> STArray# s e -> ST s [STArray# s e] Source #

chunksM :: Int -> STArray# s e -> ST s [STArray# s e] Source #

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

prefixM :: (e -> Bool) -> STArray# s e -> ST s Int Source #

suffixM :: (e -> Bool) -> STArray# s e -> ST s Int Source #

mprefix :: (e -> ST s Bool) -> STArray# s e -> ST s Int Source #

msuffix :: (e -> ST s Bool) -> STArray# s e -> ST s Int Source #

type SplitM1 m l e = SplitM m (l e) e Source #

Kind (Type -> Type) SplitM structure.