module Language.Sifflet.Export.Python
(PyPretty(..)
, PModule(..)
, PStatement(..)
, alterParens
, ret
, condS
, var
, ident
, char
, fun
, operatorTable
)
where
import Data.List (intercalate)
import qualified Data.Map as M
import Language.Sifflet.Expr
import Text.Sifflet.Pretty
class PyPretty a where
pyPretty :: a -> String
pyPrettyList :: String -> String -> String -> [a] -> String
pyPrettyList pre tween post xs =
pre ++ intercalate tween (map pyPretty xs) ++ post
pyPrettyParens :: (PyPretty a) => [a] -> String
pyPrettyParens = pyPrettyList "(" ", " ")"
instance PyPretty Symbol where
pyPretty = pretty
instance PyPretty Operator where
pyPretty = pretty
newtype PModule = PModule [PStatement]
deriving (Eq, Show)
instance PyPretty PModule where
pyPretty (PModule ss) = sepLines2 (map pyPretty ss)
data PStatement = PReturn Expr
| PImport String
| PCondS Expr
PStatement
PStatement
| PFun Symbol
[Symbol]
PStatement
deriving (Eq, Show)
instance PyPretty PStatement where
pyPretty s =
case s of
PReturn e -> "return " ++ pyPretty e
PImport modName -> "import " ++ modName
PCondS c a b ->
sepLines ["if " ++ pyPretty c ++ ":",
indentLine 4 (pyPretty a),
"else:",
indentLine 4 (pyPretty b)]
PFun fid params body ->
sepLines ["def " ++ pyPretty fid ++
pyPrettyParens params ++ ":",
indentLine 4 (pyPretty body)]
instance PyPretty Expr where
pyPretty pexpr =
case pexpr of
EUndefined -> "undefined"
EChar _ -> error ("Python pyPretty of Expr: " ++
"EChar should have been converted to " ++
"EString")
EList _ -> error ("Python pyPretty of Expr: " ++
"EList should have been converted to " ++
"ECall li ...")
EIf c a b ->
unwords [pyPretty a, "if", pyPretty c, "else", pyPretty b]
EGroup e -> pyPrettyParens [e]
ESymbol vid -> pyPretty vid
ENumber n -> show n
EBool b -> show b
EString s -> show s
ELambda (Symbol x) body ->
unwords ["lambda", show x, ":", pyPretty body]
EApp fexpr argExpr ->
concat [pyPretty fexpr, pyPrettyParens [argExpr]]
ECall fexpr argExprs ->
concat [pyPretty fexpr, pyPrettyParens argExprs]
EOp op left right ->
unwords [pyPretty left, pyPretty op, pyPretty right]
alterParens :: (Expr -> Expr) -> PStatement -> PStatement
alterParens t s =
case s of
PReturn e -> PReturn (t e)
PCondS c a b -> PCondS (t c) (alterParens t a) (alterParens t b)
PFun fid params b -> PFun fid params (alterParens t b)
_ -> s
ret :: Expr -> PStatement
ret pexpr = PReturn pexpr
condS :: Expr -> Expr -> Expr -> PStatement
condS c a b = PCondS c (ret a) (ret b)
var :: String -> Expr
var name = ESymbol (Symbol name)
ident :: String -> Symbol
ident s = Symbol s
char :: Char -> Expr
char c = EString [c]
param :: String -> Symbol
param name = Symbol name
fun :: String -> [String] -> Expr -> PStatement
fun fname paramNames bodyExpr =
PFun (ident fname) (map param paramNames) (ret bodyExpr)
operatorTable :: M.Map String Operator
operatorTable =
M.fromList (map (\ op -> (opName op, op))
[ (Operator "*" 7 True GroupLtoR)
, (Operator "//" 7 False GroupLtoR)
, (Operator "/" 7 False GroupLtoR)
, (Operator "%" 7 False GroupLtoR)
, (Operator "+" 6 True GroupLtoR)
, (Operator "-" 6 False GroupLtoR)
, (Operator "==" 4 False GroupNone)
, (Operator "!=" 4 False GroupNone)
, (Operator ">" 4 False GroupNone)
, (Operator ">=" 4 False GroupNone)
, (Operator "<" 4 False GroupNone)
, (Operator "<=" 4 False GroupNone)
])