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.LinearM is a module that provides BorderedM
and LinearM
classes.
Synopsis
- module SDP.Linear
- class (Monad m, Index i) => BorderedM m b i | b -> m, b -> i where
- getBounds :: b -> m (i, i)
- getLower :: b -> m i
- getUpper :: b -> m i
- getSizeOf :: b -> m Int
- getSizesOf :: b -> m [Int]
- nowIndexIn :: b -> i -> m Bool
- getOffsetOf :: b -> i -> m Int
- getIndexOf :: b -> Int -> m i
- getIndices :: b -> m [i]
- type BorderedM1 m l i e = BorderedM m (l e) i
- type BorderedM2 m l i e = BorderedM m (l i e) i
- class Monad m => LinearM m l e | l -> m, l -> e where
- newNull :: m l
- nowNull :: l -> m Bool
- singleM :: e -> m l
- getHead :: l -> m e
- getLast :: l -> m e
- prepend :: e -> l -> m l
- append :: l -> e -> m l
- newLinear :: [e] -> m l
- newLinearN :: Int -> [e] -> m l
- fromFoldableM :: Foldable f => f e -> m l
- getLeft :: l -> m [e]
- getRight :: l -> m [e]
- (!#>) :: l -> Int -> m e
- writeM :: l -> Int -> e -> m ()
- copied :: l -> m l
- copied' :: l -> Int -> Int -> m l
- reversed :: l -> m l
- merged :: Foldable f => f l -> m l
- filled :: Int -> e -> m l
- copyTo :: l -> Int -> l -> Int -> Int -> m ()
- ofoldrM :: (Int -> e -> r -> m r) -> r -> l -> m r
- ofoldlM :: (Int -> r -> e -> m r) -> r -> l -> m r
- ofoldrM' :: (Int -> e -> r -> m r) -> r -> l -> m r
- ofoldlM' :: (Int -> r -> e -> m r) -> r -> l -> m r
- foldrM :: (e -> r -> m r) -> r -> l -> m r
- foldlM :: (r -> e -> m r) -> r -> l -> m r
- foldrM' :: (e -> r -> m r) -> r -> l -> m r
- foldlM' :: (r -> e -> m r) -> r -> l -> m r
- swapM :: l -> Int -> Int -> m ()
- type LinearM1 m l e = LinearM m (l e) e
- class LinearM m s e => SplitM m s e where
- takeM :: Int -> s -> m s
- dropM :: Int -> s -> m s
- keepM :: Int -> s -> m s
- sansM :: Int -> s -> m s
- splitM :: Int -> s -> m (s, s)
- divideM :: Int -> s -> m (s, s)
- splitsM :: Foldable f => f Int -> s -> m [s]
- dividesM :: Foldable f => f Int -> s -> m [s]
- partsM :: Foldable f => f Int -> s -> m [s]
- chunksM :: Int -> s -> m [s]
- eachM :: Int -> s -> m s
- prefixM :: (e -> Bool) -> s -> m Int
- suffixM :: (e -> Bool) -> s -> m Int
- mprefix :: (e -> m Bool) -> s -> m Int
- msuffix :: (e -> m Bool) -> s -> m Int
- type SplitM1 m l e = SplitM m (l e) e
Exports
module SDP.Linear
BorderedM class
class (Monad m, Index i) => BorderedM m b i | b -> m, b -> i where Source #
getBounds :: b -> m (i, i) Source #
getSizeOf :: b -> m Int Source #
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
type BorderedM1 m l i e = BorderedM m (l e) i Source #
Kind (* -> *)
BorderedM
structure.
type BorderedM2 m l i e = BorderedM m (l i e) i Source #
Kind (* -> * -> *)
BorderedM
structure.
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.
Monadic single
.
nowNull :: l -> m Bool Source #
Monadic isNull
.
Monadic single
.
getHead
is monadic version of head
. This procedure mustn't modify the
source structure or return references to its mutable fields.
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.
Create copy.
copied' :: l -> Int -> Int -> m l Source #
copied' es l n
returns the slice of es
from l
of length n
.
Monadic reverse
.
merged :: Foldable f => f l -> m l Source #
Monadic concat
.
filled :: Int -> e -> m l Source #
Monadic version of replicate
.
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 #
ofoldlM' :: (Int -> r -> e -> m r) -> r -> l -> m r Source #
foldrM :: (e -> r -> m r) -> r -> l -> m r Source #
foldlM :: (r -> e -> m r) -> r -> l -> m r Source #
foldrM' :: (e -> r -> m r) -> r -> l -> m r Source #
foldlM' :: (r -> e -> m r) -> r -> l -> m r Source #
swapM :: l -> Int -> Int -> m () Source #
Just swap two elements.
Instances
LinearM STM (TArray# e) e Source # | |
Defined in SDP.Prim.TArray 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 # merged :: Foldable f => f (TArray# e) -> STM (TArray# e) Source # filled :: Int -> e -> STM (TArray# e) 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 # | |
(MonadIO io, Unboxed e) => LinearM io (MIOBytes# io e) e Source # | |
Defined in SDP.Prim.SBytes 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 # merged :: Foldable f => f (MIOBytes# io e) -> io (MIOBytes# io e) Source # filled :: Int -> e -> io (MIOBytes# io e) 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 # | |
MonadIO io => LinearM io (MIOArray# io e) e Source # | |
Defined in SDP.Prim.SArray 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 # merged :: Foldable f => f (MIOArray# io e) -> io (MIOArray# io e) Source # filled :: Int -> e -> io (MIOArray# io e) 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 # | |
(BorderedM1 m rep Int e, SplitM1 m rep e) => LinearM m (AnyChunks rep e) e Source # | |
Defined in SDP.Templates.AnyChunks 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 # merged :: Foldable f => f (AnyChunks rep e) -> m (AnyChunks rep e) Source # filled :: Int -> e -> m (AnyChunks rep e) 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 # | |
(Index i, LinearM1 m rep e, BorderedM1 m rep Int e) => LinearM m (AnyBorder rep i e) e Source # | |
Defined in SDP.Templates.AnyBorder 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 # merged :: Foldable f => f (AnyBorder rep i e) -> m (AnyBorder rep i e) Source # filled :: Int -> e -> m (AnyBorder rep i e) 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 # | |
Unboxed e => LinearM (ST s) (STBytes# s e) e Source # | |
Defined in SDP.Prim.SBytes 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 # merged :: Foldable f => f (STBytes# s e) -> ST s (STBytes# s e) Source # filled :: Int -> e -> ST s (STBytes# s e) 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 # | |
LinearM (ST s) (STArray# s e) e Source # | |
Defined in SDP.Prim.SArray 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 # merged :: Foldable f => f (STArray# s e) -> ST s (STArray# s e) Source # filled :: Int -> e -> ST s (STArray# s e) 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 # |
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.
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.
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.
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.
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.
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
.