sifflet-lib-1.0: Library of modules shared by sifflet and its tests and its exporters.Source codeContentsIndex
Sifflet.Foreign.Python
Description
Abstract syntax tree and pretty-printing for Python. Works for Python 2 and 3. A lot of the data structures are inspired by the language-python package; I have chosen not to have language-python as a dependency of sifflet-lib, however, because it would be overkill and still allows to little control over pretty-printing of Python expressionsw.
Synopsis
data PModule = PModule [PStatement]
data PStatement
= PReturn PExpr
| PImport String
| PCondS PExpr PStatement PStatement
| PFun PIdentifier [PParameter] PStatement
data PExpr
= PCondE PExpr PExpr PExpr
| PParen PExpr
| PCall PExpr [PExpr]
| POperate POperator PExpr PExpr
| PVariable PIdentifier
| PInt Integer
| PFloat Double
| PBool Bool
| PString String
data PIdentifier = PIdentifier String
data PParameter = PParameter PIdentifier
data POperator = POperator {
opName :: String
opPrec :: Precedence
opAssoc :: Bool
}
type Precedence = Int
alterParens :: (PExpr -> PExpr) -> PStatement -> PStatement
atomic :: PExpr -> Bool
compound :: PExpr -> Bool
ret :: PExpr -> PStatement
condS :: PExpr -> PExpr -> PExpr -> PStatement
condE :: PExpr -> PExpr -> PExpr -> PExpr
var :: String -> PExpr
ident :: String -> PIdentifier
pInt :: Integer -> PExpr
pFloat :: Double -> PExpr
bool :: Bool -> PExpr
char :: Char -> PExpr
string :: String -> PExpr
paren :: PExpr -> PExpr
noParens :: PExpr -> PExpr
fullParens :: PExpr -> PExpr
bestParens :: PExpr -> PExpr
simplifyParens :: PExpr -> PExpr
par :: PExpr -> PExpr
unpar :: PExpr -> PExpr
call :: String -> [PExpr] -> PExpr
param :: String -> PParameter
fun :: String -> [String] -> PExpr -> PStatement
opTimes :: POperator
opIDiv :: POperator
opFDiv :: POperator
opMod :: POperator
opPlus :: POperator
opMinus :: POperator
opEq :: POperator
opNe :: POperator
opGt :: POperator
opGe :: POperator
opLt :: POperator
opLe :: POperator
Documentation
data PModule Source
Python module -- essentially a list of statements; should it also have a name?
Constructors
PModule [PStatement]
show/hide Instances
data PStatement Source
Python statement
Constructors
PReturn PExpr
PImport Stringimport statement
PCondS PExpr PStatement PStatementif condition action alt-action
PFun PIdentifier [PParameter] PStatementfunction name, formal parameters, body
show/hide Instances
data PExpr Source
Python expression
Constructors
PCondE PExpr PExpr PExprif: condition, value, alt-value
PParen PExprexpression in parentheses; is this needed?
PCall PExpr [PExpr]function call: function expression (typically a PVariable), argument expressions
POperate POperator PExpr PExprbinary operation: operator, left, right base cases
PVariable PIdentifiervariable identifier
PInt Integer
PFloat Double
PBool Bool
PString String
show/hide Instances
data PIdentifier Source
Python identifier (variable name, etc.)
Constructors
PIdentifier String
show/hide Instances
data PParameter Source
Python function formal parameter
Constructors
PParameter PIdentifier
show/hide Instances
data POperator Source
Python operator, such as * or +
Constructors
POperator
opName :: String
opPrec :: Precedence
opAssoc :: Boolassociative?
show/hide Instances
type Precedence = IntSource
Operator priority, actually should be > 0 or >= 0
alterParens :: (PExpr -> PExpr) -> PStatement -> PStatementSource
Alter the parentheses of a statement by applying a transformer t to the expressions in the statement.
atomic :: PExpr -> BoolSource
compound :: PExpr -> BoolSource
ret :: PExpr -> PStatementSource
Python return statement
condS :: PExpr -> PExpr -> PExpr -> PStatementSource
Python if STATEMENT
condE :: PExpr -> PExpr -> PExpr -> PExprSource
Python if EXPRESSION
var :: String -> PExprSource
Python variable
ident :: String -> PIdentifierSource
Python identifier
pInt :: Integer -> PExprSource
Python integer expression
pFloat :: Double -> PExprSource
Python float expression
bool :: Bool -> PExprSource
Python boolean expression
char :: Char -> PExprSource
Python character expression = string expression with one character
string :: String -> PExprSource
Python string expression
paren :: PExpr -> PExprSource
Python expression in parentheses.
noParens :: PExpr -> PExprSource
Remove all grouping parentheses in expression. Does not affect parentheses required for function arguments or parameters. This will sometimes alter the semantics.
fullParens :: PExpr -> PExprSource
Wrap each subexpression in grouping parentheses. This will typically look like too many parentheses.
bestParens :: PExpr -> PExprSource
Use parentheses for grouping where needed, but cautiously, erring on the side of extra parentheses if not sure they can be removed.
simplifyParens :: PExpr -> PExprSource
Remove grouping parentheses that are provably not needed. This may not remove *all* unnecessary grouping parentheses. You can always add more cases to make it better!
par :: PExpr -> PExprSource

Adding and removing top-level parentheses. Axioms: par (unpar e) == e; unpar (par e) == e.

Add parentheses around an expression. Top level only.

unpar :: PExpr -> PExprSource
Remove parentheses around an expression. Top level only.
call :: String -> [PExpr] -> PExprSource
Python function call expression
param :: String -> PParameterSource
Python function formal parameter
fun :: String -> [String] -> PExpr -> PStatementSource
Defines function definition
opTimes :: POperatorSource
opIDiv :: POperatorSource

Binary operators Precedence levels are rather *informally* described in The Python Language Reference, http:docs.python.orgreference. I am adopting the infixr levels from Haskell, which seem to be consistent with Python, at least for the operators that Sifflet uses.

Arithmetic operators + and - have lower precedence than *, , /, %

opFDiv :: POperatorSource
opMod :: POperatorSource
opPlus :: POperatorSource
opMinus :: POperatorSource
opEq :: POperatorSource
opNe :: POperatorSource
Comparison operators have precedence lower than any arithmetic operator. Here, I've specified associative = False, because association doesn't even make sense; (a == b) == c is in general not well typed.
opGt :: POperatorSource
opGe :: POperatorSource
opLt :: POperatorSource
opLe :: POperatorSource
Produced by Haddock version 2.6.1