symantic-grammar-0.3.0.20180213: Library for symantic grammars.

Safe HaskellNone
LanguageHaskell2010

Language.Symantic.Grammar.Operators

Contents

Description

Symantics to handle Prefix, Postfix or Infix operators, of different Precedences and possibly with left and/or right Associativity.

Synopsis

Class Gram_Op

class (Gram_Char g, Gram_String g, Gram_Rule g, Gram_Alt g, Gram_Try g, Gram_App g, Gram_AltApp g, Gram_CF g) => Gram_Op g where Source #

Symantics for operators.

Methods

operators Source #

Arguments

:: CF g a

expression

-> CF g (Unifix, a -> a)

prefix operator

-> CF g (Infix, a -> a -> a)

infix operator

-> CF g (Unifix, a -> a)

postfix operator

-> CF g (Either Error_Fixity a) 

infixrG :: CF g a -> CF g (a -> a -> a) -> CF g a Source #

infixlG :: CF g a -> CF g (a -> a -> a) -> CF g a Source #

Instances

Gram_Op RuleEBNF Source # 

Methods

operators :: CF RuleEBNF a -> CF RuleEBNF (Unifix, a -> a) -> CF RuleEBNF (Infix, a -> a -> a) -> CF RuleEBNF (Unifix, a -> a) -> CF RuleEBNF (Either Error_Fixity a) Source #

infixrG :: CF RuleEBNF a -> CF RuleEBNF (a -> a -> a) -> CF RuleEBNF a Source #

infixlG :: CF RuleEBNF a -> CF RuleEBNF (a -> a -> a) -> CF RuleEBNF a Source #

Gram_Op EBNF Source # 

Methods

operators :: CF EBNF a -> CF EBNF (Unifix, a -> a) -> CF EBNF (Infix, a -> a -> a) -> CF EBNF (Unifix, a -> a) -> CF EBNF (Either Error_Fixity a) Source #

infixrG :: CF EBNF a -> CF EBNF (a -> a -> a) -> CF EBNF a Source #

infixlG :: CF EBNF a -> CF EBNF (a -> a -> a) -> CF EBNF a Source #

Gram_Op g => Gram_Op (CF g) Source # 

Methods

operators :: CF (CF g) a -> CF (CF g) (Unifix, a -> a) -> CF (CF g) (Infix, a -> a -> a) -> CF (CF g) (Unifix, a -> a) -> CF (CF g) (Either Error_Fixity a) Source #

infixrG :: CF (CF g) a -> CF (CF g) (a -> a -> a) -> CF (CF g) a Source #

infixlG :: CF (CF g) a -> CF (CF g) (a -> a -> a) -> CF (CF g) a Source #

Type Error_Fixity

Type OpTree

data OpTree a Source #

Tree of operators.

Useful to recombine operators according to their Precedence.

Constructors

OpTree0 a 
OpTree1 Unifix (a -> a) (OpTree a) 
OpTree2 Infix (a -> a -> a) (OpTree a) (OpTree a) 

Instances

Show a => Show (OpTree a) Source # 

Methods

showsPrec :: Int -> OpTree a -> ShowS #

show :: OpTree a -> String #

showList :: [OpTree a] -> ShowS #

insertUnifix :: (Unifix, a -> a) -> OpTree a -> OpTree a Source #

Insert an Unifix operator into an OpTree.

insertInfix :: OpTree a -> (Infix, a -> a -> a) -> Either Error_Fixity (OpTree a) -> Either Error_Fixity (OpTree a) Source #

Insert an Infix operator into an OpTree.

evalOpTree :: OpTree a -> a Source #

Collapse an OpTree.