language-toolkit-1.2.0.0: A set of tools for analyzing languages via logic and automata
Copyright(c) 2018-2024 Dakotah Lambert
LicenseMIT
Safe HaskellSafe-Inferred
LanguageHaskell2010
ExtensionsCpp

LTK.Porters.Pleb

Description

The (P)iecewise / (L)ocal (E)xpression (B)uilder. This module defines a parser for a representation of logical formulae over subsequence- and adjacency-factors, as well as a mechanism for evaluating (creating an FSA from) the resulting expression tree.

There are two special variables:

  • it describes the most recent expression, and
  • universe collects all symbols used.
Synopsis

Documentation

type Dictionary a = Map String a Source #

An association between names and values.

newtype Parse a Source #

The base type for a combinatorial parser.

Constructors

Parse 

Fields

Instances

Instances details
Alternative Parse Source # 
Instance details

Defined in LTK.Porters.Pleb

Methods

empty :: Parse a #

(<|>) :: Parse a -> Parse a -> Parse a #

some :: Parse a -> Parse [a] #

many :: Parse a -> Parse [a] #

Applicative Parse Source # 
Instance details

Defined in LTK.Porters.Pleb

Methods

pure :: a -> Parse a #

(<*>) :: Parse (a -> b) -> Parse a -> Parse b #

liftA2 :: (a -> b -> c) -> Parse a -> Parse b -> Parse c #

(*>) :: Parse a -> Parse b -> Parse b #

(<*) :: Parse a -> Parse b -> Parse a #

Functor Parse Source # 
Instance details

Defined in LTK.Porters.Pleb

Methods

fmap :: (a -> b) -> Parse a -> Parse b #

(<$) :: a -> Parse b -> Parse a #

Monad Parse Source # 
Instance details

Defined in LTK.Porters.Pleb

Methods

(>>=) :: Parse a -> (a -> Parse b) -> Parse b #

(>>) :: Parse a -> Parse b -> Parse b #

return :: a -> Parse a #

type Env = (Dictionary (Set String), Dictionary Expr) Source #

The environment: defined sets of symbols and defined expressions.

data Expr Source #

An expression, the root of an expression tree.

Instances

Instances details
Read Expr Source # 
Instance details

Defined in LTK.Porters.Pleb

Show Expr Source # 
Instance details

Defined in LTK.Porters.Pleb

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

Eq Expr Source # 
Instance details

Defined in LTK.Porters.Pleb

Methods

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

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

Ord Expr Source # 
Instance details

Defined in LTK.Porters.Pleb

Methods

compare :: Expr -> Expr -> Ordering #

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

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

(>) :: Expr -> Expr -> Bool #

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

max :: Expr -> Expr -> Expr #

min :: Expr -> Expr -> Expr #

data SymSet Source #

A set of symbols.

Instances

Instances details
Read SymSet Source # 
Instance details

Defined in LTK.Porters.Pleb

Show SymSet Source # 
Instance details

Defined in LTK.Porters.Pleb

Eq SymSet Source # 
Instance details

Defined in LTK.Porters.Pleb

Methods

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

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

Ord SymSet Source # 
Instance details

Defined in LTK.Porters.Pleb

data Token Source #

A syntactic unit.

Instances

Instances details
Read Token Source # 
Instance details

Defined in LTK.Porters.Pleb

Show Token Source # 
Instance details

Defined in LTK.Porters.Pleb

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Eq Token Source # 
Instance details

Defined in LTK.Porters.Pleb

Methods

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

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

Ord Token Source # 
Instance details

Defined in LTK.Porters.Pleb

Methods

compare :: Token -> Token -> Ordering #

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

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

(>) :: Token -> Token -> Bool #

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

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

compileEnv :: Env -> Env Source #

Transform all saved expressions into automata to prevent reevaluation.

groundEnv :: Env -> Env Source #

Convert saved automata from descriptions of constraints to descriptions of stringsets. This action effectively removes metadata describing constraint types from the environment.

insertExpr :: Env -> Expr -> Env Source #

Add a new expression to the environment, call it "(it)".

fromAutomaton :: FSA Integer String -> Expr Source #

Generate an expression (sub)tree from an FSA.

fromSemanticAutomaton :: FSA Integer (Maybe String) -> Expr Source #

Generate an expression (sub)tree from an FSA that contains metadata regarding the constraint(s) it represents.

makeAutomaton :: Env -> Expr -> Maybe (FSA Integer (Maybe String)) Source #

Create an FSA from an expression tree and environment, complete with metadata regarding the constraint(s) it represents.

makeAutomatonE :: Env -> Expr -> Either String (FSA Integer (Maybe String)) Source #

Create an FSA from an expression tree and environment, complete with metadata regarding the constraint(s) it represents.

doStatements :: Env -> String -> Env Source #

Parse an input string and update the environment according to the result of the parse.

doStatementsWithError :: Env -> String -> Either String Env Source #

Parse an input string and update the environment according to the result of the parse. Pass along errors encountered.

parseExpr :: Parse Expr Source #

Parse an expression from a Token stream.

readPleb :: String -> Either String (FSA Integer String) Source #

Parse an input string and create a stringset-automaton from the result.

restoreUniverse :: Env -> Env Source #

Reset the "universe" to contain all and only other symbols used.

Since: 1.2

restrictUniverse :: Env -> Env Source #

Remove any symbols not present in (universe) from the environment.

tokenize :: String -> [Token] Source #

Convert a string into a stream of tokens ready for parsing.