ListLike-4.7.4: Generalized support for list-like structures
CopyrightCopyright (C) 2007 John Goerzen
LicenseBSD3
MaintainerJohn Goerzen <jgoerzen@complete.org>
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.ListLike

Description

Generic operations over list-like structures

Written by John Goerzen, jgoerzen@complete.org

Please start with the introduction at Data.ListLike.

Synopsis

Introduction

Welcome to ListLike.

This module provides abstractions over typical list operations. It is designed to let you freely interchange different ways to represent sequences of data. It works with lists, various types of ByteStrings, and much more.

In this module, you'll find generic versions of most of the functions you're used to using in the Prelude, Data.List, and System.IO. They carry the same names, too. Therefore, you'll want to be careful how you import the module. I suggest using:

import qualified Data.ListLike as LL

Then, you can use LL.fold, LL.map, etc. to get the generic version of the functions you want. Alternatively, you can hide the other versions from Prelude and import specific generic functions from here, such as:

import Prelude hiding (map)
import Data.ListLike (map)

The module Data.ListLike actually simply re-exports the items found in a number of its sub-modules. If you want a smaller subset of Data.ListLike, look at the documentation for its sub-modules and import the relevant one.

In most cases, functions here can act as drop-in replacements for their list-specific counterparts. They will use the same underlying implementations for lists, so there should be no performance difference.

You can make your own types instances of ListLike as well. For more details, see the notes for the ListLike typeclass.

Creation & Basic Functions

empty :: ListLike full item => full Source #

The empty list

singleton :: ListLike full item => item -> full Source #

Creates a single-element list out of an element

cons :: ListLike full item => item -> full -> full Source #

Like (:) for lists: adds an element to the beginning of a list

snoc :: ListLike full item => full -> item -> full Source #

Adds an element to the *end* of a ListLike.

append :: ListLike full item => full -> full -> full Source #

Combines two lists. Like (++).

uncons :: ListLike full item => full -> Maybe (item, full) Source #

Extract head and tail, return Nothing if empty

head :: ListLike full item => full -> item Source #

Extracts the first element of a ListLike.

last :: ListLike full item => full -> item Source #

Extracts the last element of a ListLike.

tail :: ListLike full item => full -> full Source #

Gives all elements after the head.

init :: ListLike full item => full -> full Source #

All elements of the list except the last one. See also inits.

null :: ListLike full item => full -> Bool Source #

Tests whether the list is empty.

length :: ListLike full item => full -> Int Source #

Length of the list. See also genericLength.

List transformations

map :: (ListLike full item, ListLike full' item') => (item -> item') -> full -> full' Source #

Apply a function to each element, returning any other valid ListLike. rigidMap will always be at least as fast, if not faster, than this function and is recommended if it will work for your purposes. See also mapM.

rigidMap :: ListLike full item => (item -> item) -> full -> full Source #

Like map, but without the possibility of changing the type of the item. This can have performance benefits for things such as ByteStrings, since it will let the ByteString use its native low-level map implementation.

reverse :: ListLike full item => full -> full Source #

Reverse the elements in a list.

intersperse :: ListLike full item => item -> full -> full Source #

Add an item between each element in the structure

Conversions

toList :: IsList l => l -> [Item l] #

The toList function extracts a list of Item l from the structure l. It should satisfy fromList . toList = id.

fromList :: IsList l => [Item l] -> l #

The fromList function constructs the structure l from the given list of Item l

fromListLike :: (ListLike full item, ListLike full' item) => full -> full' Source #

Converts one ListLike to another. See also toList'. Default implementation is fromListLike = map id

Reducing lists (folds), from FoldableLL

foldl :: FoldableLL full item => (a -> item -> a) -> a -> full -> a Source #

Left-associative fold

foldl' :: FoldableLL full item => (a -> item -> a) -> a -> full -> a Source #

Strict version of foldl.

foldl1 :: FoldableLL full item => (item -> item -> item) -> full -> item Source #

A variant of foldl with no base case. Requires at least 1 list element.

foldr :: FoldableLL full item => (item -> b -> b) -> b -> full -> b Source #

Right-associative fold

foldr' :: FoldableLL full item => (item -> b -> b) -> b -> full -> b Source #

Strict version of foldr

foldr1 :: FoldableLL full item => (item -> item -> item) -> full -> item Source #

Like foldr, but with no starting value

Special folds

concat :: (ListLike full item, ListLike full' full) => full' -> full Source #

Flatten the structure.

concatMap :: (ListLike full item, ListLike full' item') => (item -> full') -> full -> full' Source #

Map a function over the items and concatenate the results. See also rigidConcatMap.

rigidConcatMap :: ListLike full item => (item -> full) -> full -> full Source #

Like concatMap, but without the possibility of changing the type of the item. This can have performance benefits for some things such as ByteString.

and :: ListLike full Bool => full -> Bool Source #

Returns True if all elements are True

or :: ListLike full Bool => full -> Bool Source #

Returns True if any element is True

any :: ListLike full item => (item -> Bool) -> full -> Bool Source #

True if any items satisfy the function

all :: ListLike full item => (item -> Bool) -> full -> Bool Source #

True if all items satisfy the function

sum :: (Num a, ListLike full a) => full -> a Source #

The sum of the list

product :: (Num a, ListLike full a) => full -> a Source #

The product of the list

maximum :: (ListLike full item, Ord item) => full -> item Source #

The maximum value of the list

minimum :: (ListLike full item, Ord item) => full -> item Source #

The minimum value of the list

fold :: (FoldableLL full item, Monoid item) => full -> item Source #

Combine the elements of a structure using a monoid. fold = foldMap id

foldMap :: (FoldableLL full item, Monoid m) => (item -> m) -> full -> m Source #

Map each element to a monoid, then combine the results

Building lists

Scans

Accumulating maps

Infinite lists

iterate :: InfiniteListLike full item => (item -> item) -> item -> full Source #

An infinite list of repeated calls of the function to args

repeat :: InfiniteListLike full item => item -> full Source #

An infinite list where each element is the same

replicate :: ListLike full item => Int -> item -> full Source #

Generate a structure with the specified length with every element set to the item passed in. See also genericReplicate

cycle :: InfiniteListLike full item => full -> full Source #

Converts a finite list into a circular one

Unfolding

Sublists

Extracting sublists

take :: ListLike full item => Int -> full -> full Source #

Takes the first n elements of the list. See also genericTake.

drop :: ListLike full item => Int -> full -> full Source #

Drops the first n elements of the list. See also genericDrop

splitAt :: ListLike full item => Int -> full -> (full, full) Source #

Equivalent to (take n xs, drop n xs). See also genericSplitAt.

takeWhile :: ListLike full item => (item -> Bool) -> full -> full Source #

Returns all elements at start of list that satisfy the function.

dropWhile :: ListLike full item => (item -> Bool) -> full -> full Source #

Drops all elements from the start of the list that satisfy the function.

dropWhileEnd :: ListLike full item => (item -> Bool) -> full -> full Source #

Drops all elements from the end of the list that satisfy the function.

span :: ListLike full item => (item -> Bool) -> full -> (full, full) Source #

The equivalent of (takeWhile f xs, dropWhile f xs)

break :: ListLike full item => (item -> Bool) -> full -> (full, full) Source #

The equivalent of span (not . f)

group :: (ListLike full item, ListLike full' full, Eq item) => full -> full' Source #

Split a list into sublists, each which contains equal arguments. For order-preserving types, concatenating these sublists will produce the original list. See also groupBy.

inits :: (ListLike full item, ListLike full' full) => full -> full' Source #

All initial segments of the list, shortest first

tails :: (ListLike full item, ListLike full' full) => full -> full' Source #

All final segnemts, longest first

Predicates

isPrefixOf :: (ListLike full item, Eq item) => full -> full -> Bool Source #

True when the first list is at the beginning of the second.

isSuffixOf :: (ListLike full item, Eq item) => full -> full -> Bool Source #

True when the first list is at the beginning of the second.

isInfixOf :: (ListLike full item, Eq item) => full -> full -> Bool Source #

True when the first list is wholly containted within the second

Modify based on predicate

stripPrefix :: (ListLike full item, Eq item) => full -> full -> Maybe full Source #

Remove a prefix from a listlike if possible

stripSuffix :: (ListLike full item, Eq item) => full -> full -> Maybe full Source #

Remove a suffix from a listlike if possible

Searching lists

Searching by equality

elem :: (ListLike full item, Eq item) => item -> full -> Bool Source #

True if the item occurs in the list

notElem :: (ListLike full item, Eq item) => item -> full -> Bool Source #

True if the item does not occur in the list

Searching with a predicate

find :: ListLike full item => (item -> Bool) -> full -> Maybe item Source #

Take a function and return the first matching element, or Nothing if there is no such element.

filter :: ListLike full item => (item -> Bool) -> full -> full Source #

Returns only the elements that satisfy the function.

partition :: ListLike full item => (item -> Bool) -> full -> (full, full) Source #

Returns the lists that do and do not satisfy the function. Same as (filter p xs, filter (not . p) xs)

Indexing lists

index :: ListLike full item => full -> Int -> item Source #

The element at 0-based index i. Raises an exception if i is out of bounds. Like (!!) for lists.

elemIndex :: (ListLike full item, Eq item) => item -> full -> Maybe Int Source #

Returns the index of the element, if it exists.

elemIndices :: (ListLike full item, Eq item, ListLike result Int) => item -> full -> result Source #

Returns the indices of the matching elements. See also findIndices

findIndex :: ListLike full item => (item -> Bool) -> full -> Maybe Int Source #

Take a function and return the index of the first matching element, or Nothing if no element matches

findIndices :: (ListLike full item, ListLike result Int) => (item -> Bool) -> full -> result Source #

Returns the indices of all elements satisfying the function

Zipping and unzipping lists

zip :: (ListLike full item, ListLike fullb itemb, ListLike result (item, itemb)) => full -> fullb -> result Source #

Takes two lists and returns a list of corresponding pairs.

zipWith :: (ListLike full item, ListLike fullb itemb, ListLike result resultitem) => (item -> itemb -> resultitem) -> full -> fullb -> result Source #

Takes two lists and combines them with a custom combining function

unzip :: (ListLike full (itema, itemb), ListLike ra itema, ListLike rb itemb) => full -> (ra, rb) Source #

Converts a list of pairs into two separate lists of elements

Monadic Operations

sequence :: (ListLike full item, Monad m, ListLike fullinp (m item)) => fullinp -> m full Source #

Evaluate each action in the sequence and collect the results

sequence_ :: (Monad m, FoldableLL full (m item)) => full -> m () Source #

Evaluate each action, ignoring the results. Same as mapM_ id.

mapM :: (ListLike full item, Monad m, ListLike full' item') => (item -> m item') -> full -> m full' Source #

A map in monad space. Same as sequence . map

See also rigidMapM

rigidMapM :: (ListLike full item, Monad m) => (item -> m item) -> full -> m full Source #

Like mapM, but without the possibility of changing the type of the item. This can have performance benefits with some types.

mapM_ :: (Monad m, FoldableLL full item) => (item -> m b) -> full -> m () Source #

A map in monad space, discarding results.

Input and Output

class ListLike full item => ListLikeIO full item | full -> item where Source #

An extension to ListLike for those data types that support I/O. These functions mirror those in System.IO for the most part. They also share the same names; see the comments in Data.ListLike for help importing them.

Note that some types may not be capable of lazy reading or writing. Therefore, the usual semantics of System.IO functions regarding laziness may or may not be available from a particular implementation.

Minimal complete definition:

  • hGetLine
  • hGetContents
  • hGet
  • hGetNonBlocking
  • hPutStr

Minimal complete definition

hGetLine, hGetContents, hGet, hGetNonBlocking, hPutStr

Methods

hGetLine :: Handle -> IO full Source #

Reads a line from the specified handle

hGetContents :: Handle -> IO full Source #

Read entire handle contents. May be done lazily like hGetContents.

hGet :: Handle -> Int -> IO full Source #

Read specified number of bytes. See hGet for particular semantics.

hGetNonBlocking :: Handle -> Int -> IO full Source #

Non-blocking read. See hGetNonBlocking for more.

hPutStr :: Handle -> full -> IO () Source #

Writing entire data.

hPutStrLn :: Handle -> full -> IO () Source #

Write data plus newline character.

getLine :: IO full Source #

Read one line

getContents :: IO full Source #

Read entire content from stdin. See hGetContents.

putStr :: full -> IO () Source #

Write data to stdout.

putStrLn :: full -> IO () Source #

Write data plus newline character to stdout.

interact :: (full -> full) -> IO () Source #

Interact with stdin and stdout by using a function to transform input to output. May be lazy. See interact for more.

readFile :: FilePath -> IO full Source #

Read file. May be lazy.

writeFile :: FilePath -> full -> IO () Source #

Write data to file.

appendFile :: FilePath -> full -> IO () Source #

Append data to file.

Instances

Instances details
ListLikeIO String Char Source # 
Instance details

Defined in Data.ListLike.Instances

ListLikeIO ByteString Word8 Source # 
Instance details

Defined in Data.ListLike.Instances

ListLikeIO ByteString Word8 Source # 
Instance details

Defined in Data.ListLike.Instances

ListLikeIO Builder Char Source # 
Instance details

Defined in Data.ListLike.Text.Builder

ListLikeIO Text Char Source # 
Instance details

Defined in Data.ListLike.Text.TextLazy

ListLikeIO Text Char Source # 
Instance details

Defined in Data.ListLike.Text.Text

ListLikeIO CharStringLazy Char Source # 
Instance details

Defined in Data.ListLike.CharString

ListLikeIO CharString Char Source # 
Instance details

Defined in Data.ListLike.CharString

ListLikeIO Chars Char Source # 
Instance details

Defined in Data.ListLike.Chars

ListLikeIO (Seq Char) Char Source # 
Instance details

Defined in Data.ListLike.Instances

ListLikeIO (UTF8 ByteString) Char Source # 
Instance details

Defined in Data.ListLike.UTF8

ListLikeIO (UTF8 ByteString) Char Source # 
Instance details

Defined in Data.ListLike.UTF8

(Integral i, Ix i) => ListLikeIO (Array i Char) Char Source # 
Instance details

Defined in Data.ListLike.Instances

Special lists

Strings

toString :: StringLike s => s -> String Source #

Converts the structure to a String

lines :: (StringLike s, ListLike full s) => s -> full Source #

Breaks a string into a list of strings

words :: (StringLike s, ListLike full s) => s -> full Source #

Breaks a string into a list of words

show :: (StringLike s, Show a) => a -> s Source #

Generalize the Show method t return any StringLike.

fromStringLike :: (StringLike s, StringLike s') => s -> s' Source #

Deprecated: Use fromString . toString or something more efficient using local knowledge

fromText :: (StringLike s, StringLike Text) => Text -> s Source #

Override this to avoid extra String conversions.

fromLazyText :: (StringLike s, StringLike Text) => Text -> s Source #

Override this to avoid extra String conversions.

"Set" operations

nub :: (ListLike full item, Eq item) => full -> full Source #

Removes duplicate elements from the list. See also nubBy

delete :: (ListLike full item, Eq item) => item -> full -> full Source #

Removes the first instance of the element from the list. See also deleteBy

deleteFirsts :: (ListLike full item, Eq item) => full -> full -> full Source #

List difference. Removes from the first list the first instance of each element of the second list. See (\\) and deleteFirstsBy

union :: (ListLike full item, Eq item) => full -> full -> full Source #

List union: the set of elements that occur in either list. Duplicate elements in the first list will remain duplicate. See also unionBy.

intersect :: (ListLike full item, Eq item) => full -> full -> full Source #

List intersection: the set of elements that occur in both lists. See also intersectBy

Ordered lists

sort :: (ListLike full item, Ord item) => full -> full Source #

Sorts the list. On data types that do not preserve ordering, or enforce their own ordering, the result may not be what you expect. See also sortBy.

insert :: (ListLike full item, Ord item) => item -> full -> full Source #

Inserts the element at the last place where it is still less than or equal to the next element. On data types that do not preserve ordering, or enforce their own ordering, the result may not be what you expect. On types such as maps, this may result in changing an existing item. See also insertBy.

Generalized functions

The "By" operations

User-supplied equality (replacing an Eq context)

nubBy :: ListLike full item => (item -> item -> Bool) -> full -> full Source #

Generic version of nub

deleteBy :: ListLike full item => (item -> item -> Bool) -> item -> full -> full Source #

Generic version of deleteBy

deleteFirstsBy :: ListLike full item => (item -> item -> Bool) -> full -> full -> full Source #

Generic version of deleteFirsts

unionBy :: ListLike full item => (item -> item -> Bool) -> full -> full -> full Source #

Generic version of union

intersectBy :: ListLike full item => (item -> item -> Bool) -> full -> full -> full Source #

Generic version of intersect

groupBy :: (ListLike full item, ListLike full' full, Eq item) => (item -> item -> Bool) -> full -> full' Source #

Generic version of group.

User-supplied comparison (replacing an Ord context)

sortBy :: ListLike full item => (item -> item -> Ordering) -> full -> full Source #

Sort function taking a custom comparison function

insertBy :: ListLike full item => (item -> item -> Ordering) -> item -> full -> full Source #

Like insert, but with a custom comparison function

The "generic" operations

genericLength :: (ListLike full item, Num a) => full -> a Source #

Length of the list

genericTake :: (ListLike full item, Integral a) => a -> full -> full Source #

Generic version of take

genericDrop :: (ListLike full item, Integral a) => a -> full -> full Source #

Generic version of drop

genericSplitAt :: (ListLike full item, Integral a) => a -> full -> (full, full) Source #

Generic version of splitAt

genericReplicate :: (ListLike full item, Integral a) => a -> item -> full Source #

Generic version of replicate

Notes on specific instances

Lists

Functions for operating on regular lists almost all use the native implementations in Data.List, Prelude, or similar standard modules. The exceptions are:

Arrays

Array is an instance of ListLike. Here are some notes about it:

  • The index you use must be an integral
  • ListLike functions that take an index always take a 0-based index for compatibility with other ListLike instances. This is translated by the instance functions into the proper offset from the bounds in the Array.
  • ListLike functions preserve the original Array index numbers when possible. Functions such as cons will reduce the lower bound to do their job. snoc and append increase the upper bound. drop raises the lower bound and take lowers the upper bound.
  • Functions that change the length of the array by an amount not known in advance, such as filter, will generate a new array with the lower bound set to 0. Furthermore, these functions cannot operate on infinite lists because they must know their length in order to generate the array. hGetContents and its friends will therefore require the entire file to be read into memory before processing is possible.
  • empty, singleton, and fromList also generate an array with the lower bound set to 0.
  • Many of these functions will generate runtime exceptions if you have not assigned a value to every slot in the array.

ByteStrings

Both strict and lazy ByteStreams can be used with ListLike.

ByteString ListLike instances operate on Word8 elements. This is because both Data.ByteString.ByteString and Data.ByteString.Char8.ByteString have the same underlying type. If you wish to use the Char8 representation, the newtype wrappers CharString and CharStringLazy are available.

Most ListLike operations map directly to ByteStream options. Notable exceptions:

  • map uses the ListLike implementation. rigidMap is more efficient. The same goes for concatMap vs. rigidConcatMap.
  • isInfixOf, sequence, mapM and similar monad operations, insert, union, intersect, sortBy, and similar functions are not implemented in ByteStream and use a naive default implementation.
  • The lazy ByteStream module implements fewer funtions than the strict ByteStream module. In some cases, default implementations are used. In others, notably related to I/O, the lazy ByteStreams are converted back and forth to strict ones as appropriate.

data Chars Source #

Constructors

B Builder 
T Text 

Instances

Instances details
IsList Chars Source # 
Instance details

Defined in Data.ListLike.Chars

Associated Types

type Item Chars #

Eq Chars Source # 
Instance details

Defined in Data.ListLike.Chars

Methods

(==) :: Chars -> Chars -> Bool #

(/=) :: Chars -> Chars -> Bool #

Ord Chars Source # 
Instance details

Defined in Data.ListLike.Chars

Methods

compare :: Chars -> Chars -> Ordering #

(<) :: Chars -> Chars -> Bool #

(<=) :: Chars -> Chars -> Bool #

(>) :: Chars -> Chars -> Bool #

(>=) :: Chars -> Chars -> Bool #

max :: Chars -> Chars -> Chars #

min :: Chars -> Chars -> Chars #

Show Chars Source # 
Instance details

Defined in Data.ListLike.Chars

Methods

showsPrec :: Int -> Chars -> ShowS #

show :: Chars -> String #

showList :: [Chars] -> ShowS #

IsString Chars Source # 
Instance details

Defined in Data.ListLike.Chars

Methods

fromString :: String -> Chars #

Semigroup Chars Source # 
Instance details

Defined in Data.ListLike.Chars

Methods

(<>) :: Chars -> Chars -> Chars #

sconcat :: NonEmpty Chars -> Chars #

stimes :: Integral b => b -> Chars -> Chars #

Monoid Chars Source # 
Instance details

Defined in Data.ListLike.Chars

Methods

mempty :: Chars #

mappend :: Chars -> Chars -> Chars #

mconcat :: [Chars] -> Chars #

NFData Chars Source # 
Instance details

Defined in Data.ListLike.Chars

Methods

rnf :: Chars -> () #

StringLike Chars Source # 
Instance details

Defined in Data.ListLike.Chars

FoldableLL Chars Char Source # 
Instance details

Defined in Data.ListLike.Chars

Methods

foldl :: (a -> Char -> a) -> a -> Chars -> a Source #

foldl' :: (a -> Char -> a) -> a -> Chars -> a Source #

foldl1 :: (Char -> Char -> Char) -> Chars -> Char Source #

foldr :: (Char -> b -> b) -> b -> Chars -> b Source #

foldr' :: (Char -> b -> b) -> b -> Chars -> b Source #

foldr1 :: (Char -> Char -> Char) -> Chars -> Char Source #

ListLike Chars Char Source # 
Instance details

Defined in Data.ListLike.Chars

Methods

empty :: Chars Source #

singleton :: Char -> Chars Source #

cons :: Char -> Chars -> Chars Source #

snoc :: Chars -> Char -> Chars Source #

append :: Chars -> Chars -> Chars Source #

head :: Chars -> Char Source #

uncons :: Chars -> Maybe (Char, Chars) Source #

last :: Chars -> Char Source #

tail :: Chars -> Chars Source #

init :: Chars -> Chars Source #

null :: Chars -> Bool Source #

length :: Chars -> Int Source #

map :: ListLike full' item' => (Char -> item') -> Chars -> full' Source #

rigidMap :: (Char -> Char) -> Chars -> Chars Source #

reverse :: Chars -> Chars Source #

intersperse :: Char -> Chars -> Chars Source #

concat :: ListLike full' Chars => full' -> Chars Source #

concatMap :: ListLike full' item' => (Char -> full') -> Chars -> full' Source #

rigidConcatMap :: (Char -> Chars) -> Chars -> Chars Source #

any :: (Char -> Bool) -> Chars -> Bool Source #

all :: (Char -> Bool) -> Chars -> Bool Source #

maximum :: Chars -> Char Source #

minimum :: Chars -> Char Source #

replicate :: Int -> Char -> Chars Source #

take :: Int -> Chars -> Chars Source #

drop :: Int -> Chars -> Chars Source #

splitAt :: Int -> Chars -> (Chars, Chars) Source #

takeWhile :: (Char -> Bool) -> Chars -> Chars Source #

dropWhile :: (Char -> Bool) -> Chars -> Chars Source #

dropWhileEnd :: (Char -> Bool) -> Chars -> Chars Source #

span :: (Char -> Bool) -> Chars -> (Chars, Chars) Source #

break :: (Char -> Bool) -> Chars -> (Chars, Chars) Source #

group :: (ListLike full' Chars, Eq Char) => Chars -> full' Source #

inits :: ListLike full' Chars => Chars -> full' Source #

tails :: ListLike full' Chars => Chars -> full' Source #

isPrefixOf :: Chars -> Chars -> Bool Source #

isSuffixOf :: Chars -> Chars -> Bool Source #

isInfixOf :: Chars -> Chars -> Bool Source #

stripPrefix :: Chars -> Chars -> Maybe Chars Source #

stripSuffix :: Chars -> Chars -> Maybe Chars Source #

elem :: Char -> Chars -> Bool Source #

notElem :: Char -> Chars -> Bool Source #

find :: (Char -> Bool) -> Chars -> Maybe Char Source #

filter :: (Char -> Bool) -> Chars -> Chars Source #

partition :: (Char -> Bool) -> Chars -> (Chars, Chars) Source #

index :: Chars -> Int -> Char Source #

elemIndex :: Char -> Chars -> Maybe Int Source #

elemIndices :: (Eq Char, ListLike result Int) => Char -> Chars -> result Source #

findIndex :: (Char -> Bool) -> Chars -> Maybe Int Source #

findIndices :: ListLike result Int => (Char -> Bool) -> Chars -> result Source #

sequence :: (Monad m, ListLike fullinp (m Char)) => fullinp -> m Chars Source #

mapM :: (Monad m, ListLike full' item') => (Char -> m item') -> Chars -> m full' Source #

rigidMapM :: Monad m => (Char -> m Char) -> Chars -> m Chars Source #

nub :: Chars -> Chars Source #

delete :: Char -> Chars -> Chars Source #

deleteFirsts :: Chars -> Chars -> Chars Source #

union :: Chars -> Chars -> Chars Source #

intersect :: Chars -> Chars -> Chars Source #

sort :: Chars -> Chars Source #

insert :: Char -> Chars -> Chars Source #

toList' :: Chars -> [Char] Source #

fromList' :: [Char] -> Chars Source #

fromListLike :: ListLike full' Char => Chars -> full' Source #

nubBy :: (Char -> Char -> Bool) -> Chars -> Chars Source #

deleteBy :: (Char -> Char -> Bool) -> Char -> Chars -> Chars Source #

deleteFirstsBy :: (Char -> Char -> Bool) -> Chars -> Chars -> Chars Source #

unionBy :: (Char -> Char -> Bool) -> Chars -> Chars -> Chars Source #

intersectBy :: (Char -> Char -> Bool) -> Chars -> Chars -> Chars Source #

groupBy :: (ListLike full' Chars, Eq Char) => (Char -> Char -> Bool) -> Chars -> full' Source #

sortBy :: (Char -> Char -> Ordering) -> Chars -> Chars Source #

insertBy :: (Char -> Char -> Ordering) -> Char -> Chars -> Chars Source #

genericLength :: Num a => Chars -> a Source #

genericTake :: Integral a => a -> Chars -> Chars Source #

genericDrop :: Integral a => a -> Chars -> Chars Source #

genericSplitAt :: Integral a => a -> Chars -> (Chars, Chars) Source #

genericReplicate :: Integral a => a -> Char -> Chars Source #

ListLikeIO Chars Char Source # 
Instance details

Defined in Data.ListLike.Chars

type Item Chars Source # 
Instance details

Defined in Data.ListLike.Chars

type Item Chars = Char

newtype CharString Source #

Newtype wrapper around Data.ByteString.Char8.ByteString, this allows for ListLike instances with Char elements.

Constructors

CS 

Fields

Instances

Instances details
IsList CharString Source # 
Instance details

Defined in Data.ListLike.CharString

Associated Types

type Item CharString #

Eq CharString Source # 
Instance details

Defined in Data.ListLike.CharString

Ord CharString Source # 
Instance details

Defined in Data.ListLike.CharString

Read CharString Source # 
Instance details

Defined in Data.ListLike.CharString

Show CharString Source # 
Instance details

Defined in Data.ListLike.CharString

IsString CharString Source # 
Instance details

Defined in Data.ListLike.CharString

Semigroup CharString Source # 
Instance details

Defined in Data.ListLike.CharString

Monoid CharString Source # 
Instance details

Defined in Data.ListLike.CharString

StringLike CharString Source # 
Instance details

Defined in Data.ListLike.CharString

FoldableLL CharString Char Source # 
Instance details

Defined in Data.ListLike.CharString

Methods

foldl :: (a -> Char -> a) -> a -> CharString -> a Source #

foldl' :: (a -> Char -> a) -> a -> CharString -> a Source #

foldl1 :: (Char -> Char -> Char) -> CharString -> Char Source #

foldr :: (Char -> b -> b) -> b -> CharString -> b Source #

foldr' :: (Char -> b -> b) -> b -> CharString -> b Source #

foldr1 :: (Char -> Char -> Char) -> CharString -> Char Source #

ListLike CharString Char Source # 
Instance details

Defined in Data.ListLike.CharString

Methods

empty :: CharString Source #

singleton :: Char -> CharString Source #

cons :: Char -> CharString -> CharString Source #

snoc :: CharString -> Char -> CharString Source #

append :: CharString -> CharString -> CharString Source #

head :: CharString -> Char Source #

uncons :: CharString -> Maybe (Char, CharString) Source #

last :: CharString -> Char Source #

tail :: CharString -> CharString Source #

init :: CharString -> CharString Source #

null :: CharString -> Bool Source #

length :: CharString -> Int Source #

map :: ListLike full' item' => (Char -> item') -> CharString -> full' Source #

rigidMap :: (Char -> Char) -> CharString -> CharString Source #

reverse :: CharString -> CharString Source #

intersperse :: Char -> CharString -> CharString Source #

concat :: ListLike full' CharString => full' -> CharString Source #

concatMap :: ListLike full' item' => (Char -> full') -> CharString -> full' Source #

rigidConcatMap :: (Char -> CharString) -> CharString -> CharString Source #

any :: (Char -> Bool) -> CharString -> Bool Source #

all :: (Char -> Bool) -> CharString -> Bool Source #

maximum :: CharString -> Char Source #

minimum :: CharString -> Char Source #

replicate :: Int -> Char -> CharString Source #

take :: Int -> CharString -> CharString Source #

drop :: Int -> CharString -> CharString Source #

splitAt :: Int -> CharString -> (CharString, CharString) Source #

takeWhile :: (Char -> Bool) -> CharString -> CharString Source #

dropWhile :: (Char -> Bool) -> CharString -> CharString Source #

dropWhileEnd :: (Char -> Bool) -> CharString -> CharString Source #

span :: (Char -> Bool) -> CharString -> (CharString, CharString) Source #

break :: (Char -> Bool) -> CharString -> (CharString, CharString) Source #

group :: (ListLike full' CharString, Eq Char) => CharString -> full' Source #

inits :: ListLike full' CharString => CharString -> full' Source #

tails :: ListLike full' CharString => CharString -> full' Source #

isPrefixOf :: CharString -> CharString -> Bool Source #

isSuffixOf :: CharString -> CharString -> Bool Source #

isInfixOf :: CharString -> CharString -> Bool Source #

stripPrefix :: CharString -> CharString -> Maybe CharString Source #

stripSuffix :: CharString -> CharString -> Maybe CharString Source #

elem :: Char -> CharString -> Bool Source #

notElem :: Char -> CharString -> Bool Source #

find :: (Char -> Bool) -> CharString -> Maybe Char Source #

filter :: (Char -> Bool) -> CharString -> CharString Source #

partition :: (Char -> Bool) -> CharString -> (CharString, CharString) Source #

index :: CharString -> Int -> Char Source #

elemIndex :: Char -> CharString -> Maybe Int Source #

elemIndices :: (Eq Char, ListLike result Int) => Char -> CharString -> result Source #

findIndex :: (Char -> Bool) -> CharString -> Maybe Int Source #

findIndices :: ListLike result Int => (Char -> Bool) -> CharString -> result Source #

sequence :: (Monad m, ListLike fullinp (m Char)) => fullinp -> m CharString Source #

mapM :: (Monad m, ListLike full' item') => (Char -> m item') -> CharString -> m full' Source #

rigidMapM :: Monad m => (Char -> m Char) -> CharString -> m CharString Source #

nub :: CharString -> CharString Source #

delete :: Char -> CharString -> CharString Source #

deleteFirsts :: CharString -> CharString -> CharString Source #

union :: CharString -> CharString -> CharString Source #

intersect :: CharString -> CharString -> CharString Source #

sort :: CharString -> CharString Source #

insert :: Char -> CharString -> CharString Source #

toList' :: CharString -> [Char] Source #

fromList' :: [Char] -> CharString Source #

fromListLike :: ListLike full' Char => CharString -> full' Source #

nubBy :: (Char -> Char -> Bool) -> CharString -> CharString Source #

deleteBy :: (Char -> Char -> Bool) -> Char -> CharString -> CharString Source #

deleteFirstsBy :: (Char -> Char -> Bool) -> CharString -> CharString -> CharString Source #

unionBy :: (Char -> Char -> Bool) -> CharString -> CharString -> CharString Source #

intersectBy :: (Char -> Char -> Bool) -> CharString -> CharString -> CharString Source #

groupBy :: (ListLike full' CharString, Eq Char) => (Char -> Char -> Bool) -> CharString -> full' Source #

sortBy :: (Char -> Char -> Ordering) -> CharString -> CharString Source #

insertBy :: (Char -> Char -> Ordering) -> Char -> CharString -> CharString Source #

genericLength :: Num a => CharString -> a Source #

genericTake :: Integral a => a -> CharString -> CharString Source #

genericDrop :: Integral a => a -> CharString -> CharString Source #

genericSplitAt :: Integral a => a -> CharString -> (CharString, CharString) Source #

genericReplicate :: Integral a => a -> Char -> CharString Source #

ListLikeIO CharString Char Source # 
Instance details

Defined in Data.ListLike.CharString

type Item CharString Source # 
Instance details

Defined in Data.ListLike.CharString

newtype CharStringLazy Source #

Newtype wrapper around Data.ByteString.Lazy.Char8.ByteString, this allows for ListLike instances with Char elements.

Constructors

CSL 

Fields

Instances

Instances details
IsList CharStringLazy Source # 
Instance details

Defined in Data.ListLike.CharString

Associated Types

type Item CharStringLazy #

Eq CharStringLazy Source # 
Instance details

Defined in Data.ListLike.CharString

Ord CharStringLazy Source # 
Instance details

Defined in Data.ListLike.CharString

Read CharStringLazy Source # 
Instance details

Defined in Data.ListLike.CharString

Show CharStringLazy Source # 
Instance details

Defined in Data.ListLike.CharString

IsString CharStringLazy Source # 
Instance details

Defined in Data.ListLike.CharString

Semigroup CharStringLazy Source # 
Instance details

Defined in Data.ListLike.CharString

Monoid CharStringLazy Source # 
Instance details

Defined in Data.ListLike.CharString

StringLike CharStringLazy Source # 
Instance details

Defined in Data.ListLike.CharString

FoldableLL CharStringLazy Char Source # 
Instance details

Defined in Data.ListLike.CharString

Methods

foldl :: (a -> Char -> a) -> a -> CharStringLazy -> a Source #

foldl' :: (a -> Char -> a) -> a -> CharStringLazy -> a Source #

foldl1 :: (Char -> Char -> Char) -> CharStringLazy -> Char Source #

foldr :: (Char -> b -> b) -> b -> CharStringLazy -> b Source #

foldr' :: (Char -> b -> b) -> b -> CharStringLazy -> b Source #

foldr1 :: (Char -> Char -> Char) -> CharStringLazy -> Char Source #

ListLike CharStringLazy Char Source # 
Instance details

Defined in Data.ListLike.CharString

Methods

empty :: CharStringLazy Source #

singleton :: Char -> CharStringLazy Source #

cons :: Char -> CharStringLazy -> CharStringLazy Source #

snoc :: CharStringLazy -> Char -> CharStringLazy Source #

append :: CharStringLazy -> CharStringLazy -> CharStringLazy Source #

head :: CharStringLazy -> Char Source #

uncons :: CharStringLazy -> Maybe (Char, CharStringLazy) Source #

last :: CharStringLazy -> Char Source #

tail :: CharStringLazy -> CharStringLazy Source #

init :: CharStringLazy -> CharStringLazy Source #

null :: CharStringLazy -> Bool Source #

length :: CharStringLazy -> Int Source #

map :: ListLike full' item' => (Char -> item') -> CharStringLazy -> full' Source #

rigidMap :: (Char -> Char) -> CharStringLazy -> CharStringLazy Source #

reverse :: CharStringLazy -> CharStringLazy Source #

intersperse :: Char -> CharStringLazy -> CharStringLazy Source #

concat :: ListLike full' CharStringLazy => full' -> CharStringLazy Source #

concatMap :: ListLike full' item' => (Char -> full') -> CharStringLazy -> full' Source #

rigidConcatMap :: (Char -> CharStringLazy) -> CharStringLazy -> CharStringLazy Source #

any :: (Char -> Bool) -> CharStringLazy -> Bool Source #

all :: (Char -> Bool) -> CharStringLazy -> Bool Source #

maximum :: CharStringLazy -> Char Source #

minimum :: CharStringLazy -> Char Source #

replicate :: Int -> Char -> CharStringLazy Source #

take :: Int -> CharStringLazy -> CharStringLazy Source #

drop :: Int -> CharStringLazy -> CharStringLazy Source #

splitAt :: Int -> CharStringLazy -> (CharStringLazy, CharStringLazy) Source #

takeWhile :: (Char -> Bool) -> CharStringLazy -> CharStringLazy Source #

dropWhile :: (Char -> Bool) -> CharStringLazy -> CharStringLazy Source #

dropWhileEnd :: (Char -> Bool) -> CharStringLazy -> CharStringLazy Source #

span :: (Char -> Bool) -> CharStringLazy -> (CharStringLazy, CharStringLazy) Source #

break :: (Char -> Bool) -> CharStringLazy -> (CharStringLazy, CharStringLazy) Source #

group :: (ListLike full' CharStringLazy, Eq Char) => CharStringLazy -> full' Source #

inits :: ListLike full' CharStringLazy => CharStringLazy -> full' Source #

tails :: ListLike full' CharStringLazy => CharStringLazy -> full' Source #

isPrefixOf :: CharStringLazy -> CharStringLazy -> Bool Source #

isSuffixOf :: CharStringLazy -> CharStringLazy -> Bool Source #

isInfixOf :: CharStringLazy -> CharStringLazy -> Bool Source #

stripPrefix :: CharStringLazy -> CharStringLazy -> Maybe CharStringLazy Source #

stripSuffix :: CharStringLazy -> CharStringLazy -> Maybe CharStringLazy Source #

elem :: Char -> CharStringLazy -> Bool Source #

notElem :: Char -> CharStringLazy -> Bool Source #

find :: (Char -> Bool) -> CharStringLazy -> Maybe Char Source #

filter :: (Char -> Bool) -> CharStringLazy -> CharStringLazy Source #

partition :: (Char -> Bool) -> CharStringLazy -> (CharStringLazy, CharStringLazy) Source #

index :: CharStringLazy -> Int -> Char Source #

elemIndex :: Char -> CharStringLazy -> Maybe Int Source #

elemIndices :: (Eq Char, ListLike result Int) => Char -> CharStringLazy -> result Source #

findIndex :: (Char -> Bool) -> CharStringLazy -> Maybe Int Source #

findIndices :: ListLike result Int => (Char -> Bool) -> CharStringLazy -> result Source #

sequence :: (Monad m, ListLike fullinp (m Char)) => fullinp -> m CharStringLazy Source #

mapM :: (Monad m, ListLike full' item') => (Char -> m item') -> CharStringLazy -> m full' Source #

rigidMapM :: Monad m => (Char -> m Char) -> CharStringLazy -> m CharStringLazy Source #

nub :: CharStringLazy -> CharStringLazy Source #

delete :: Char -> CharStringLazy -> CharStringLazy Source #

deleteFirsts :: CharStringLazy -> CharStringLazy -> CharStringLazy Source #

union :: CharStringLazy -> CharStringLazy -> CharStringLazy Source #

intersect :: CharStringLazy -> CharStringLazy -> CharStringLazy Source #

sort :: CharStringLazy -> CharStringLazy Source #

insert :: Char -> CharStringLazy -> CharStringLazy Source #

toList' :: CharStringLazy -> [Char] Source #

fromList' :: [Char] -> CharStringLazy Source #

fromListLike :: ListLike full' Char => CharStringLazy -> full' Source #

nubBy :: (Char -> Char -> Bool) -> CharStringLazy -> CharStringLazy Source #

deleteBy :: (Char -> Char -> Bool) -> Char -> CharStringLazy -> CharStringLazy Source #

deleteFirstsBy :: (Char -> Char -> Bool) -> CharStringLazy -> CharStringLazy -> CharStringLazy Source #

unionBy :: (Char -> Char -> Bool) -> CharStringLazy -> CharStringLazy -> CharStringLazy Source #

intersectBy :: (Char -> Char -> Bool) -> CharStringLazy -> CharStringLazy -> CharStringLazy Source #

groupBy :: (ListLike full' CharStringLazy, Eq Char) => (Char -> Char -> Bool) -> CharStringLazy -> full' Source #

sortBy :: (Char -> Char -> Ordering) -> CharStringLazy -> CharStringLazy Source #

insertBy :: (Char -> Char -> Ordering) -> Char -> CharStringLazy -> CharStringLazy Source #

genericLength :: Num a => CharStringLazy -> a Source #

genericTake :: Integral a => a -> CharStringLazy -> CharStringLazy Source #

genericDrop :: Integral a => a -> CharStringLazy -> CharStringLazy Source #

genericSplitAt :: Integral a => a -> CharStringLazy -> (CharStringLazy, CharStringLazy) Source #

genericReplicate :: Integral a => a -> Char -> CharStringLazy Source #

ListLikeIO CharStringLazy Char Source # 
Instance details

Defined in Data.ListLike.CharString

type Item CharStringLazy Source # 
Instance details

Defined in Data.ListLike.CharString

Base Typeclasses

The ListLike class

class (IsList full, item ~ Item full, FoldableLL full item, Monoid full) => ListLike full item | full -> item Source #

The class implementing list-like functions.

It is worth noting that types such as Map can be instances of ListLike. Due to their specific ways of operating, they may not behave in the expected way in some cases. For instance, cons may not increase the size of a map if the key you have given is already in the map; it will just replace the value already there.

Implementators must define at least:

  • singleton
  • head
  • tail
  • null or genericLength

Instances

Instances details
ListLike ByteString Word8 Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

empty :: ByteString Source #

singleton :: Word8 -> ByteString Source #

cons :: Word8 -> ByteString -> ByteString Source #

snoc :: ByteString -> Word8 -> ByteString Source #

append :: ByteString -> ByteString -> ByteString Source #

head :: ByteString -> Word8 Source #

uncons :: ByteString -> Maybe (Word8, ByteString) Source #

last :: ByteString -> Word8 Source #

tail :: ByteString -> ByteString Source #

init :: ByteString -> ByteString Source #

null :: ByteString -> Bool Source #

length :: ByteString -> Int Source #

map :: ListLike full' item' => (Word8 -> item') -> ByteString -> full' Source #

rigidMap :: (Word8 -> Word8) -> ByteString -> ByteString Source #

reverse :: ByteString -> ByteString Source #

intersperse :: Word8 -> ByteString -> ByteString Source #

concat :: ListLike full' ByteString => full' -> ByteString Source #

concatMap :: ListLike full' item' => (Word8 -> full') -> ByteString -> full' Source #

rigidConcatMap :: (Word8 -> ByteString) -> ByteString -> ByteString Source #

any :: (Word8 -> Bool) -> ByteString -> Bool Source #

all :: (Word8 -> Bool) -> ByteString -> Bool Source #

maximum :: ByteString -> Word8 Source #

minimum :: ByteString -> Word8 Source #

replicate :: Int -> Word8 -> ByteString Source #

take :: Int -> ByteString -> ByteString Source #

drop :: Int -> ByteString -> ByteString Source #

splitAt :: Int -> ByteString -> (ByteString, ByteString) Source #

takeWhile :: (Word8 -> Bool) -> ByteString -> ByteString Source #

dropWhile :: (Word8 -> Bool) -> ByteString -> ByteString Source #

dropWhileEnd :: (Word8 -> Bool) -> ByteString -> ByteString Source #

span :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) Source #

break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) Source #

group :: (ListLike full' ByteString, Eq Word8) => ByteString -> full' Source #

inits :: ListLike full' ByteString => ByteString -> full' Source #

tails :: ListLike full' ByteString => ByteString -> full' Source #

isPrefixOf :: ByteString -> ByteString -> Bool Source #

isSuffixOf :: ByteString -> ByteString -> Bool Source #

isInfixOf :: ByteString -> ByteString -> Bool Source #

stripPrefix :: ByteString -> ByteString -> Maybe ByteString Source #

stripSuffix :: ByteString -> ByteString -> Maybe ByteString Source #

elem :: Word8 -> ByteString -> Bool Source #

notElem :: Word8 -> ByteString -> Bool Source #

find :: (Word8 -> Bool) -> ByteString -> Maybe Word8 Source #

filter :: (Word8 -> Bool) -> ByteString -> ByteString Source #

partition :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) Source #

index :: ByteString -> Int -> Word8 Source #

elemIndex :: Word8 -> ByteString -> Maybe Int Source #

elemIndices :: (Eq Word8, ListLike result Int) => Word8 -> ByteString -> result Source #

findIndex :: (Word8 -> Bool) -> ByteString -> Maybe Int Source #

findIndices :: ListLike result Int => (Word8 -> Bool) -> ByteString -> result Source #

sequence :: (Monad m, ListLike fullinp (m Word8)) => fullinp -> m ByteString Source #

mapM :: (Monad m, ListLike full' item') => (Word8 -> m item') -> ByteString -> m full' Source #

rigidMapM :: Monad m => (Word8 -> m Word8) -> ByteString -> m ByteString Source #

nub :: ByteString -> ByteString Source #

delete :: Word8 -> ByteString -> ByteString Source #

deleteFirsts :: ByteString -> ByteString -> ByteString Source #

union :: ByteString -> ByteString -> ByteString Source #

intersect :: ByteString -> ByteString -> ByteString Source #

sort :: ByteString -> ByteString Source #

insert :: Word8 -> ByteString -> ByteString Source #

toList' :: ByteString -> [Word8] Source #

fromList' :: [Word8] -> ByteString Source #

fromListLike :: ListLike full' Word8 => ByteString -> full' Source #

nubBy :: (Word8 -> Word8 -> Bool) -> ByteString -> ByteString Source #

deleteBy :: (Word8 -> Word8 -> Bool) -> Word8 -> ByteString -> ByteString Source #

deleteFirstsBy :: (Word8 -> Word8 -> Bool) -> ByteString -> ByteString -> ByteString Source #

unionBy :: (Word8 -> Word8 -> Bool) -> ByteString -> ByteString -> ByteString Source #

intersectBy :: (Word8 -> Word8 -> Bool) -> ByteString -> ByteString -> ByteString Source #

groupBy :: (ListLike full' ByteString, Eq Word8) => (Word8 -> Word8 -> Bool) -> ByteString -> full' Source #

sortBy :: (Word8 -> Word8 -> Ordering) -> ByteString -> ByteString Source #

insertBy :: (Word8 -> Word8 -> Ordering) -> Word8 -> ByteString -> ByteString Source #

genericLength :: Num a => ByteString -> a Source #

genericTake :: Integral a => a -> ByteString -> ByteString Source #

genericDrop :: Integral a => a -> ByteString -> ByteString Source #

genericSplitAt :: Integral a => a -> ByteString -> (ByteString, ByteString) Source #

genericReplicate :: Integral a => a -> Word8 -> ByteString Source #

ListLike ByteString Word8 Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

empty :: ByteString Source #

singleton :: Word8 -> ByteString Source #

cons :: Word8 -> ByteString -> ByteString Source #

snoc :: ByteString -> Word8 -> ByteString Source #

append :: ByteString -> ByteString -> ByteString Source #

head :: ByteString -> Word8 Source #

uncons :: ByteString -> Maybe (Word8, ByteString) Source #

last :: ByteString -> Word8 Source #

tail :: ByteString -> ByteString Source #

init :: ByteString -> ByteString Source #

null :: ByteString -> Bool Source #

length :: ByteString -> Int Source #

map :: ListLike full' item' => (Word8 -> item') -> ByteString -> full' Source #

rigidMap :: (Word8 -> Word8) -> ByteString -> ByteString Source #

reverse :: ByteString -> ByteString Source #

intersperse :: Word8 -> ByteString -> ByteString Source #

concat :: ListLike full' ByteString => full' -> ByteString Source #

concatMap :: ListLike full' item' => (Word8 -> full') -> ByteString -> full' Source #

rigidConcatMap :: (Word8 -> ByteString) -> ByteString -> ByteString Source #

any :: (Word8 -> Bool) -> ByteString -> Bool Source #

all :: (Word8 -> Bool) -> ByteString -> Bool Source #

maximum :: ByteString -> Word8 Source #

minimum :: ByteString -> Word8 Source #

replicate :: Int -> Word8 -> ByteString Source #

take :: Int -> ByteString -> ByteString Source #

drop :: Int -> ByteString -> ByteString Source #

splitAt :: Int -> ByteString -> (ByteString, ByteString) Source #

takeWhile :: (Word8 -> Bool) -> ByteString -> ByteString Source #

dropWhile :: (Word8 -> Bool) -> ByteString -> ByteString Source #

dropWhileEnd :: (Word8 -> Bool) -> ByteString -> ByteString Source #

span :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) Source #

break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) Source #

group :: (ListLike full' ByteString, Eq Word8) => ByteString -> full' Source #

inits :: ListLike full' ByteString => ByteString -> full' Source #

tails :: ListLike full' ByteString => ByteString -> full' Source #

isPrefixOf :: ByteString -> ByteString -> Bool Source #

isSuffixOf :: ByteString -> ByteString -> Bool Source #

isInfixOf :: ByteString -> ByteString -> Bool Source #

stripPrefix :: ByteString -> ByteString -> Maybe ByteString Source #

stripSuffix :: ByteString -> ByteString -> Maybe ByteString Source #

elem :: Word8 -> ByteString -> Bool Source #

notElem :: Word8 -> ByteString -> Bool Source #

find :: (Word8 -> Bool) -> ByteString -> Maybe Word8 Source #

filter :: (Word8 -> Bool) -> ByteString -> ByteString Source #

partition :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) Source #

index :: ByteString -> Int -> Word8 Source #

elemIndex :: Word8 -> ByteString -> Maybe Int Source #

elemIndices :: (Eq Word8, ListLike result Int) => Word8 -> ByteString -> result Source #

findIndex :: (Word8 -> Bool) -> ByteString -> Maybe Int Source #

findIndices :: ListLike result Int => (Word8 -> Bool) -> ByteString -> result Source #

sequence :: (Monad m, ListLike fullinp (m Word8)) => fullinp -> m ByteString Source #

mapM :: (Monad m, ListLike full' item') => (Word8 -> m item') -> ByteString -> m full' Source #

rigidMapM :: Monad m => (Word8 -> m Word8) -> ByteString -> m ByteString Source #

nub :: ByteString -> ByteString Source #

delete :: Word8 -> ByteString -> ByteString Source #

deleteFirsts :: ByteString -> ByteString -> ByteString Source #

union :: ByteString -> ByteString -> ByteString Source #

intersect :: ByteString -> ByteString -> ByteString Source #

sort :: ByteString -> ByteString Source #

insert :: Word8 -> ByteString -> ByteString Source #

toList' :: ByteString -> [Word8] Source #

fromList' :: [Word8] -> ByteString Source #

fromListLike :: ListLike full' Word8 => ByteString -> full' Source #

nubBy :: (Word8 -> Word8 -> Bool) -> ByteString -> ByteString Source #

deleteBy :: (Word8 -> Word8 -> Bool) -> Word8 -> ByteString -> ByteString Source #

deleteFirstsBy :: (Word8 -> Word8 -> Bool) -> ByteString -> ByteString -> ByteString Source #

unionBy :: (Word8 -> Word8 -> Bool) -> ByteString -> ByteString -> ByteString Source #

intersectBy :: (Word8 -> Word8 -> Bool) -> ByteString -> ByteString -> ByteString Source #

groupBy :: (ListLike full' ByteString, Eq Word8) => (Word8 -> Word8 -> Bool) -> ByteString -> full' Source #

sortBy :: (Word8 -> Word8 -> Ordering) -> ByteString -> ByteString Source #

insertBy :: (Word8 -> Word8 -> Ordering) -> Word8 -> ByteString -> ByteString Source #

genericLength :: Num a => ByteString -> a Source #

genericTake :: Integral a => a -> ByteString -> ByteString Source #

genericDrop :: Integral a => a -> ByteString -> ByteString Source #

genericSplitAt :: Integral a => a -> ByteString -> (ByteString, ByteString) Source #

genericReplicate :: Integral a => a -> Word8 -> ByteString Source #

ListLike Builder Char Source # 
Instance details

Defined in Data.ListLike.Text.Builder

Methods

empty :: Builder Source #

singleton :: Char -> Builder Source #

cons :: Char -> Builder -> Builder Source #

snoc :: Builder -> Char -> Builder Source #

append :: Builder -> Builder -> Builder Source #

head :: Builder -> Char Source #

uncons :: Builder -> Maybe (Char, Builder) Source #

last :: Builder -> Char Source #

tail :: Builder -> Builder Source #

init :: Builder -> Builder Source #

null :: Builder -> Bool Source #

length :: Builder -> Int Source #

map :: ListLike full' item' => (Char -> item') -> Builder -> full' Source #

rigidMap :: (Char -> Char) -> Builder -> Builder Source #

reverse :: Builder -> Builder Source #

intersperse :: Char -> Builder -> Builder Source #

concat :: ListLike full' Builder => full' -> Builder Source #

concatMap :: ListLike full' item' => (Char -> full') -> Builder -> full' Source #

rigidConcatMap :: (Char -> Builder) -> Builder -> Builder Source #

any :: (Char -> Bool) -> Builder -> Bool Source #

all :: (Char -> Bool) -> Builder -> Bool Source #

maximum :: Builder -> Char Source #

minimum :: Builder -> Char Source #

replicate :: Int -> Char -> Builder Source #

take :: Int -> Builder -> Builder Source #

drop :: Int -> Builder -> Builder Source #

splitAt :: Int -> Builder -> (Builder, Builder) Source #

takeWhile :: (Char -> Bool) -> Builder -> Builder Source #

dropWhile :: (Char -> Bool) -> Builder -> Builder Source #

dropWhileEnd :: (Char -> Bool) -> Builder -> Builder Source #

span :: (Char -> Bool) -> Builder -> (Builder, Builder) Source #

break :: (Char -> Bool) -> Builder -> (Builder, Builder) Source #

group :: (ListLike full' Builder, Eq Char) => Builder -> full' Source #

inits :: ListLike full' Builder => Builder -> full' Source #

tails :: ListLike full' Builder => Builder -> full' Source #

isPrefixOf :: Builder -> Builder -> Bool Source #

isSuffixOf :: Builder -> Builder -> Bool Source #

isInfixOf :: Builder -> Builder -> Bool Source #

stripPrefix :: Builder -> Builder -> Maybe Builder Source #

stripSuffix :: Builder -> Builder -> Maybe Builder Source #

elem :: Char -> Builder -> Bool Source #

notElem :: Char -> Builder -> Bool Source #

find :: (Char -> Bool) -> Builder -> Maybe Char Source #

filter :: (Char -> Bool) -> Builder -> Builder Source #

partition :: (Char -> Bool) -> Builder -> (Builder, Builder) Source #

index :: Builder -> Int -> Char Source #

elemIndex :: Char -> Builder -> Maybe Int Source #

elemIndices :: (Eq Char, ListLike result Int) => Char -> Builder -> result Source #

findIndex :: (Char -> Bool) -> Builder -> Maybe Int Source #

findIndices :: ListLike result Int => (Char -> Bool) -> Builder -> result Source #

sequence :: (Monad m, ListLike fullinp (m Char)) => fullinp -> m Builder Source #

mapM :: (Monad m, ListLike full' item') => (Char -> m item') -> Builder -> m full' Source #

rigidMapM :: Monad m => (Char -> m Char) -> Builder -> m Builder Source #

nub :: Builder -> Builder Source #

delete :: Char -> Builder -> Builder Source #

deleteFirsts :: Builder -> Builder -> Builder Source #

union :: Builder -> Builder -> Builder Source #

intersect :: Builder -> Builder -> Builder Source #

sort :: Builder -> Builder Source #

insert :: Char -> Builder -> Builder Source #

toList' :: Builder -> [Char] Source #

fromList' :: [Char] -> Builder Source #

fromListLike :: ListLike full' Char => Builder -> full' Source #

nubBy :: (Char -> Char -> Bool) -> Builder -> Builder Source #

deleteBy :: (Char -> Char -> Bool) -> Char -> Builder -> Builder Source #

deleteFirstsBy :: (Char -> Char -> Bool) -> Builder -> Builder -> Builder Source #

unionBy :: (Char -> Char -> Bool) -> Builder -> Builder -> Builder Source #

intersectBy :: (Char -> Char -> Bool) -> Builder -> Builder -> Builder Source #

groupBy :: (ListLike full' Builder, Eq Char) => (Char -> Char -> Bool) -> Builder -> full' Source #

sortBy :: (Char -> Char -> Ordering) -> Builder -> Builder Source #

insertBy :: (Char -> Char -> Ordering) -> Char -> Builder -> Builder Source #

genericLength :: Num a => Builder -> a Source #

genericTake :: Integral a => a -> Builder -> Builder Source #

genericDrop :: Integral a => a -> Builder -> Builder Source #

genericSplitAt :: Integral a => a -> Builder -> (Builder, Builder) Source #

genericReplicate :: Integral a => a -> Char -> Builder Source #

ListLike Text Char Source # 
Instance details

Defined in Data.ListLike.Text.TextLazy

Methods

empty :: Text Source #

singleton :: Char -> Text Source #

cons :: Char -> Text -> Text Source #

snoc :: Text -> Char -> Text Source #

append :: Text -> Text -> Text Source #

head :: Text -> Char Source #

uncons :: Text -> Maybe (Char, Text) Source #

last :: Text -> Char Source #

tail :: Text -> Text Source #

init :: Text -> Text Source #

null :: Text -> Bool Source #

length :: Text -> Int Source #

map :: ListLike full' item' => (Char -> item') -> Text -> full' Source #

rigidMap :: (Char -> Char) -> Text -> Text Source #

reverse :: Text -> Text Source #

intersperse :: Char -> Text -> Text Source #

concat :: ListLike full' Text => full' -> Text Source #

concatMap :: ListLike full' item' => (Char -> full') -> Text -> full' Source #

rigidConcatMap :: (Char -> Text) -> Text -> Text Source #

any :: (Char -> Bool) -> Text -> Bool Source #

all :: (Char -> Bool) -> Text -> Bool Source #

maximum :: Text -> Char Source #

minimum :: Text -> Char Source #

replicate :: Int -> Char -> Text Source #

take :: Int -> Text -> Text Source #

drop :: Int -> Text -> Text Source #

splitAt :: Int -> Text -> (Text, Text) Source #

takeWhile :: (Char -> Bool) -> Text -> Text Source #

dropWhile :: (Char -> Bool) -> Text -> Text Source #

dropWhileEnd :: (Char -> Bool) -> Text -> Text Source #

span :: (Char -> Bool) -> Text -> (Text, Text) Source #

break :: (Char -> Bool) -> Text -> (Text, Text) Source #

group :: (ListLike full' Text, Eq Char) => Text -> full' Source #

inits :: ListLike full' Text => Text -> full' Source #

tails :: ListLike full' Text => Text -> full' Source #

isPrefixOf :: Text -> Text -> Bool Source #

isSuffixOf :: Text -> Text -> Bool Source #

isInfixOf :: Text -> Text -> Bool Source #

stripPrefix :: Text -> Text -> Maybe Text Source #

stripSuffix :: Text -> Text -> Maybe Text Source #

elem :: Char -> Text -> Bool Source #

notElem :: Char -> Text -> Bool Source #

find :: (Char -> Bool) -> Text -> Maybe Char Source #

filter :: (Char -> Bool) -> Text -> Text Source #

partition :: (Char -> Bool) -> Text -> (Text, Text) Source #

index :: Text -> Int -> Char Source #

elemIndex :: Char -> Text -> Maybe Int Source #

elemIndices :: (Eq Char, ListLike result Int) => Char -> Text -> result Source #

findIndex :: (Char -> Bool) -> Text -> Maybe Int Source #

findIndices :: ListLike result Int => (Char -> Bool) -> Text -> result Source #

sequence :: (Monad m, ListLike fullinp (m Char)) => fullinp -> m Text Source #

mapM :: (Monad m, ListLike full' item') => (Char -> m item') -> Text -> m full' Source #

rigidMapM :: Monad m => (Char -> m Char) -> Text -> m Text Source #

nub :: Text -> Text Source #

delete :: Char -> Text -> Text Source #

deleteFirsts :: Text -> Text -> Text Source #

union :: Text -> Text -> Text Source #

intersect :: Text -> Text -> Text Source #

sort :: Text -> Text Source #

insert :: Char -> Text -> Text Source #

toList' :: Text -> [Char] Source #

fromList' :: [Char] -> Text Source #

fromListLike :: ListLike full' Char => Text -> full' Source #

nubBy :: (Char -> Char -> Bool) -> Text -> Text Source #

deleteBy :: (Char -> Char -> Bool) -> Char -> Text -> Text Source #

deleteFirstsBy :: (Char -> Char -> Bool) -> Text -> Text -> Text Source #

unionBy :: (Char -> Char -> Bool) -> Text -> Text -> Text Source #

intersectBy :: (Char -> Char -> Bool) -> Text -> Text -> Text Source #

groupBy :: (ListLike full' Text, Eq Char) => (Char -> Char -> Bool) -> Text -> full' Source #

sortBy :: (Char -> Char -> Ordering) -> Text -> Text Source #

insertBy :: (Char -> Char -> Ordering) -> Char -> Text -> Text Source #

genericLength :: Num a => Text -> a Source #

genericTake :: Integral a => a -> Text -> Text Source #

genericDrop :: Integral a => a -> Text -> Text Source #

genericSplitAt :: Integral a => a -> Text -> (Text, Text) Source #

genericReplicate :: Integral a => a -> Char -> Text Source #

ListLike Text Char Source # 
Instance details

Defined in Data.ListLike.Text.Text

Methods

empty :: Text Source #

singleton :: Char -> Text Source #

cons :: Char -> Text -> Text Source #

snoc :: Text -> Char -> Text Source #

append :: Text -> Text -> Text Source #

head :: Text -> Char Source #

uncons :: Text -> Maybe (Char, Text) Source #

last :: Text -> Char Source #

tail :: Text -> Text Source #

init :: Text -> Text Source #

null :: Text -> Bool Source #

length :: Text -> Int Source #

map :: ListLike full' item' => (Char -> item') -> Text -> full' Source #

rigidMap :: (Char -> Char) -> Text -> Text Source #

reverse :: Text -> Text Source #

intersperse :: Char -> Text -> Text Source #

concat :: ListLike full' Text => full' -> Text Source #

concatMap :: ListLike full' item' => (Char -> full') -> Text -> full' Source #

rigidConcatMap :: (Char -> Text) -> Text -> Text Source #

any :: (Char -> Bool) -> Text -> Bool Source #

all :: (Char -> Bool) -> Text -> Bool Source #

maximum :: Text -> Char Source #

minimum :: Text -> Char Source #

replicate :: Int -> Char -> Text Source #

take :: Int -> Text -> Text Source #

drop :: Int -> Text -> Text Source #

splitAt :: Int -> Text -> (Text, Text) Source #

takeWhile :: (Char -> Bool) -> Text -> Text Source #

dropWhile :: (Char -> Bool) -> Text -> Text Source #

dropWhileEnd :: (Char -> Bool) -> Text -> Text Source #

span :: (Char -> Bool) -> Text -> (Text, Text) Source #

break :: (Char -> Bool) -> Text -> (Text, Text) Source #

group :: (ListLike full' Text, Eq Char) => Text -> full' Source #

inits :: ListLike full' Text => Text -> full' Source #

tails :: ListLike full' Text => Text -> full' Source #

isPrefixOf :: Text -> Text -> Bool Source #

isSuffixOf :: Text -> Text -> Bool Source #

isInfixOf :: Text -> Text -> Bool Source #

stripPrefix :: Text -> Text -> Maybe Text Source #

stripSuffix :: Text -> Text -> Maybe Text Source #

elem :: Char -> Text -> Bool Source #

notElem :: Char -> Text -> Bool Source #

find :: (Char -> Bool) -> Text -> Maybe Char Source #

filter :: (Char -> Bool) -> Text -> Text Source #

partition :: (Char -> Bool) -> Text -> (Text, Text) Source #

index :: Text -> Int -> Char Source #

elemIndex :: Char -> Text -> Maybe Int Source #

elemIndices :: (Eq Char, ListLike result Int) => Char -> Text -> result Source #

findIndex :: (Char -> Bool) -> Text -> Maybe Int Source #

findIndices :: ListLike result Int => (Char -> Bool) -> Text -> result Source #

sequence :: (Monad m, ListLike fullinp (m Char)) => fullinp -> m Text Source #

mapM :: (Monad m, ListLike full' item') => (Char -> m item') -> Text -> m full' Source #

rigidMapM :: Monad m => (Char -> m Char) -> Text -> m Text Source #

nub :: Text -> Text Source #

delete :: Char -> Text -> Text Source #

deleteFirsts :: Text -> Text -> Text Source #

union :: Text -> Text -> Text Source #

intersect :: Text -> Text -> Text Source #

sort :: Text -> Text Source #

insert :: Char -> Text -> Text Source #

toList' :: Text -> [Char] Source #

fromList' :: [Char] -> Text Source #

fromListLike :: ListLike full' Char => Text -> full' Source #

nubBy :: (Char -> Char -> Bool) -> Text -> Text Source #

deleteBy :: (Char -> Char -> Bool) -> Char -> Text -> Text Source #

deleteFirstsBy :: (Char -> Char -> Bool) -> Text -> Text -> Text Source #

unionBy :: (Char -> Char -> Bool) -> Text -> Text -> Text Source #

intersectBy :: (Char -> Char -> Bool) -> Text -> Text -> Text Source #

groupBy :: (ListLike full' Text, Eq Char) => (Char -> Char -> Bool) -> Text -> full' Source #

sortBy :: (Char -> Char -> Ordering) -> Text -> Text Source #

insertBy :: (Char -> Char -> Ordering) -> Char -> Text -> Text Source #

genericLength :: Num a => Text -> a Source #

genericTake :: Integral a => a -> Text -> Text Source #

genericDrop :: Integral a => a -> Text -> Text Source #

genericSplitAt :: Integral a => a -> Text -> (Text, Text) Source #

genericReplicate :: Integral a => a -> Char -> Text Source #

ListLike CharStringLazy Char Source # 
Instance details

Defined in Data.ListLike.CharString

Methods

empty :: CharStringLazy Source #

singleton :: Char -> CharStringLazy Source #

cons :: Char -> CharStringLazy -> CharStringLazy Source #

snoc :: CharStringLazy -> Char -> CharStringLazy Source #

append :: CharStringLazy -> CharStringLazy -> CharStringLazy Source #

head :: CharStringLazy -> Char Source #

uncons :: CharStringLazy -> Maybe (Char, CharStringLazy) Source #

last :: CharStringLazy -> Char Source #

tail :: CharStringLazy -> CharStringLazy Source #

init :: CharStringLazy -> CharStringLazy Source #

null :: CharStringLazy -> Bool Source #

length :: CharStringLazy -> Int Source #

map :: ListLike full' item' => (Char -> item') -> CharStringLazy -> full' Source #

rigidMap :: (Char -> Char) -> CharStringLazy -> CharStringLazy Source #

reverse :: CharStringLazy -> CharStringLazy Source #

intersperse :: Char -> CharStringLazy -> CharStringLazy Source #

concat :: ListLike full' CharStringLazy => full' -> CharStringLazy Source #

concatMap :: ListLike full' item' => (Char -> full') -> CharStringLazy -> full' Source #

rigidConcatMap :: (Char -> CharStringLazy) -> CharStringLazy -> CharStringLazy Source #

any :: (Char -> Bool) -> CharStringLazy -> Bool Source #

all :: (Char -> Bool) -> CharStringLazy -> Bool Source #

maximum :: CharStringLazy -> Char Source #

minimum :: CharStringLazy -> Char Source #

replicate :: Int -> Char -> CharStringLazy Source #

take :: Int -> CharStringLazy -> CharStringLazy Source #

drop :: Int -> CharStringLazy -> CharStringLazy Source #

splitAt :: Int -> CharStringLazy -> (CharStringLazy, CharStringLazy) Source #

takeWhile :: (Char -> Bool) -> CharStringLazy -> CharStringLazy Source #

dropWhile :: (Char -> Bool) -> CharStringLazy -> CharStringLazy Source #

dropWhileEnd :: (Char -> Bool) -> CharStringLazy -> CharStringLazy Source #

span :: (Char -> Bool) -> CharStringLazy -> (CharStringLazy, CharStringLazy) Source #

break :: (Char -> Bool) -> CharStringLazy -> (CharStringLazy, CharStringLazy) Source #

group :: (ListLike full' CharStringLazy, Eq Char) => CharStringLazy -> full' Source #

inits :: ListLike full' CharStringLazy => CharStringLazy -> full' Source #

tails :: ListLike full' CharStringLazy => CharStringLazy -> full' Source #

isPrefixOf :: CharStringLazy -> CharStringLazy -> Bool Source #

isSuffixOf :: CharStringLazy -> CharStringLazy -> Bool Source #

isInfixOf :: CharStringLazy -> CharStringLazy -> Bool Source #

stripPrefix :: CharStringLazy -> CharStringLazy -> Maybe CharStringLazy Source #

stripSuffix :: CharStringLazy -> CharStringLazy -> Maybe CharStringLazy Source #

elem :: Char -> CharStringLazy -> Bool Source #

notElem :: Char -> CharStringLazy -> Bool Source #

find :: (Char -> Bool) -> CharStringLazy -> Maybe Char Source #

filter :: (Char -> Bool) -> CharStringLazy -> CharStringLazy Source #

partition :: (Char -> Bool) -> CharStringLazy -> (CharStringLazy, CharStringLazy) Source #

index :: CharStringLazy -> Int -> Char Source #

elemIndex :: Char -> CharStringLazy -> Maybe Int Source #

elemIndices :: (Eq Char, ListLike result Int) => Char -> CharStringLazy -> result Source #

findIndex :: (Char -> Bool) -> CharStringLazy -> Maybe Int Source #

findIndices :: ListLike result Int => (Char -> Bool) -> CharStringLazy -> result Source #

sequence :: (Monad m, ListLike fullinp (m Char)) => fullinp -> m CharStringLazy Source #

mapM :: (Monad m, ListLike full' item') => (Char -> m item') -> CharStringLazy -> m full' Source #

rigidMapM :: Monad m => (Char -> m Char) -> CharStringLazy -> m CharStringLazy Source #

nub :: CharStringLazy -> CharStringLazy Source #

delete :: Char -> CharStringLazy -> CharStringLazy Source #

deleteFirsts :: CharStringLazy -> CharStringLazy -> CharStringLazy Source #

union :: CharStringLazy -> CharStringLazy -> CharStringLazy Source #

intersect :: CharStringLazy -> CharStringLazy -> CharStringLazy Source #

sort :: CharStringLazy -> CharStringLazy Source #

insert :: Char -> CharStringLazy -> CharStringLazy Source #

toList' :: CharStringLazy -> [Char] Source #

fromList' :: [Char] -> CharStringLazy Source #

fromListLike :: ListLike full' Char => CharStringLazy -> full' Source #

nubBy :: (Char -> Char -> Bool) -> CharStringLazy -> CharStringLazy Source #

deleteBy :: (Char -> Char -> Bool) -> Char -> CharStringLazy -> CharStringLazy Source #

deleteFirstsBy :: (Char -> Char -> Bool) -> CharStringLazy -> CharStringLazy -> CharStringLazy Source #

unionBy :: (Char -> Char -> Bool) -> CharStringLazy -> CharStringLazy -> CharStringLazy Source #

intersectBy :: (Char -> Char -> Bool) -> CharStringLazy -> CharStringLazy -> CharStringLazy Source #

groupBy :: (ListLike full' CharStringLazy, Eq Char) => (Char -> Char -> Bool) -> CharStringLazy -> full' Source #

sortBy :: (Char -> Char -> Ordering) -> CharStringLazy -> CharStringLazy Source #

insertBy :: (Char -> Char -> Ordering) -> Char -> CharStringLazy -> CharStringLazy Source #

genericLength :: Num a => CharStringLazy -> a Source #

genericTake :: Integral a => a -> CharStringLazy -> CharStringLazy Source #

genericDrop :: Integral a => a -> CharStringLazy -> CharStringLazy Source #

genericSplitAt :: Integral a => a -> CharStringLazy -> (CharStringLazy, CharStringLazy) Source #

genericReplicate :: Integral a => a -> Char -> CharStringLazy Source #

ListLike CharString Char Source # 
Instance details

Defined in Data.ListLike.CharString

Methods

empty :: CharString Source #

singleton :: Char -> CharString Source #

cons :: Char -> CharString -> CharString Source #

snoc :: CharString -> Char -> CharString Source #

append :: CharString -> CharString -> CharString Source #

head :: CharString -> Char Source #

uncons :: CharString -> Maybe (Char, CharString) Source #

last :: CharString -> Char Source #

tail :: CharString -> CharString Source #

init :: CharString -> CharString Source #

null :: CharString -> Bool Source #

length :: CharString -> Int Source #

map :: ListLike full' item' => (Char -> item') -> CharString -> full' Source #

rigidMap :: (Char -> Char) -> CharString -> CharString Source #

reverse :: CharString -> CharString Source #

intersperse :: Char -> CharString -> CharString Source #

concat :: ListLike full' CharString => full' -> CharString Source #

concatMap :: ListLike full' item' => (Char -> full') -> CharString -> full' Source #

rigidConcatMap :: (Char -> CharString) -> CharString -> CharString Source #

any :: (Char -> Bool) -> CharString -> Bool Source #

all :: (Char -> Bool) -> CharString -> Bool Source #

maximum :: CharString -> Char Source #

minimum :: CharString -> Char Source #

replicate :: Int -> Char -> CharString Source #

take :: Int -> CharString -> CharString Source #

drop :: Int -> CharString -> CharString Source #

splitAt :: Int -> CharString -> (CharString, CharString) Source #

takeWhile :: (Char -> Bool) -> CharString -> CharString Source #

dropWhile :: (Char -> Bool) -> CharString -> CharString Source #

dropWhileEnd :: (Char -> Bool) -> CharString -> CharString Source #

span :: (Char -> Bool) -> CharString -> (CharString, CharString) Source #

break :: (Char -> Bool) -> CharString -> (CharString, CharString) Source #

group :: (ListLike full' CharString, Eq Char) => CharString -> full' Source #

inits :: ListLike full' CharString => CharString -> full' Source #

tails :: ListLike full' CharString => CharString -> full' Source #

isPrefixOf :: CharString -> CharString -> Bool Source #

isSuffixOf :: CharString -> CharString -> Bool Source #

isInfixOf :: CharString -> CharString -> Bool Source #

stripPrefix :: CharString -> CharString -> Maybe CharString Source #

stripSuffix :: CharString -> CharString -> Maybe CharString Source #

elem :: Char -> CharString -> Bool Source #

notElem :: Char -> CharString -> Bool Source #

find :: (Char -> Bool) -> CharString -> Maybe Char Source #

filter :: (Char -> Bool) -> CharString -> CharString Source #

partition :: (Char -> Bool) -> CharString -> (CharString, CharString) Source #

index :: CharString -> Int -> Char Source #

elemIndex :: Char -> CharString -> Maybe Int Source #

elemIndices :: (Eq Char, ListLike result Int) => Char -> CharString -> result Source #

findIndex :: (Char -> Bool) -> CharString -> Maybe Int Source #

findIndices :: ListLike result Int => (Char -> Bool) -> CharString -> result Source #

sequence :: (Monad m, ListLike fullinp (m Char)) => fullinp -> m CharString Source #

mapM :: (Monad m, ListLike full' item') => (Char -> m item') -> CharString -> m full' Source #

rigidMapM :: Monad m => (Char -> m Char) -> CharString -> m CharString Source #

nub :: CharString -> CharString Source #

delete :: Char -> CharString -> CharString Source #

deleteFirsts :: CharString -> CharString -> CharString Source #

union :: CharString -> CharString -> CharString Source #

intersect :: CharString -> CharString -> CharString Source #

sort :: CharString -> CharString Source #

insert :: Char -> CharString -> CharString Source #

toList' :: CharString -> [Char] Source #

fromList' :: [Char] -> CharString Source #

fromListLike :: ListLike full' Char => CharString -> full' Source #

nubBy :: (Char -> Char -> Bool) -> CharString -> CharString Source #

deleteBy :: (Char -> Char -> Bool) -> Char -> CharString -> CharString Source #

deleteFirstsBy :: (Char -> Char -> Bool) -> CharString -> CharString -> CharString Source #

unionBy :: (Char -> Char -> Bool) -> CharString -> CharString -> CharString Source #

intersectBy :: (Char -> Char -> Bool) -> CharString -> CharString -> CharString Source #

groupBy :: (ListLike full' CharString, Eq Char) => (Char -> Char -> Bool) -> CharString -> full' Source #

sortBy :: (Char -> Char -> Ordering) -> CharString -> CharString Source #

insertBy :: (Char -> Char -> Ordering) -> Char -> CharString -> CharString Source #

genericLength :: Num a => CharString -> a Source #

genericTake :: Integral a => a -> CharString -> CharString Source #

genericDrop :: Integral a => a -> CharString -> CharString Source #

genericSplitAt :: Integral a => a -> CharString -> (CharString, CharString) Source #

genericReplicate :: Integral a => a -> Char -> CharString Source #

ListLike Chars Char Source # 
Instance details

Defined in Data.ListLike.Chars

Methods

empty :: Chars Source #

singleton :: Char -> Chars Source #

cons :: Char -> Chars -> Chars Source #

snoc :: Chars -> Char -> Chars Source #

append :: Chars -> Chars -> Chars Source #

head :: Chars -> Char Source #

uncons :: Chars -> Maybe (Char, Chars) Source #

last :: Chars -> Char Source #

tail :: Chars -> Chars Source #

init :: Chars -> Chars Source #

null :: Chars -> Bool Source #

length :: Chars -> Int Source #

map :: ListLike full' item' => (Char -> item') -> Chars -> full' Source #

rigidMap :: (Char -> Char) -> Chars -> Chars Source #

reverse :: Chars -> Chars Source #

intersperse :: Char -> Chars -> Chars Source #

concat :: ListLike full' Chars => full' -> Chars Source #

concatMap :: ListLike full' item' => (Char -> full') -> Chars -> full' Source #

rigidConcatMap :: (Char -> Chars) -> Chars -> Chars Source #

any :: (Char -> Bool) -> Chars -> Bool Source #

all :: (Char -> Bool) -> Chars -> Bool Source #

maximum :: Chars -> Char Source #

minimum :: Chars -> Char Source #

replicate :: Int -> Char -> Chars Source #

take :: Int -> Chars -> Chars Source #

drop :: Int -> Chars -> Chars Source #

splitAt :: Int -> Chars -> (Chars, Chars) Source #

takeWhile :: (Char -> Bool) -> Chars -> Chars Source #

dropWhile :: (Char -> Bool) -> Chars -> Chars Source #

dropWhileEnd :: (Char -> Bool) -> Chars -> Chars Source #

span :: (Char -> Bool) -> Chars -> (Chars, Chars) Source #

break :: (Char -> Bool) -> Chars -> (Chars, Chars) Source #

group :: (ListLike full' Chars, Eq Char) => Chars -> full' Source #

inits :: ListLike full' Chars => Chars -> full' Source #

tails :: ListLike full' Chars => Chars -> full' Source #

isPrefixOf :: Chars -> Chars -> Bool Source #

isSuffixOf :: Chars -> Chars -> Bool Source #

isInfixOf :: Chars -> Chars -> Bool Source #

stripPrefix :: Chars -> Chars -> Maybe Chars Source #

stripSuffix :: Chars -> Chars -> Maybe Chars Source #

elem :: Char -> Chars -> Bool Source #

notElem :: Char -> Chars -> Bool Source #

find :: (Char -> Bool) -> Chars -> Maybe Char Source #

filter :: (Char -> Bool) -> Chars -> Chars Source #

partition :: (Char -> Bool) -> Chars -> (Chars, Chars) Source #

index :: Chars -> Int -> Char Source #

elemIndex :: Char -> Chars -> Maybe Int Source #

elemIndices :: (Eq Char, ListLike result Int) => Char -> Chars -> result Source #

findIndex :: (Char -> Bool) -> Chars -> Maybe Int Source #

findIndices :: ListLike result Int => (Char -> Bool) -> Chars -> result Source #

sequence :: (Monad m, ListLike fullinp (m Char)) => fullinp -> m Chars Source #

mapM :: (Monad m, ListLike full' item') => (Char -> m item') -> Chars -> m full' Source #

rigidMapM :: Monad m => (Char -> m Char) -> Chars -> m Chars Source #

nub :: Chars -> Chars Source #

delete :: Char -> Chars -> Chars Source #

deleteFirsts :: Chars -> Chars -> Chars Source #

union :: Chars -> Chars -> Chars Source #

intersect :: Chars -> Chars -> Chars Source #

sort :: Chars -> Chars Source #

insert :: Char -> Chars -> Chars Source #

toList' :: Chars -> [Char] Source #

fromList' :: [Char] -> Chars Source #

fromListLike :: ListLike full' Char => Chars -> full' Source #

nubBy :: (Char -> Char -> Bool) -> Chars -> Chars Source #

deleteBy :: (Char -> Char -> Bool) -> Char -> Chars -> Chars Source #

deleteFirstsBy :: (Char -> Char -> Bool) -> Chars -> Chars -> Chars Source #

unionBy :: (Char -> Char -> Bool) -> Chars -> Chars -> Chars Source #

intersectBy :: (Char -> Char -> Bool) -> Chars -> Chars -> Chars Source #

groupBy :: (ListLike full' Chars, Eq Char) => (Char -> Char -> Bool) -> Chars -> full' Source #

sortBy :: (Char -> Char -> Ordering) -> Chars -> Chars Source #

insertBy :: (Char -> Char -> Ordering) -> Char -> Chars -> Chars Source #

genericLength :: Num a => Chars -> a Source #

genericTake :: Integral a => a -> Chars -> Chars Source #

genericDrop :: Integral a => a -> Chars -> Chars Source #

genericSplitAt :: Integral a => a -> Chars -> (Chars, Chars) Source #

genericReplicate :: Integral a => a -> Char -> Chars Source #

ListLike [a] a Source # 
Instance details

Defined in Data.ListLike.Base

Methods

empty :: [a] Source #

singleton :: a -> [a] Source #

cons :: a -> [a] -> [a] Source #

snoc :: [a] -> a -> [a] Source #

append :: [a] -> [a] -> [a] Source #

head :: [a] -> a Source #

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

last :: [a] -> a Source #

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

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

null :: [a] -> Bool Source #

length :: [a] -> Int Source #

map :: ListLike full' item' => (a -> item') -> [a] -> full' Source #

rigidMap :: (a -> a) -> [a] -> [a] Source #

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

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

concat :: ListLike full' [a] => full' -> [a] Source #

concatMap :: ListLike full' item' => (a -> full') -> [a] -> full' Source #

rigidConcatMap :: (a -> [a]) -> [a] -> [a] Source #

any :: (a -> Bool) -> [a] -> Bool Source #

all :: (a -> Bool) -> [a] -> Bool Source #

maximum :: [a] -> a Source #

minimum :: [a] -> a Source #

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

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

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

splitAt :: Int -> [a] -> ([a], [a]) Source #

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

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

dropWhileEnd :: (a -> Bool) -> [a] -> [a] Source #

span :: (a -> Bool) -> [a] -> ([a], [a]) Source #

break :: (a -> Bool) -> [a] -> ([a], [a]) Source #

group :: (ListLike full' [a], Eq a) => [a] -> full' Source #

inits :: ListLike full' [a] => [a] -> full' Source #

tails :: ListLike full' [a] => [a] -> full' Source #

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

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

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

stripPrefix :: [a] -> [a] -> Maybe [a] Source #

stripSuffix :: [a] -> [a] -> Maybe [a] Source #

elem :: a -> [a] -> Bool Source #

notElem :: a -> [a] -> Bool Source #

find :: (a -> Bool) -> [a] -> Maybe a Source #

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

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

index :: [a] -> Int -> a Source #

elemIndex :: a -> [a] -> Maybe Int Source #

elemIndices :: (Eq a, ListLike result Int) => a -> [a] -> result Source #

findIndex :: (a -> Bool) -> [a] -> Maybe Int Source #

findIndices :: ListLike result Int => (a -> Bool) -> [a] -> result Source #

sequence :: (Monad m, ListLike fullinp (m a)) => fullinp -> m [a] Source #

mapM :: (Monad m, ListLike full' item') => (a -> m item') -> [a] -> m full' Source #

rigidMapM :: Monad m => (a -> m a) -> [a] -> m [a] Source #

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

delete :: a -> [a] -> [a] Source #

deleteFirsts :: [a] -> [a] -> [a] Source #

union :: [a] -> [a] -> [a] Source #

intersect :: [a] -> [a] -> [a] Source #

sort :: [a] -> [a] Source #

insert :: a -> [a] -> [a] Source #

toList' :: [a] -> [a] Source #

fromList' :: [a] -> [a] Source #

fromListLike :: ListLike full' a => [a] -> full' Source #

nubBy :: (a -> a -> Bool) -> [a] -> [a] Source #

deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a] Source #

deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] Source #

unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] Source #

intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] Source #

groupBy :: (ListLike full' [a], Eq a) => (a -> a -> Bool) -> [a] -> full' Source #

sortBy :: (a -> a -> Ordering) -> [a] -> [a] Source #

insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] Source #

genericLength :: Num a0 => [a] -> a0 Source #

genericTake :: Integral a0 => a0 -> [a] -> [a] Source #

genericDrop :: Integral a0 => a0 -> [a] -> [a] Source #

genericSplitAt :: Integral a0 => a0 -> [a] -> ([a], [a]) Source #

genericReplicate :: Integral a0 => a0 -> a -> [a] Source #

(IsList (v a), Item (v a) ~ a, Monoid (v a), Eq (v a), Vector v a) => ListLike (v a) a Source # 
Instance details

Defined in Data.ListLike.Vector.Generic

Methods

empty :: v a Source #

singleton :: a -> v a Source #

cons :: a -> v a -> v a Source #

snoc :: v a -> a -> v a Source #

append :: v a -> v a -> v a Source #

head :: v a -> a Source #

uncons :: v a -> Maybe (a, v a) Source #

last :: v a -> a Source #

tail :: v a -> v a Source #

init :: v a -> v a Source #

null :: v a -> Bool Source #

length :: v a -> Int Source #

map :: ListLike full' item' => (a -> item') -> v a -> full' Source #

rigidMap :: (a -> a) -> v a -> v a Source #

reverse :: v a -> v a Source #

intersperse :: a -> v a -> v a Source #

concat :: ListLike full' (v a) => full' -> v a Source #

concatMap :: ListLike full' item' => (a -> full') -> v a -> full' Source #

rigidConcatMap :: (a -> v a) -> v a -> v a Source #

any :: (a -> Bool) -> v a -> Bool Source #

all :: (a -> Bool) -> v a -> Bool Source #

maximum :: v a -> a Source #

minimum :: v a -> a Source #

replicate :: Int -> a -> v a Source #

take :: Int -> v a -> v a Source #

drop :: Int -> v a -> v a Source #

splitAt :: Int -> v a -> (v a, v a) Source #

takeWhile :: (a -> Bool) -> v a -> v a Source #

dropWhile :: (a -> Bool) -> v a -> v a Source #

dropWhileEnd :: (a -> Bool) -> v a -> v a Source #

span :: (a -> Bool) -> v a -> (v a, v a) Source #

break :: (a -> Bool) -> v a -> (v a, v a) Source #

group :: (ListLike full' (v a), Eq a) => v a -> full' Source #

inits :: ListLike full' (v a) => v a -> full' Source #

tails :: ListLike full' (v a) => v a -> full' Source #

isPrefixOf :: v a -> v a -> Bool Source #

isSuffixOf :: v a -> v a -> Bool Source #

isInfixOf :: v a -> v a -> Bool Source #

stripPrefix :: v a -> v a -> Maybe (v a) Source #

stripSuffix :: v a -> v a -> Maybe (v a) Source #

elem :: a -> v a -> Bool Source #

notElem :: a -> v a -> Bool Source #

find :: (a -> Bool) -> v a -> Maybe a Source #

filter :: (a -> Bool) -> v a -> v a Source #

partition :: (a -> Bool) -> v a -> (v a, v a) Source #

index :: v a -> Int -> a Source #

elemIndex :: a -> v a -> Maybe Int Source #

elemIndices :: (Eq a, ListLike result Int) => a -> v a -> result Source #

findIndex :: (a -> Bool) -> v a -> Maybe Int Source #

findIndices :: ListLike result Int => (a -> Bool) -> v a -> result Source #

sequence :: (Monad m, ListLike fullinp (m a)) => fullinp -> m (v a) Source #

mapM :: (Monad m, ListLike full' item') => (a -> m item') -> v a -> m full' Source #

rigidMapM :: Monad m => (a -> m a) -> v a -> m (v a) Source #

nub :: v a -> v a Source #

delete :: a -> v a -> v a Source #

deleteFirsts :: v a -> v a -> v a Source #

union :: v a -> v a -> v a Source #

intersect :: v a -> v a -> v a Source #

sort :: v a -> v a Source #

insert :: a -> v a -> v a Source #

toList' :: v a -> [a] Source #

fromList' :: [a] -> v a Source #

fromListLike :: ListLike full' a => v a -> full' Source #

nubBy :: (a -> a -> Bool) -> v a -> v a Source #

deleteBy :: (a -> a -> Bool) -> a -> v a -> v a Source #

deleteFirstsBy :: (a -> a -> Bool) -> v a -> v a -> v a Source #

unionBy :: (a -> a -> Bool) -> v a -> v a -> v a Source #

intersectBy :: (a -> a -> Bool) -> v a -> v a -> v a Source #

groupBy :: (ListLike full' (v a), Eq a) => (a -> a -> Bool) -> v a -> full' Source #

sortBy :: (a -> a -> Ordering) -> v a -> v a Source #

insertBy :: (a -> a -> Ordering) -> a -> v a -> v a Source #

genericLength :: Num a0 => v a -> a0 Source #

genericTake :: Integral a0 => a0 -> v a -> v a Source #

genericDrop :: Integral a0 => a0 -> v a -> v a Source #

genericSplitAt :: Integral a0 => a0 -> v a -> (v a, v a) Source #

genericReplicate :: Integral a0 => a0 -> a -> v a Source #

ListLike (Seq a) a Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

empty :: Seq a Source #

singleton :: a -> Seq a Source #

cons :: a -> Seq a -> Seq a Source #

snoc :: Seq a -> a -> Seq a Source #

append :: Seq a -> Seq a -> Seq a Source #

head :: Seq a -> a Source #

uncons :: Seq a -> Maybe (a, Seq a) Source #

last :: Seq a -> a Source #

tail :: Seq a -> Seq a Source #

init :: Seq a -> Seq a Source #

null :: Seq a -> Bool Source #

length :: Seq a -> Int Source #

map :: ListLike full' item' => (a -> item') -> Seq a -> full' Source #

rigidMap :: (a -> a) -> Seq a -> Seq a Source #

reverse :: Seq a -> Seq a Source #

intersperse :: a -> Seq a -> Seq a Source #

concat :: ListLike full' (Seq a) => full' -> Seq a Source #

concatMap :: ListLike full' item' => (a -> full') -> Seq a -> full' Source #

rigidConcatMap :: (a -> Seq a) -> Seq a -> Seq a Source #

any :: (a -> Bool) -> Seq a -> Bool Source #

all :: (a -> Bool) -> Seq a -> Bool Source #

maximum :: Seq a -> a Source #

minimum :: Seq a -> a Source #

replicate :: Int -> a -> Seq a Source #

take :: Int -> Seq a -> Seq a Source #

drop :: Int -> Seq a -> Seq a Source #

splitAt :: Int -> Seq a -> (Seq a, Seq a) Source #

takeWhile :: (a -> Bool) -> Seq a -> Seq a Source #

dropWhile :: (a -> Bool) -> Seq a -> Seq a Source #

dropWhileEnd :: (a -> Bool) -> Seq a -> Seq a Source #

span :: (a -> Bool) -> Seq a -> (Seq a, Seq a) Source #

break :: (a -> Bool) -> Seq a -> (Seq a, Seq a) Source #

group :: (ListLike full' (Seq a), Eq a) => Seq a -> full' Source #

inits :: ListLike full' (Seq a) => Seq a -> full' Source #

tails :: ListLike full' (Seq a) => Seq a -> full' Source #

isPrefixOf :: Seq a -> Seq a -> Bool Source #

isSuffixOf :: Seq a -> Seq a -> Bool Source #

isInfixOf :: Seq a -> Seq a -> Bool Source #

stripPrefix :: Seq a -> Seq a -> Maybe (Seq a) Source #

stripSuffix :: Seq a -> Seq a -> Maybe (Seq a) Source #

elem :: a -> Seq a -> Bool Source #

notElem :: a -> Seq a -> Bool Source #

find :: (a -> Bool) -> Seq a -> Maybe a Source #

filter :: (a -> Bool) -> Seq a -> Seq a Source #

partition :: (a -> Bool) -> Seq a -> (Seq a, Seq a) Source #

index :: Seq a -> Int -> a Source #

elemIndex :: a -> Seq a -> Maybe Int Source #

elemIndices :: (Eq a, ListLike result Int) => a -> Seq a -> result Source #

findIndex :: (a -> Bool) -> Seq a -> Maybe Int Source #

findIndices :: ListLike result Int => (a -> Bool) -> Seq a -> result Source #

sequence :: (Monad m, ListLike fullinp (m a)) => fullinp -> m (Seq a) Source #

mapM :: (Monad m, ListLike full' item') => (a -> m item') -> Seq a -> m full' Source #

rigidMapM :: Monad m => (a -> m a) -> Seq a -> m (Seq a) Source #

nub :: Seq a -> Seq a Source #

delete :: a -> Seq a -> Seq a Source #

deleteFirsts :: Seq a -> Seq a -> Seq a Source #

union :: Seq a -> Seq a -> Seq a Source #

intersect :: Seq a -> Seq a -> Seq a Source #

sort :: Seq a -> Seq a Source #

insert :: a -> Seq a -> Seq a Source #

toList' :: Seq a -> [a] Source #

fromList' :: [a] -> Seq a Source #

fromListLike :: ListLike full' a => Seq a -> full' Source #

nubBy :: (a -> a -> Bool) -> Seq a -> Seq a Source #

deleteBy :: (a -> a -> Bool) -> a -> Seq a -> Seq a Source #

deleteFirstsBy :: (a -> a -> Bool) -> Seq a -> Seq a -> Seq a Source #

unionBy :: (a -> a -> Bool) -> Seq a -> Seq a -> Seq a Source #

intersectBy :: (a -> a -> Bool) -> Seq a -> Seq a -> Seq a Source #

groupBy :: (ListLike full' (Seq a), Eq a) => (a -> a -> Bool) -> Seq a -> full' Source #

sortBy :: (a -> a -> Ordering) -> Seq a -> Seq a Source #

insertBy :: (a -> a -> Ordering) -> a -> Seq a -> Seq a Source #

genericLength :: Num a0 => Seq a -> a0 Source #

genericTake :: Integral a0 => a0 -> Seq a -> Seq a Source #

genericDrop :: Integral a0 => a0 -> Seq a -> Seq a Source #

genericSplitAt :: Integral a0 => a0 -> Seq a -> (Seq a, Seq a) Source #

genericReplicate :: Integral a0 => a0 -> a -> Seq a Source #

ListLike (DList a) a Source # 
Instance details

Defined in Data.ListLike.DList

Methods

empty :: DList a Source #

singleton :: a -> DList a Source #

cons :: a -> DList a -> DList a Source #

snoc :: DList a -> a -> DList a Source #

append :: DList a -> DList a -> DList a Source #

head :: DList a -> a Source #

uncons :: DList a -> Maybe (a, DList a) Source #

last :: DList a -> a Source #

tail :: DList a -> DList a Source #

init :: DList a -> DList a Source #

null :: DList a -> Bool Source #

length :: DList a -> Int Source #

map :: ListLike full' item' => (a -> item') -> DList a -> full' Source #

rigidMap :: (a -> a) -> DList a -> DList a Source #

reverse :: DList a -> DList a Source #

intersperse :: a -> DList a -> DList a Source #

concat :: ListLike full' (DList a) => full' -> DList a Source #

concatMap :: ListLike full' item' => (a -> full') -> DList a -> full' Source #

rigidConcatMap :: (a -> DList a) -> DList a -> DList a Source #

any :: (a -> Bool) -> DList a -> Bool Source #

all :: (a -> Bool) -> DList a -> Bool Source #

maximum :: DList a -> a Source #

minimum :: DList a -> a Source #

replicate :: Int -> a -> DList a Source #

take :: Int -> DList a -> DList a Source #

drop :: Int -> DList a -> DList a Source #

splitAt :: Int -> DList a -> (DList a, DList a) Source #

takeWhile :: (a -> Bool) -> DList a -> DList a Source #

dropWhile :: (a -> Bool) -> DList a -> DList a Source #

dropWhileEnd :: (a -> Bool) -> DList a -> DList a Source #

span :: (a -> Bool) -> DList a -> (DList a, DList a) Source #

break :: (a -> Bool) -> DList a -> (DList a, DList a) Source #

group :: (ListLike full' (DList a), Eq a) => DList a -> full' Source #

inits :: ListLike full' (DList a) => DList a -> full' Source #

tails :: ListLike full' (DList a) => DList a -> full' Source #

isPrefixOf :: DList a -> DList a -> Bool Source #

isSuffixOf :: DList a -> DList a -> Bool Source #

isInfixOf :: DList a -> DList a -> Bool Source #

stripPrefix :: DList a -> DList a -> Maybe (DList a) Source #

stripSuffix :: DList a -> DList a -> Maybe (DList a) Source #

elem :: a -> DList a -> Bool Source #

notElem :: a -> DList a -> Bool Source #

find :: (a -> Bool) -> DList a -> Maybe a Source #

filter :: (a -> Bool) -> DList a -> DList a Source #

partition :: (a -> Bool) -> DList a -> (DList a, DList a) Source #

index :: DList a -> Int -> a Source #

elemIndex :: a -> DList a -> Maybe Int Source #

elemIndices :: (Eq a, ListLike result Int) => a -> DList a -> result Source #

findIndex :: (a -> Bool) -> DList a -> Maybe Int Source #

findIndices :: ListLike result Int => (a -> Bool) -> DList a -> result Source #

sequence :: (Monad m, ListLike fullinp (m a)) => fullinp -> m (DList a) Source #

mapM :: (Monad m, ListLike full' item') => (a -> m item') -> DList a -> m full' Source #

rigidMapM :: Monad m => (a -> m a) -> DList a -> m (DList a) Source #

nub :: DList a -> DList a Source #

delete :: a -> DList a -> DList a Source #

deleteFirsts :: DList a -> DList a -> DList a Source #

union :: DList a -> DList a -> DList a Source #

intersect :: DList a -> DList a -> DList a Source #

sort :: DList a -> DList a Source #

insert :: a -> DList a -> DList a Source #

toList' :: DList a -> [a] Source #

fromList' :: [a] -> DList a Source #

fromListLike :: ListLike full' a => DList a -> full' Source #

nubBy :: (a -> a -> Bool) -> DList a -> DList a Source #

deleteBy :: (a -> a -> Bool) -> a -> DList a -> DList a Source #

deleteFirstsBy :: (a -> a -> Bool) -> DList a -> DList a -> DList a Source #

unionBy :: (a -> a -> Bool) -> DList a -> DList a -> DList a Source #

intersectBy :: (a -> a -> Bool) -> DList a -> DList a -> DList a Source #

groupBy :: (ListLike full' (DList a), Eq a) => (a -> a -> Bool) -> DList a -> full' Source #

sortBy :: (a -> a -> Ordering) -> DList a -> DList a Source #

insertBy :: (a -> a -> Ordering) -> a -> DList a -> DList a Source #

genericLength :: Num a0 => DList a -> a0 Source #

genericTake :: Integral a0 => a0 -> DList a -> DList a Source #

genericDrop :: Integral a0 => a0 -> DList a -> DList a Source #

genericSplitAt :: Integral a0 => a0 -> DList a -> (DList a, DList a) Source #

genericReplicate :: Integral a0 => a0 -> a -> DList a Source #

ListLike (FMList a) a Source # 
Instance details

Defined in Data.ListLike.FMList

Methods

empty :: FMList a Source #

singleton :: a -> FMList a Source #

cons :: a -> FMList a -> FMList a Source #

snoc :: FMList a -> a -> FMList a Source #

append :: FMList a -> FMList a -> FMList a Source #

head :: FMList a -> a Source #

uncons :: FMList a -> Maybe (a, FMList a) Source #

last :: FMList a -> a Source #

tail :: FMList a -> FMList a Source #

init :: FMList a -> FMList a Source #

null :: FMList a -> Bool Source #

length :: FMList a -> Int Source #

map :: ListLike full' item' => (a -> item') -> FMList a -> full' Source #

rigidMap :: (a -> a) -> FMList a -> FMList a Source #

reverse :: FMList a -> FMList a Source #

intersperse :: a -> FMList a -> FMList a Source #

concat :: ListLike full' (FMList a) => full' -> FMList a Source #

concatMap :: ListLike full' item' => (a -> full') -> FMList a -> full' Source #

rigidConcatMap :: (a -> FMList a) -> FMList a -> FMList a Source #

any :: (a -> Bool) -> FMList a -> Bool Source #

all :: (a -> Bool) -> FMList a -> Bool Source #

maximum :: FMList a -> a Source #

minimum :: FMList a -> a Source #

replicate :: Int -> a -> FMList a Source #

take :: Int -> FMList a -> FMList a Source #

drop :: Int -> FMList a -> FMList a Source #

splitAt :: Int -> FMList a -> (FMList a, FMList a) Source #

takeWhile :: (a -> Bool) -> FMList a -> FMList a Source #

dropWhile :: (a -> Bool) -> FMList a -> FMList a Source #

dropWhileEnd :: (a -> Bool) -> FMList a -> FMList a Source #

span :: (a -> Bool) -> FMList a -> (FMList a, FMList a) Source #

break :: (a -> Bool) -> FMList a -> (FMList a, FMList a) Source #

group :: (ListLike full' (FMList a), Eq a) => FMList a -> full' Source #

inits :: ListLike full' (FMList a) => FMList a -> full' Source #

tails :: ListLike full' (FMList a) => FMList a -> full' Source #

isPrefixOf :: FMList a -> FMList a -> Bool Source #

isSuffixOf :: FMList a -> FMList a -> Bool Source #

isInfixOf :: FMList a -> FMList a -> Bool Source #

stripPrefix :: FMList a -> FMList a -> Maybe (FMList a) Source #

stripSuffix :: FMList a -> FMList a -> Maybe (FMList a) Source #

elem :: a -> FMList a -> Bool Source #

notElem :: a -> FMList a -> Bool Source #

find :: (a -> Bool) -> FMList a -> Maybe a Source #

filter :: (a -> Bool) -> FMList a -> FMList a Source #

partition :: (a -> Bool) -> FMList a -> (FMList a, FMList a) Source #

index :: FMList a -> Int -> a Source #

elemIndex :: a -> FMList a -> Maybe Int Source #

elemIndices :: (Eq a, ListLike result Int) => a -> FMList a -> result Source #

findIndex :: (a -> Bool) -> FMList a -> Maybe Int Source #

findIndices :: ListLike result Int => (a -> Bool) -> FMList a -> result Source #

sequence :: (Monad m, ListLike fullinp (m a)) => fullinp -> m (FMList a) Source #

mapM :: (Monad m, ListLike full' item') => (a -> m item') -> FMList a -> m full' Source #

rigidMapM :: Monad m => (a -> m a) -> FMList a -> m (FMList a) Source #

nub :: FMList a -> FMList a Source #

delete :: a -> FMList a -> FMList a Source #

deleteFirsts :: FMList a -> FMList a -> FMList a Source #

union :: FMList a -> FMList a -> FMList a Source #

intersect :: FMList a -> FMList a -> FMList a Source #

sort :: FMList a -> FMList a Source #

insert :: a -> FMList a -> FMList a Source #

toList' :: FMList a -> [a] Source #

fromList' :: [a] -> FMList a Source #

fromListLike :: ListLike full' a => FMList a -> full' Source #

nubBy :: (a -> a -> Bool) -> FMList a -> FMList a Source #

deleteBy :: (a -> a -> Bool) -> a -> FMList a -> FMList a Source #

deleteFirstsBy :: (a -> a -> Bool) -> FMList a -> FMList a -> FMList a Source #

unionBy :: (a -> a -> Bool) -> FMList a -> FMList a -> FMList a Source #

intersectBy :: (a -> a -> Bool) -> FMList a -> FMList a -> FMList a Source #

groupBy :: (ListLike full' (FMList a), Eq a) => (a -> a -> Bool) -> FMList a -> full' Source #

sortBy :: (a -> a -> Ordering) -> FMList a -> FMList a Source #

insertBy :: (a -> a -> Ordering) -> a -> FMList a -> FMList a Source #

genericLength :: Num a0 => FMList a -> a0 Source #

genericTake :: Integral a0 => a0 -> FMList a -> FMList a Source #

genericDrop :: Integral a0 => a0 -> FMList a -> FMList a Source #

genericSplitAt :: Integral a0 => a0 -> FMList a -> (FMList a, FMList a) Source #

genericReplicate :: Integral a0 => a0 -> a -> FMList a Source #

ListLike (UTF8 ByteString) Char Source # 
Instance details

Defined in Data.ListLike.UTF8

Methods

empty :: UTF8 ByteString Source #

singleton :: Char -> UTF8 ByteString Source #

cons :: Char -> UTF8 ByteString -> UTF8 ByteString Source #

snoc :: UTF8 ByteString -> Char -> UTF8 ByteString Source #

append :: UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

head :: UTF8 ByteString -> Char Source #

uncons :: UTF8 ByteString -> Maybe (Char, UTF8 ByteString) Source #

last :: UTF8 ByteString -> Char Source #

tail :: UTF8 ByteString -> UTF8 ByteString Source #

init :: UTF8 ByteString -> UTF8 ByteString Source #

null :: UTF8 ByteString -> Bool Source #

length :: UTF8 ByteString -> Int Source #

map :: ListLike full' item' => (Char -> item') -> UTF8 ByteString -> full' Source #

rigidMap :: (Char -> Char) -> UTF8 ByteString -> UTF8 ByteString Source #

reverse :: UTF8 ByteString -> UTF8 ByteString Source #

intersperse :: Char -> UTF8 ByteString -> UTF8 ByteString Source #

concat :: ListLike full' (UTF8 ByteString) => full' -> UTF8 ByteString Source #

concatMap :: ListLike full' item' => (Char -> full') -> UTF8 ByteString -> full' Source #

rigidConcatMap :: (Char -> UTF8 ByteString) -> UTF8 ByteString -> UTF8 ByteString Source #

any :: (Char -> Bool) -> UTF8 ByteString -> Bool Source #

all :: (Char -> Bool) -> UTF8 ByteString -> Bool Source #

maximum :: UTF8 ByteString -> Char Source #

minimum :: UTF8 ByteString -> Char Source #

replicate :: Int -> Char -> UTF8 ByteString Source #

take :: Int -> UTF8 ByteString -> UTF8 ByteString Source #

drop :: Int -> UTF8 ByteString -> UTF8 ByteString Source #

splitAt :: Int -> UTF8 ByteString -> (UTF8 ByteString, UTF8 ByteString) Source #

takeWhile :: (Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString Source #

dropWhile :: (Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString Source #

dropWhileEnd :: (Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString Source #

span :: (Char -> Bool) -> UTF8 ByteString -> (UTF8 ByteString, UTF8 ByteString) Source #

break :: (Char -> Bool) -> UTF8 ByteString -> (UTF8 ByteString, UTF8 ByteString) Source #

group :: (ListLike full' (UTF8 ByteString), Eq Char) => UTF8 ByteString -> full' Source #

inits :: ListLike full' (UTF8 ByteString) => UTF8 ByteString -> full' Source #

tails :: ListLike full' (UTF8 ByteString) => UTF8 ByteString -> full' Source #

isPrefixOf :: UTF8 ByteString -> UTF8 ByteString -> Bool Source #

isSuffixOf :: UTF8 ByteString -> UTF8 ByteString -> Bool Source #

isInfixOf :: UTF8 ByteString -> UTF8 ByteString -> Bool Source #

stripPrefix :: UTF8 ByteString -> UTF8 ByteString -> Maybe (UTF8 ByteString) Source #

stripSuffix :: UTF8 ByteString -> UTF8 ByteString -> Maybe (UTF8 ByteString) Source #

elem :: Char -> UTF8 ByteString -> Bool Source #

notElem :: Char -> UTF8 ByteString -> Bool Source #

find :: (Char -> Bool) -> UTF8 ByteString -> Maybe Char Source #

filter :: (Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString Source #

partition :: (Char -> Bool) -> UTF8 ByteString -> (UTF8 ByteString, UTF8 ByteString) Source #

index :: UTF8 ByteString -> Int -> Char Source #

elemIndex :: Char -> UTF8 ByteString -> Maybe Int Source #

elemIndices :: (Eq Char, ListLike result Int) => Char -> UTF8 ByteString -> result Source #

findIndex :: (Char -> Bool) -> UTF8 ByteString -> Maybe Int Source #

findIndices :: ListLike result Int => (Char -> Bool) -> UTF8 ByteString -> result Source #

sequence :: (Monad m, ListLike fullinp (m Char)) => fullinp -> m (UTF8 ByteString) Source #

mapM :: (Monad m, ListLike full' item') => (Char -> m item') -> UTF8 ByteString -> m full' Source #

rigidMapM :: Monad m => (Char -> m Char) -> UTF8 ByteString -> m (UTF8 ByteString) Source #

nub :: UTF8 ByteString -> UTF8 ByteString Source #

delete :: Char -> UTF8 ByteString -> UTF8 ByteString Source #

deleteFirsts :: UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

union :: UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

intersect :: UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

sort :: UTF8 ByteString -> UTF8 ByteString Source #

insert :: Char -> UTF8 ByteString -> UTF8 ByteString Source #

toList' :: UTF8 ByteString -> [Char] Source #

fromList' :: [Char] -> UTF8 ByteString Source #

fromListLike :: ListLike full' Char => UTF8 ByteString -> full' Source #

nubBy :: (Char -> Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString Source #

deleteBy :: (Char -> Char -> Bool) -> Char -> UTF8 ByteString -> UTF8 ByteString Source #

deleteFirstsBy :: (Char -> Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

unionBy :: (Char -> Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

intersectBy :: (Char -> Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

groupBy :: (ListLike full' (UTF8 ByteString), Eq Char) => (Char -> Char -> Bool) -> UTF8 ByteString -> full' Source #

sortBy :: (Char -> Char -> Ordering) -> UTF8 ByteString -> UTF8 ByteString Source #

insertBy :: (Char -> Char -> Ordering) -> Char -> UTF8 ByteString -> UTF8 ByteString Source #

genericLength :: Num a => UTF8 ByteString -> a Source #

genericTake :: Integral a => a -> UTF8 ByteString -> UTF8 ByteString Source #

genericDrop :: Integral a => a -> UTF8 ByteString -> UTF8 ByteString Source #

genericSplitAt :: Integral a => a -> UTF8 ByteString -> (UTF8 ByteString, UTF8 ByteString) Source #

genericReplicate :: Integral a => a -> Char -> UTF8 ByteString Source #

ListLike (UTF8 ByteString) Char Source # 
Instance details

Defined in Data.ListLike.UTF8

Methods

empty :: UTF8 ByteString Source #

singleton :: Char -> UTF8 ByteString Source #

cons :: Char -> UTF8 ByteString -> UTF8 ByteString Source #

snoc :: UTF8 ByteString -> Char -> UTF8 ByteString Source #

append :: UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

head :: UTF8 ByteString -> Char Source #

uncons :: UTF8 ByteString -> Maybe (Char, UTF8 ByteString) Source #

last :: UTF8 ByteString -> Char Source #

tail :: UTF8 ByteString -> UTF8 ByteString Source #

init :: UTF8 ByteString -> UTF8 ByteString Source #

null :: UTF8 ByteString -> Bool Source #

length :: UTF8 ByteString -> Int Source #

map :: ListLike full' item' => (Char -> item') -> UTF8 ByteString -> full' Source #

rigidMap :: (Char -> Char) -> UTF8 ByteString -> UTF8 ByteString Source #

reverse :: UTF8 ByteString -> UTF8 ByteString Source #

intersperse :: Char -> UTF8 ByteString -> UTF8 ByteString Source #

concat :: ListLike full' (UTF8 ByteString) => full' -> UTF8 ByteString Source #

concatMap :: ListLike full' item' => (Char -> full') -> UTF8 ByteString -> full' Source #

rigidConcatMap :: (Char -> UTF8 ByteString) -> UTF8 ByteString -> UTF8 ByteString Source #

any :: (Char -> Bool) -> UTF8 ByteString -> Bool Source #

all :: (Char -> Bool) -> UTF8 ByteString -> Bool Source #

maximum :: UTF8 ByteString -> Char Source #

minimum :: UTF8 ByteString -> Char Source #

replicate :: Int -> Char -> UTF8 ByteString Source #

take :: Int -> UTF8 ByteString -> UTF8 ByteString Source #

drop :: Int -> UTF8 ByteString -> UTF8 ByteString Source #

splitAt :: Int -> UTF8 ByteString -> (UTF8 ByteString, UTF8 ByteString) Source #

takeWhile :: (Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString Source #

dropWhile :: (Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString Source #

dropWhileEnd :: (Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString Source #

span :: (Char -> Bool) -> UTF8 ByteString -> (UTF8 ByteString, UTF8 ByteString) Source #

break :: (Char -> Bool) -> UTF8 ByteString -> (UTF8 ByteString, UTF8 ByteString) Source #

group :: (ListLike full' (UTF8 ByteString), Eq Char) => UTF8 ByteString -> full' Source #

inits :: ListLike full' (UTF8 ByteString) => UTF8 ByteString -> full' Source #

tails :: ListLike full' (UTF8 ByteString) => UTF8 ByteString -> full' Source #

isPrefixOf :: UTF8 ByteString -> UTF8 ByteString -> Bool Source #

isSuffixOf :: UTF8 ByteString -> UTF8 ByteString -> Bool Source #

isInfixOf :: UTF8 ByteString -> UTF8 ByteString -> Bool Source #

stripPrefix :: UTF8 ByteString -> UTF8 ByteString -> Maybe (UTF8 ByteString) Source #

stripSuffix :: UTF8 ByteString -> UTF8 ByteString -> Maybe (UTF8 ByteString) Source #

elem :: Char -> UTF8 ByteString -> Bool Source #

notElem :: Char -> UTF8 ByteString -> Bool Source #

find :: (Char -> Bool) -> UTF8 ByteString -> Maybe Char Source #

filter :: (Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString Source #

partition :: (Char -> Bool) -> UTF8 ByteString -> (UTF8 ByteString, UTF8 ByteString) Source #

index :: UTF8 ByteString -> Int -> Char Source #

elemIndex :: Char -> UTF8 ByteString -> Maybe Int Source #

elemIndices :: (Eq Char, ListLike result Int) => Char -> UTF8 ByteString -> result Source #

findIndex :: (Char -> Bool) -> UTF8 ByteString -> Maybe Int Source #

findIndices :: ListLike result Int => (Char -> Bool) -> UTF8 ByteString -> result Source #

sequence :: (Monad m, ListLike fullinp (m Char)) => fullinp -> m (UTF8 ByteString) Source #

mapM :: (Monad m, ListLike full' item') => (Char -> m item') -> UTF8 ByteString -> m full' Source #

rigidMapM :: Monad m => (Char -> m Char) -> UTF8 ByteString -> m (UTF8 ByteString) Source #

nub :: UTF8 ByteString -> UTF8 ByteString Source #

delete :: Char -> UTF8 ByteString -> UTF8 ByteString Source #

deleteFirsts :: UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

union :: UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

intersect :: UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

sort :: UTF8 ByteString -> UTF8 ByteString Source #

insert :: Char -> UTF8 ByteString -> UTF8 ByteString Source #

toList' :: UTF8 ByteString -> [Char] Source #

fromList' :: [Char] -> UTF8 ByteString Source #

fromListLike :: ListLike full' Char => UTF8 ByteString -> full' Source #

nubBy :: (Char -> Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString Source #

deleteBy :: (Char -> Char -> Bool) -> Char -> UTF8 ByteString -> UTF8 ByteString Source #

deleteFirstsBy :: (Char -> Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

unionBy :: (Char -> Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

intersectBy :: (Char -> Char -> Bool) -> UTF8 ByteString -> UTF8 ByteString -> UTF8 ByteString Source #

groupBy :: (ListLike full' (UTF8 ByteString), Eq Char) => (Char -> Char -> Bool) -> UTF8 ByteString -> full' Source #

sortBy :: (Char -> Char -> Ordering) -> UTF8 ByteString -> UTF8 ByteString Source #

insertBy :: (Char -> Char -> Ordering) -> Char -> UTF8 ByteString -> UTF8 ByteString Source #

genericLength :: Num a => UTF8 ByteString -> a Source #

genericTake :: Integral a => a -> UTF8 ByteString -> UTF8 ByteString Source #

genericDrop :: Integral a => a -> UTF8 ByteString -> UTF8 ByteString Source #

genericSplitAt :: Integral a => a -> UTF8 ByteString -> (UTF8 ByteString, UTF8 ByteString) Source #

genericReplicate :: Integral a => a -> Char -> UTF8 ByteString Source #

Unbox a => ListLike (Vector a) a Source # 
Instance details

Defined in Data.ListLike.Vector.Unboxed

Methods

empty :: Vector a Source #

singleton :: a -> Vector a Source #

cons :: a -> Vector a -> Vector a Source #

snoc :: Vector a -> a -> Vector a Source #

append :: Vector a -> Vector a -> Vector a Source #

head :: Vector a -> a Source #

uncons :: Vector a -> Maybe (a, Vector a) Source #

last :: Vector a -> a Source #

tail :: Vector a -> Vector a Source #

init :: Vector a -> Vector a Source #

null :: Vector a -> Bool Source #

length :: Vector a -> Int Source #

map :: ListLike full' item' => (a -> item') -> Vector a -> full' Source #

rigidMap :: (a -> a) -> Vector a -> Vector a Source #

reverse :: Vector a -> Vector a Source #

intersperse :: a -> Vector a -> Vector a Source #

concat :: ListLike full' (Vector a) => full' -> Vector a Source #

concatMap :: ListLike full' item' => (a -> full') -> Vector a -> full' Source #

rigidConcatMap :: (a -> Vector a) -> Vector a -> Vector a Source #

any :: (a -> Bool) -> Vector a -> Bool Source #

all :: (a -> Bool) -> Vector a -> Bool Source #

maximum :: Vector a -> a Source #

minimum :: Vector a -> a Source #

replicate :: Int -> a -> Vector a Source #

take :: Int -> Vector a -> Vector a Source #

drop :: Int -> Vector a -> Vector a Source #

splitAt :: Int -> Vector a -> (Vector a, Vector a) Source #

takeWhile :: (a -> Bool) -> Vector a -> Vector a Source #

dropWhile :: (a -> Bool) -> Vector a -> Vector a Source #

dropWhileEnd :: (a -> Bool) -> Vector a -> Vector a Source #

span :: (a -> Bool) -> Vector a -> (Vector a, Vector a) Source #

break :: (a -> Bool) -> Vector a -> (Vector a, Vector a) Source #

group :: (ListLike full' (Vector a), Eq a) => Vector a -> full' Source #

inits :: ListLike full' (Vector a) => Vector a -> full' Source #

tails :: ListLike full' (Vector a) => Vector a -> full' Source #

isPrefixOf :: Vector a -> Vector a -> Bool Source #

isSuffixOf :: Vector a -> Vector a -> Bool Source #

isInfixOf :: Vector a -> Vector a -> Bool Source #

stripPrefix :: Vector a -> Vector a -> Maybe (Vector a) Source #

stripSuffix :: Vector a -> Vector a -> Maybe (Vector a) Source #

elem :: a -> Vector a -> Bool Source #

notElem :: a -> Vector a -> Bool Source #

find :: (a -> Bool) -> Vector a -> Maybe a Source #

filter :: (a -> Bool) -> Vector a -> Vector a Source #

partition :: (a -> Bool) -> Vector a -> (Vector a, Vector a) Source #

index :: Vector a -> Int -> a Source #

elemIndex :: a -> Vector a -> Maybe Int Source #

elemIndices :: (Eq a, ListLike result Int) => a -> Vector a -> result Source #

findIndex :: (a -> Bool) -> Vector a -> Maybe Int Source #

findIndices :: ListLike result Int => (a -> Bool) -> Vector a -> result Source #

sequence :: (Monad m, ListLike fullinp (m a)) => fullinp -> m (Vector a) Source #

mapM :: (Monad m, ListLike full' item') => (a -> m item') -> Vector a -> m full' Source #

rigidMapM :: Monad m => (a -> m a) -> Vector a -> m (Vector a) Source #

nub :: Vector a -> Vector a Source #

delete :: a -> Vector a -> Vector a Source #

deleteFirsts :: Vector a -> Vector a -> Vector a Source #

union :: Vector a -> Vector a -> Vector a Source #

intersect :: Vector a -> Vector a -> Vector a Source #

sort :: Vector a -> Vector a Source #

insert :: a -> Vector a -> Vector a Source #

toList' :: Vector a -> [a] Source #

fromList' :: [a] -> Vector a Source #

fromListLike :: ListLike full' a => Vector a -> full' Source #

nubBy :: (a -> a -> Bool) -> Vector a -> Vector a Source #

deleteBy :: (a -> a -> Bool) -> a -> Vector a -> Vector a Source #

deleteFirstsBy :: (a -> a -> Bool) -> Vector a -> Vector a -> Vector a Source #

unionBy :: (a -> a -> Bool) -> Vector a -> Vector a -> Vector a Source #

intersectBy :: (a -> a -> Bool) -> Vector a -> Vector a -> Vector a Source #

groupBy :: (ListLike full' (Vector a), Eq a) => (a -> a -> Bool) -> Vector a -> full' Source #

sortBy :: (a -> a -> Ordering) -> Vector a -> Vector a Source #

insertBy :: (a -> a -> Ordering) -> a -> Vector a -> Vector a Source #

genericLength :: Num a0 => Vector a -> a0 Source #

genericTake :: Integral a0 => a0 -> Vector a -> Vector a Source #

genericDrop :: Integral a0 => a0 -> Vector a -> Vector a Source #

genericSplitAt :: Integral a0 => a0 -> Vector a -> (Vector a, Vector a) Source #

genericReplicate :: Integral a0 => a0 -> a -> Vector a Source #

Storable a => ListLike (Vector a) a Source # 
Instance details

Defined in Data.ListLike.Vector.Storable

Methods

empty :: Vector a Source #

singleton :: a -> Vector a Source #

cons :: a -> Vector a -> Vector a Source #

snoc :: Vector a -> a -> Vector a Source #

append :: Vector a -> Vector a -> Vector a Source #

head :: Vector a -> a Source #

uncons :: Vector a -> Maybe (a, Vector a) Source #

last :: Vector a -> a Source #

tail :: Vector a -> Vector a Source #

init :: Vector a -> Vector a Source #

null :: Vector a -> Bool Source #

length :: Vector a -> Int Source #

map :: ListLike full' item' => (a -> item') -> Vector a -> full' Source #

rigidMap :: (a -> a) -> Vector a -> Vector a Source #

reverse :: Vector a -> Vector a Source #

intersperse :: a -> Vector a -> Vector a Source #

concat :: ListLike full' (Vector a) => full' -> Vector a Source #

concatMap :: ListLike full' item' => (a -> full') -> Vector a -> full' Source #

rigidConcatMap :: (a -> Vector a) -> Vector a -> Vector a Source #

any :: (a -> Bool) -> Vector a -> Bool Source #

all :: (a -> Bool) -> Vector a -> Bool Source #

maximum :: Vector a -> a Source #

minimum :: Vector a -> a Source #

replicate :: Int -> a -> Vector a Source #

take :: Int -> Vector a -> Vector a Source #

drop :: Int -> Vector a -> Vector a Source #

splitAt :: Int -> Vector a -> (Vector a, Vector a) Source #

takeWhile :: (a -> Bool) -> Vector a -> Vector a Source #

dropWhile :: (a -> Bool) -> Vector a -> Vector a Source #

dropWhileEnd :: (a -> Bool) -> Vector a -> Vector a Source #

span :: (a -> Bool) -> Vector a -> (Vector a, Vector a) Source #

break :: (a -> Bool) -> Vector a -> (Vector a, Vector a) Source #

group :: (ListLike full' (Vector a), Eq a) => Vector a -> full' Source #

inits :: ListLike full' (Vector a) => Vector a -> full' Source #

tails :: ListLike full' (Vector a) => Vector a -> full' Source #

isPrefixOf :: Vector a -> Vector a -> Bool Source #

isSuffixOf :: Vector a -> Vector a -> Bool Source #

isInfixOf :: Vector a -> Vector a -> Bool Source #

stripPrefix :: Vector a -> Vector a -> Maybe (Vector a) Source #

stripSuffix :: Vector a -> Vector a -> Maybe (Vector a) Source #

elem :: a -> Vector a -> Bool Source #

notElem :: a -> Vector a -> Bool Source #

find :: (a -> Bool) -> Vector a -> Maybe a Source #

filter :: (a -> Bool) -> Vector a -> Vector a Source #

partition :: (a -> Bool) -> Vector a -> (Vector a, Vector a) Source #

index :: Vector a -> Int -> a Source #

elemIndex :: a -> Vector a -> Maybe Int Source #

elemIndices :: (Eq a, ListLike result Int) => a -> Vector a -> result Source #

findIndex :: (a -> Bool) -> Vector a -> Maybe Int Source #

findIndices :: ListLike result Int => (a -> Bool) -> Vector a -> result Source #

sequence :: (Monad m, ListLike fullinp (m a)) => fullinp -> m (Vector a) Source #

mapM :: (Monad m, ListLike full' item') => (a -> m item') -> Vector a -> m full' Source #

rigidMapM :: Monad m => (a -> m a) -> Vector a -> m (Vector a) Source #

nub :: Vector a -> Vector a Source #

delete :: a -> Vector a -> Vector a Source #

deleteFirsts :: Vector a -> Vector a -> Vector a Source #

union :: Vector a -> Vector a -> Vector a Source #

intersect :: Vector a -> Vector a -> Vector a Source #

sort :: Vector a -> Vector a Source #

insert :: a -> Vector a -> Vector a Source #

toList' :: Vector a -> [a] Source #

fromList' :: [a] -> Vector a Source #

fromListLike :: ListLike full' a => Vector a -> full' Source #

nubBy :: (a -> a -> Bool) -> Vector a -> Vector a Source #

deleteBy :: (a -> a -> Bool) -> a -> Vector a -> Vector a Source #

deleteFirstsBy :: (a -> a -> Bool) -> Vector a -> Vector a -> Vector a Source #

unionBy :: (a -> a -> Bool) -> Vector a -> Vector a -> Vector a Source #

intersectBy :: (a -> a -> Bool) -> Vector a -> Vector a -> Vector a Source #

groupBy :: (ListLike full' (Vector a), Eq a) => (a -> a -> Bool) -> Vector a -> full' Source #

sortBy :: (a -> a -> Ordering) -> Vector a -> Vector a Source #

insertBy :: (a -> a -> Ordering) -> a -> Vector a -> Vector a Source #

genericLength :: Num a0 => Vector a -> a0 Source #

genericTake :: Integral a0 => a0 -> Vector a -> Vector a Source #

genericDrop :: Integral a0 => a0 -> Vector a -> Vector a Source #

genericSplitAt :: Integral a0 => a0 -> Vector a -> (Vector a, Vector a) Source #

genericReplicate :: Integral a0 => a0 -> a -> Vector a Source #

ListLike (Vector a) a Source # 
Instance details

Defined in Data.ListLike.Vector.Vector

Methods

empty :: Vector a Source #

singleton :: a -> Vector a Source #

cons :: a -> Vector a -> Vector a Source #

snoc :: Vector a -> a -> Vector a Source #

append :: Vector a -> Vector a -> Vector a Source #

head :: Vector a -> a Source #

uncons :: Vector a -> Maybe (a, Vector a) Source #

last :: Vector a -> a Source #

tail :: Vector a -> Vector a Source #

init :: Vector a -> Vector a Source #

null :: Vector a -> Bool Source #

length :: Vector a -> Int Source #

map :: ListLike full' item' => (a -> item') -> Vector a -> full' Source #

rigidMap :: (a -> a) -> Vector a -> Vector a Source #

reverse :: Vector a -> Vector a Source #

intersperse :: a -> Vector a -> Vector a Source #

concat :: ListLike full' (Vector a) => full' -> Vector a Source #

concatMap :: ListLike full' item' => (a -> full') -> Vector a -> full' Source #

rigidConcatMap :: (a -> Vector a) -> Vector a -> Vector a Source #

any :: (a -> Bool) -> Vector a -> Bool Source #

all :: (a -> Bool) -> Vector a -> Bool Source #

maximum :: Vector a -> a Source #

minimum :: Vector a -> a Source #

replicate :: Int -> a -> Vector a Source #

take :: Int -> Vector a -> Vector a Source #

drop :: Int -> Vector a -> Vector a Source #

splitAt :: Int -> Vector a -> (Vector a, Vector a) Source #

takeWhile :: (a -> Bool) -> Vector a -> Vector a Source #

dropWhile :: (a -> Bool) -> Vector a -> Vector a Source #

dropWhileEnd :: (a -> Bool) -> Vector a -> Vector a Source #

span :: (a -> Bool) -> Vector a -> (Vector a, Vector a) Source #

break :: (a -> Bool) -> Vector a -> (Vector a, Vector a) Source #

group :: (ListLike full' (Vector a), Eq a) => Vector a -> full' Source #

inits :: ListLike full' (Vector a) => Vector a -> full' Source #

tails :: ListLike full' (Vector a) => Vector a -> full' Source #

isPrefixOf :: Vector a -> Vector a -> Bool Source #

isSuffixOf :: Vector a -> Vector a -> Bool Source #

isInfixOf :: Vector a -> Vector a -> Bool Source #

stripPrefix :: Vector a -> Vector a -> Maybe (Vector a) Source #

stripSuffix :: Vector a -> Vector a -> Maybe (Vector a) Source #

elem :: a -> Vector a -> Bool Source #

notElem :: a -> Vector a -> Bool Source #

find :: (a -> Bool) -> Vector a -> Maybe a Source #

filter :: (a -> Bool) -> Vector a -> Vector a Source #

partition :: (a -> Bool) -> Vector a -> (Vector a, Vector a) Source #

index :: Vector a -> Int -> a Source #

elemIndex :: a -> Vector a -> Maybe Int Source #

elemIndices :: (Eq a, ListLike result Int) => a -> Vector a -> result Source #

findIndex :: (a -> Bool) -> Vector a -> Maybe Int Source #

findIndices :: ListLike result Int => (a -> Bool) -> Vector a -> result Source #

sequence :: (Monad m, ListLike fullinp (m a)) => fullinp -> m (Vector a) Source #

mapM :: (Monad m, ListLike full' item') => (a -> m item') -> Vector a -> m full' Source #

rigidMapM :: Monad m => (a -> m a) -> Vector a -> m (Vector a) Source #

nub :: Vector a -> Vector a Source #

delete :: a -> Vector a -> Vector a Source #

deleteFirsts :: Vector a -> Vector a -> Vector a Source #

union :: Vector a -> Vector a -> Vector a Source #

intersect :: Vector a -> Vector a -> Vector a Source #

sort :: Vector a -> Vector a Source #

insert :: a -> Vector a -> Vector a Source #

toList' :: Vector a -> [a] Source #

fromList' :: [a] -> Vector a Source #

fromListLike :: ListLike full' a => Vector a -> full' Source #

nubBy :: (a -> a -> Bool) -> Vector a -> Vector a Source #

deleteBy :: (a -> a -> Bool) -> a -> Vector a -> Vector a Source #

deleteFirstsBy :: (a -> a -> Bool) -> Vector a -> Vector a -> Vector a Source #

unionBy :: (a -> a -> Bool) -> Vector a -> Vector a -> Vector a Source #

intersectBy :: (a -> a -> Bool) -> Vector a -> Vector a -> Vector a Source #

groupBy :: (ListLike full' (Vector a), Eq a) => (a -> a -> Bool) -> Vector a -> full' Source #

sortBy :: (a -> a -> Ordering) -> Vector a -> Vector a Source #

insertBy :: (a -> a -> Ordering) -> a -> Vector a -> Vector a Source #

genericLength :: Num a0 => Vector a -> a0 Source #

genericTake :: Integral a0 => a0 -> Vector a -> Vector a Source #

genericDrop :: Integral a0 => a0 -> Vector a -> Vector a Source #

genericSplitAt :: Integral a0 => a0 -> Vector a -> (Vector a, Vector a) Source #

genericReplicate :: Integral a0 => a0 -> a -> Vector a Source #

(Integral i, Ix i) => ListLike (Array i e) e Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

empty :: Array i e Source #

singleton :: e -> Array i e Source #

cons :: e -> Array i e -> Array i e Source #

snoc :: Array i e -> e -> Array i e Source #

append :: Array i e -> Array i e -> Array i e Source #

head :: Array i e -> e Source #

uncons :: Array i e -> Maybe (e, Array i e) Source #

last :: Array i e -> e Source #

tail :: Array i e -> Array i e Source #

init :: Array i e -> Array i e Source #

null :: Array i e -> Bool Source #

length :: Array i e -> Int Source #

map :: ListLike full' item' => (e -> item') -> Array i e -> full' Source #

rigidMap :: (e -> e) -> Array i e -> Array i e Source #

reverse :: Array i e -> Array i e Source #

intersperse :: e -> Array i e -> Array i e Source #

concat :: ListLike full' (Array i e) => full' -> Array i e Source #

concatMap :: ListLike full' item' => (e -> full') -> Array i e -> full' Source #

rigidConcatMap :: (e -> Array i e) -> Array i e -> Array i e Source #

any :: (e -> Bool) -> Array i e -> Bool Source #

all :: (e -> Bool) -> Array i e -> Bool Source #

maximum :: Array i e -> e Source #

minimum :: Array i e -> e Source #

replicate :: Int -> e -> Array i e Source #

take :: Int -> Array i e -> Array i e Source #

drop :: Int -> Array i e -> Array i e Source #

splitAt :: Int -> Array i e -> (Array i e, Array i e) Source #

takeWhile :: (e -> Bool) -> Array i e -> Array i e Source #

dropWhile :: (e -> Bool) -> Array i e -> Array i e Source #

dropWhileEnd :: (e -> Bool) -> Array i e -> Array i e Source #

span :: (e -> Bool) -> Array i e -> (Array i e, Array i e) Source #

break :: (e -> Bool) -> Array i e -> (Array i e, Array i e) Source #

group :: (ListLike full' (Array i e), Eq e) => Array i e -> full' Source #

inits :: ListLike full' (Array i e) => Array i e -> full' Source #

tails :: ListLike full' (Array i e) => Array i e -> full' Source #

isPrefixOf :: Array i e -> Array i e -> Bool Source #

isSuffixOf :: Array i e -> Array i e -> Bool Source #

isInfixOf :: Array i e -> Array i e -> Bool Source #

stripPrefix :: Array i e -> Array i e -> Maybe (Array i e) Source #

stripSuffix :: Array i e -> Array i e -> Maybe (Array i e) Source #

elem :: e -> Array i e -> Bool Source #

notElem :: e -> Array i e -> Bool Source #

find :: (e -> Bool) -> Array i e -> Maybe e Source #

filter :: (e -> Bool) -> Array i e -> Array i e Source #

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

index :: Array i e -> Int -> e Source #

elemIndex :: e -> Array i e -> Maybe Int Source #

elemIndices :: (Eq e, ListLike result Int) => e -> Array i e -> result Source #

findIndex :: (e -> Bool) -> Array i e -> Maybe Int Source #

findIndices :: ListLike result Int => (e -> Bool) -> Array i e -> result Source #

sequence :: (Monad m, ListLike fullinp (m e)) => fullinp -> m (Array i e) Source #

mapM :: (Monad m, ListLike full' item') => (e -> m item') -> Array i e -> m full' Source #

rigidMapM :: Monad m => (e -> m e) -> Array i e -> m (Array i e) Source #

nub :: Array i e -> Array i e Source #

delete :: e -> Array i e -> Array i e Source #

deleteFirsts :: Array i e -> Array i e -> Array i e Source #

union :: Array i e -> Array i e -> Array i e Source #

intersect :: Array i e -> Array i e -> Array i e Source #

sort :: Array i e -> Array i e Source #

insert :: e -> Array i e -> Array i e Source #

toList' :: Array i e -> [e] Source #

fromList' :: [e] -> Array i e Source #

fromListLike :: ListLike full' e => Array i e -> full' Source #

nubBy :: (e -> e -> Bool) -> Array i e -> Array i e Source #

deleteBy :: (e -> e -> Bool) -> e -> Array i e -> Array i e Source #

deleteFirstsBy :: (e -> e -> Bool) -> Array i e -> Array i e -> Array i e Source #

unionBy :: (e -> e -> Bool) -> Array i e -> Array i e -> Array i e Source #

intersectBy :: (e -> e -> Bool) -> Array i e -> Array i e -> Array i e Source #

groupBy :: (ListLike full' (Array i e), Eq e) => (e -> e -> Bool) -> Array i e -> full' Source #

sortBy :: (e -> e -> Ordering) -> Array i e -> Array i e Source #

insertBy :: (e -> e -> Ordering) -> e -> Array i e -> Array i e Source #

genericLength :: Num a => Array i e -> a Source #

genericTake :: Integral a => a -> Array i e -> Array i e Source #

genericDrop :: Integral a => a -> Array i e -> Array i e Source #

genericSplitAt :: Integral a => a -> Array i e -> (Array i e, Array i e) Source #

genericReplicate :: Integral a => a -> e -> Array i e Source #

type ListOps full = ListLike full (Item full) Source #

A version of ListLike with a single type parameter, the item type is obtained using the Item type function from IsList.

The FoldableLL class

class FoldableLL full item | full -> item Source #

This is the primary class for structures that are to be considered foldable. A minimum complete definition provides foldl and foldr.

Instances of FoldableLL can be folded, and can be many and varied.

These functions are used heavily in Data.ListLike.

Minimal complete definition

foldl, foldr

Instances

Instances details
FoldableLL ByteString Word8 Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

foldl :: (a -> Word8 -> a) -> a -> ByteString -> a Source #

foldl' :: (a -> Word8 -> a) -> a -> ByteString -> a Source #

foldl1 :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8 Source #

foldr :: (Word8 -> b -> b) -> b -> ByteString -> b Source #

foldr' :: (Word8 -> b -> b) -> b -> ByteString -> b Source #

foldr1 :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8 Source #

FoldableLL ByteString Word8 Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

foldl :: (a -> Word8 -> a) -> a -> ByteString -> a Source #

foldl' :: (a -> Word8 -> a) -> a -> ByteString -> a Source #

foldl1 :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8 Source #

foldr :: (Word8 -> b -> b) -> b -> ByteString -> b Source #

foldr' :: (Word8 -> b -> b) -> b -> ByteString -> b Source #

foldr1 :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8 Source #

FoldableLL Builder Char Source # 
Instance details

Defined in Data.ListLike.Text.Builder

Methods

foldl :: (a -> Char -> a) -> a -> Builder -> a Source #

foldl' :: (a -> Char -> a) -> a -> Builder -> a Source #

foldl1 :: (Char -> Char -> Char) -> Builder -> Char Source #

foldr :: (Char -> b -> b) -> b -> Builder -> b Source #

foldr' :: (Char -> b -> b) -> b -> Builder -> b Source #

foldr1 :: (Char -> Char -> Char) -> Builder -> Char Source #

FoldableLL Text Char Source # 
Instance details

Defined in Data.ListLike.Text.TextLazy

Methods

foldl :: (a -> Char -> a) -> a -> Text -> a Source #

foldl' :: (a -> Char -> a) -> a -> Text -> a Source #

foldl1 :: (Char -> Char -> Char) -> Text -> Char Source #

foldr :: (Char -> b -> b) -> b -> Text -> b Source #

foldr' :: (Char -> b -> b) -> b -> Text -> b Source #

foldr1 :: (Char -> Char -> Char) -> Text -> Char Source #

FoldableLL Text Char Source # 
Instance details

Defined in Data.ListLike.Text.Text

Methods

foldl :: (a -> Char -> a) -> a -> Text -> a Source #

foldl' :: (a -> Char -> a) -> a -> Text -> a Source #

foldl1 :: (Char -> Char -> Char) -> Text -> Char Source #

foldr :: (Char -> b -> b) -> b -> Text -> b Source #

foldr' :: (Char -> b -> b) -> b -> Text -> b Source #

foldr1 :: (Char -> Char -> Char) -> Text -> Char Source #

FoldableLL CharStringLazy Char Source # 
Instance details

Defined in Data.ListLike.CharString

Methods

foldl :: (a -> Char -> a) -> a -> CharStringLazy -> a Source #

foldl' :: (a -> Char -> a) -> a -> CharStringLazy -> a Source #

foldl1 :: (Char -> Char -> Char) -> CharStringLazy -> Char Source #

foldr :: (Char -> b -> b) -> b -> CharStringLazy -> b Source #

foldr' :: (Char -> b -> b) -> b -> CharStringLazy -> b Source #

foldr1 :: (Char -> Char -> Char) -> CharStringLazy -> Char Source #

FoldableLL CharString Char Source # 
Instance details

Defined in Data.ListLike.CharString

Methods

foldl :: (a -> Char -> a) -> a -> CharString -> a Source #

foldl' :: (a -> Char -> a) -> a -> CharString -> a Source #

foldl1 :: (Char -> Char -> Char) -> CharString -> Char Source #

foldr :: (Char -> b -> b) -> b -> CharString -> b Source #

foldr' :: (Char -> b -> b) -> b -> CharString -> b Source #

foldr1 :: (Char -> Char -> Char) -> CharString -> Char Source #

FoldableLL Chars Char Source # 
Instance details

Defined in Data.ListLike.Chars

Methods

foldl :: (a -> Char -> a) -> a -> Chars -> a Source #

foldl' :: (a -> Char -> a) -> a -> Chars -> a Source #

foldl1 :: (Char -> Char -> Char) -> Chars -> Char Source #

foldr :: (Char -> b -> b) -> b -> Chars -> b Source #

foldr' :: (Char -> b -> b) -> b -> Chars -> b Source #

foldr1 :: (Char -> Char -> Char) -> Chars -> Char Source #

FoldableLL [a] a Source # 
Instance details

Defined in Data.ListLike.FoldableLL

Methods

foldl :: (a0 -> a -> a0) -> a0 -> [a] -> a0 Source #

foldl' :: (a0 -> a -> a0) -> a0 -> [a] -> a0 Source #

foldl1 :: (a -> a -> a) -> [a] -> a Source #

foldr :: (a -> b -> b) -> b -> [a] -> b Source #

foldr' :: (a -> b -> b) -> b -> [a] -> b Source #

foldr1 :: (a -> a -> a) -> [a] -> a Source #

Vector v a => FoldableLL (v a) a Source # 
Instance details

Defined in Data.ListLike.Vector.Generic

Methods

foldl :: (a0 -> a -> a0) -> a0 -> v a -> a0 Source #

foldl' :: (a0 -> a -> a0) -> a0 -> v a -> a0 Source #

foldl1 :: (a -> a -> a) -> v a -> a Source #

foldr :: (a -> b -> b) -> b -> v a -> b Source #

foldr' :: (a -> b -> b) -> b -> v a -> b Source #

foldr1 :: (a -> a -> a) -> v a -> a Source #

FoldableLL (Seq a) a Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

foldl :: (a0 -> a -> a0) -> a0 -> Seq a -> a0 Source #

foldl' :: (a0 -> a -> a0) -> a0 -> Seq a -> a0 Source #

foldl1 :: (a -> a -> a) -> Seq a -> a Source #

foldr :: (a -> b -> b) -> b -> Seq a -> b Source #

foldr' :: (a -> b -> b) -> b -> Seq a -> b Source #

foldr1 :: (a -> a -> a) -> Seq a -> a Source #

FoldableLL (DList a) a Source # 
Instance details

Defined in Data.ListLike.DList

Methods

foldl :: (a0 -> a -> a0) -> a0 -> DList a -> a0 Source #

foldl' :: (a0 -> a -> a0) -> a0 -> DList a -> a0 Source #

foldl1 :: (a -> a -> a) -> DList a -> a Source #

foldr :: (a -> b -> b) -> b -> DList a -> b Source #

foldr' :: (a -> b -> b) -> b -> DList a -> b Source #

foldr1 :: (a -> a -> a) -> DList a -> a Source #

FoldableLL (FMList a) a Source # 
Instance details

Defined in Data.ListLike.FMList

Methods

foldl :: (a0 -> a -> a0) -> a0 -> FMList a -> a0 Source #

foldl' :: (a0 -> a -> a0) -> a0 -> FMList a -> a0 Source #

foldl1 :: (a -> a -> a) -> FMList a -> a Source #

foldr :: (a -> b -> b) -> b -> FMList a -> b Source #

foldr' :: (a -> b -> b) -> b -> FMList a -> b Source #

foldr1 :: (a -> a -> a) -> FMList a -> a Source #

FoldableLL (UTF8 ByteString) Char Source # 
Instance details

Defined in Data.ListLike.UTF8

Methods

foldl :: (a -> Char -> a) -> a -> UTF8 ByteString -> a Source #

foldl' :: (a -> Char -> a) -> a -> UTF8 ByteString -> a Source #

foldl1 :: (Char -> Char -> Char) -> UTF8 ByteString -> Char Source #

foldr :: (Char -> b -> b) -> b -> UTF8 ByteString -> b Source #

foldr' :: (Char -> b -> b) -> b -> UTF8 ByteString -> b Source #

foldr1 :: (Char -> Char -> Char) -> UTF8 ByteString -> Char Source #

FoldableLL (UTF8 ByteString) Char Source # 
Instance details

Defined in Data.ListLike.UTF8

Methods

foldl :: (a -> Char -> a) -> a -> UTF8 ByteString -> a Source #

foldl' :: (a -> Char -> a) -> a -> UTF8 ByteString -> a Source #

foldl1 :: (Char -> Char -> Char) -> UTF8 ByteString -> Char Source #

foldr :: (Char -> b -> b) -> b -> UTF8 ByteString -> b Source #

foldr' :: (Char -> b -> b) -> b -> UTF8 ByteString -> b Source #

foldr1 :: (Char -> Char -> Char) -> UTF8 ByteString -> Char Source #

Unbox a => FoldableLL (Vector a) a Source # 
Instance details

Defined in Data.ListLike.Vector.Unboxed

Methods

foldl :: (a0 -> a -> a0) -> a0 -> Vector a -> a0 Source #

foldl' :: (a0 -> a -> a0) -> a0 -> Vector a -> a0 Source #

foldl1 :: (a -> a -> a) -> Vector a -> a Source #

foldr :: (a -> b -> b) -> b -> Vector a -> b Source #

foldr' :: (a -> b -> b) -> b -> Vector a -> b Source #

foldr1 :: (a -> a -> a) -> Vector a -> a Source #

Storable a => FoldableLL (Vector a) a Source # 
Instance details

Defined in Data.ListLike.Vector.Storable

Methods

foldl :: (a0 -> a -> a0) -> a0 -> Vector a -> a0 Source #

foldl' :: (a0 -> a -> a0) -> a0 -> Vector a -> a0 Source #

foldl1 :: (a -> a -> a) -> Vector a -> a Source #

foldr :: (a -> b -> b) -> b -> Vector a -> b Source #

foldr' :: (a -> b -> b) -> b -> Vector a -> b Source #

foldr1 :: (a -> a -> a) -> Vector a -> a Source #

FoldableLL (Vector a) a Source # 
Instance details

Defined in Data.ListLike.Vector.Vector

Methods

foldl :: (a0 -> a -> a0) -> a0 -> Vector a -> a0 Source #

foldl' :: (a0 -> a -> a0) -> a0 -> Vector a -> a0 Source #

foldl1 :: (a -> a -> a) -> Vector a -> a Source #

foldr :: (a -> b -> b) -> b -> Vector a -> b Source #

foldr' :: (a -> b -> b) -> b -> Vector a -> b Source #

foldr1 :: (a -> a -> a) -> Vector a -> a Source #

Ix i => FoldableLL (Array i e) e Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

foldl :: (a -> e -> a) -> a -> Array i e -> a Source #

foldl' :: (a -> e -> a) -> a -> Array i e -> a Source #

foldl1 :: (e -> e -> e) -> Array i e -> e Source #

foldr :: (e -> b -> b) -> b -> Array i e -> b Source #

foldr' :: (e -> b -> b) -> b -> Array i e -> b Source #

foldr1 :: (e -> e -> e) -> Array i e -> e Source #

The StringLike class

class IsString s => StringLike s Source #

An extension to ListLike for those data types that are similar to a String. Minimal complete definition is toString and fromString.

Minimal complete definition

toString

Instances

Instances details
StringLike String Source # 
Instance details

Defined in Data.ListLike.Instances

StringLike Builder Source # 
Instance details

Defined in Data.ListLike.Text.Builder

StringLike Text Source # 
Instance details

Defined in Data.ListLike.Text.TextLazy

Methods

toString :: Text -> String Source #

lines :: ListLike full Text => Text -> full Source #

words :: ListLike full Text => Text -> full Source #

unlines :: ListLike full Text => full -> Text Source #

unwords :: ListLike full Text => full -> Text Source #

show :: Show a => a -> Text Source #

fromStringLike :: StringLike s' => Text -> s' Source #

fromText :: Text0 -> Text Source #

fromLazyText :: Text -> Text Source #

StringLike Text Source # 
Instance details

Defined in Data.ListLike.Text.Text

Methods

toString :: Text -> String Source #

lines :: ListLike full Text => Text -> full Source #

words :: ListLike full Text => Text -> full Source #

unlines :: ListLike full Text => full -> Text Source #

unwords :: ListLike full Text => full -> Text Source #

show :: Show a => a -> Text Source #

fromStringLike :: StringLike s' => Text -> s' Source #

fromText :: Text -> Text Source #

fromLazyText :: Text0 -> Text Source #

StringLike CharStringLazy Source # 
Instance details

Defined in Data.ListLike.CharString

StringLike CharString Source # 
Instance details

Defined in Data.ListLike.CharString

StringLike Chars Source # 
Instance details

Defined in Data.ListLike.Chars

(Eq (v Char), Vector v Char) => StringLike (v Char) Source # 
Instance details

Defined in Data.ListLike.Vector.Generic

Methods

toString :: v Char -> String Source #

lines :: ListLike full (v Char) => v Char -> full Source #

words :: ListLike full (v Char) => v Char -> full Source #

unlines :: ListLike full (v Char) => full -> v Char Source #

unwords :: ListLike full (v Char) => full -> v Char Source #

show :: Show a => a -> v Char Source #

fromStringLike :: StringLike s' => v Char -> s' Source #

fromText :: Text -> v Char Source #

fromLazyText :: Text -> v Char Source #

StringLike (Seq Char) Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

toString :: Seq Char -> String Source #

lines :: ListLike full (Seq Char) => Seq Char -> full Source #

words :: ListLike full (Seq Char) => Seq Char -> full Source #

unlines :: ListLike full (Seq Char) => full -> Seq Char Source #

unwords :: ListLike full (Seq Char) => full -> Seq Char Source #

show :: Show a => a -> Seq Char Source #

fromStringLike :: StringLike s' => Seq Char -> s' Source #

fromText :: Text -> Seq Char Source #

fromLazyText :: Text -> Seq Char Source #

StringLike (DList Char) Source # 
Instance details

Defined in Data.ListLike.DList

StringLike (FMList Char) Source # 
Instance details

Defined in Data.ListLike.FMList

StringLike (UTF8 ByteString) Source # 
Instance details

Defined in Data.ListLike.UTF8

StringLike (UTF8 ByteString) Source # 
Instance details

Defined in Data.ListLike.UTF8

StringLike (Vector Char) Source # 
Instance details

Defined in Data.ListLike.Vector.Unboxed

StringLike (Vector Char) Source # 
Instance details

Defined in Data.ListLike.Vector.Storable

StringLike (Vector Char) Source # 
Instance details

Defined in Data.ListLike.Vector.Vector

(Integral i, Ix i) => StringLike (Array i Char) Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

toString :: Array i Char -> String Source #

lines :: ListLike full (Array i Char) => Array i Char -> full Source #

words :: ListLike full (Array i Char) => Array i Char -> full Source #

unlines :: ListLike full (Array i Char) => full -> Array i Char Source #

unwords :: ListLike full (Array i Char) => full -> Array i Char Source #

show :: Show a => a -> Array i Char Source #

fromStringLike :: StringLike s' => Array i Char -> s' Source #

fromText :: Text -> Array i Char Source #

fromLazyText :: Text -> Array i Char Source #

The InfiniteListLike class

class ListLike full item => InfiniteListLike full item | full -> item Source #

An extension to ListLike for those data types that are capable of dealing with infinite lists. Some ListLike functions are capable of working with finite or infinite lists. The functions here require infinite list capability in order to work at all.

Instances

Instances details
InfiniteListLike [a] a Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

iterate :: (a -> a) -> a -> [a] Source #

repeat :: a -> [a] Source #

cycle :: [a] -> [a] Source #

InfiniteListLike (FMList a) a Source # 
Instance details

Defined in Data.ListLike.FMList

Methods

iterate :: (a -> a) -> a -> FMList a Source #

repeat :: a -> FMList a Source #

cycle :: FMList a -> FMList a Source #