aasam-0.2.0.0: Convert distfix precedence grammars to unambiguous context-free grammars.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Aasam

Synopsis

Documentation

m :: Precedence -> Either AasamError ContextFree Source #

Takes a distfix precedence grammar. If there is an error, produces an AasamError, else produces a corresponding unambiguous context-free grammar.

All possible errors are enumerated in the documentation for Precedence.

type Precedence = Set PrecedenceProduction Source #

The type of a distfix precedence grammar. The following must be true of any parameter to m.

  • All precedences must be positive integers.
  • No initial word may also be a subsequent word of another production.
  • No initial sequence of words may also be the whole sequence of another production.
  • No precedence of a production of one fixity may also be the precedence of a production of another fixity.
  • The set of precedences must be either empty or the set of integers between 1 and greatest precedence, inclusive.

data PrecedenceProduction Source #

The type of a distfix precedence production.

Int parameters are precedences.

NonEmpty Text parameters are lists of terminal symbols expressed as strings. A particular data constructor implies a corresponding interspersal pattern of non-terminals in the terminal list when the production is interpreted. For example,

Infixl 1 (fromList ["?", ":"])

corresponds to the left-associative production, E -> E ? E : E.

Constructors

Prefix Int (NonEmpty Text) 
Postfix Int (NonEmpty Text) 
Infixl Int (NonEmpty Text) 
Infixr Int (NonEmpty Text) 
Closed (NonEmpty Text) 

Instances

Instances details
Data PrecedenceProduction Source # 
Instance details

Defined in Grammars

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrecedenceProduction -> c PrecedenceProduction

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrecedenceProduction

toConstr :: PrecedenceProduction -> Constr

dataTypeOf :: PrecedenceProduction -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrecedenceProduction)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrecedenceProduction)

gmapT :: (forall b. Data b => b -> b) -> PrecedenceProduction -> PrecedenceProduction

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrecedenceProduction -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrecedenceProduction -> r

gmapQ :: (forall d. Data d => d -> u) -> PrecedenceProduction -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrecedenceProduction -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrecedenceProduction -> m PrecedenceProduction

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrecedenceProduction -> m PrecedenceProduction

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrecedenceProduction -> m PrecedenceProduction

Show PrecedenceProduction Source # 
Instance details

Defined in Grammars

Methods

showsPrec :: Int -> PrecedenceProduction -> ShowS

show :: PrecedenceProduction -> String

showList :: [PrecedenceProduction] -> ShowS

Eq PrecedenceProduction Source # 
Instance details

Defined in Grammars

Ord PrecedenceProduction Source # 
Instance details

Defined in Grammars

type ContextFree = (NonTerminal, Set CfgProduction) Source #

The type of a context-free grammar. On the left the starting non-terminal, and on the right is the set of productions in the grammar.

type CfgProduction = (NonTerminal, CfgString) Source #

The type of a context-free production. The left and right items correspond respectively to the left and right hand sides of a production rule.

newtype Terminal Source #

Constructors

Terminal Text 

Instances

Instances details
Show Terminal Source # 
Instance details

Defined in Grammars

Methods

showsPrec :: Int -> Terminal -> ShowS

show :: Terminal -> String

showList :: [Terminal] -> ShowS

Eq Terminal Source # 
Instance details

Defined in Grammars

Methods

(==) :: Terminal -> Terminal -> Bool

(/=) :: Terminal -> Terminal -> Bool

Ord Terminal Source # 
Instance details

Defined in Grammars

Methods

compare :: Terminal -> Terminal -> Ordering

(<) :: Terminal -> Terminal -> Bool

(<=) :: Terminal -> Terminal -> Bool

(>) :: Terminal -> Terminal -> Bool

(>=) :: Terminal -> Terminal -> Bool

max :: Terminal -> Terminal -> Terminal

min :: Terminal -> Terminal -> Terminal

newtype NonTerminal Source #

Constructors

NonTerminal Text 

Instances

Instances details
Show NonTerminal Source # 
Instance details

Defined in Grammars

Methods

showsPrec :: Int -> NonTerminal -> ShowS

show :: NonTerminal -> String

showList :: [NonTerminal] -> ShowS

Eq NonTerminal Source # 
Instance details

Defined in Grammars

Methods

(==) :: NonTerminal -> NonTerminal -> Bool

(/=) :: NonTerminal -> NonTerminal -> Bool

Ord NonTerminal Source # 
Instance details

Defined in Grammars

newtype AasamError Source #

The type of errors. Contains a list of strings, each of which describes an error of the input grammar.

Constructors

AasamError [Text] 

Instances

Instances details
Show AasamError Source # 
Instance details

Defined in Aasam

Methods

showsPrec :: Int -> AasamError -> ShowS

show :: AasamError -> String

showList :: [AasamError] -> ShowS

Eq AasamError Source # 
Instance details

Defined in Aasam

Methods

(==) :: AasamError -> AasamError -> Bool

(/=) :: AasamError -> AasamError -> Bool

Ord AasamError Source # 
Instance details

Defined in Aasam