fst-0.10.0.1: Finite state transducers

Safe HaskellSafe-Inferred
LanguageHaskell98

FST.TransducerInterface

Contents

Description

Main API for finite-state transducer library. Importing this module gives you access to the folllowing functions.

Regular expressions

Functions for constructing a simplified regular expression.

s          :: a -> Reg a              -- symbol
eps        :: Reg a                   -- epsilon
empty      :: Reg a                   -- empty set
allS       :: Reg a                   -- all symbol
star       :: Reg a -> Reg a          -- kleene’s star
plus       :: Reg a -> Reg a          -- kleene’s plus
complement :: Reg a -> Reg a          -- complement
(<|>)      :: Reg a -> Reg a -> Reg a -- union
(|>)       :: Reg a -> Reg a -> Reg a -- product
(<&>)      :: Reg a -> Reg a -> Reg a -- intersection
(<->)      :: Reg a -> Reg a -> Reg a -- set minus
symbols    :: Reg a -> a              -- collect all symbols.

Regular relations

Functions for constructing a simplified regular relation.

r       :: a -> a -> Reg a            -- relation
empty   :: RReg a                     -- empty set
idR     :: Reg a -> RReg a            -- identity
star    :: RReg a -> RReg a           -- kleene’s star
plus    :: RReg a -> RReg a           -- kleene’s plus
(<|>)   :: RReg a -> RReg a -> RReg a -- union
(|>)    :: RReg a -> RReg a -> RReg a -- product
(<*>)   :: Reg a -> Reg a -> RReg a   -- cross product
(<.>)   :: RReg a -> RReg a -> RReg a -- composition
symbols :: RReg a -> a                -- collect all symbols

Parsing regular relations

Functions for parsing regular relations.

parseProgram takes a string containing a fstStudio program, and try to parse it - if unsuccessful, it returns a error message. parseExp parses a string containing a regular relation.

parseProgram :: String -> Either String (RReg String)
parseExp     :: String -> Either String (RReg String)

Construction and running

Functions for constructing and running a nite state transducer. The function compile construct a deterministic, epsilonfree, minimal transducer, and compileN construct a epsilonfree, possibly non-deterministic, non-minimal transducer. The Sigma type provides a way to add symbols that is not present in the regular relation. applyDown and applyUp are used to run the transducer.

type Sigma a = [a]

compile         :: Ord a => RReg a -> Sigma a -> Transducer a
compileN        :: Ord a => RReg a -> Sigma a -> Transducer a
determinize     :: Ord a => Transducer a -> Transducer a
minimize        :: Ord a => Transducer a -> Transducer a
unionT          :: Ord a => Transducer a -> Transducer a -> Transducer a
productT        :: Ord a => Transducer a -> Transducer a -> Transducer a
starT           :: Ord a => Transducer a -> Transducer a
compositionT    :: Ord a => Transducer a -> Transducer a -> Transducer a
emptyTransducer :: Transducer a
applyDown       :: Ord a => Transducer a -> [a] -> Maybe [[a]]
applyUp         :: Ord a => Transducer a -> [a] -> Maybe [[a]]
load            :: FilePath -> IO (Either String (Transducer String))
save            :: FilePath -> Transducer String -> IO (Either String ())

Transducer Information

Functions for getting information about a built transducer.

type StateTy = Int

states              :: Transducer a -> [StateTy]
isFinal             :: Transducer a -> StateTy -> Bool
initial             :: Transducer a -> StateTy
finals              :: Transducer a -> [StateTy]
transitonsU         :: Transducer a -> (StateTy,a) -> [(a,StateTy)]
transitionsD        :: Transducer a -> (StateTy,a) -> [(a,StateTy)]
showTransducer      :: Transducer a -> String
numberOfStates      :: Transducer a -> Int
numberOfTransitions :: Transducer a -> Int

Synopsis

Functions on regular expressions and relations

Types

data Transducer a Source

Data type for a transducer

Transducer-building functions

compile :: Ord a => RReg a -> Sigma a -> Transducer a Source

Construct a deterministic, epsilon-free, minimal transducer

compileN :: Ord a => RReg a -> Sigma a -> Transducer a Source

Construct an epsilon-free, possibly non-deterministic, non-minimal transducer

minimize :: Ord a => Transducer a -> Transducer a Source

Make a transducer minimal

determinize :: Ord a => Transducer a -> Transducer a Source

Make a transducer deterministic

emptyTransducer :: Ord a => Transducer a Source

The empty transucer

Query functions on transducer

numberOfStates :: Ord a => Transducer a -> Int Source

Return the number of states in a transducer

numberOfTransitions :: Ord a => Transducer a -> Int Source

Return the number of transitions in a transducer

transitions :: Eq a => Transducer a -> (StateTy, Relation a) -> [StateTy] Source

Get transition as a list of states

showTransducer :: Show a => Transducer a -> String Source

Show a transducer

Transducer combinators

unionT :: Eq a => Transducer a -> Transducer a -> Transducer a Source

Union of two transducers

productT :: Eq a => Transducer a -> Transducer a -> Transducer a Source

Product of two transducers

starT :: Eq a => Transducer a -> Transducer a Source

Kleene star of two transducers

compositionT :: Eq a => Transducer a -> Transducer a -> Transducer a Source

Compose two transducers

File IO functions

load :: FilePath -> ErrorT String IO (Transducer String) Source

Load a transducer from file

save :: FilePath -> Transducer String -> ErrorT String IO () Source

Save a transducer from file

open :: FilePath -> ErrorT String IO String Source

Open a file and return contents as string

saveToFile :: FilePath -> String -> ErrorT String IO () Source

Save contents (as string) to a file

Parse functions

parseProgram :: String -> Either String (RReg String) Source

Parse a program from a string

parseExp :: String -> Either String (RReg String) Source

Parse a regular expression from a string

Run functions

applyUp :: Eq a => Transducer a -> [a] -> Maybe [[a]] Source

Apply a transducer upwards

applyDown :: Eq a => Transducer a -> [a] -> Maybe [[a]] Source

Apply a transducer downwards