hpython-0.1: Python language tools

Copyright(C) CSIRO 2017-2018
LicenseBSD3
MaintainerIsaac Elliott <isaace71295@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Language.Python.Syntax.Operator.Binary

Description

This module contains a datatype for binary operators and a precedence table with associated operations. This presentation of operators is simpler and more flexible than hard-coding them into the syntax tree.

Synopsis

Documentation

data BinOp a Source #

A Python binary operator, such as +, along with its trailing Whitespace

The type variable allows annotations, but it can simply be made () for an unannotated BinOp.

Constructors

Is a [Whitespace]
a is b
IsNot a [Whitespace] [Whitespace]
a is not b
In a [Whitespace]
a in b
NotIn a [Whitespace] [Whitespace]
a not in b
Minus a [Whitespace]
a - b
Exp a [Whitespace]
a ** b
BoolAnd a [Whitespace]
a and b
BoolOr a [Whitespace]
a or b
Eq a [Whitespace]
a == b
Lt a [Whitespace]
a < b
LtEq a [Whitespace]
a <= b
Gt a [Whitespace]
a > b
GtEq a [Whitespace]
a >= b
NotEq a [Whitespace]
a != b
Multiply a [Whitespace]
a * b
Divide a [Whitespace]
a / b
FloorDivide a [Whitespace]
a // b
Percent a [Whitespace]
a % b
Plus a [Whitespace]
a + b
BitOr a [Whitespace]
a | b
BitXor a [Whitespace]
a ^ b
BitAnd a [Whitespace]
a & b
ShiftLeft a [Whitespace]
a << b
ShiftRight a [Whitespace]
a >> b
At a [Whitespace]

a b@

Instances
Functor BinOp Source # 
Instance details

Defined in Language.Python.Syntax.Operator.Binary

Methods

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

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

Foldable BinOp Source # 
Instance details

Defined in Language.Python.Syntax.Operator.Binary

Methods

fold :: Monoid m => BinOp m -> m #

foldMap :: Monoid m => (a -> m) -> BinOp a -> m #

foldr :: (a -> b -> b) -> b -> BinOp a -> b #

foldr' :: (a -> b -> b) -> b -> BinOp a -> b #

foldl :: (b -> a -> b) -> b -> BinOp a -> b #

foldl' :: (b -> a -> b) -> b -> BinOp a -> b #

foldr1 :: (a -> a -> a) -> BinOp a -> a #

foldl1 :: (a -> a -> a) -> BinOp a -> a #

toList :: BinOp a -> [a] #

null :: BinOp a -> Bool #

length :: BinOp a -> Int #

elem :: Eq a => a -> BinOp a -> Bool #

maximum :: Ord a => BinOp a -> a #

minimum :: Ord a => BinOp a -> a #

sum :: Num a => BinOp a -> a #

product :: Num a => BinOp a -> a #

Traversable BinOp Source # 
Instance details

Defined in Language.Python.Syntax.Operator.Binary

Methods

traverse :: Applicative f => (a -> f b) -> BinOp a -> f (BinOp b) #

sequenceA :: Applicative f => BinOp (f a) -> f (BinOp a) #

mapM :: Monad m => (a -> m b) -> BinOp a -> m (BinOp b) #

sequence :: Monad m => BinOp (m a) -> m (BinOp a) #

Eq a => Eq (BinOp a) Source # 
Instance details

Defined in Language.Python.Syntax.Operator.Binary

Methods

(==) :: BinOp a -> BinOp a -> Bool #

(/=) :: BinOp a -> BinOp a -> Bool #

Show a => Show (BinOp a) Source # 
Instance details

Defined in Language.Python.Syntax.Operator.Binary

Methods

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

show :: BinOp a -> String #

showList :: [BinOp a] -> ShowS #

HasTrailingWhitespace (BinOp a) Source # 
Instance details

Defined in Language.Python.Syntax.Operator.Binary

HasNewlines (BinOp a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

data Assoc Source #

The associativity of an operator. Each operator is either left-associative or right associative.

Left associative:

x + y + z = (x + y) + z

Right associative:

x + y + z = x + (y + z)

Constructors

L 
R 
Instances
Eq Assoc Source # 
Instance details

Defined in Language.Python.Syntax.Operator.Binary

Methods

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

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

Show Assoc Source # 
Instance details

Defined in Language.Python.Syntax.Operator.Binary

Methods

showsPrec :: Int -> Assoc -> ShowS #

show :: Assoc -> String #

showList :: [Assoc] -> ShowS #

data OpEntry Source #

An operator along with its precedence and associativity.

Constructors

OpEntry 

Fields

operatorTable :: [OpEntry] Source #

operatorTable is a list of all operators in ascending order of precedence.

sameOperator :: BinOp a -> BinOp a' -> Bool Source #

Compare two BinOps to determine whether they represent the same operator, ignoring annotations and trailing whitespace.

isComparison :: BinOp a -> Bool Source #

Is a BinOp a comparison, such as <=

lookupOpEntry :: BinOp a -> [OpEntry] -> OpEntry Source #

Retrieve the information for a given operator from the operator table.