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 HaskellTrustworthy
LanguageHaskell2010

SDP.Linear

Description

SDP.Linear is a module that provides several convenient interfaces for working with various linear data structures.

Synopsis

Exports

module SDP.Index

module SDP.Sort

module SDP.Zip

Bordered class

class (Index i, Estimate b) => Bordered b i | b -> i where Source #

Class of bordered data structures.

Minimal complete definition

(bounds | lower, upper)

Methods

bounds :: b -> (i, i) Source #

Returns the exact upper and lower bounds of given structure. If the structure doesn't have explicitly defined boundaries (list, for example), use the defaultBounds . sizeOf.

lower :: b -> i Source #

Returns lower bound of structure

upper :: b -> i Source #

Returns upper bound of structure

sizeOf :: b -> Int Source #

Returns actual size of structure.

sizesOf :: b -> [Int] Source #

Returns actual sizes of structure.

indexIn :: b -> i -> Bool Source #

Checks if an index falls within the boundaries of the structure.

indices :: b -> [i] Source #

Returns index range list.

indexOf :: b -> Int -> i Source #

Returns index by offset in structure.

offsetOf :: b -> i -> Int Source #

Returns index offset in structure bounds.

Instances

Instances details
Bordered [e] Int Source # 
Instance details

Defined in SDP.Linear

Methods

bounds :: [e] -> (Int, Int) Source #

lower :: [e] -> Int Source #

upper :: [e] -> Int Source #

sizeOf :: [e] -> Int Source #

sizesOf :: [e] -> [Int] Source #

indexIn :: [e] -> Int -> Bool Source #

indices :: [e] -> [Int] Source #

indexOf :: [e] -> Int -> Int Source #

offsetOf :: [e] -> Int -> Int Source #

Bordered (SBytes# e) Int Source # 
Instance details

Defined in SDP.Prim.SBytes

Bordered (SArray# e) Int Source # 
Instance details

Defined in SDP.Prim.SArray

Bordered (TArray# e) Int Source # 
Instance details

Defined in SDP.Prim.TArray

Index i => Bordered (i, i) i Source # 
Instance details

Defined in SDP.Linear

Methods

bounds :: (i, i) -> (i, i) Source #

lower :: (i, i) -> i Source #

upper :: (i, i) -> i Source #

sizeOf :: (i, i) -> Int Source #

sizesOf :: (i, i) -> [Int] Source #

indexIn :: (i, i) -> i -> Bool Source #

indices :: (i, i) -> [i] Source #

indexOf :: (i, i) -> Int -> i Source #

offsetOf :: (i, i) -> i -> Int Source #

Bordered (MIOBytes# io e) Int Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

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

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

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

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

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

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

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

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

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

Bordered (STBytes# s e) Int Source # 
Instance details

Defined in SDP.Prim.SBytes

Bordered (MIOArray# io e) Int Source # 
Instance details

Defined in SDP.Prim.SArray

Methods

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

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

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

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

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

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

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

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

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

Bordered (STArray# s e) Int Source # 
Instance details

Defined in SDP.Prim.SArray

Bordered1 rep Int e => Bordered (AnyChunks rep e) Int Source # 
Instance details

Defined in SDP.Templates.AnyChunks

Methods

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

lower :: AnyChunks rep e -> Int Source #

upper :: AnyChunks rep e -> Int Source #

sizeOf :: AnyChunks rep e -> Int Source #

sizesOf :: AnyChunks rep e -> [Int] Source #

indexIn :: AnyChunks rep e -> Int -> Bool Source #

indices :: AnyChunks rep e -> [Int] Source #

indexOf :: AnyChunks rep e -> Int -> Int Source #

offsetOf :: AnyChunks rep e -> Int -> Int Source #

Index i => Bordered (AnyBorder rep i e) i Source # 
Instance details

Defined in SDP.Templates.AnyBorder

Methods

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

lower :: AnyBorder rep i e -> i Source #

upper :: AnyBorder rep i e -> i Source #

sizeOf :: AnyBorder rep i e -> Int Source #

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

indexIn :: AnyBorder rep i e -> i -> Bool Source #

indices :: AnyBorder rep i e -> [i] Source #

indexOf :: AnyBorder rep i e -> Int -> i Source #

offsetOf :: AnyBorder rep i e -> i -> Int Source #

type Bordered1 l i e = Bordered (l e) i Source #

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

type Bordered2 l i e = Bordered (l i e) i Source #

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

Linear class

class Nullable l => Linear l e | l -> e where Source #

Class of list-like data structures, which

  • can be converted to and from list
  • can be created from singleton or Foldable stream
  • support filter operations, separation, concatenation and selection
  • It can be represented as head, tail, init and last elements and constructed from head and tail or init and last.

Minimal complete definition

(listL | listR), (fromList | fromFoldable), (head, tail | uncons), (init, last | unsnoc)

Methods

uncons :: l -> (e, l) Source #

Separates line to head and tail, deconstructor for :> pattern.

uncons' :: l -> Maybe (e, l) Source #

Same as isNull ?- uncons

toHead :: e -> l -> l Source #

Prepends element to line, constructor for :> pattern.

head :: l -> e Source #

Returns first element of line, may fail.

tail :: l -> l Source #

Returns line except first, may fail.

unsnoc :: l -> (l, e) Source #

Separates line to init and last, deconstructor for :< pattern.

unsnoc' :: l -> Maybe (l, e) Source #

Same as isNull ?- unsnoc

toLast :: l -> e -> l Source #

Appends element to line, constructor for :< pattern.

init :: l -> l Source #

Returns line except last element, may fail.

last :: l -> e Source #

Returns last element, may fail.

single :: e -> l Source #

Just singleton.

(++) :: l -> l -> l infixr 5 Source #

Concatenation of two lines.

replicate :: Int -> e -> l Source #

replicate n e returns a line of n repetitions of the element e.

fromList :: [e] -> l Source #

Creates line from list.

fromListN :: Int -> [e] -> l Source #

Create finite line from (possibly infinite) list.

listR :: l -> [e] Source #

Right to left view of line.

listL :: l -> [e] Source #

Left to right view of line, same to toList.

fromFoldable :: Foldable f => f e -> l Source #

Generalized fromList.

(!^) :: l -> Int -> e infixl 9 Source #

Returns the element of a sequence by offset, may be completely unsafe. This is an optimistic read function and shouldn't perform checks for efficiency reasons.

If you need safety, use (!) or (!?). The generalization of this function by index type (.!).

es !^ i = listL es !! i

write :: l -> Int -> e -> l Source #

write es n e writes value e in position n (offset), returns new structure. If n is out of range, returns equal structure (es or copy).

concat :: Foldable f => f l -> l Source #

Generalized concat.

concatMap :: Foldable f => (a -> l) -> f a -> l Source #

Generalized concatMap.

intersperse :: e -> l -> l Source #

Generalized intersperse.

filter :: (e -> Bool) -> l -> l infix 8 Source #

Generalized filter.

except :: (e -> Bool) -> l -> l infix 8 Source #

Inverted filter.

partition :: (e -> Bool) -> l -> (l, l) Source #

Generalization of partition.

partitions :: Foldable f => f (e -> Bool) -> l -> [l] Source #

Generalization of partition, that select sublines by predicates.

select :: (e -> Maybe a) -> l -> [a] Source #

select f es is selective map of es elements to new list.

select' :: (t e ~ l, Linear1 t a) => (e -> Maybe a) -> l -> t a Source #

select' f es is selective map of es elements to new line.

extract :: (e -> Maybe a) -> l -> ([a], l) Source #

extract f es returns a selective map of es elements to new list and the remaining elements of the line.

extract' :: (t e ~ l, Linear1 t a) => (e -> Maybe a) -> l -> (t a, l) Source #

extract' f es returns a selective map of es elements to new line and the remaining elements of the line.

selects :: Foldable f => f (e -> Maybe a) -> l -> ([[a]], l) Source #

selects fs es sequentially applies the functions from fs to the remainder of es, returns a list of selections and the remainder of the last selection.

selects' :: (Foldable f, t e ~ l, Linear1 t a) => f (e -> Maybe a) -> l -> ([t a], l) Source #

selects' fs es sequentially applies the functions from fs to the remainder of es, returns a line of selections and the remainder of the last selection.

isSubseqOf :: Eq e => l -> l -> Bool Source #

The isSubseqOf xs ys checks if all the elements of the xs occur, in order, in the ys. The elements don't have to occur consecutively.

reverse :: l -> l Source #

Generalized reverse.

force :: l -> l Source #

O(1) force, same as id.

before :: l -> Int -> e -> l Source #

before es i e insert e to es before element with offset i. If i goes beyond the lower or upper bounds, e is prepended or appended to es respectively.

before [0 .. 5] (-1) 7 == [7,0,1,2,3,4,5]
before [0 .. 5]   0  7 == [7,0,1,2,3,4,5]
before [0 .. 5]   3  7 == [0,1,2,7,3,4,5]
before [0 .. 5]   5  7 == [0,1,2,3,4,7,5]
before [0 .. 5]  19  7 == [0,1,2,3,4,5,7]

Since: 0.2.1

after :: l -> Int -> e -> l Source #

after es i e insert e to es after element with offset i.

after es i e == before es (i + 1) e

Since: 0.2.1

remove :: Int -> l -> l Source #

remove es i delete element with offset i from es.

remove (-1) [0 .. 5] == [0 .. 5]
remove   6  [0 .. 5] == [0 .. 5]
remove   0  [0 .. 5] == [1,2,3,4,5]
remove   3  [0 .. 5] == [0,1,2,4,5]
remove   5  [0 .. 5] == [0,1,2,3,4]

Since: 0.2.1

subsequences :: l -> [l] Source #

Generalized subsequences.

iterate :: Int -> (e -> e) -> e -> l Source #

iterate n f x returns sequence of n applications of f to x.

Note that iterate returns finite sequence, instead Prelude prototype.

nub :: Eq e => l -> l Source #

Same as nubBy (==).

nubBy :: Equal e -> l -> l Source #

Generalization of nubBy.

ofoldr :: (Int -> e -> b -> b) -> b -> l -> b Source #

ofoldr is right fold with offset.

ofoldl :: (Int -> b -> e -> b) -> b -> l -> b Source #

ofoldl is left fold with offset.

ofoldr' :: (Int -> e -> b -> b) -> b -> l -> b Source #

ofoldr' is strict version of ofoldr.

ofoldl' :: (Int -> b -> e -> b) -> b -> l -> b Source #

ofoldl' is strict version of ofoldl.

o_foldr :: (e -> b -> b) -> b -> l -> b Source #

o_foldr is just foldr in Linear context.

o_foldl :: (b -> e -> b) -> b -> l -> b Source #

o_foldl is just foldl in Linear context.

o_foldr' :: (e -> b -> b) -> b -> l -> b Source #

o_foldr' is just foldr' in Linear context.

o_foldl' :: (b -> e -> b) -> b -> l -> b Source #

o_foldl' is just foldl' in Linear context.

o_foldr1 :: (e -> e -> e) -> l -> e Source #

o_foldr1 is just foldr1 in Linear context.

Since: 0.2.1

o_foldl1 :: (e -> e -> e) -> l -> e Source #

o_foldl1 is just foldl1 in Linear context.

Since: 0.2.1

o_foldr1' :: (e -> e -> e) -> l -> e Source #

o_foldr1' is just strict foldr1 in Linear context.

Since: 0.2.1

o_foldl1' :: (e -> e -> e) -> l -> e Source #

o_foldl1' is just foldl1' in Linear context.

Since: 0.2.1

Instances

Instances details
Linear [e] e Source # 
Instance details

Defined in SDP.Linear

Methods

uncons :: [e] -> (e, [e]) Source #

uncons' :: [e] -> Maybe (e, [e]) Source #

toHead :: e -> [e] -> [e] Source #

head :: [e] -> e Source #

tail :: [e] -> [e] Source #

unsnoc :: [e] -> ([e], e) Source #

unsnoc' :: [e] -> Maybe ([e], e) Source #

toLast :: [e] -> e -> [e] Source #

init :: [e] -> [e] Source #

last :: [e] -> e Source #

single :: e -> [e] Source #

(++) :: [e] -> [e] -> [e] Source #

replicate :: Int -> e -> [e] Source #

fromList :: [e] -> [e] Source #

fromListN :: Int -> [e] -> [e] Source #

listR :: [e] -> [e] Source #

listL :: [e] -> [e] Source #

fromFoldable :: Foldable f => f e -> [e] Source #

(!^) :: [e] -> Int -> e Source #

write :: [e] -> Int -> e -> [e] Source #

concat :: Foldable f => f [e] -> [e] Source #

concatMap :: Foldable f => (a -> [e]) -> f a -> [e] Source #

intersperse :: e -> [e] -> [e] Source #

filter :: (e -> Bool) -> [e] -> [e] Source #

except :: (e -> Bool) -> [e] -> [e] Source #

partition :: (e -> Bool) -> [e] -> ([e], [e]) Source #

partitions :: Foldable f => f (e -> Bool) -> [e] -> [[e]] Source #

select :: (e -> Maybe a) -> [e] -> [a] Source #

select' :: (t e ~ [e], Linear1 t a) => (e -> Maybe a) -> [e] -> t a Source #

extract :: (e -> Maybe a) -> [e] -> ([a], [e]) Source #

extract' :: (t e ~ [e], Linear1 t a) => (e -> Maybe a) -> [e] -> (t a, [e]) Source #

selects :: Foldable f => f (e -> Maybe a) -> [e] -> ([[a]], [e]) Source #

selects' :: (Foldable f, t e ~ [e], Linear1 t a) => f (e -> Maybe a) -> [e] -> ([t a], [e]) Source #

isSubseqOf :: [e] -> [e] -> Bool Source #

reverse :: [e] -> [e] Source #

force :: [e] -> [e] Source #

before :: [e] -> Int -> e -> [e] Source #

after :: [e] -> Int -> e -> [e] Source #

remove :: Int -> [e] -> [e] Source #

subsequences :: [e] -> [[e]] Source #

iterate :: Int -> (e -> e) -> e -> [e] Source #

nub :: [e] -> [e] Source #

nubBy :: Equal e -> [e] -> [e] Source #

ofoldr :: (Int -> e -> b -> b) -> b -> [e] -> b Source #

ofoldl :: (Int -> b -> e -> b) -> b -> [e] -> b Source #

ofoldr' :: (Int -> e -> b -> b) -> b -> [e] -> b Source #

ofoldl' :: (Int -> b -> e -> b) -> b -> [e] -> b Source #

o_foldr :: (e -> b -> b) -> b -> [e] -> b Source #

o_foldl :: (b -> e -> b) -> b -> [e] -> b Source #

o_foldr' :: (e -> b -> b) -> b -> [e] -> b Source #

o_foldl' :: (b -> e -> b) -> b -> [e] -> b Source #

o_foldr1 :: (e -> e -> e) -> [e] -> e Source #

o_foldl1 :: (e -> e -> e) -> [e] -> e Source #

o_foldr1' :: (e -> e -> e) -> [e] -> e Source #

o_foldl1' :: (e -> e -> e) -> [e] -> e Source #

Unboxed e => Linear (SBytes# e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

uncons :: SBytes# e -> (e, SBytes# e) Source #

uncons' :: SBytes# e -> Maybe (e, SBytes# e) Source #

toHead :: e -> SBytes# e -> SBytes# e Source #

head :: SBytes# e -> e Source #

tail :: SBytes# e -> SBytes# e Source #

unsnoc :: SBytes# e -> (SBytes# e, e) Source #

unsnoc' :: SBytes# e -> Maybe (SBytes# e, e) Source #

toLast :: SBytes# e -> e -> SBytes# e Source #

init :: SBytes# e -> SBytes# e Source #

last :: SBytes# e -> e Source #

single :: e -> SBytes# e Source #

(++) :: SBytes# e -> SBytes# e -> SBytes# e Source #

replicate :: Int -> e -> SBytes# e Source #

fromList :: [e] -> SBytes# e Source #

fromListN :: Int -> [e] -> SBytes# e Source #

listR :: SBytes# e -> [e] Source #

listL :: SBytes# e -> [e] Source #

fromFoldable :: Foldable f => f e -> SBytes# e Source #

(!^) :: SBytes# e -> Int -> e Source #

write :: SBytes# e -> Int -> e -> SBytes# e Source #

concat :: Foldable f => f (SBytes# e) -> SBytes# e Source #

concatMap :: Foldable f => (a -> SBytes# e) -> f a -> SBytes# e Source #

intersperse :: e -> SBytes# e -> SBytes# e Source #

filter :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

except :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

partition :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

partitions :: Foldable f => f (e -> Bool) -> SBytes# e -> [SBytes# e] Source #

select :: (e -> Maybe a) -> SBytes# e -> [a] Source #

select' :: (t e ~ SBytes# e, Linear1 t a) => (e -> Maybe a) -> SBytes# e -> t a Source #

extract :: (e -> Maybe a) -> SBytes# e -> ([a], SBytes# e) Source #

extract' :: (t e ~ SBytes# e, Linear1 t a) => (e -> Maybe a) -> SBytes# e -> (t a, SBytes# e) Source #

selects :: Foldable f => f (e -> Maybe a) -> SBytes# e -> ([[a]], SBytes# e) Source #

selects' :: (Foldable f, t e ~ SBytes# e, Linear1 t a) => f (e -> Maybe a) -> SBytes# e -> ([t a], SBytes# e) Source #

isSubseqOf :: SBytes# e -> SBytes# e -> Bool Source #

reverse :: SBytes# e -> SBytes# e Source #

force :: SBytes# e -> SBytes# e Source #

before :: SBytes# e -> Int -> e -> SBytes# e Source #

after :: SBytes# e -> Int -> e -> SBytes# e Source #

remove :: Int -> SBytes# e -> SBytes# e Source #

subsequences :: SBytes# e -> [SBytes# e] Source #

iterate :: Int -> (e -> e) -> e -> SBytes# e Source #

nub :: SBytes# e -> SBytes# e Source #

nubBy :: Equal e -> SBytes# e -> SBytes# e Source #

ofoldr :: (Int -> e -> b -> b) -> b -> SBytes# e -> b Source #

ofoldl :: (Int -> b -> e -> b) -> b -> SBytes# e -> b Source #

ofoldr' :: (Int -> e -> b -> b) -> b -> SBytes# e -> b Source #

ofoldl' :: (Int -> b -> e -> b) -> b -> SBytes# e -> b Source #

o_foldr :: (e -> b -> b) -> b -> SBytes# e -> b Source #

o_foldl :: (b -> e -> b) -> b -> SBytes# e -> b Source #

o_foldr' :: (e -> b -> b) -> b -> SBytes# e -> b Source #

o_foldl' :: (b -> e -> b) -> b -> SBytes# e -> b Source #

o_foldr1 :: (e -> e -> e) -> SBytes# e -> e Source #

o_foldl1 :: (e -> e -> e) -> SBytes# e -> e Source #

o_foldr1' :: (e -> e -> e) -> SBytes# e -> e Source #

o_foldl1' :: (e -> e -> e) -> SBytes# e -> e Source #

Linear (SArray# e) e Source # 
Instance details

Defined in SDP.Prim.SArray

Methods

uncons :: SArray# e -> (e, SArray# e) Source #

uncons' :: SArray# e -> Maybe (e, SArray# e) Source #

toHead :: e -> SArray# e -> SArray# e Source #

head :: SArray# e -> e Source #

tail :: SArray# e -> SArray# e Source #

unsnoc :: SArray# e -> (SArray# e, e) Source #

unsnoc' :: SArray# e -> Maybe (SArray# e, e) Source #

toLast :: SArray# e -> e -> SArray# e Source #

init :: SArray# e -> SArray# e Source #

last :: SArray# e -> e Source #

single :: e -> SArray# e Source #

(++) :: SArray# e -> SArray# e -> SArray# e Source #

replicate :: Int -> e -> SArray# e Source #

fromList :: [e] -> SArray# e Source #

fromListN :: Int -> [e] -> SArray# e Source #

listR :: SArray# e -> [e] Source #

listL :: SArray# e -> [e] Source #

fromFoldable :: Foldable f => f e -> SArray# e Source #

(!^) :: SArray# e -> Int -> e Source #

write :: SArray# e -> Int -> e -> SArray# e Source #

concat :: Foldable f => f (SArray# e) -> SArray# e Source #

concatMap :: Foldable f => (a -> SArray# e) -> f a -> SArray# e Source #

intersperse :: e -> SArray# e -> SArray# e Source #

filter :: (e -> Bool) -> SArray# e -> SArray# e Source #

except :: (e -> Bool) -> SArray# e -> SArray# e Source #

partition :: (e -> Bool) -> SArray# e -> (SArray# e, SArray# e) Source #

partitions :: Foldable f => f (e -> Bool) -> SArray# e -> [SArray# e] Source #

select :: (e -> Maybe a) -> SArray# e -> [a] Source #

select' :: (t e ~ SArray# e, Linear1 t a) => (e -> Maybe a) -> SArray# e -> t a Source #

extract :: (e -> Maybe a) -> SArray# e -> ([a], SArray# e) Source #

extract' :: (t e ~ SArray# e, Linear1 t a) => (e -> Maybe a) -> SArray# e -> (t a, SArray# e) Source #

selects :: Foldable f => f (e -> Maybe a) -> SArray# e -> ([[a]], SArray# e) Source #

selects' :: (Foldable f, t e ~ SArray# e, Linear1 t a) => f (e -> Maybe a) -> SArray# e -> ([t a], SArray# e) Source #

isSubseqOf :: SArray# e -> SArray# e -> Bool Source #

reverse :: SArray# e -> SArray# e Source #

force :: SArray# e -> SArray# e Source #

before :: SArray# e -> Int -> e -> SArray# e Source #

after :: SArray# e -> Int -> e -> SArray# e Source #

remove :: Int -> SArray# e -> SArray# e Source #

subsequences :: SArray# e -> [SArray# e] Source #

iterate :: Int -> (e -> e) -> e -> SArray# e Source #

nub :: SArray# e -> SArray# e Source #

nubBy :: Equal e -> SArray# e -> SArray# e Source #

ofoldr :: (Int -> e -> b -> b) -> b -> SArray# e -> b Source #

ofoldl :: (Int -> b -> e -> b) -> b -> SArray# e -> b Source #

ofoldr' :: (Int -> e -> b -> b) -> b -> SArray# e -> b Source #

ofoldl' :: (Int -> b -> e -> b) -> b -> SArray# e -> b Source #

o_foldr :: (e -> b -> b) -> b -> SArray# e -> b Source #

o_foldl :: (b -> e -> b) -> b -> SArray# e -> b Source #

o_foldr' :: (e -> b -> b) -> b -> SArray# e -> b Source #

o_foldl' :: (b -> e -> b) -> b -> SArray# e -> b Source #

o_foldr1 :: (e -> e -> e) -> SArray# e -> e Source #

o_foldl1 :: (e -> e -> e) -> SArray# e -> e Source #

o_foldr1' :: (e -> e -> e) -> SArray# e -> e Source #

o_foldl1' :: (e -> e -> e) -> SArray# e -> e Source #

(Bordered1 rep Int e, Linear1 rep e) => Linear (AnyChunks rep e) e Source # 
Instance details

Defined in SDP.Templates.AnyChunks

Methods

uncons :: AnyChunks rep e -> (e, AnyChunks rep e) Source #

uncons' :: AnyChunks rep e -> Maybe (e, AnyChunks rep e) Source #

toHead :: e -> AnyChunks rep e -> AnyChunks rep e Source #

head :: AnyChunks rep e -> e Source #

tail :: AnyChunks rep e -> AnyChunks rep e Source #

unsnoc :: AnyChunks rep e -> (AnyChunks rep e, e) Source #

unsnoc' :: AnyChunks rep e -> Maybe (AnyChunks rep e, e) Source #

toLast :: AnyChunks rep e -> e -> AnyChunks rep e Source #

init :: AnyChunks rep e -> AnyChunks rep e Source #

last :: AnyChunks rep e -> e Source #

single :: e -> AnyChunks rep e Source #

(++) :: AnyChunks rep e -> AnyChunks rep e -> AnyChunks rep e Source #

replicate :: Int -> e -> AnyChunks rep e Source #

fromList :: [e] -> AnyChunks rep e Source #

fromListN :: Int -> [e] -> AnyChunks rep e Source #

listR :: AnyChunks rep e -> [e] Source #

listL :: AnyChunks rep e -> [e] Source #

fromFoldable :: Foldable f => f e -> AnyChunks rep e Source #

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

write :: AnyChunks rep e -> Int -> e -> AnyChunks rep e Source #

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

concatMap :: Foldable f => (a -> AnyChunks rep e) -> f a -> AnyChunks rep e Source #

intersperse :: e -> AnyChunks rep e -> AnyChunks rep e Source #

filter :: (e -> Bool) -> AnyChunks rep e -> AnyChunks rep e Source #

except :: (e -> Bool) -> AnyChunks rep e -> AnyChunks rep e Source #

partition :: (e -> Bool) -> AnyChunks rep e -> (AnyChunks rep e, AnyChunks rep e) Source #

partitions :: Foldable f => f (e -> Bool) -> AnyChunks rep e -> [AnyChunks rep e] Source #

select :: (e -> Maybe a) -> AnyChunks rep e -> [a] Source #

select' :: (t e ~ AnyChunks rep e, Linear1 t a) => (e -> Maybe a) -> AnyChunks rep e -> t a Source #

extract :: (e -> Maybe a) -> AnyChunks rep e -> ([a], AnyChunks rep e) Source #

extract' :: (t e ~ AnyChunks rep e, Linear1 t a) => (e -> Maybe a) -> AnyChunks rep e -> (t a, AnyChunks rep e) Source #

selects :: Foldable f => f (e -> Maybe a) -> AnyChunks rep e -> ([[a]], AnyChunks rep e) Source #

selects' :: (Foldable f, t e ~ AnyChunks rep e, Linear1 t a) => f (e -> Maybe a) -> AnyChunks rep e -> ([t a], AnyChunks rep e) Source #

isSubseqOf :: AnyChunks rep e -> AnyChunks rep e -> Bool Source #

reverse :: AnyChunks rep e -> AnyChunks rep e Source #

force :: AnyChunks rep e -> AnyChunks rep e Source #

before :: AnyChunks rep e -> Int -> e -> AnyChunks rep e Source #

after :: AnyChunks rep e -> Int -> e -> AnyChunks rep e Source #

remove :: Int -> AnyChunks rep e -> AnyChunks rep e Source #

subsequences :: AnyChunks rep e -> [AnyChunks rep e] Source #

iterate :: Int -> (e -> e) -> e -> AnyChunks rep e Source #

nub :: AnyChunks rep e -> AnyChunks rep e Source #

nubBy :: Equal e -> AnyChunks rep e -> AnyChunks rep e Source #

ofoldr :: (Int -> e -> b -> b) -> b -> AnyChunks rep e -> b Source #

ofoldl :: (Int -> b -> e -> b) -> b -> AnyChunks rep e -> b Source #

ofoldr' :: (Int -> e -> b -> b) -> b -> AnyChunks rep e -> b Source #

ofoldl' :: (Int -> b -> e -> b) -> b -> AnyChunks rep e -> b Source #

o_foldr :: (e -> b -> b) -> b -> AnyChunks rep e -> b Source #

o_foldl :: (b -> e -> b) -> b -> AnyChunks rep e -> b Source #

o_foldr' :: (e -> b -> b) -> b -> AnyChunks rep e -> b Source #

o_foldl' :: (b -> e -> b) -> b -> AnyChunks rep e -> b Source #

o_foldr1 :: (e -> e -> e) -> AnyChunks rep e -> e Source #

o_foldl1 :: (e -> e -> e) -> AnyChunks rep e -> e Source #

o_foldr1' :: (e -> e -> e) -> AnyChunks rep e -> e Source #

o_foldl1' :: (e -> e -> e) -> AnyChunks rep e -> e Source #

(Index i, Linear1 rep e, Bordered1 rep Int e) => Linear (AnyBorder rep i e) e Source # 
Instance details

Defined in SDP.Templates.AnyBorder

Methods

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

uncons' :: AnyBorder rep i e -> Maybe (e, AnyBorder rep i e) Source #

toHead :: e -> AnyBorder rep i e -> AnyBorder rep i e Source #

head :: AnyBorder rep i e -> e Source #

tail :: AnyBorder rep i e -> AnyBorder rep i e Source #

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

unsnoc' :: AnyBorder rep i e -> Maybe (AnyBorder rep i e, e) Source #

toLast :: AnyBorder rep i e -> e -> AnyBorder rep i e Source #

init :: AnyBorder rep i e -> AnyBorder rep i e Source #

last :: AnyBorder rep i e -> e Source #

single :: e -> AnyBorder rep i e Source #

(++) :: AnyBorder rep i e -> AnyBorder rep i e -> AnyBorder rep i e Source #

replicate :: Int -> e -> AnyBorder rep i e Source #

fromList :: [e] -> AnyBorder rep i e Source #

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

listR :: AnyBorder rep i e -> [e] Source #

listL :: AnyBorder rep i e -> [e] Source #

fromFoldable :: Foldable f => f e -> AnyBorder rep i e Source #

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

write :: AnyBorder rep i e -> Int -> e -> AnyBorder rep i e Source #

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

concatMap :: Foldable f => (a -> AnyBorder rep i e) -> f a -> AnyBorder rep i e Source #

intersperse :: e -> AnyBorder rep i e -> AnyBorder rep i e Source #

filter :: (e -> Bool) -> AnyBorder rep i e -> AnyBorder rep i e Source #

except :: (e -> Bool) -> AnyBorder rep i e -> AnyBorder rep i e Source #

partition :: (e -> Bool) -> AnyBorder rep i e -> (AnyBorder rep i e, AnyBorder rep i e) Source #

partitions :: Foldable f => f (e -> Bool) -> AnyBorder rep i e -> [AnyBorder rep i e] Source #

select :: (e -> Maybe a) -> AnyBorder rep i e -> [a] Source #

select' :: (t e ~ AnyBorder rep i e, Linear1 t a) => (e -> Maybe a) -> AnyBorder rep i e -> t a Source #

extract :: (e -> Maybe a) -> AnyBorder rep i e -> ([a], AnyBorder rep i e) Source #

extract' :: (t e ~ AnyBorder rep i e, Linear1 t a) => (e -> Maybe a) -> AnyBorder rep i e -> (t a, AnyBorder rep i e) Source #

selects :: Foldable f => f (e -> Maybe a) -> AnyBorder rep i e -> ([[a]], AnyBorder rep i e) Source #

selects' :: (Foldable f, t e ~ AnyBorder rep i e, Linear1 t a) => f (e -> Maybe a) -> AnyBorder rep i e -> ([t a], AnyBorder rep i e) Source #

isSubseqOf :: AnyBorder rep i e -> AnyBorder rep i e -> Bool Source #

reverse :: AnyBorder rep i e -> AnyBorder rep i e Source #

force :: AnyBorder rep i e -> AnyBorder rep i e Source #

before :: AnyBorder rep i e -> Int -> e -> AnyBorder rep i e Source #

after :: AnyBorder rep i e -> Int -> e -> AnyBorder rep i e Source #

remove :: Int -> AnyBorder rep i e -> AnyBorder rep i e Source #

subsequences :: AnyBorder rep i e -> [AnyBorder rep i e] Source #

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

nub :: AnyBorder rep i e -> AnyBorder rep i e Source #

nubBy :: Equal e -> AnyBorder rep i e -> AnyBorder rep i e Source #

ofoldr :: (Int -> e -> b -> b) -> b -> AnyBorder rep i e -> b Source #

ofoldl :: (Int -> b -> e -> b) -> b -> AnyBorder rep i e -> b Source #

ofoldr' :: (Int -> e -> b -> b) -> b -> AnyBorder rep i e -> b Source #

ofoldl' :: (Int -> b -> e -> b) -> b -> AnyBorder rep i e -> b Source #

o_foldr :: (e -> b -> b) -> b -> AnyBorder rep i e -> b Source #

o_foldl :: (b -> e -> b) -> b -> AnyBorder rep i e -> b Source #

o_foldr' :: (e -> b -> b) -> b -> AnyBorder rep i e -> b Source #

o_foldl' :: (b -> e -> b) -> b -> AnyBorder rep i e -> b Source #

o_foldr1 :: (e -> e -> e) -> AnyBorder rep i e -> e Source #

o_foldl1 :: (e -> e -> e) -> AnyBorder rep i e -> e Source #

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

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

type Linear1 l e = Linear (l e) e Source #

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

type Linear2 l i e = Linear (l i e) e Source #

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

pattern (:>) :: Linear l e => e -> l -> l infixr 5 Source #

Pattern (:>) is left-size view of line. Same as uncons and toHead.

pattern (:<) :: Linear l e => l -> e -> l infixl 5 Source #

Pattern (:<) is right-size view of line. Same as unsnoc and toLast.

Rank 2 quantified constraints

GHC 8.6.1+ only

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

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

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

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

type Linear' l = forall e. Linear (l e) e Source #

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

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

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

Split class

class Linear s e => Split s e | s -> e where Source #

Split - class of splittable data structures.

Minimal complete definition

(take | sans), (drop | keep)

Methods

take :: Int -> s -> s Source #

take n es takes first n elements of es.

default take :: Bordered s i => Int -> s -> s Source #

drop :: Int -> s -> s Source #

drop n es drops first n elements of es.

default drop :: Bordered s i => Int -> s -> s Source #

keep :: Int -> s -> s Source #

keep n es takes last n elements of es.

default keep :: Bordered s i => Int -> s -> s Source #

sans :: Int -> s -> s Source #

sans n es drops last n elements of es.

default sans :: Bordered s i => Int -> s -> s Source #

save :: Int -> s -> s Source #

save n es takes first n elements of es if n > 0 and last -n elements otherwise.

skip :: Int -> s -> s Source #

skip n es drops first n elements of es if n > 0 and last -n elements otherwise.

split :: Int -> s -> (s, s) Source #

split n es is same to (take n es, drop n es).

divide :: Int -> s -> (s, s) Source #

divide n es is same to (sans n es, keep n es).

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

Splits line into sequences of given sizes (left to right).

splits [5, 3, 12] ['a'..'z'] = ["abcde","fgh","ijklmnopqrst","uvwxyz"]

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

Splits line into sequences of given sizes (right to left).

divides [5,3,12] ['a'..'z'] == ["abcdef","ghijk","lmn","opqrstuvwxyz"]

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

Splits structures into parts by given offsets.

parts [0,5,6,12,26] ['a'..'z'] = ["","abcde","f","ghijkl","mnopqrstuvwxyz",""]
-- if previous offset is equal or greater, subline is empty and next
begins from previous:
parts [0, 5, 4, 12, 26] ['a' .. 'z'] = ["","abcde","","fghijklm","nopqrstuvwxyz",""]

chunks :: Int -> s -> [s] Source #

Splits structures into chunks of size n and the rest.

chunks x [] = [] -- forall x
chunks 0 es = [] -- forall es
chunks 3 [1 .. 10] == [[1,2,3],[4,5,6],[7,8,9],[10]]

splitBy :: (e -> Bool) -> s -> (s, s) Source #

Split line by first (left) separation element. If there is no such element, splitBy es = (es, Z).

splitBy (== '.') "foo" == ("foo","")
splitBy (== '.') "foo." == ("foo","")
splitBy (== '.') ".foo" == ("","foo")
splitBy (== '.') "foo.bar" == ("foo","bar")
splitBy (== '.') "foo.bar.baz" == ("foo","bar.baz")

divideBy :: (e -> Bool) -> s -> (s, s) Source #

Split line by last (right) separation element. If there is no such element, divide es = (Z, es).

divideBy (== '.') "foo" == ("","foo")
divideBy (== '.') ".foo" == ("","foo")
divideBy (== '.') "foo." == ("foo","")
divideBy (== '.') "foo.bar" == ("foo","bar")
divideBy (== '.') "foo.bar.baz" == ("foo.bar","baz")

splitsBy :: (e -> Bool) -> s -> [s] Source #

Splits line by separation elements.

splitsOn :: Eq e => s -> s -> [s] Source #

splitsOn sub line splits line by sub.

splitsOn "fo" "foobar bazfoobar1" == ["","obar baz","obar1"]

replaceBy :: Eq e => s -> s -> s -> s Source #

replaceBy sub new line replace every non-overlapping occurrence of sub in line with new.

replaceBy "foo" "bar" "foobafoorbaz" == "barbabarrbaz"

removeAll :: Eq e => s -> s -> s Source #

Removes every non-overlapping occurrence of sub with Z.

removeAll = concat ... splitsOn
(`replaceBy` Z) = removeAll

combo :: Equal e -> s -> Int Source #

combo f es returns the length of the es subsequence (left to tight) whose elements are in order f.

combo (<) [] == 0
combo (<) [1] == 1
combo (<) [7, 4, 12] == 1
combo (<) [1, 7, 3, 12] == 2

justifyL :: Int -> e -> s -> s Source #

justifyL n e es appends e elements if the es is shorter than n, justifyL n e es prepends (n - sizeOf es) elements e to es from the takes n elements if longer. left side if (sizeOf es < n). Otherwise returns the first n elements of es, like take n es do.

justifyR :: Int -> e -> s -> s Source #

justifyR n e es appends (n - sizeOf es) elements e to es from the right side if (sizeOf es < n). Otherwise returns the first n elements of es, like keep n es do.

each :: Int -> s -> s Source #

each n es returns each n-th element of structure. If n == 1, returns es. If n < 1, returns Z.

eachFrom :: Int -> Int -> s -> s Source #

eachFrom o n es returns each nth element of structure, beginning from o.

eachFrom o n = each n . drop o
eachFrom 0 2 [1 .. 20] == [2, 4 .. 20]
eachFrom 1 2 [1 .. 20] == [3, 5 .. 19]

isPrefixOf :: Eq e => s -> s -> Bool Source #

sub `isPrefixOf` es checks if sub is beginning of es.

isSuffixOf :: Eq e => s -> s -> Bool Source #

sub `isSuffixOf` es checks if sub is ending of es.

isInfixOf :: Eq e => s -> s -> Bool Source #

isInfixOf checks whether the first line is the substring of the second

prefix :: (e -> Bool) -> s -> Int Source #

prefix gives length of init, satisfying preducate.

suffix :: (e -> Bool) -> s -> Int Source #

suffix gives length of tail, satisfying predicate.

infixes :: Eq e => s -> s -> [Int] Source #

infixes inf es returns a list of inf positions in es, without intersections.

"" `infixes` es = []
"abba" `infixes` "baababba" == [4]
"abab" `infixes` "baababab" == [2]
"aaaa" `infixes` "aaaaaaaa" == [0, 4]

dropSide :: (e -> Bool) -> s -> s Source #

dropSide f = dropWhile f . dropEnd f.

takeWhile :: (e -> Bool) -> s -> s Source #

Takes the longest init by predicate.

dropWhile :: (e -> Bool) -> s -> s Source #

Drops the longest init by predicate.

takeEnd :: (e -> Bool) -> s -> s Source #

Takes the longest suffix by predicate.

dropEnd :: (e -> Bool) -> s -> s Source #

Drops the longest prefix by predicate.

spanl :: (e -> Bool) -> s -> (s, s) Source #

Left-side span.

breakl :: (e -> Bool) -> s -> (s, s) Source #

Left-side break.

spanr :: (e -> Bool) -> s -> (s, s) Source #

Right-side span.

breakr :: (e -> Bool) -> s -> (s, s) Source #

Right-side break.

selectWhile :: (e -> Maybe a) -> s -> [a] Source #

selectWhile f es selects results of applying f to es (left to right) untill first fail.

selectEnd :: (e -> Maybe a) -> s -> [a] Source #

selectEnd f es selects results of applying f to es (right to left) untill first fail.

extractWhile :: (e -> Maybe a) -> s -> ([a], s) Source #

extractWhile f es selects results of applying f to es (left to right) untill first fail. Returns selected results and rest of line.

extractEnd :: (e -> Maybe a) -> s -> (s, [a]) Source #

extractEnd f es selects results of applying f to es (right to left) untill first fail. Returns rest of line and selected results.

selectWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> s -> t a Source #

selectWhile' is selectWhile version for generalized structures.

selectEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> s -> t a Source #

selectEnd' is selectEnd version for generalized structures.

extractWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> s -> (t a, s) Source #

extractWhile' is extractWhile version for generalized structures.

extractEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> s -> (s, t a) Source #

extractEnd' is extractEnd version for generalized structures.

Instances

Instances details
Split [e] e Source # 
Instance details

Defined in SDP.Linear

Methods

take :: Int -> [e] -> [e] Source #

drop :: Int -> [e] -> [e] Source #

keep :: Int -> [e] -> [e] Source #

sans :: Int -> [e] -> [e] Source #

save :: Int -> [e] -> [e] Source #

skip :: Int -> [e] -> [e] Source #

split :: Int -> [e] -> ([e], [e]) Source #

divide :: Int -> [e] -> ([e], [e]) Source #

splits :: Foldable f => f Int -> [e] -> [[e]] Source #

divides :: Foldable f => f Int -> [e] -> [[e]] Source #

parts :: Foldable f => f Int -> [e] -> [[e]] Source #

chunks :: Int -> [e] -> [[e]] Source #

splitBy :: (e -> Bool) -> [e] -> ([e], [e]) Source #

divideBy :: (e -> Bool) -> [e] -> ([e], [e]) Source #

splitsBy :: (e -> Bool) -> [e] -> [[e]] Source #

splitsOn :: [e] -> [e] -> [[e]] Source #

replaceBy :: [e] -> [e] -> [e] -> [e] Source #

removeAll :: [e] -> [e] -> [e] Source #

combo :: Equal e -> [e] -> Int Source #

justifyL :: Int -> e -> [e] -> [e] Source #

justifyR :: Int -> e -> [e] -> [e] Source #

each :: Int -> [e] -> [e] Source #

eachFrom :: Int -> Int -> [e] -> [e] Source #

isPrefixOf :: [e] -> [e] -> Bool Source #

isSuffixOf :: [e] -> [e] -> Bool Source #

isInfixOf :: [e] -> [e] -> Bool Source #

prefix :: (e -> Bool) -> [e] -> Int Source #

suffix :: (e -> Bool) -> [e] -> Int Source #

infixes :: [e] -> [e] -> [Int] Source #

dropSide :: (e -> Bool) -> [e] -> [e] Source #

takeWhile :: (e -> Bool) -> [e] -> [e] Source #

dropWhile :: (e -> Bool) -> [e] -> [e] Source #

takeEnd :: (e -> Bool) -> [e] -> [e] Source #

dropEnd :: (e -> Bool) -> [e] -> [e] Source #

spanl :: (e -> Bool) -> [e] -> ([e], [e]) Source #

breakl :: (e -> Bool) -> [e] -> ([e], [e]) Source #

spanr :: (e -> Bool) -> [e] -> ([e], [e]) Source #

breakr :: (e -> Bool) -> [e] -> ([e], [e]) Source #

selectWhile :: (e -> Maybe a) -> [e] -> [a] Source #

selectEnd :: (e -> Maybe a) -> [e] -> [a] Source #

extractWhile :: (e -> Maybe a) -> [e] -> ([a], [e]) Source #

extractEnd :: (e -> Maybe a) -> [e] -> ([e], [a]) Source #

selectWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> [e] -> t a Source #

selectEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> [e] -> t a Source #

extractWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> [e] -> (t a, [e]) Source #

extractEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> [e] -> ([e], t a) Source #

Unboxed e => Split (SBytes# e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

take :: Int -> SBytes# e -> SBytes# e Source #

drop :: Int -> SBytes# e -> SBytes# e Source #

keep :: Int -> SBytes# e -> SBytes# e Source #

sans :: Int -> SBytes# e -> SBytes# e Source #

save :: Int -> SBytes# e -> SBytes# e Source #

skip :: Int -> SBytes# e -> SBytes# e Source #

split :: Int -> SBytes# e -> (SBytes# e, SBytes# e) Source #

divide :: Int -> SBytes# e -> (SBytes# e, SBytes# e) Source #

splits :: Foldable f => f Int -> SBytes# e -> [SBytes# e] Source #

divides :: Foldable f => f Int -> SBytes# e -> [SBytes# e] Source #

parts :: Foldable f => f Int -> SBytes# e -> [SBytes# e] Source #

chunks :: Int -> SBytes# e -> [SBytes# e] Source #

splitBy :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

divideBy :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

splitsBy :: (e -> Bool) -> SBytes# e -> [SBytes# e] Source #

splitsOn :: SBytes# e -> SBytes# e -> [SBytes# e] Source #

replaceBy :: SBytes# e -> SBytes# e -> SBytes# e -> SBytes# e Source #

removeAll :: SBytes# e -> SBytes# e -> SBytes# e Source #

combo :: Equal e -> SBytes# e -> Int Source #

justifyL :: Int -> e -> SBytes# e -> SBytes# e Source #

justifyR :: Int -> e -> SBytes# e -> SBytes# e Source #

each :: Int -> SBytes# e -> SBytes# e Source #

eachFrom :: Int -> Int -> SBytes# e -> SBytes# e Source #

isPrefixOf :: SBytes# e -> SBytes# e -> Bool Source #

isSuffixOf :: SBytes# e -> SBytes# e -> Bool Source #

isInfixOf :: SBytes# e -> SBytes# e -> Bool Source #

prefix :: (e -> Bool) -> SBytes# e -> Int Source #

suffix :: (e -> Bool) -> SBytes# e -> Int Source #

infixes :: SBytes# e -> SBytes# e -> [Int] Source #

dropSide :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

takeWhile :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

dropWhile :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

takeEnd :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

dropEnd :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

spanl :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

breakl :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

spanr :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

breakr :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

selectWhile :: (e -> Maybe a) -> SBytes# e -> [a] Source #

selectEnd :: (e -> Maybe a) -> SBytes# e -> [a] Source #

extractWhile :: (e -> Maybe a) -> SBytes# e -> ([a], SBytes# e) Source #

extractEnd :: (e -> Maybe a) -> SBytes# e -> (SBytes# e, [a]) Source #

selectWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> SBytes# e -> t a Source #

selectEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> SBytes# e -> t a Source #

extractWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> SBytes# e -> (t a, SBytes# e) Source #

extractEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> SBytes# e -> (SBytes# e, t a) Source #

Split (SArray# e) e Source # 
Instance details

Defined in SDP.Prim.SArray

Methods

take :: Int -> SArray# e -> SArray# e Source #

drop :: Int -> SArray# e -> SArray# e Source #

keep :: Int -> SArray# e -> SArray# e Source #

sans :: Int -> SArray# e -> SArray# e Source #

save :: Int -> SArray# e -> SArray# e Source #

skip :: Int -> SArray# e -> SArray# e Source #

split :: Int -> SArray# e -> (SArray# e, SArray# e) Source #

divide :: Int -> SArray# e -> (SArray# e, SArray# e) Source #

splits :: Foldable f => f Int -> SArray# e -> [SArray# e] Source #

divides :: Foldable f => f Int -> SArray# e -> [SArray# e] Source #

parts :: Foldable f => f Int -> SArray# e -> [SArray# e] Source #

chunks :: Int -> SArray# e -> [SArray# e] Source #

splitBy :: (e -> Bool) -> SArray# e -> (SArray# e, SArray# e) Source #

divideBy :: (e -> Bool) -> SArray# e -> (SArray# e, SArray# e) Source #

splitsBy :: (e -> Bool) -> SArray# e -> [SArray# e] Source #

splitsOn :: SArray# e -> SArray# e -> [SArray# e] Source #

replaceBy :: SArray# e -> SArray# e -> SArray# e -> SArray# e Source #

removeAll :: SArray# e -> SArray# e -> SArray# e Source #

combo :: Equal e -> SArray# e -> Int Source #

justifyL :: Int -> e -> SArray# e -> SArray# e Source #

justifyR :: Int -> e -> SArray# e -> SArray# e Source #

each :: Int -> SArray# e -> SArray# e Source #

eachFrom :: Int -> Int -> SArray# e -> SArray# e Source #

isPrefixOf :: SArray# e -> SArray# e -> Bool Source #

isSuffixOf :: SArray# e -> SArray# e -> Bool Source #

isInfixOf :: SArray# e -> SArray# e -> Bool Source #

prefix :: (e -> Bool) -> SArray# e -> Int Source #

suffix :: (e -> Bool) -> SArray# e -> Int Source #

infixes :: SArray# e -> SArray# e -> [Int] Source #

dropSide :: (e -> Bool) -> SArray# e -> SArray# e Source #

takeWhile :: (e -> Bool) -> SArray# e -> SArray# e Source #

dropWhile :: (e -> Bool) -> SArray# e -> SArray# e Source #

takeEnd :: (e -> Bool) -> SArray# e -> SArray# e Source #

dropEnd :: (e -> Bool) -> SArray# e -> SArray# e Source #

spanl :: (e -> Bool) -> SArray# e -> (SArray# e, SArray# e) Source #

breakl :: (e -> Bool) -> SArray# e -> (SArray# e, SArray# e) Source #

spanr :: (e -> Bool) -> SArray# e -> (SArray# e, SArray# e) Source #

breakr :: (e -> Bool) -> SArray# e -> (SArray# e, SArray# e) Source #

selectWhile :: (e -> Maybe a) -> SArray# e -> [a] Source #

selectEnd :: (e -> Maybe a) -> SArray# e -> [a] Source #

extractWhile :: (e -> Maybe a) -> SArray# e -> ([a], SArray# e) Source #

extractEnd :: (e -> Maybe a) -> SArray# e -> (SArray# e, [a]) Source #

selectWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> SArray# e -> t a Source #

selectEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> SArray# e -> t a Source #

extractWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> SArray# e -> (t a, SArray# e) Source #

extractEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> SArray# e -> (SArray# e, t a) Source #

(Bordered1 rep Int e, Split1 rep e) => Split (AnyChunks rep e) e Source # 
Instance details

Defined in SDP.Templates.AnyChunks

Methods

take :: Int -> AnyChunks rep e -> AnyChunks rep e Source #

drop :: Int -> AnyChunks rep e -> AnyChunks rep e Source #

keep :: Int -> AnyChunks rep e -> AnyChunks rep e Source #

sans :: Int -> AnyChunks rep e -> AnyChunks rep e Source #

save :: Int -> AnyChunks rep e -> AnyChunks rep e Source #

skip :: Int -> AnyChunks rep e -> AnyChunks rep e Source #

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

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

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

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

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

chunks :: Int -> AnyChunks rep e -> [AnyChunks rep e] Source #

splitBy :: (e -> Bool) -> AnyChunks rep e -> (AnyChunks rep e, AnyChunks rep e) Source #

divideBy :: (e -> Bool) -> AnyChunks rep e -> (AnyChunks rep e, AnyChunks rep e) Source #

splitsBy :: (e -> Bool) -> AnyChunks rep e -> [AnyChunks rep e] Source #

splitsOn :: AnyChunks rep e -> AnyChunks rep e -> [AnyChunks rep e] Source #

replaceBy :: AnyChunks rep e -> AnyChunks rep e -> AnyChunks rep e -> AnyChunks rep e Source #

removeAll :: AnyChunks rep e -> AnyChunks rep e -> AnyChunks rep e Source #

combo :: Equal e -> AnyChunks rep e -> Int Source #

justifyL :: Int -> e -> AnyChunks rep e -> AnyChunks rep e Source #

justifyR :: Int -> e -> AnyChunks rep e -> AnyChunks rep e Source #

each :: Int -> AnyChunks rep e -> AnyChunks rep e Source #

eachFrom :: Int -> Int -> AnyChunks rep e -> AnyChunks rep e Source #

isPrefixOf :: AnyChunks rep e -> AnyChunks rep e -> Bool Source #

isSuffixOf :: AnyChunks rep e -> AnyChunks rep e -> Bool Source #

isInfixOf :: AnyChunks rep e -> AnyChunks rep e -> Bool Source #

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

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

infixes :: AnyChunks rep e -> AnyChunks rep e -> [Int] Source #

dropSide :: (e -> Bool) -> AnyChunks rep e -> AnyChunks rep e Source #

takeWhile :: (e -> Bool) -> AnyChunks rep e -> AnyChunks rep e Source #

dropWhile :: (e -> Bool) -> AnyChunks rep e -> AnyChunks rep e Source #

takeEnd :: (e -> Bool) -> AnyChunks rep e -> AnyChunks rep e Source #

dropEnd :: (e -> Bool) -> AnyChunks rep e -> AnyChunks rep e Source #

spanl :: (e -> Bool) -> AnyChunks rep e -> (AnyChunks rep e, AnyChunks rep e) Source #

breakl :: (e -> Bool) -> AnyChunks rep e -> (AnyChunks rep e, AnyChunks rep e) Source #

spanr :: (e -> Bool) -> AnyChunks rep e -> (AnyChunks rep e, AnyChunks rep e) Source #

breakr :: (e -> Bool) -> AnyChunks rep e -> (AnyChunks rep e, AnyChunks rep e) Source #

selectWhile :: (e -> Maybe a) -> AnyChunks rep e -> [a] Source #

selectEnd :: (e -> Maybe a) -> AnyChunks rep e -> [a] Source #

extractWhile :: (e -> Maybe a) -> AnyChunks rep e -> ([a], AnyChunks rep e) Source #

extractEnd :: (e -> Maybe a) -> AnyChunks rep e -> (AnyChunks rep e, [a]) Source #

selectWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> AnyChunks rep e -> t a Source #

selectEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> AnyChunks rep e -> t a Source #

extractWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> AnyChunks rep e -> (t a, AnyChunks rep e) Source #

extractEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> AnyChunks rep e -> (AnyChunks rep e, t a) Source #

(Index i, Split1 rep e, Bordered1 rep Int e) => Split (AnyBorder rep i e) e Source # 
Instance details

Defined in SDP.Templates.AnyBorder

Methods

take :: Int -> AnyBorder rep i e -> AnyBorder rep i e Source #

drop :: Int -> AnyBorder rep i e -> AnyBorder rep i e Source #

keep :: Int -> AnyBorder rep i e -> AnyBorder rep i e Source #

sans :: Int -> AnyBorder rep i e -> AnyBorder rep i e Source #

save :: Int -> AnyBorder rep i e -> AnyBorder rep i e Source #

skip :: Int -> AnyBorder rep i e -> AnyBorder rep i e Source #

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

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

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

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

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

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

splitBy :: (e -> Bool) -> AnyBorder rep i e -> (AnyBorder rep i e, AnyBorder rep i e) Source #

divideBy :: (e -> Bool) -> AnyBorder rep i e -> (AnyBorder rep i e, AnyBorder rep i e) Source #

splitsBy :: (e -> Bool) -> AnyBorder rep i e -> [AnyBorder rep i e] Source #

splitsOn :: AnyBorder rep i e -> AnyBorder rep i e -> [AnyBorder rep i e] Source #

replaceBy :: AnyBorder rep i e -> AnyBorder rep i e -> AnyBorder rep i e -> AnyBorder rep i e Source #

removeAll :: AnyBorder rep i e -> AnyBorder rep i e -> AnyBorder rep i e Source #

combo :: Equal e -> AnyBorder rep i e -> Int Source #

justifyL :: Int -> e -> AnyBorder rep i e -> AnyBorder rep i e Source #

justifyR :: Int -> e -> AnyBorder rep i e -> AnyBorder rep i e Source #

each :: Int -> AnyBorder rep i e -> AnyBorder rep i e Source #

eachFrom :: Int -> Int -> AnyBorder rep i e -> AnyBorder rep i e Source #

isPrefixOf :: AnyBorder rep i e -> AnyBorder rep i e -> Bool Source #

isSuffixOf :: AnyBorder rep i e -> AnyBorder rep i e -> Bool Source #

isInfixOf :: AnyBorder rep i e -> AnyBorder rep i e -> Bool Source #

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

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

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

dropSide :: (e -> Bool) -> AnyBorder rep i e -> AnyBorder rep i e Source #

takeWhile :: (e -> Bool) -> AnyBorder rep i e -> AnyBorder rep i e Source #

dropWhile :: (e -> Bool) -> AnyBorder rep i e -> AnyBorder rep i e Source #

takeEnd :: (e -> Bool) -> AnyBorder rep i e -> AnyBorder rep i e Source #

dropEnd :: (e -> Bool) -> AnyBorder rep i e -> AnyBorder rep i e Source #

spanl :: (e -> Bool) -> AnyBorder rep i e -> (AnyBorder rep i e, AnyBorder rep i e) Source #

breakl :: (e -> Bool) -> AnyBorder rep i e -> (AnyBorder rep i e, AnyBorder rep i e) Source #

spanr :: (e -> Bool) -> AnyBorder rep i e -> (AnyBorder rep i e, AnyBorder rep i e) Source #

breakr :: (e -> Bool) -> AnyBorder rep i e -> (AnyBorder rep i e, AnyBorder rep i e) Source #

selectWhile :: (e -> Maybe a) -> AnyBorder rep i e -> [a] Source #

selectEnd :: (e -> Maybe a) -> AnyBorder rep i e -> [a] Source #

extractWhile :: (e -> Maybe a) -> AnyBorder rep i e -> ([a], AnyBorder rep i e) Source #

extractEnd :: (e -> Maybe a) -> AnyBorder rep i e -> (AnyBorder rep i e, [a]) Source #

selectWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> AnyBorder rep i e -> t a Source #

selectEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> AnyBorder rep i e -> t a Source #

extractWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> AnyBorder rep i e -> (t a, AnyBorder rep i e) Source #

extractEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> AnyBorder rep i e -> (AnyBorder rep i e, t a) Source #

type Split1 s e = Split (s e) e Source #

Kind (Type -> Type) Split structure.

Related functions

stripPrefix :: (Split s e, Bordered s i, Eq e) => s -> s -> s Source #

stripPrefix sub line strips prefix sub of line (if any).

stripSuffix :: (Split s e, Bordered s i, Eq e) => s -> s -> s Source #

stripSuffix sub line strips suffix sub of line (if any).

stripPrefix' :: (Split s e, Bordered s i, Eq e) => s -> s -> Maybe s Source #

stripPrefix' sub line strips prefix sub of line or returns Nothing.

stripSuffix' :: (Split s e, Bordered s i, Eq e) => s -> s -> Maybe s Source #

stripSuffix sub line strips suffix sub of line or returns Nothing.

intercalate :: (Foldable f, Linear1 f l, Linear l e) => l -> f l -> l Source #

intercalate is generalization of intercalate

tails :: Linear l e => l -> [l] Source #

tails es returns sequence of es tails.

inits :: Linear l e => l -> [l] Source #

tails is generalization of inits.

ascending :: (Split s e, Sort s e, Ord e) => s -> [Int] -> Bool Source #

ascending es lengths checks if the subsequences of es of lengths lengths is sorted.