language-toolkit-1.2.0.0: A set of tools for analyzing languages via logic and automata
Copyright(c) 2016-2023 Dakotah Lambert
LicenseMIT
Safe HaskellTrustworthy
LanguageHaskell2010
Extensions
  • Cpp
  • TypeSynonymInstances
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • FunctionalDependencies

LTK.Containers

Description

contain other entities.

Synopsis

Documentation

class Container c a | c -> a where Source #

The Container class is used for types that can contain objects and can be combined with union, intersection, and difference (relative complement). Instances of Container should satisfy the following laws:

isIn == flip contains
isNotIn == flip doesNotContain
doesNotContain a == not . contains a
contains a empty == False
contains a (singleton b) == (a == b)
contains a (insert b c) == (a == b) || contains a c
contains a (union c1 c2) == contains a c1 || contains a c2
contains a (intersection c1 c2) == contains a c1 && contains a c2
intersection c c == c
difference c c == empty

Minimal complete definition

(contains | isIn), union, intersection, difference, empty, isEmpty, (insert | singleton)

Methods

isIn :: Eq a => c -> a -> Bool Source #

isNotIn :: Eq a => c -> a -> Bool Source #

contains :: Eq a => a -> c -> Bool Source #

doesNotContain :: Eq a => a -> c -> Bool Source #

isEmpty :: c -> Bool Source #

union :: c -> c -> c Source #

(union a b) returns a collection of elements that are in one of a or b, or both.

intersection :: Eq a => c -> c -> c Source #

(intersection a b) returns a collection of elements that are in both a and b.

difference :: Eq a => c -> c -> c Source #

(difference a b) returns a collection of elements that are in a but not in b.

symmetricDifference :: Eq a => c -> c -> c Source #

(symmetricDifference a b) returns a collection of elements that are in one of a or b, but not both.

empty :: c Source #

insert :: a -> c -> c Source #

singleton :: a -> c Source #

isSubsetOf :: Eq a => c -> c -> Bool Source #

(isSubsetOf y x) tells if x is a subset of y.

isSupersetOf :: Eq a => c -> c -> Bool Source #

(isSupersetOf y x) tells if x is a superset of y.

isProperSubsetOf :: Eq a => c -> c -> Bool Source #

(isProperSubsetOf y x) tells whether x is a proper subset of y.

isProperSupersetOf :: Eq a => c -> c -> Bool Source #

(isProperSupersetOf y x) tells whether x is a proper superset of y.

Instances

Instances details
Ord a => Container (Set a) a Source # 
Instance details

Defined in LTK.Containers

Methods

isIn :: Set a -> a -> Bool Source #

isNotIn :: Set a -> a -> Bool Source #

contains :: a -> Set a -> Bool Source #

doesNotContain :: a -> Set a -> Bool Source #

isEmpty :: Set a -> Bool Source #

union :: Set a -> Set a -> Set a Source #

intersection :: Set a -> Set a -> Set a Source #

difference :: Set a -> Set a -> Set a Source #

symmetricDifference :: Set a -> Set a -> Set a Source #

empty :: Set a Source #

insert :: a -> Set a -> Set a Source #

singleton :: a -> Set a Source #

isSubsetOf :: Set a -> Set a -> Bool Source #

isSupersetOf :: Set a -> Set a -> Bool Source #

isProperSubsetOf :: Set a -> Set a -> Bool Source #

isProperSupersetOf :: Set a -> Set a -> Bool Source #

Ord a => Container (Multiset a) a Source # 
Instance details

Defined in LTK.Containers

Container [a] a Source # 
Instance details

Defined in LTK.Containers

Methods

isIn :: [a] -> a -> Bool Source #

isNotIn :: [a] -> a -> Bool Source #

contains :: a -> [a] -> Bool Source #

doesNotContain :: a -> [a] -> Bool Source #

isEmpty :: [a] -> Bool Source #

union :: [a] -> [a] -> [a] Source #

intersection :: [a] -> [a] -> [a] Source #

difference :: [a] -> [a] -> [a] Source #

symmetricDifference :: [a] -> [a] -> [a] Source #

empty :: [a] Source #

insert :: a -> [a] -> [a] Source #

singleton :: a -> [a] Source #

isSubsetOf :: [a] -> [a] -> Bool Source #

isSupersetOf :: [a] -> [a] -> Bool Source #

isProperSubsetOf :: [a] -> [a] -> Bool Source #

isProperSupersetOf :: [a] -> [a] -> Bool Source #

Ord e => Container (ForbiddenSubstrings e) (TaggedSubstring e) Source # 
Instance details

Defined in LTK.Extract.SL

Ord e => Container (ForbiddenSubsequences e) [e] Source # 
Instance details

Defined in LTK.Extract.SP

(Enum n, Ord n, Ord e) => Container (FSA n e) [e] Source # 
Instance details

Defined in LTK.FSA

Methods

isIn :: FSA n e -> [e] -> Bool Source #

isNotIn :: FSA n e -> [e] -> Bool Source #

contains :: [e] -> FSA n e -> Bool Source #

doesNotContain :: [e] -> FSA n e -> Bool Source #

isEmpty :: FSA n e -> Bool Source #

union :: FSA n e -> FSA n e -> FSA n e Source #

intersection :: FSA n e -> FSA n e -> FSA n e Source #

difference :: FSA n e -> FSA n e -> FSA n e Source #

symmetricDifference :: FSA n e -> FSA n e -> FSA n e Source #

empty :: FSA n e Source #

insert :: [e] -> FSA n e -> FSA n e Source #

singleton :: [e] -> FSA n e Source #

isSubsetOf :: FSA n e -> FSA n e -> Bool Source #

isSupersetOf :: FSA n e -> FSA n e -> Bool Source #

isProperSubsetOf :: FSA n e -> FSA n e -> Bool Source #

isProperSupersetOf :: FSA n e -> FSA n e -> Bool Source #

class Linearizable l where Source #

The Linearizable class is used for types that can be traversed linearly in one direction.

Methods

choose :: l a -> (a, l a) Source #

Return the next element and the collection of remaining elements.

Instances

Instances details
Linearizable Set Source # 
Instance details

Defined in LTK.Containers

Methods

choose :: Set a -> (a, Set a) Source #

Linearizable Multiset Source # 
Instance details

Defined in LTK.Containers

Methods

choose :: Multiset a -> (a, Multiset a) Source #

Linearizable List Source # 
Instance details

Defined in LTK.Containers

Methods

choose :: [a] -> (a, [a]) Source #

chooseOne :: Linearizable l => l a -> a Source #

Like choose, but discards the remaining elements.

discardOne :: Linearizable l => l a -> l a Source #

Like choose, but discards the next element.

class Linearizable c => Collapsible c where Source #

The Collapsible class is used for types that can be collapsed to a single value, like a fold over a list. Any structure \(c\) that is Collapsible must necessarily be Linearizable, since:

collapse (:) [] c

performs a linearization.

Minimal complete definition

collapse | size

Methods

collapse :: (a -> b -> b) -> b -> c a -> b Source #

size :: Integral a => c b -> a Source #

Instances

Instances details
Collapsible Set Source # 
Instance details

Defined in LTK.Containers

Methods

collapse :: (a -> b -> b) -> b -> Set a -> b Source #

size :: Integral a => Set b -> a Source #

Collapsible Multiset Source # 
Instance details

Defined in LTK.Containers

Methods

collapse :: (a -> b -> b) -> b -> Multiset a -> b Source #

size :: Integral a => Multiset b -> a Source #

Collapsible List Source # 
Instance details

Defined in LTK.Containers

Methods

collapse :: (a -> b -> b) -> b -> [a] -> b Source #

size :: Integral a => [b] -> a Source #

isize :: Collapsible c => c b -> Integer Source #

The size of the input as an integer

zsize :: Collapsible c => c b -> Bool Source #

Analogue to isEmpty for Collapsible structures

fromCollapsible :: (Collapsible s, Container c a) => s a -> c Source #

Build a Container from the elements of a Collapsible. This can be used to cast between most types of Container. Time complexity is \(O(nci)\), where \(n\) is the number of elements in the source, \(c\) is the cost of accessing a next element of the source, and \(i\) is the cost of inserting an element into the destination.

Combining multiple Containers

unionAll :: (Container c a, Collapsible s) => s c -> c Source #

Combine Containers with union.

intersectAll :: (Container c a, Eq a, Collapsible s) => s c -> c Source #

Combine Containers with intersection. An empty source yields an empty result.

interleave :: (Linearizable c, Container (c a) a) => c a -> c a -> c a Source #

Combine two linearizable containers such that the elements of the first and second are inserted in an interleaving manner. For lists, this guarantees that a finite initial segment will contain elements from each, in contrast to the (++) operator.

Since: 0.3

Generic versions of Prelude functions and similar

anyS :: Collapsible s => (a -> Bool) -> s a -> Bool Source #

True iff some element satisfies a predicate.

allS :: Collapsible s => (a -> Bool) -> s a -> Bool Source #

True iff all elements satisfy a predicate.

both :: (a -> Bool) -> (a -> Bool) -> a -> Bool Source #

True iff the given object satisfies both given predicates.

Since: 0.3

tmap :: (Collapsible s, Container (s b1) b) => (a -> b) -> s a -> s b1 Source #

Appy a function to each element of a Collapsible.

keep :: (Collapsible s, Container (s a) a) => (a -> Bool) -> s a -> s a Source #

Retain only those elements that satisfy a predicate.

groupBy :: (Eq b, Collapsible s, Container (s a) a, Container (s (s a)) (s a)) => (a -> b) -> s a -> s (s a) Source #

Partition a Container. For example,

groupBy (`mod` 3) [0..9] == [[0,3,6,9],[1,4,7],[2,5,8]]

partitionBy :: (Ord a, Ord n) => (n -> a) -> Set n -> Set (Set n) Source #

A fast groupBy for Set objects.

Since: 0.2

refinePartitionBy :: (Ord a, Ord n) => (n -> a) -> Set (Set n) -> Set (Set n) Source #

A convenience function for the partition refinement operation.

Since: 0.2

Multisets

data Multiset a Source #

A Multiset is a Set that may contain more than one instance of any given element.

Instances

Instances details
Collapsible Multiset Source # 
Instance details

Defined in LTK.Containers

Methods

collapse :: (a -> b -> b) -> b -> Multiset a -> b Source #

size :: Integral a => Multiset b -> a Source #

Linearizable Multiset Source # 
Instance details

Defined in LTK.Containers

Methods

choose :: Multiset a -> (a, Multiset a) Source #

Ord a => Monoid (Multiset a) Source # 
Instance details

Defined in LTK.Containers

Methods

mempty :: Multiset a #

mappend :: Multiset a -> Multiset a -> Multiset a #

mconcat :: [Multiset a] -> Multiset a #

Ord a => Semigroup (Multiset a) Source # 
Instance details

Defined in LTK.Containers

Methods

(<>) :: Multiset a -> Multiset a -> Multiset a #

sconcat :: NonEmpty (Multiset a) -> Multiset a #

stimes :: Integral b => b -> Multiset a -> Multiset a #

(Ord a, Read a) => Read (Multiset a) Source # 
Instance details

Defined in LTK.Containers

Show a => Show (Multiset a) Source # 
Instance details

Defined in LTK.Containers

Methods

showsPrec :: Int -> Multiset a -> ShowS #

show :: Multiset a -> String #

showList :: [Multiset a] -> ShowS #

Eq a => Eq (Multiset a) Source # 
Instance details

Defined in LTK.Containers

Methods

(==) :: Multiset a -> Multiset a -> Bool #

(/=) :: Multiset a -> Multiset a -> Bool #

Ord a => Ord (Multiset a) Source # 
Instance details

Defined in LTK.Containers

Methods

compare :: Multiset a -> Multiset a -> Ordering #

(<) :: Multiset a -> Multiset a -> Bool #

(<=) :: Multiset a -> Multiset a -> Bool #

(>) :: Multiset a -> Multiset a -> Bool #

(>=) :: Multiset a -> Multiset a -> Bool #

max :: Multiset a -> Multiset a -> Multiset a #

min :: Multiset a -> Multiset a -> Multiset a #

Ord a => Container (Multiset a) a Source # 
Instance details

Defined in LTK.Containers

multiplicity :: Ord a => Multiset a -> a -> Integer Source #

Analogous to isIn, returning the number of occurrences of an element in a Multiset. Time complexity is \(O(\log{n})\), where \(n\) is the number of distinct elements in the Multiset.

multiplicities :: Ord a => Multiset a -> Set Integer Source #

Every multiplicity that occurs in the multiset.

Since: 1.0

multisetFromList :: Ord a => [a] -> Multiset a Source #

A specialization of fromCollapsible.

setFromMultiset :: Multiset a -> Set a Source #

A specialization of fromCollapsible with time complexity \(O(n)\), where \(n\) is the number of distinct elements in the source.

Set of Set with alternate ordering

The choose instance for Set will always pick the least available element. If one wants to process elements in a different order, one can simply wrap the elements in such a way that they sort in the intended order of processing. This section contains some such wrapper types.

newtype IncreasingSize x Source #

Wrap a Collapsible type to sort in order of increasing size. For elements of the same size, treat them normally.

Constructors

IncreasingSize 

Fields

Instances

Instances details
Functor IncreasingSize Source # 
Instance details

Defined in LTK.Containers

Methods

fmap :: (a -> b) -> IncreasingSize a -> IncreasingSize b #

(<$) :: a -> IncreasingSize b -> IncreasingSize a #

Read x => Read (IncreasingSize x) Source # 
Instance details

Defined in LTK.Containers

Show x => Show (IncreasingSize x) Source # 
Instance details

Defined in LTK.Containers

Eq x => Eq (IncreasingSize x) Source # 
Instance details

Defined in LTK.Containers

(Collapsible x, Ord (x a)) => Ord (IncreasingSize (x a)) Source # 
Instance details

Defined in LTK.Containers

Methods

compare :: IncreasingSize (x a) -> IncreasingSize (x a) -> Ordering #

(<) :: IncreasingSize (x a) -> IncreasingSize (x a) -> Bool #

(<=) :: IncreasingSize (x a) -> IncreasingSize (x a) -> Bool #

(>) :: IncreasingSize (x a) -> IncreasingSize (x a) -> Bool #

(>=) :: IncreasingSize (x a) -> IncreasingSize (x a) -> Bool #

max :: IncreasingSize (x a) -> IncreasingSize (x a) -> IncreasingSize (x a) #

min :: IncreasingSize (x a) -> IncreasingSize (x a) -> IncreasingSize (x a) #

newtype DecreasingSize x Source #

Wrap a Collapsible type to sort in order of decreasing size. For elements of the same size, treat them normally.

Constructors

DecreasingSize 

Fields

Instances

Instances details
Functor DecreasingSize Source # 
Instance details

Defined in LTK.Containers

Methods

fmap :: (a -> b) -> DecreasingSize a -> DecreasingSize b #

(<$) :: a -> DecreasingSize b -> DecreasingSize a #

Read x => Read (DecreasingSize x) Source # 
Instance details

Defined in LTK.Containers

Show x => Show (DecreasingSize x) Source # 
Instance details

Defined in LTK.Containers

Eq x => Eq (DecreasingSize x) Source # 
Instance details

Defined in LTK.Containers

(Collapsible x, Ord (x a)) => Ord (DecreasingSize (x a)) Source # 
Instance details

Defined in LTK.Containers

Methods

compare :: DecreasingSize (x a) -> DecreasingSize (x a) -> Ordering #

(<) :: DecreasingSize (x a) -> DecreasingSize (x a) -> Bool #

(<=) :: DecreasingSize (x a) -> DecreasingSize (x a) -> Bool #

(>) :: DecreasingSize (x a) -> DecreasingSize (x a) -> Bool #

(>=) :: DecreasingSize (x a) -> DecreasingSize (x a) -> Bool #

max :: DecreasingSize (x a) -> DecreasingSize (x a) -> DecreasingSize (x a) #

min :: DecreasingSize (x a) -> DecreasingSize (x a) -> DecreasingSize (x a) #

Miscellaneous classes

class HasAlphabet g where Source #

Allow for overloading of the term alphabet.

Since: 0.3

Methods

alphabet :: g e -> Set e Source #

Instances

Instances details
HasAlphabet SLG Source # 
Instance details

Defined in LTK.Learn.SL

Methods

alphabet :: SLG e -> Set e Source #

HasAlphabet SPG Source # 
Instance details

Defined in LTK.Learn.SP

Methods

alphabet :: SPG e -> Set e Source #

HasAlphabet TSLG Source # 
Instance details

Defined in LTK.Learn.TSL.AugmentedSubsequences

Methods

alphabet :: TSLG e -> Set e Source #

HasAlphabet TSLG Source # 
Instance details

Defined in LTK.Learn.TSL.ViaSL

Methods

alphabet :: TSLG e -> Set e Source #

HasAlphabet (FSA n) Source # 
Instance details

Defined in LTK.FSA

Methods

alphabet :: FSA n e -> Set e Source #

Miscellaneous functions

extractMonotonic :: (Ord a, Ord b) => (a -> b) -> b -> Set a -> Set a Source #

A fast method to extract elements from a set whose image under a monotonic function is a certain value. The precondition that the function is monotonic is not checked.

Since: 0.2

sequencesOver :: [x] -> [[x]] Source #

All possible sequences over a given alphabet, generated in a breadth-first manner.

Since: 0.3

tr :: (Container (s a) a, Collapsible s, Eq a) => [a] -> [a] -> s a -> s a Source #

Translate elements. All instances of elements of the search set are replaced by the corresponding elements of the replacement set in the given string. If the replacement set is smaller than the search set, it is made longer by repeating the last element.

>>> tr "aeiou" "x" "colorless green ideas"
"cxlxrlxss grxxn xdxxs"
>>> tr "abcdefghijklmnopqrstuvwxyz" "nopqrstuvwxyzabcdefghijklm" "cat"
"png"