Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- data Fixity
- data Unifix
- data Infix = Infix {}
- infixL :: Precedence -> Infix
- infixR :: Precedence -> Infix
- infixB :: Side -> Precedence -> Infix
- infixN :: Precedence -> Infix
- infixN0 :: Infix
- infixN5 :: Infix
- needsParenInfix :: (Infix, Side) -> Infix -> Bool
- type Precedence = Int
- class PrecedenceOf a where
- precedence :: a -> Precedence
- data Associativity
- data Side
Type Fixity
Instances
Eq Fixity Source # | |
Show Fixity Source # | |
PrecedenceOf Fixity Source # | |
Defined in Symantic.CLI.Fixity precedence :: Fixity -> Precedence Source # |
Type Unifix
Instances
Eq Unifix Source # | |
Show Unifix Source # | |
PrecedenceOf Unifix Source # | |
Defined in Symantic.CLI.Fixity precedence :: Unifix -> Precedence Source # |
Type Infix
Instances
Eq Infix Source # | |
Show Infix Source # | |
PrecedenceOf Infix Source # | |
Defined in Symantic.CLI.Fixity precedence :: Infix -> Precedence Source # |
infixL :: Precedence -> Infix Source #
infixR :: Precedence -> Infix Source #
infixN :: Precedence -> Infix Source #
needsParenInfix :: (Infix, Side) -> Infix -> Bool Source #
Given Precedence
and Associativity
of its parent operator,
and the operand Side
it is in,
return whether an Infix
operator
needs to be enclosed by parenthesis.
Type Precedence
type Precedence = Int Source #
Class PrecedenceOf
class PrecedenceOf a where Source #
precedence :: a -> Precedence Source #
Instances
PrecedenceOf Infix Source # | |
Defined in Symantic.CLI.Fixity precedence :: Infix -> Precedence Source # | |
PrecedenceOf Unifix Source # | |
Defined in Symantic.CLI.Fixity precedence :: Unifix -> Precedence Source # | |
PrecedenceOf Fixity Source # | |
Defined in Symantic.CLI.Fixity precedence :: Fixity -> Precedence Source # |
Type Associativity
data Associativity Source #
AssocL | Associate to the left: |
AssocR | Associate to the right: |
AssocB Side | Associate to both sides, but to |
Instances
Eq Associativity Source # | |
Defined in Symantic.CLI.Fixity (==) :: Associativity -> Associativity -> Bool # (/=) :: Associativity -> Associativity -> Bool # | |
Show Associativity Source # | |
Defined in Symantic.CLI.Fixity showsPrec :: Int -> Associativity -> ShowS # show :: Associativity -> String # showList :: [Associativity] -> ShowS # |