ecta-1.0.0.3
Safe HaskellNone
LanguageHaskell2010

Data.ECTA

Description

Equality-constrained deterministic finite tree automata

Specialized to DAGs, plus at most one globally unique recursive node

Synopsis

Documentation

data Edge where Source #

Bundled Patterns

pattern Edge :: Symbol -> [Node] -> Edge 

Instances

Instances details
Eq Edge Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Methods

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

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

Ord Edge Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Methods

compare :: Edge -> Edge -> Ordering #

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

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

(>) :: Edge -> Edge -> Bool #

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

max :: Edge -> Edge -> Edge #

min :: Edge -> Edge -> Edge #

Show Edge Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Methods

showsPrec :: Int -> Edge -> ShowS #

show :: Edge -> String #

showList :: [Edge] -> ShowS #

Hashable Edge Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Methods

hashWithSalt :: Int -> Edge -> Int #

hash :: Edge -> Int #

Interned Edge Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Associated Types

data Description Edge Source #

type Uninterned Edge Source #

Eq (Description Edge) Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Generic (Description Edge) Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Associated Types

type Rep (Description Edge) :: Type -> Type #

Hashable (Description Edge) Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

data Description Edge Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

type Uninterned Edge Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

type Rep (Description Edge) Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

type Rep (Description Edge) = D1 ('MetaData "Description" "Data.ECTA.Internal.ECTA.Type" "ecta-1.0.0.3-GsgcdoZGkFZA4oJqDsbHRS" 'False) (C1 ('MetaCons "DEdge" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 UninternedEdge)))

data Node Source #

Constructors

EmptyNode 

Bundled Patterns

pattern Node :: [Edge] -> Node 

Instances

Instances details
Eq Node Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Methods

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

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

Ord Node Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Methods

compare :: Node -> Node -> Ordering #

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

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

(>) :: Node -> Node -> Bool #

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

max :: Node -> Node -> Node #

min :: Node -> Node -> Node #

Show Node Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

Hashable Node Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Methods

hashWithSalt :: Int -> Node -> Int #

hash :: Node -> Int #

Interned Node Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Associated Types

data Description Node Source #

type Uninterned Node Source #

Pathable Node Node Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Operations

Associated Types

type Emptyable Node Source #

Eq (Description Node) Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Generic (Description Node) Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Associated Types

type Rep (Description Node) :: Type -> Type #

Hashable (Description Node) Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

Pathable [Node] Node Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Operations

Associated Types

type Emptyable Node Source #

Methods

getPath :: Path -> [Node] -> Emptyable Node Source #

getAllAtPath :: Path -> [Node] -> [Node] Source #

modifyAtPath :: (Node -> Node) -> Path -> [Node] -> [Node] Source #

data Description Node Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

type Uninterned Node Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

type Emptyable Node Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Operations

type Emptyable Node Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Operations

type Rep (Description Node) Source # 
Instance details

Defined in Data.ECTA.Internal.ECTA.Type

type Rep (Description Node) = D1 ('MetaData "Description" "Data.ECTA.Internal.ECTA.Type" "ecta-1.0.0.3-GsgcdoZGkFZA4oJqDsbHRS" 'False) (C1 ('MetaCons "DNode" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UninternedNode)))

numNestedMu :: Node -> Int Source #

Maximum number of nested Mus in the term

@O(1) provided that there are no unbounded Mu chains in the term.

createMu :: (Node -> Node) -> Node Source #

Construct recursive node

Implementation note: createMu and matchMu interact in non-trivial ways; see docs of the Mu pattern synonym for performance considerations.

Operations

pathsMatching :: (Node -> Bool) -> Node -> [Path] Source #

Warning: Linear in number of paths, exponential in size of graph. Only use for very small graphs.

mapNodes :: (Node -> Node) -> Node -> Node Source #

Precondition: For all i, f (Rec i) is either a Rec node meant to represent the enclosing Mu, or contains no Rec node not beneath another Mu.

crush :: forall m. Monoid m => (Node -> m) -> Node -> m Source #

onNormalNodes :: Monoid m => (Node -> m) -> Node -> m Source #

Enumeration

naiveDenotation :: Node -> [Term] Source #

Inefficient enumeration

For ECTAs with Mu nodes may produce an infinite list or may loop indefinitely, depending on the ECTAs. For example, for

createMu $ \r -> Node [Edge "f" [r], Edge "a" []]

it will produce

[ Term "a" []
, Term "f" [Term "a" []]
, Term "f" [Term "f" [Term "a" []]]
, ...
]

This happens to work currently because non-recursive edges are interned before recursive edges.

TODO: It would be much nicer if this did fair enumeration. It would avoid the beforementioned dependency on interning order, and it would give better enumeration for examples such as

Node [Edge "h" [
    createMu $ \r -> Node [Edge "f" [r], Edge "a" []]
  , createMu $ \r -> Node [Edge "g" [r], Edge "b" []]
  ]]

This will currently produce

[ Term "h" [Term "a" [], Term "b" []]
, Term "h" [Term "a" [], Term "g" [Term "b" []]]
, Term "h" [Term "a" [], Term "g" [Term "g" [Term "b" []]]]
, ..
]

where it always unfolds the second argument to h, never the first.

Visualization / debugging

toDot :: Node -> Graph Source #

To visualize an FTA: 1) Call `prettyPrintDot $ toDot fta` from GHCI 2) Copy the output to viz-js.jom or another GraphViz implementation