module Language.Sifflet.Export.ToPython
(
PythonOptions(..)
, defaultPythonOptions
, exprToPExpr
, nameToPython
, fixIdentifierChars
, functionToPyDef
, defToPy
, functionsToPyModule
, functionsToPrettyPy
, exportPython
)
where
import Data.Char (isAlpha, isDigit, ord)
import Data.Map ((!))
import System.FilePath (replaceFileName)
import Graphics.UI.Sifflet.Types (VPUI(..))
import Language.Sifflet.Export.Exporter
import Language.Sifflet.Export.Python
import Language.Sifflet.Expr
import Language.Sifflet.Util
import System.Sifflet.Paths
data PythonOptions = PythonOptions
deriving (Eq, Show)
defaultPythonOptions :: PythonOptions
defaultPythonOptions = PythonOptions
exprToPExpr :: Expr -> Expr
exprToPExpr expr =
case expr of
EUndefined -> EUndefined
ESymbol _ -> expr
EBool _ -> expr
EChar c -> EString [c]
ENumber _ -> expr
EString _ -> expr
EIf cond action altAction ->
EIf (exprToPExpr cond)
(exprToPExpr action)
(exprToPExpr altAction)
EList exprs ->
ECall (Symbol "li") (map exprToPExpr exprs)
ELambda x body -> ELambda x (EGroup body)
ECall (Symbol fname) args ->
case nameToPython fname of
Left op ->
case args of
[left, right] ->
EOp op (EGroup (exprToPExpr left))
(EGroup (exprToPExpr right))
_ -> error "exprToPExpr: operation does not have 2 operands"
Right pname ->
ECall (Symbol pname) (map exprToPExpr args)
_ -> errcats ["exprToPExpr: extended expr:", show expr]
nameToPython :: String -> Either Operator String
nameToPython name =
let oper oname = Left $ operatorTable ! oname
in case name of
"+" -> oper "+"
"-" -> oper "-"
"*" -> oper "*"
"div" -> oper "//"
"mod" -> oper "%"
"/" -> oper "/"
"==" -> oper "=="
"/=" -> oper "!="
">" -> oper ">"
">=" -> oper ">="
"<" -> oper "<"
"<=" -> oper "<="
"add1" -> Right "add1"
"sub1" -> Right "sub1"
"zero?" -> Right "eqZero"
"positive?" -> Right "gtZero"
"negative?" -> Right "ltZero"
"null" -> Right "null"
"head" -> Right "head"
"tail" -> Right "tail"
":" -> Right "cons"
_ -> Right (fixIdentifierChars name)
fixIdentifierChars :: String -> String
fixIdentifierChars =
let fix s =
case s of
[] -> []
c:cs ->
if isAlpha c || isDigit c || c == '_'
then c : fix cs
else case c of
'?' -> "_QUESTION_" ++ fix cs
_ -> "_CHR" ++ show (ord c) ++ "_" ++ fix cs
in fix
functionToPyDef :: Function -> PStatement
functionToPyDef = defToPy . functionToDef
defToPy :: FunctionDefTuple -> PStatement
defToPy (fname, paramNames, _, _, body) =
fun (fixIdentifierChars fname)
paramNames
((simplifyExpr pyRules) (exprToPExpr body))
pyRules :: [Expr -> Expr]
pyRules = commonRulesForSimplifyingExprs
functionsToPyModule :: Functions -> PModule
functionsToPyModule (Functions fs) = PModule (map functionToPyDef fs)
functionsToPrettyPy :: Functions -> String
functionsToPrettyPy = pyPretty . functionsToPyModule
exportPython :: VPUI -> PythonOptions -> Exporter
exportPython vpui _options funcs path =
let header = "# File: " ++ path ++ "\n" ++
"# Generated by the Sifflet->Python exporter.\n" ++
"\n" ++
"# You may need to copy the file sifflet.py into " ++
"this directory\n" ++
"# from the directory where Sifflet is installed.\n" ++
"\n" ++
"from sifflet import *\n\n"
libDest = replaceFileName path "sifflet.py"
in do copyLibFile vpui "sifflet.py" libDest
writeFile path (header ++ functionsToPrettyPy funcs)