compdata-automata-0.9: Tree automata on Compositional Data Types

Copyright(c) 2013 Patrick Bahr
LicenseBSD3
MaintainerPatrick Bahr <paba@diku.dk>
Stabilityexperimental
Portabilitynon-portable (GHC Extensions)
Safe HaskellNone
LanguageHaskell98

Data.Comp.MacroAutomata

Contents

Description

This module defines macro tree transducers (MTTs). It provides functions to run MTTs and to compose them with top down tree transducers. It also defines MTTs with regular look-ahead which combines MTTs with bottom-up tree acceptors.

Synopsis

Macro Tree Transducers

type MacroTrans f q g = forall a. q a -> f (q (Context g a) -> a) -> Context g a Source

This type represents total deterministic macro tree transducers (MTTs).

type MacroTrans' f q g = forall a. q (Context g a) -> f (q (Context g a) -> Context g a) -> Context g a Source

This is a variant of the type MacroTrans that makes it easier to define MTTs as it avoids the explicit use of Hole when using placeholders in the result.

mkMacroTrans :: (Functor f, Functor q) => MacroTrans' f q g -> MacroTrans f q g Source

This function turns an MTT defined using the more convenient type MacroTrans' into its canonical form of type MacroTrans.

runMacroTrans :: (Functor g, Functor f, Functor q) => MacroTrans f q g -> q (Cxt h g a) -> Cxt h f a -> Cxt h g a Source

This function defines the semantics of MTTs. It applies a given MTT to an input with and an initial state.

compMacroDown :: (Functor f, Functor g, Functor h, Functor p) => MacroTrans g p h -> DownTrans f q g -> MacroTrans f (p :&: q) h Source

This function composes a DTT followed by an MTT. The resulting MTT's semantics is equivalent to the function composition of the semantics of the original MTT and DTT.

compDownMacro :: forall f g h q p. (Functor f, Functor g, Functor h, Functor q) => DownTrans g p h -> MacroTrans f q g -> MacroTrans f (q :^: p) h Source

This function composes an MTT followed by a DTT. The resulting MTT's semantics is equivalent to first running the original MTT and then the DTT.

Macro Tree Transducers with Singleton State Space

type MacroTransId f g = forall a. a -> f (Context g a -> a) -> Context g a Source

This type is an instantiation of the MacroTrans type to a state space with only a single state with a single accumulation parameter (i.e. the state space is the identity functor).

type MacroTransId' f g = forall a. Context g a -> f (Context g a -> Context g a) -> Context g a Source

This type is a variant of the MacroTransId which is more convenient to work with as it avoids the explicit use of Hole to embed placeholders into the result.

fromMacroTransId :: Functor f => MacroTransId f g -> MacroTrans f I g Source

This function transforms an MTT of type |MacroTransId| into the canonical type such that it can be run.

fromMacroTransId' :: Functor f => MacroTransId' f g -> MacroTrans f I g Source

This function transforms an MTT of type |MacroTransId'| into the canonical type such that it can be run.

Macro Tree Transducers with Regular Look-Ahead

type MacroTransLA f q p g = forall a. q a -> p -> f (q (Context g a) -> a, p) -> Context g a Source

This type represents MTTs with regular look-ahead, i.e. MTTs that have access to information that is generated by a separate UTA.

type MacroTransLA' f q p g = forall a. q (Context g a) -> p -> f (q (Context g a) -> Context g a, p) -> Context g a Source

This type is a more convenient variant of MacroTransLA with which one can avoid using Hole explicitly when injecting placeholders in the result.

mkMacroTransLA :: (Functor q, Functor f) => MacroTransLA' f q p g -> MacroTransLA f q p g Source

This function turns an MTT with regular look-ahead defined using the more convenient type |MacroTransLA'| into its canonical form of type |MacroTransLA|.

runMacroTransLA :: forall g f q p. (Functor g, Functor f, Functor q) => UpState f p -> MacroTransLA f q p g -> q (Term g) -> Term f -> Term g Source

This function defines the semantics of MTTs with regular look-ahead. It applies a given MTT with regular look-ahead (including an accompanying bottom-up state transition function) to an input with and an initial state.

compDownMacroLA :: forall f g h q1 q2 p. (Functor f, Functor g, Functor h, Functor q1) => DownTrans g q2 h -> MacroTransLA f q1 p g -> MacroTransLA f (q1 :^: q2) p h Source

This function composes an MTT with regular look-ahead followed by a DTT.

Macro Tree Transducers with Regular Look-Ahead

data (q :^: p) a Source

This type constructor is used to define the state space of an MTT that is obtained by composing an MTT followed by a DTT.

Constructors

(q (p -> a)) :^: p 

Instances

Functor q => Functor ((:^:) q p) 

newtype I a :: * -> *

Constructors

I 

Fields

unI :: a
 

Instances

Annotations

propAnnMacro :: (Functor f, Functor q, DistAnn f p f', DistAnn g p g', Functor g) => MacroTrans f q g -> MacroTrans f' q g' Source

Lift a macro tree transducer over signatures f and g to a macro tree transducer over the same signatures, but extended with annotations.

propAnnMacroLA :: (Functor f, Functor q, DistAnn f p f', DistAnn g p g', Functor g) => MacroTransLA f q p g -> MacroTransLA f' q p g' Source

Lift a macro tree transducer with regular look-ahead over signatures f and g to a macro tree transducer with regular look-ahead over the same signatures, but extended with annotations.