{-# LANGUAGE QuasiQuotes #-} module Language.Java.Paragon.PiGeneration where import Language.Java.Paragon.Syntax import Control.Applicative import Language.Java.Paragon.QuasiQuoter piTransform :: CompilationUnit -> CompilationUnit piTransform = transformCompilationUnit --for generating Pi there should be a package name -- no imports -- one type for each compilationUnit since the execution is for one class but we can transform without considering that condition transformCompilationUnit :: CompilationUnit -> CompilationUnit transformCompilationUnit (CompilationUnit mpDecl _ tdecls) = CompilationUnit mpDecl [] (transformTypeDecl<$>tdecls) ---------------- transformTypeDecl :: TypeDecl -> TypeDecl transformTypeDecl (InterfaceTypeDecl (InterfaceDecl mods iden tparams refts ib)) = ClassTypeDecl (ClassDecl mods iden tparams Nothing refts (transformInterfaceBody ib)) -- Maybe typeDecl transformTypeDecl (ClassTypeDecl (ClassDecl mods iden tparams mt refts (ClassBody dcls))) = ClassTypeDecl (ClassDecl mods iden tparams mt refts (ClassBody $ transformDecl<$>dcls)) ---------------- transformDecl :: Decl -> Decl transformDecl (MemberDecl md) = MemberDecl $ transformMemberDecl md ---------------- transformInterfaceBody :: InterfaceBody -> ClassBody transformInterfaceBody (InterfaceBody mds) = ClassBody $ (\md->MemberDecl (transformMemberDecl md))<$>mds ------------- transformMemberDecl :: MemberDecl -> MemberDecl transformMemberDecl f@(FieldDecl fmods [typeQQ|actor|] vdecs) = f transformMemberDecl (FieldDecl fmods ft vdecs) = (FieldDecl fmods ft (transformVarDecls vdecs)) transformMemberDecl m@(MethodDecl mmods mtparams mmaybet mident mformparams mexceptionspecs mb) | Typemethod `elem` mmods = m | otherwise = MethodDecl mmods mtparams mmaybet mident mformparams mexceptionspecs (transformMethodBody mb) transformMemberDecl (ConstructorDecl cmods ctparams cident cformparams cexceptionspecs cb) = ConstructorDecl cmods ctparams cident cformparams cexceptionspecs (transformConstructorBody cb) transformMemberDecl x = x -- I assumed the LockDecl and PolicyDecl should not be touch -- Also I didnt write code for inner classes/interfaces ------ transformVarDecls :: [VarDecl] -> [VarDecl] transformVarDecls vds = [ VarDecl varDeclId Nothing | (VarDecl varDeclId _) <- vds] ------- transformMethodBody :: MethodBody -> MethodBody transformMethodBody = const $MethodBody Nothing -- [methodBodyQQ|{}|] -- maybe we have to add nothing instead of "just emptyMethodBody" ------- transformConstructorBody :: ConstructorBody -> ConstructorBody transformConstructorBody (ConstructorBody explConstrInvm bs) = ConstructorBody Nothing [] -- second argument nothing ?