dawg-0.8.2: Directed acyclic word graphs

Safe HaskellNone
LanguageHaskell2010

Data.DAWG.Node

Description

Internal representation of automata nodes.

Synopsis

Documentation

data Node t a b Source #

Two nodes (states) belong to the same equivalence class (and, consequently, they must be represented as one node in the graph) iff they are equal with respect to their values and outgoing edges.

Since Leaf nodes are distinguished from Branch nodes, two values equal with respect to == function are always kept in one Leaf node in the graph. It doesn't change the fact that to all Branch nodes one value is assigned through the epsilon transition.

Invariant: the eps identifier always points to the Leaf node. Edges in the edgeMap, on the other hand, point to Branch nodes.

Constructors

Branch 

Fields

Leaf 

Fields

Instances
(Eq a, Eq b, Unbox a) => Eq (Node Trans a b) Source # 
Instance details

Defined in Data.DAWG.Node

Methods

(==) :: Node Trans a b -> Node Trans a b -> Bool #

(/=) :: Node Trans a b -> Node Trans a b -> Bool #

(Eq a, Eq b, Unbox a) => Eq (Node Trans a b) Source # 
Instance details

Defined in Data.DAWG.Node

Methods

(==) :: Node Trans a b -> Node Trans a b -> Bool #

(/=) :: Node Trans a b -> Node Trans a b -> Bool #

(Ord a, Ord b, Unbox a) => Ord (Node Trans a b) Source # 
Instance details

Defined in Data.DAWG.Node

Methods

compare :: Node Trans a b -> Node Trans a b -> Ordering #

(<) :: Node Trans a b -> Node Trans a b -> Bool #

(<=) :: Node Trans a b -> Node Trans a b -> Bool #

(>) :: Node Trans a b -> Node Trans a b -> Bool #

(>=) :: Node Trans a b -> Node Trans a b -> Bool #

max :: Node Trans a b -> Node Trans a b -> Node Trans a b #

min :: Node Trans a b -> Node Trans a b -> Node Trans a b #

(Ord a, Ord b, Unbox a) => Ord (Node Trans a b) Source # 
Instance details

Defined in Data.DAWG.Node

Methods

compare :: Node Trans a b -> Node Trans a b -> Ordering #

(<) :: Node Trans a b -> Node Trans a b -> Bool #

(<=) :: Node Trans a b -> Node Trans a b -> Bool #

(>) :: Node Trans a b -> Node Trans a b -> Bool #

(>=) :: Node Trans a b -> Node Trans a b -> Bool #

max :: Node Trans a b -> Node Trans a b -> Node Trans a b #

min :: Node Trans a b -> Node Trans a b -> Node Trans a b #

(Unbox a, Show t, Show a, Show b) => Show (Node t a b) Source # 
Instance details

Defined in Data.DAWG.Node

Methods

showsPrec :: Int -> Node t a b -> ShowS #

show :: Node t a b -> String #

showList :: [Node t a b] -> ShowS #

(Unbox a, Binary t, Binary a, Binary b) => Binary (Node t a b) Source # 
Instance details

Defined in Data.DAWG.Node

Methods

put :: Node t a b -> Put #

get :: Get (Node t a b) #

putList :: [Node t a b] -> Put #

(Trans t, Ord (Node t a b)) => Hash (Node t a b) Source # 
Instance details

Defined in Data.DAWG.Node

Methods

hash :: Node t a b -> Int Source #

onSym :: Trans t => Sym -> Node t a b -> Maybe ID Source #

Transition function.

onSym' :: (Trans t, Unbox a) => Sym -> Node t a b -> Maybe (ID, a) Source #

Transition function.

edges :: Trans t => Node t a b -> [(Sym, ID)] Source #

List of symbol/edge pairs outgoing from the node.

children :: Trans t => Node t a b -> [ID] Source #

List of children identifiers.

insert :: Trans t => Sym -> ID -> Node t a b -> Node t a b Source #

Substitue edge determined by a given symbol.

reID :: Trans t => (ID -> ID) -> Node t a b -> Node t a b Source #

Assign new identifiers.