module Language.Clafer.Generator.Python where
import Language.Clafer.Common
import Language.Clafer.Front.Absclafer
import Language.Clafer.Intermediate.Intclafer
import Data.Char
tag:: String -> String -> String
tag name exp' = concat ["<", name, ">", exp', "</", name, ">\n"]
tagType :: String -> String -> String -> String
tagType name typename exp' = opening ++ rest
where
opening = concat ["<", name, " xsi:type=\"cl:", typename, "\""]
rest
| null exp' =" />"
| otherwise = concat [">", exp', "</", name, ">"]
genPythonInteger :: Integer -> String
genPythonInteger n = concat ["IntegerLiteral.IntegerLiteral(", show n, ")" ]
isNull :: String -> String
isNull [] = "\"\""
isNull x = x
boolHelper:: String -> String
boolHelper (x:xs) = toUpper x : xs
boolHelper [] = []
genPythonBoolean :: String -> Bool -> String
genPythonBoolean label b = concat [label, "=", boolHelper $ toLowerS $ show b]
genPythonString :: String -> String
genPythonString str = concat [ "StringLiteral.StringLiteral(", show str, ")"]
genPythonIntPair :: (Integer, Integer) -> String
genPythonIntPair (x, y) = concat
[ "(", genPythonInteger x
, ","
, genPythonInteger y, ")"]
genPythonModule :: IModule -> Result
genPythonModule imodule = concat
[ "from ast import Module\n"
, "from ast import GCard\n"
, "from ast import Supers\n"
, "from ast import Clafer\n"
, "from ast import Exp\n"
, "from ast import Declaration\n"
, "from ast import LocalDeclaration\n"
, "from ast import IRConstraint\n"
, "from ast import FunExp\n"
, "from ast import ClaferId\n"
, "from ast import DeclPExp\n"
, "from ast import Goal\n\n"
, "from ast import IntegerLiteral\n"
, "from ast import DoubleLiteral\n"
, "from ast import StringLiteral\n"
, "def getModule():\n"
, "\tstack = []\n"
, "\tmodule = Module.Module(\"\")\n"
, "\tstack.append(module)\n"
, concatMap genPythonElement $ _mDecls imodule
, "\treturn module"
]
genPythonClafer :: IClafer -> Result
genPythonClafer x = case x of
IClafer pos' abstract' gcard' id' uid' super' card' glcard' elements' ->
concat [ "\t", genPythonPosition pos', "\n"
, "\t", genPythonAbstract abstract', "\n"
, "\t", maybe "" genPythonGCard gcard', "\n"
, "\t", genPythonId id', "\n"
, "\t", genPythonUid uid', "\n"
, "\t", genPythonSuper super', "\n"
, "\t", maybe "" genPythonCard card', "\n"
, "\t", genPythonGlCard glcard', "\n"
, "\tcurrClafer = Clafer.Clafer(pos=pos, isAbstract=isAbstract, gcard=groupCard, ident=id, uid=uid, my_supers=my_supers, card=card, glCard=globalCard)\n"
, "\tstack[-1].addElement(currClafer)\n"
, "\tstack.append(currClafer)\n"
, concatMap genPythonElement elements'
, "\tstack.pop()\n"]
genPythonAbstract :: Bool -> String
genPythonAbstract isAbstract' = concat [ genPythonBoolean "isAbstract" isAbstract']
genPythonGCard :: IGCard -> String
genPythonGCard (IGCard isKeyword' interval') = concat
[ "groupCard = GCard.GCard(", genPythonBoolean "isKeyword" isKeyword', ", "
, "interval=" , genPythonInterval interval' , ")"]
genPythonInterval :: (Integer, Integer) -> String
genPythonInterval (nMin, nMax) = concat
[ "(", genPythonInteger nMin
, ",", genPythonInteger nMax
, ")"]
genPythonId :: String -> String
genPythonId ident' = concat[ "id=\"", ident', "\""]
genPythonUid :: String -> String
genPythonUid uid' = concat [ "uid=\"", uid', "\""]
genPythonSuper :: ISuper -> String
genPythonSuper x = case x of
ISuper isOverlapping' pexps' -> concat
[ "my_supers = Supers.Supers(", genPythonBoolean "isOverlapping" isOverlapping', ", elements=["
, concatMap (genPythonPExp "Super") pexps' , "])"]
genPythonCard :: (Integer, Integer) -> String
genPythonCard interval' = concat [ "card=" , genPythonInterval interval']
genPythonGlCard :: (Integer, Integer) -> String
genPythonGlCard interval' = concat ["globalCard=", genPythonInterval interval']
genPythonElement :: IElement -> String
genPythonElement x = case x of
IEClafer clafer' -> concat ["##### clafer #####\n" ,genPythonClafer clafer']
IEConstraint isHard' pexp' -> concat
[ "##### constraint #####\n", "\tconstraint = IRConstraint.IRConstraint(" , genPythonBoolean "isHard" isHard' , " ,"
, " exp=", genPythonPExp "ParentExp" pexp' , ")\n"
, "\tstack[-1].addElement(constraint)\n"]
IEGoal isMaximize' pexp' -> concat
[ "##### goal #####\n" ,"\tgoal = Goal.Goal(" , genPythonBoolean "isMaximize" isMaximize'
, ", exp=", genPythonPExp "ParentExp" pexp' , ")\n"
, "\tstack[-1].addElement(goal)\n"]
genPythonPExp :: String -> PExp -> String
genPythonPExp tagName (PExp iType' pid' pos' iexp') = concat
[ "\n\t\tExp.Exp","(expType=\"", tagName, "\", ", maybe "exptype=\"\"" genPythonIType iType'
, ", parentId=\"", pid', "\""
, ", " , genPythonPosition pos'
, ", iExpType=\"" , genPythonIExpType iexp' , "\""
, ", iExp=[" , genPythonIExp iexp' ,"])"]
genPythonPosition :: Span -> String
genPythonPosition (Span (Pos s1 s2) (Pos e1 e2)) = concat
[ "pos=(", genPythonIntPair (s1, s2), ", ", genPythonIntPair (e1, e2), ")"]
genPythonIExpType :: IExp -> String
genPythonIExpType x = case x of
IDeclPExp _ _ _ -> "IDeclarationParentExp"
IFunExp _ _ -> "IFunctionExp"
IInt _ -> "IIntExp"
IDouble _ -> "IDoubleExp"
IStr _ -> "IStringExp"
IClaferId _ _ _ -> "IClaferId"
declHelper :: [IDecl] -> String
declHelper [] = "None, "
declHelper x = concatMap genPythonDecl x
genPythonIExp :: IExp -> String
genPythonIExp x = case x of
IDeclPExp quant' decls' pexp' -> concat
[ "DeclPExp.DeclPExp(" , "quantifier=\"", (genPythonQuantType quant'), "\", "
, "declaration=", declHelper decls'
, "bodyParentExp=" , genPythonPExp "BodyParentExp" pexp', ")"]
IFunExp op' exps' -> concat
[ "FunExp.FunExp(operation=\"" , (if op' == "-" && length exps' == 1 then "UNARY_MINUS" else op') , "\", elements="
, "[", concatMap (\y -> genPythonPExp "Argument" y ++",") (init exps') , genPythonPExp "Argument" (last exps') ,"])" ]
IInt n -> genPythonInteger n
IDouble n -> concat [ "DoubleLiteral.DoubleLiteral(", show n, ")"] --DoubleLiteral
IStr str -> genPythonString str
IClaferId modName' sident' isTop' -> concat
[ "ClaferId.ClaferId(moduleName=\"", modName' , "\", "
, "my_id=\"", sident' , "\", "
, genPythonBoolean "isTop" isTop', ")"]
genPythonDecl :: IDecl -> String
genPythonDecl (IDecl disj locids pexp) = concat
[ "\n\t\tDeclaration.Declaration(" , genPythonBoolean "isDisjunct" disj, ", localDeclarations=["
, concatMap (\x -> "LocalDeclaration.LocalDeclaration(\"" ++ x ++ "\"), ") (init locids), "LocalDeclaration.LocalDeclaration(\"" , (last locids), "\")], "
, " body=", genPythonPExp "Body" pexp , "),"]
genPythonQuantType :: IQuant -> String
genPythonQuantType x = case x of
INo -> "No"
ILone -> "Lone"
IOne -> "One"
ISome -> "Some"
IAll -> "All"
genPythonITypeType :: IType -> String
genPythonITypeType x = case x of
TBoolean -> "Boolean"
TString -> "String"
TInteger -> "Integer"
TReal -> "Real"
TClafer _-> "Set"
genPythonIType :: IType -> String
genPythonIType x = concat [ "exptype=\"", (genPythonITypeType x), "\"" ]