GTALib-0.0.6: A library for GTA programming

Safe HaskellNone

GTA.Data.JoinList

Description

This module provides the GTA framework on join lists, such as definitions of the data structure and its algebra, parallel/serial generators, aggregators, etc.

Synopsis

Documentation

data JoinList a Source

Join lists.

 x ++ y ==> x `Times` y
 [a]    ==> Single a
 []     ==> Nil

We assume that Times is associative and Nil is its identity:

 x `Times` (y `Times` z) == (x `Times` y) `Times` z
 x `Times` Nil == Nil `Times` x == x

Constructors

Times (JoinList a) (JoinList a) 
Single a 
Nil 

Instances

Eq a => Eq (JoinList a) 
Ord a => Ord (JoinList a) 
Read a => Read (JoinList a) 
Show a => Show (JoinList a) 
NFData a => NFData (JoinList a) 
GenericSemiringStructure (JoinListAlgebra b) (JoinList b) (JoinListMapFs b)

Instance declaration of GTA.Data.GenericSemiringStructure for join lists. The implementation is quite straightforward.

This can be generated automatically by genAllDecl ''JoinList.

data JoinListAlgebra b a Source

The algebra of join lists.

We assume that times is associative and nil is its identity, inheriting those of Times and Nil:

 x `times` (y `times` z) == (x `times` y) `times` z
 x `times` nil == nil `times` x == x

This can be generated automatically by genAllDecl ''JoinList.

Constructors

JoinListAlgebra 

Fields

times :: a -> a -> a
 
single :: b -> a
 
nil :: a
 

Instances

GenericSemiringStructure (JoinListAlgebra b) (JoinList b) (JoinListMapFs b)

Instance declaration of GTA.Data.GenericSemiringStructure for join lists. The implementation is quite straightforward.

This can be generated automatically by genAllDecl ''JoinList.

joinize :: forall a. [a] -> JoinList aSource

Conversion from a usual list to a join list.

dejoinize :: forall a. JoinList a -> [a]Source

Conversion from a join list to a usual list.

segs :: [a] -> Semiring a s -> sSource

This generates all segments (continuous subsequences) of a given list.

For example,

>>> segs [1,2,3] `aggregateBy` result
Bag [[1],[2],[3],[2,3],[1,2],[1,2,3],[]]

inits :: [a] -> Semiring a s -> sSource

This generates all prefixes of a given list.

For example,

>>> inits [1,2,3] `aggregateBy` result
Bag [[],[1],[1,2],[1,2,3]]

tails :: [a] -> Semiring a s -> sSource

This generates all suffixes of a given list.

For example,

>>> tails [1,2,3] `aggregateBy` result
Bag [[1,2,3],[2,3],[3],[]]

subs :: [a] -> Semiring a s -> sSource

This generates all subsequences of a given list.

For example,

>>> subs [1,2,3] `aggregateBy` result
Bag [[1,2,3],[1,2],[1,3],[1],[2,3],[2],[3],[]]

assigns :: [m] -> [a] -> Semiring (m, a) s -> sSource

This generates all assignments of elements of the first list to elements of the second list.

For example,

>>> assigns [True,False] [1,2,3] `aggregateBy` result
Bag [[(True,1),(True,2),(True,3)],[(True,1),(True,2),(False,3)],[(True,1),(False,2),(True,3)],[(True,1),(False,2),(False,3)],[(False,1),(True,2),(True,3)],[(False,1),(True,2),(False,3)],[(False,1),(False,2),(True,3)],[(False,1),(False,2),(False,3)]]

paths :: BinTree a a -> Semiring a s -> sSource

This generates all paths from the root to leaves of a given binary tree.

For example,

>>> *Main GTA.Data.BinTree> paths (BinNode 1 (BinLeaf 2) (BinNode 3 (BinLeaf 4) (BinLeaf 5))) `aggregateBy` result
Bag [[1,2],[1,3,4],[1,3,5]]

assignsBy :: (a -> [m]) -> [a] -> Semiring (m, a) s -> sSource

This is a generalization of assigns: the values to be assigned is dependent of the target.

For example,

>>> assignsBy (\a -> if odd a then [True, False] else [True]) [1,2,3] `aggregateBy` result
Bag [[(True,1),(True,2),(True,3)],[(True,1),(True,2),(False,3)],[(False,1),(True,2),(True,3)],[(False,1),(True,2),(False,3)]]

mapJ :: forall b a. (b -> a) -> JoinListMapFs b aSource

Wrapper for JoinListMapFs.

count :: Num a => Semiring b aSource

The aggregator to count the number of items in a generated bag.

maxsum :: (Ord a, Num a) => Semiring a (AddIdentity a)Source

The aggregator to take the maximum sum.

maxsumsolution :: (Ord a, Num a) => Semiring a (AddIdentity a, Bag (JoinList a))Source

The aggregator to find items with the maximum sum.

maxsumWith :: (Ord a, Num a) => (b -> a) -> Semiring b (AddIdentity a)Source

The aggregator to take the maximum sum after map f.

maxsumKWith :: (Ord a, Num a) => Int -> (b -> a) -> Semiring b [AddIdentity a]Source

The best-k extension of maxsumWith.

maxsumsolutionXKWith :: (Ord a, Num a) => Semiring c b -> Int -> (c -> a) -> Semiring c [(AddIdentity a, b)]Source

The best-k extension of maxsumsolutionXWith.

maxsumsolutionXWith :: (Ord a, Num a) => Semiring c b -> (c -> a) -> Semiring c (AddIdentity a, b)Source

The tupling of maxsumsolution and a given semiring. The second component is the aggregation of the maximum items by the given semiring.

maxsumsolutionWith :: (Ord a, Num a) => (b -> a) -> Semiring b (AddIdentity a, Bag (JoinList b))Source

The aggregator to find items with the maximum sum after map f.

maxsumsolutionKWith :: (Ord a, Num a) => Int -> (b -> a) -> Semiring b [(AddIdentity a, Bag (JoinList b))]Source

The best-k extension of maxsumsolutionWith.

maxprodWith :: (Ord a, Num a) => (b -> a) -> Semiring b (AddIdentity a)Source

The aggregator to take the maximum product of non-negative numbers after map f.

maxprodKWith :: (Ord a, Num a) => Int -> (b -> a) -> Semiring b [AddIdentity a]Source

The best-k extension of maxprodWith.

maxprodsolutionXKWith :: (Ord a, Num a) => Semiring c b -> Int -> (c -> a) -> Semiring c [(AddIdentity a, b)]Source

The best-k extension of maxprodsolutionXWith.

maxprodsolutionXWith :: (Ord a, Num a) => Semiring c b -> (c -> a) -> Semiring c (AddIdentity a, b)Source

The tupling of maxprodsolution and a given semiring. The second component is the aggregation of the maximum items by the given semiring.

maxprodsolutionWith :: (Ord a, Num a) => (b -> a) -> Semiring b (AddIdentity a, Bag (JoinList b))Source

The aggregator to find items with the maximum product. The numbers have to be non-negative.

maxprodsolutionKWith :: (Ord a, Num a) => Int -> (b -> a) -> Semiring b [(AddIdentity a, Bag (JoinList b))]Source

The best-k extension of maxprodsolutionWith.

segsP :: NFData s => [a] -> Semiring a s -> sSource

Parallel version of segs.

initsP :: NFData s => [a] -> Semiring a s -> sSource

Parallel version of inits.

tailsP :: NFData s => [a] -> Semiring a s -> sSource

Parallel version of tails.

subsP :: NFData s => [a] -> Semiring a s -> sSource

Parallel version of subs.

assignsP :: NFData s => [m] -> [a] -> Semiring (m, a) s -> sSource

Parallel version of assigns.

assignsByP :: NFData s => (a -> [m]) -> [a] -> Semiring (m, a) s -> sSource

Parallel version of assignsBy.

crossConcat :: Bag (JoinList a) -> Bag (JoinList a) -> Bag (JoinList a)Source

Constructor of a bag of join lists.

For example,

>>> (bag (map joinize [[1,2], [3]])) `crossConcat` (bag (map joinize [[4,5], [6]]))
Bag [[1,2,4,5],[1,2,6],[3,4,5],[3,6]]

bagOfSingleton :: a -> Bag (JoinList a)Source

Constructor of a bag of join lists.

For example,

>>> bagOfSingleton 1
Bag [[1]]

emptyBag :: Bag (JoinList a)Source

Constructor of a bag of join lists.

For example,

>>> emptyBag
Bag []

bagOfNil :: Bag (JoinList a)Source

Constructor of a bag of join lists.

For example,

>>> bagOfNil
Bag [[]]

bagUnion :: Bag (JoinList a) -> Bag (JoinList a) -> Bag (JoinList a)Source

Constructor of a bag of join lists.

For example,

>>> (bag (map joinize [[1,2], [3]])) `bagUnion` (bag (map joinize [[4,5], [6]]))
Bag [[1,2],[3],[4,5],[6]]

type Semiring a s = GenericSemiring (JoinListAlgebra a) sSource

The usual semiring is a generic semiring of join lists:

 a `times` (b `oplus` c) == (a `times` b) `oplus` (a `times` c)
 (a `oplus` b) `times` c == (a `times` c) `oplus` (b `times` c)
 a `times` identity == identity `times` a == identity

prop_Associativity :: Eq b => JoinListAlgebra a b -> (b, b, b) -> BoolSource

Property of times of a JoinListAlgebra:

 x `times` (y `times` z) == (x `times` y) `times` z

prop_Identity :: Eq b => JoinListAlgebra a b -> b -> BoolSource

Property of times and nil of a JoinListAlgebra:

 (x `times` nil == x) && (nil `times` x == x)

data JoinListMapFs b b' Source

A record to hold a function to be applied to elements of a list.

This can be generated automatically by genAllDecl ''JoinList.

Instances

GenericSemiringStructure (JoinListAlgebra b) (JoinList b) (JoinListMapFs b)

Instance declaration of GTA.Data.GenericSemiringStructure for join lists. The implementation is quite straightforward.

This can be generated automatically by genAllDecl ''JoinList.

homJ :: (a -> a -> a) -> (b -> a) -> a -> JoinList b -> aSource

A wrapper function for JoinList homomorphism.

homJ' :: (a -> a -> a) -> (b -> a) -> a -> JoinListAlgebra b aSource

A fake function of homJ to build JoinListAlgebra instead of executing the homomorphism with it.

mapMap :: (b -> b') -> GenericSemiring (JoinListAlgebra b') a -> GenericSemiring (JoinListAlgebra b) aSource

A transfomer that applies given function to every element in every list in a given bag.

perms :: [a] -> Semiring a s -> sSource

This generates all permutations of a given list.

For example,

>>> perms "hoge" `aggregateBy` result
Bag ["hoge","hoeg","ohge","oheg","hgoe","hgeo","ghoe","gheo","heog","hego","ehog","ehgo","oghe","ogeh","gohe","goeh","oehg","oegh","eohg","eogh","geho","geoh","egho","egoh"]

permsP :: NFData s => [a] -> Semiring a s -> sSource

Parallel version of perms.