TableAlgebra-0.6.1: Ferry Table Algebra

Database.Ferry.Algebra

Description

This package provides a convenient interface to construct Table Algebra plans that can be dealt with by Pathfinder (http:www-db.informatik.uni-tuebingen.deresearchpathfinder). A describtion of the algebra can be found at: http:dbworld.informatik.uni-tuebingen.deprojectspathfinderwikiLogical_Algebra This module only provides a subset of the complete algebra.

Synopsis

Documentation

type AlgPlan res = (Map Algebra AlgNode, res, Tags)Source

An algebraic plan is the result of constructing a graph. | The pair consists of the mapping from nodes to their respective ids | and the algres from the top node.

union :: AlgNode -> AlgNode -> GraphM a AlgNodeSource

Union between two plans

attach :: ResAttrName -> ATy -> AVal -> AlgNode -> GraphM a AlgNodeSource

Attach a column ResAttrName of type ATy with value AVal in all rows to table AlgNode

proj :: ProjInf -> AlgNode -> GraphM a AlgNodeSource

Project/rename certain column out of a plan

getLoop :: GraphM a AlgNodeSource

Get the current loop table

rownum :: AttrName -> [AttrName] -> Maybe AttrName -> AlgNode -> GraphM a AlgNodeSource

Similar to rowrank but this will assign a emph{unique} number to every row (even if two rows are equal)

rownum' :: AttrName -> [(AttrName, SortDir)] -> Maybe AttrName -> AlgNode -> GraphM a AlgNodeSource

Same as rownum but columns can be assigned an ordering direction

eqJoin :: String -> String -> AlgNode -> AlgNode -> GraphM a AlgNodeSource

Join two plans where the columns n1 of table 1 and columns n2 of table 2 are equal.

rank :: ResAttrName -> SortInf -> AlgNode -> GraphM a AlgNodeSource

Assign a number to each row in column ResAttrName incrementing sorted by SortInf. The numbering is not dense!

eqTJoin :: [(String, String)] -> ProjInf -> AlgNode -> AlgNode -> GraphM a AlgNodeSource

The same as eqJoin but with multiple columns.

distinct :: AlgNode -> GraphM a AlgNodeSource

Remove duplicate rows

rowrank :: ResAttrName -> SortInf -> AlgNode -> GraphM a AlgNodeSource

Same as rank but provides a dense numbering.

cast :: AttrName -> ResAttrName -> ATy -> AlgNode -> GraphM a AlgNodeSource

Cast column AttrName to type ATy and give it the name ResAttrName afterwards.

difference :: AlgNode -> AlgNode -> GraphM a AlgNodeSource

Compute the difference between two plans.

aggr :: [(AggrType, ResAttrName, Maybe AttrName)] -> Maybe PartAttrName -> AlgNode -> GraphM a AlgNodeSource

Apply aggregate functions to a plan

select :: SelAttrName -> AlgNode -> GraphM a AlgNodeSource

Select rows where the column SelAttrName contains True.

posSelect :: Int -> SortInf -> Maybe AttrName -> AlgNode -> GraphM a AlgNodeSource

Get's the nth element(s) of a (partitioned) table.

dbTable :: String -> Columns -> KeyInfos -> GraphM a AlgNodeSource

Construct a database table node The first argument is the emph{qualified} name of the database table. The second describes the columns in alphabetical order. The third argument describes the database keys (one table key can span over multiple columns).

notC :: AttrName -> AttrName -> AlgNode -> GraphM a AlgNodeSource

Negate the boolen value in column n and store it in column r

cross :: AlgNode -> AlgNode -> GraphM a AlgNodeSource

Make cross product from two plans

oper :: String -> ResAttrName -> LeftAttrName -> RightAttrName -> AlgNode -> GraphM a AlgNodeSource

Apply an operator to the element in LeftAttrName and RightAttrName, store the result in ResAttrName

emptyTable :: SchemaInfos -> GraphM a AlgNodeSource

Construct an empty table node with

tag :: String -> AlgNode -> GraphM a AlgNodeSource

Tag a subtree with a comment

litTable :: AVal -> String -> ATy -> GraphM a AlgNodeSource

Construct a table with one value

withBinding :: String -> a -> GraphM a r -> GraphM a rSource

Evaluate the graph construction computation with the current environment extended with a binding n to v.

withContext :: Gam a -> AlgNode -> GraphM a r -> GraphM a rSource

Evaluate the graph construction computation with a differnt gamma, | and loop table. Return within he current computational context.

getGamma :: GraphM a (Gam a)Source

Get the current variable environment

fromGam :: String -> GraphM a aSource

Lookup a variable in the environment

nat :: Integer -> AValSource

Create an algebraic nat value

int :: Integer -> AValSource

Create an algebraic int value

bool :: Bool -> AValSource

Create an algebraic boolean value

double :: Double -> AValSource

Create an algebraic double value

string :: String -> AValSource

Create an algebraic string value

stringT :: ATySource

Types of algebraic values

data SortDir Source

Sorting rows in a direction

Constructors

Asc 
Desc 

Instances

Eq SortDir 
Ord SortDir 
Show SortDir

The show instance results in values that are accepted in the xml plan.

data AggrType Source

Constructors

Avg 
Max 
Min 
Sum 
Count 
All 
Prod 
Dist 

data Column whereSource

The column data type is used to represent the table structure while compiling ferry core into an algebraic plan The col column contains the column number and the type of its contents The NCol column is used to group columns that together form an element of a record , its string argument is used to represent the field name.

Constructors

Col :: Int -> ATy -> Column 
NCol :: String -> Columns -> Column 

Instances

type Columns = [Column]Source

One table can have multiple columns

data ATy whereSource

Algebraic types At this level we do not have any structural types anymore those are represented by columns. ASur is used for surrogate values that occur for nested lists.

Constructors

AInt :: ATy 
AStr :: ATy 
ABool :: ATy 
ADec :: ATy 
ADouble :: ATy 
ANat :: ATy 
ASur :: ATy 

Instances

Eq ATy 
Ord ATy 
Show ATy

Show the algebraic types in a way that is compatible with the xml plan.

type SchemaInfos = [(AttrName, ATy)]Source

Schema information, represents a table structure, the first element of the tuple is the column name the second its type.

type KeyInfos = [KeyInfo]Source

Multiple keys

type GraphM a = ReaderT (Gam a, AlgNode) (State (Int, Map Algebra AlgNode, Tags))Source

Graphs are constructed in a monadic environment. | The graph constructed has to be a DAG. | The reader monad provides access to the variable environment Gamma and the loop table | The variable environment is a mapping from variable names to graphnodes that represent | their compiled form. | The state monad gives access to a supply of fresh variables, and maintains a map from | nodes to node ids. When a node is inserted and an equal node (equal means, equal node | and equal child nodes) already exists in the map the node id for that already existing | node is returned. This allows maximal sharing.

type Gam a = [(String, a)]Source

Variable environemtn mapping from variables to compiled nodes.

initLoop :: AlgebraSource

Shorthand for the initial loop condition used by Ferry.

runGraph :: Algebra -> GraphM res res -> AlgPlan resSource

Evaluate the monadic graph into an algebraic plan, given a loop relation.

type ProjPair = (NewAttrName, OldAttrName)Source

type ProjInf = [ProjPair]Source

Projection information, a list of new attribute names, and their old names.

attachM :: ResAttrName -> ATy -> AVal -> GraphM a AlgNode -> GraphM a AlgNodeSource

Attach a column ResAttrName of type ATy with value AVal in all rows to table AlgNode

castM :: AttrName -> ResAttrName -> ATy -> GraphM a AlgNode -> GraphM a AlgNodeSource

Cast column AttrName to type ATy and give it the name ResAttrName afterwards.

eqJoinM :: String -> String -> GraphM a AlgNode -> GraphM a AlgNode -> GraphM a AlgNodeSource

Join two plans where the columns n1 of table 1 and columns n2 of table 2 are equal.

eqTJoinM :: [(String, String)] -> ProjInf -> GraphM a AlgNode -> GraphM a AlgNode -> GraphM a AlgNodeSource

The same as eqJoin but with multiple columns.

rankM :: ResAttrName -> SortInf -> GraphM a AlgNode -> GraphM a AlgNodeSource

Assign a number to each row in column ResAttrName incrementing sorted by SortInf. The numbering is not dense!

differenceM :: GraphM a AlgNode -> GraphM a AlgNode -> GraphM a AlgNodeSource

Compute the difference between two plans.

rowrankM :: ResAttrName -> SortInf -> GraphM a AlgNode -> GraphM a AlgNodeSource

Same as rank but provides a dense numbering.

posSelectM :: Int -> SortInf -> Maybe AttrName -> GraphM a AlgNode -> GraphM a AlgNodeSource

Get's the nth element(s) of a (partitioned) table.

selectM :: SelAttrName -> GraphM a AlgNode -> GraphM a AlgNodeSource

Select rows where the column SelAttrName contains True.

distinctM :: GraphM a AlgNode -> GraphM a AlgNodeSource

Remove duplicate rows

crossM :: GraphM a AlgNode -> GraphM a AlgNode -> GraphM a AlgNodeSource

Make cross product from two plans

notM :: AttrName -> AttrName -> GraphM a AlgNode -> GraphM a AlgNodeSource

Negate the boolen value in column n and store it in column r

unionM :: GraphM a AlgNode -> GraphM a AlgNode -> GraphM a AlgNodeSource

Union between two plans

projM :: ProjInf -> GraphM a AlgNode -> GraphM a AlgNodeSource

Project/rename certain column out of a plan

aggrM :: [(AggrType, ResAttrName, Maybe AttrName)] -> Maybe PartAttrName -> GraphM a AlgNode -> GraphM a AlgNodeSource

Apply aggregate functions to a plan

rownumM :: AttrName -> [AttrName] -> Maybe AttrName -> GraphM a AlgNode -> GraphM a AlgNodeSource

Similar to rowrank but this will assign a emph{unique} number to every row (even if two rows are equal)

rownum'M :: AttrName -> [(AttrName, SortDir)] -> Maybe AttrName -> GraphM a AlgNode -> GraphM a AlgNodeSource

Same as rownum but columns can be assigned an ordering direction

operM :: String -> ResAttrName -> LeftAttrName -> RightAttrName -> GraphM a AlgNode -> GraphM a AlgNodeSource

Apply an operator to the element in LeftAttrName and RightAttrName, store the result in ResAttrName

tagM :: String -> GraphM a AlgNode -> GraphM a AlgNodeSource

Tag a subtree with a comment