module AST where
import Control.Lens (view)
import Data.Functor ((<&>))
import Data.Int (Int64)
import Data.Text (Text)
import Formatting
import Data.Generics.Labels
import GHC.Generics (Generic)
import Text.Printf (printf)
import Types
import Util.SourceLoc qualified as SL
data RelOp
= LessThan
| GreaterThan
| LessEqual
| GreaterEqual
deriving (RelOp -> RelOp -> Bool
(RelOp -> RelOp -> Bool) -> (RelOp -> RelOp -> Bool) -> Eq RelOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RelOp -> RelOp -> Bool
== :: RelOp -> RelOp -> Bool
$c/= :: RelOp -> RelOp -> Bool
/= :: RelOp -> RelOp -> Bool
Eq)
instance Show RelOp where
show :: RelOp -> String
show RelOp
LessThan = String
"<"
show RelOp
GreaterThan = String
">"
show RelOp
LessEqual = String
"<="
show RelOp
GreaterEqual = String
">="
data ArithOp
= Plus
| Minus
| Multiply
| Division
| Modulo
deriving (ArithOp -> ArithOp -> Bool
(ArithOp -> ArithOp -> Bool)
-> (ArithOp -> ArithOp -> Bool) -> Eq ArithOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ArithOp -> ArithOp -> Bool
== :: ArithOp -> ArithOp -> Bool
$c/= :: ArithOp -> ArithOp -> Bool
/= :: ArithOp -> ArithOp -> Bool
Eq)
instance Show ArithOp where
show :: ArithOp -> String
show ArithOp
Plus = String
"+"
show ArithOp
Minus = String
"-"
show ArithOp
Multiply = String
"*"
show ArithOp
Division = String
"/"
show ArithOp
Modulo = String
"%"
data EqOp
= Equal
| NotEqual
deriving (EqOp -> EqOp -> Bool
(EqOp -> EqOp -> Bool) -> (EqOp -> EqOp -> Bool) -> Eq EqOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EqOp -> EqOp -> Bool
== :: EqOp -> EqOp -> Bool
$c/= :: EqOp -> EqOp -> Bool
/= :: EqOp -> EqOp -> Bool
Eq)
instance Show EqOp where
show :: EqOp -> String
show EqOp
Equal = String
"=="
show EqOp
NotEqual = String
"!="
data CondOp
= Or
| And
deriving (CondOp -> CondOp -> Bool
(CondOp -> CondOp -> Bool)
-> (CondOp -> CondOp -> Bool) -> Eq CondOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CondOp -> CondOp -> Bool
== :: CondOp -> CondOp -> Bool
$c/= :: CondOp -> CondOp -> Bool
/= :: CondOp -> CondOp -> Bool
Eq)
instance Show CondOp where
show :: CondOp -> String
show CondOp
Or = String
"||"
show CondOp
And = String
"&&"
data NegOp
= Neg
deriving (NegOp -> NegOp -> Bool
(NegOp -> NegOp -> Bool) -> (NegOp -> NegOp -> Bool) -> Eq NegOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NegOp -> NegOp -> Bool
== :: NegOp -> NegOp -> Bool
$c/= :: NegOp -> NegOp -> Bool
/= :: NegOp -> NegOp -> Bool
Eq)
instance Show NegOp where
show :: NegOp -> String
show NegOp
Neg = String
"-"
data NotOp
= Not
deriving (NotOp -> NotOp -> Bool
(NotOp -> NotOp -> Bool) -> (NotOp -> NotOp -> Bool) -> Eq NotOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NotOp -> NotOp -> Bool
== :: NotOp -> NotOp -> Bool
$c/= :: NotOp -> NotOp -> Bool
/= :: NotOp -> NotOp -> Bool
Eq)
instance Show NotOp where
show :: NotOp -> String
show NotOp
Not = String
"!"
data ChoiceOp
= Choice
deriving (Int -> ChoiceOp -> ShowS
[ChoiceOp] -> ShowS
ChoiceOp -> String
(Int -> ChoiceOp -> ShowS)
-> (ChoiceOp -> String) -> ([ChoiceOp] -> ShowS) -> Show ChoiceOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChoiceOp -> ShowS
showsPrec :: Int -> ChoiceOp -> ShowS
$cshow :: ChoiceOp -> String
show :: ChoiceOp -> String
$cshowList :: [ChoiceOp] -> ShowS
showList :: [ChoiceOp] -> ShowS
Show, ChoiceOp -> ChoiceOp -> Bool
(ChoiceOp -> ChoiceOp -> Bool)
-> (ChoiceOp -> ChoiceOp -> Bool) -> Eq ChoiceOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChoiceOp -> ChoiceOp -> Bool
== :: ChoiceOp -> ChoiceOp -> Bool
$c/= :: ChoiceOp -> ChoiceOp -> Bool
/= :: ChoiceOp -> ChoiceOp -> Bool
Eq)
data AssignOp
= EqlAssign
| IncAssign
| DecAssign
| PlusPlus
| MinusMinus
deriving (AssignOp -> AssignOp -> Bool
(AssignOp -> AssignOp -> Bool)
-> (AssignOp -> AssignOp -> Bool) -> Eq AssignOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AssignOp -> AssignOp -> Bool
== :: AssignOp -> AssignOp -> Bool
$c/= :: AssignOp -> AssignOp -> Bool
/= :: AssignOp -> AssignOp -> Bool
Eq)
instance Show AssignOp where
show :: AssignOp -> String
show AssignOp
EqlAssign = String
"="
show AssignOp
IncAssign = String
"+="
show AssignOp
DecAssign = String
"-="
show AssignOp
PlusPlus = String
"++"
show AssignOp
MinusMinus = String
"--"
data Type
= Void
| BoolType
| CharType
| IntType
| StringType
| ArrayType !Type !Int64
| Ptr !Type
deriving (Type -> Type -> Bool
(Type -> Type -> Bool) -> (Type -> Type -> Bool) -> Eq Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Type -> Type -> Bool
== :: Type -> Type -> Bool
$c/= :: Type -> Type -> Bool
/= :: Type -> Type -> Bool
Eq)
instance Show Type where
show :: Type -> String
show Type
Void = String
"void"
show Type
BoolType = String
"bool"
show Type
CharType = String
"char"
show Type
IntType = String
"int"
show Type
StringType = String
"string"
show (ArrayType Type
tpe Int64
size) = Format String (Int64 -> Type -> String) -> Int64 -> Type -> String
forall a. Format String a -> a
formatToString (Format (Type -> String) (Int64 -> Type -> String)
forall a r. Show a => Format r (a -> r)
shown Format (Type -> String) (Int64 -> Type -> String)
-> Format String (Type -> String)
-> Format String (Int64 -> Type -> String)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format (Type -> String) (Type -> String)
"x" Format (Type -> String) (Type -> String)
-> Format String (Type -> String) -> Format String (Type -> String)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format String (Type -> String)
forall a r. Show a => Format r (a -> r)
shown) Int64
size Type
tpe
show (Ptr Type
tpe) = Format String (Type -> String) -> Type -> String
forall a. Format String a -> a
formatToString (Format (Type -> String) (Type -> String)
"ptr" Format (Type -> String) (Type -> String)
-> Format String (Type -> String) -> Format String (Type -> String)
forall r a r'. Format r a -> Format r' r -> Format r' a
%+ Format String (Type -> String)
forall a r. Show a => Format r (a -> r)
shown) Type
tpe
dataSize :: Type -> Maybe Int64
dataSize :: Type -> Maybe Int64
dataSize Type
Void = Maybe Int64
forall a. Maybe a
Nothing
dataSize Type
IntType = Int64 -> Maybe Int64
forall a. a -> Maybe a
Just Int64
8
dataSize Type
BoolType = Int64 -> Maybe Int64
forall a. a -> Maybe a
Just Int64
1
dataSize Type
StringType = Int64 -> Maybe Int64
forall a. a -> Maybe a
Just Int64
8
dataSize (ArrayType Type
tpe Int64
size) = Type -> Maybe Int64
dataSize Type
tpe Maybe Int64 -> (Int64 -> Int64) -> Maybe Int64
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Int64
s -> Int64
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
size
dataSize (Ptr Type
_) = Int64 -> Maybe Int64
forall a. a -> Maybe a
Just Int64
8
parseArithOp :: Text -> ArithOp
parseArithOp :: Text -> ArithOp
parseArithOp Text
op = case Text
op of
Text
"+" -> ArithOp
Plus
Text
"-" -> ArithOp
Minus
Text
"*" -> ArithOp
Multiply
Text
"/" -> ArithOp
Division
Text
"%" -> ArithOp
Modulo
parseRelOp :: Text -> RelOp
parseRelOp :: Text -> RelOp
parseRelOp Text
op = case Text
op of
Text
"<" -> RelOp
LessThan
Text
">" -> RelOp
GreaterThan
Text
"<=" -> RelOp
LessEqual
Text
">=" -> RelOp
GreaterEqual
parseEqOp :: Text -> EqOp
parseEqOp :: Text -> EqOp
parseEqOp Text
op = case Text
op of
Text
"==" -> EqOp
Equal
Text
"!=" -> EqOp
NotEqual
parseCondOp :: Text -> CondOp
parseCondOp :: Text -> CondOp
parseCondOp Text
op = case Text
op of
Text
"||" -> CondOp
Or
Text
"&&" -> CondOp
And
parseNegOp :: Text -> NegOp
parseNegOp :: Text -> NegOp
parseNegOp Text
op = case Text
op of
Text
"-" -> NegOp
Neg
parseNotOp :: Text -> NotOp
parseNotOp :: Text -> NotOp
parseNotOp Text
op = case Text
op of
Text
"!" -> NotOp
Not
parseAssignOp :: Text -> AssignOp
parseAssignOp :: Text -> AssignOp
parseAssignOp Text
s = case Text
s of
Text
"+=" -> AssignOp
IncAssign
Text
"-=" -> AssignOp
DecAssign
Text
"=" -> AssignOp
EqlAssign
Text
"++" -> AssignOp
PlusPlus
Text
"--" -> AssignOp
MinusMinus
data Location = Location
{ Location -> Text
name :: !Name,
Location -> Maybe Expr
idx :: !(Maybe Expr),
Location -> Either Argument FieldDecl
variableDef :: !(Either Argument FieldDecl),
Location -> Type
tpe :: !Type,
Location -> Range
loc :: !SL.Range
}
deriving ((forall x. Location -> Rep Location x)
-> (forall x. Rep Location x -> Location) -> Generic Location
forall x. Rep Location x -> Location
forall x. Location -> Rep Location x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Location -> Rep Location x
from :: forall x. Location -> Rep Location x
$cto :: forall x. Rep Location x -> Location
to :: forall x. Rep Location x -> Location
Generic)
typeOfDef :: Either Argument FieldDecl -> Type
typeOfDef :: Either Argument FieldDecl -> Type
typeOfDef (Left Argument {$sel:tpe:Argument :: Argument -> Type
tpe = Type
tpe}) = Type
tpe
typeOfDef (Right FieldDecl {$sel:tpe:FieldDecl :: FieldDecl -> Type
tpe = Type
tpe}) = Type
tpe
instance Show Location where
show :: Location -> String
show Location {$sel:name:Location :: Location -> Text
name = Text
nm, $sel:idx:Location :: Location -> Maybe Expr
idx = Maybe Expr
idx} = String -> Text -> ShowS
forall r. PrintfType r => String -> r
printf String
"Location {name=%s, idx=%s}" Text
nm (Maybe Expr -> String
forall a. Show a => a -> String
show Maybe Expr
idx)
data Assignment = Assignment
{ Assignment -> Location
location :: !Location,
Assignment -> AssignOp
op :: !AssignOp,
Assignment -> Maybe Expr
expr :: !(Maybe Expr),
Assignment -> Range
loc :: !SL.Range
}
deriving ((forall x. Assignment -> Rep Assignment x)
-> (forall x. Rep Assignment x -> Assignment) -> Generic Assignment
forall x. Rep Assignment x -> Assignment
forall x. Assignment -> Rep Assignment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Assignment -> Rep Assignment x
from :: forall x. Assignment -> Rep Assignment x
$cto :: forall x. Rep Assignment x -> Assignment
to :: forall x. Rep Assignment x -> Assignment
Generic, Int -> Assignment -> ShowS
[Assignment] -> ShowS
Assignment -> String
(Int -> Assignment -> ShowS)
-> (Assignment -> String)
-> ([Assignment] -> ShowS)
-> Show Assignment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Assignment -> ShowS
showsPrec :: Int -> Assignment -> ShowS
$cshow :: Assignment -> String
show :: Assignment -> String
$cshowList :: [Assignment] -> ShowS
showList :: [Assignment] -> ShowS
Show)
data MethodCall = MethodCall
{ MethodCall -> Text
name :: !Name,
MethodCall -> [Expr]
args :: ![Expr],
MethodCall -> Range
loc :: !SL.Range
}
deriving ((forall x. MethodCall -> Rep MethodCall x)
-> (forall x. Rep MethodCall x -> MethodCall) -> Generic MethodCall
forall x. Rep MethodCall x -> MethodCall
forall x. MethodCall -> Rep MethodCall x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MethodCall -> Rep MethodCall x
from :: forall x. MethodCall -> Rep MethodCall x
$cto :: forall x. Rep MethodCall x -> MethodCall
to :: forall x. Rep MethodCall x -> MethodCall
Generic, Int -> MethodCall -> ShowS
[MethodCall] -> ShowS
MethodCall -> String
(Int -> MethodCall -> ShowS)
-> (MethodCall -> String)
-> ([MethodCall] -> ShowS)
-> Show MethodCall
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MethodCall -> ShowS
showsPrec :: Int -> MethodCall -> ShowS
$cshow :: MethodCall -> String
show :: MethodCall -> String
$cshowList :: [MethodCall] -> ShowS
showList :: [MethodCall] -> ShowS
Show)
data ASTRoot = ASTRoot
{ ASTRoot -> [ImportDecl]
imports :: ![ImportDecl],
ASTRoot -> [FieldDecl]
vars :: ![FieldDecl],
ASTRoot -> [MethodDecl]
methods :: ![MethodDecl]
}
deriving ((forall x. ASTRoot -> Rep ASTRoot x)
-> (forall x. Rep ASTRoot x -> ASTRoot) -> Generic ASTRoot
forall x. Rep ASTRoot x -> ASTRoot
forall x. ASTRoot -> Rep ASTRoot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ASTRoot -> Rep ASTRoot x
from :: forall x. ASTRoot -> Rep ASTRoot x
$cto :: forall x. Rep ASTRoot x -> ASTRoot
to :: forall x. Rep ASTRoot x -> ASTRoot
Generic, Int -> ASTRoot -> ShowS
[ASTRoot] -> ShowS
ASTRoot -> String
(Int -> ASTRoot -> ShowS)
-> (ASTRoot -> String) -> ([ASTRoot] -> ShowS) -> Show ASTRoot
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ASTRoot -> ShowS
showsPrec :: Int -> ASTRoot -> ShowS
$cshow :: ASTRoot -> String
show :: ASTRoot -> String
$cshowList :: [ASTRoot] -> ShowS
showList :: [ASTRoot] -> ShowS
Show)
data ImportDecl = ImportDecl
{ ImportDecl -> Text
name :: !Name,
ImportDecl -> Range
loc :: !SL.Range
}
deriving ((forall x. ImportDecl -> Rep ImportDecl x)
-> (forall x. Rep ImportDecl x -> ImportDecl) -> Generic ImportDecl
forall x. Rep ImportDecl x -> ImportDecl
forall x. ImportDecl -> Rep ImportDecl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ImportDecl -> Rep ImportDecl x
from :: forall x. ImportDecl -> Rep ImportDecl x
$cto :: forall x. Rep ImportDecl x -> ImportDecl
to :: forall x. Rep ImportDecl x -> ImportDecl
Generic, Int -> ImportDecl -> ShowS
[ImportDecl] -> ShowS
ImportDecl -> String
(Int -> ImportDecl -> ShowS)
-> (ImportDecl -> String)
-> ([ImportDecl] -> ShowS)
-> Show ImportDecl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ImportDecl -> ShowS
showsPrec :: Int -> ImportDecl -> ShowS
$cshow :: ImportDecl -> String
show :: ImportDecl -> String
$cshowList :: [ImportDecl] -> ShowS
showList :: [ImportDecl] -> ShowS
Show)
data FieldDecl = FieldDecl
{ FieldDecl -> Text
name :: !Name,
FieldDecl -> Type
tpe :: !Type,
FieldDecl -> Range
loc :: !SL.Range
}
deriving ((forall x. FieldDecl -> Rep FieldDecl x)
-> (forall x. Rep FieldDecl x -> FieldDecl) -> Generic FieldDecl
forall x. Rep FieldDecl x -> FieldDecl
forall x. FieldDecl -> Rep FieldDecl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FieldDecl -> Rep FieldDecl x
from :: forall x. FieldDecl -> Rep FieldDecl x
$cto :: forall x. Rep FieldDecl x -> FieldDecl
to :: forall x. Rep FieldDecl x -> FieldDecl
Generic, Int -> FieldDecl -> ShowS
[FieldDecl] -> ShowS
FieldDecl -> String
(Int -> FieldDecl -> ShowS)
-> (FieldDecl -> String)
-> ([FieldDecl] -> ShowS)
-> Show FieldDecl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldDecl -> ShowS
showsPrec :: Int -> FieldDecl -> ShowS
$cshow :: FieldDecl -> String
show :: FieldDecl -> String
$cshowList :: [FieldDecl] -> ShowS
showList :: [FieldDecl] -> ShowS
Show)
data Argument = Argument
{ Argument -> Text
name :: !Name,
Argument -> Type
tpe :: !Type,
Argument -> Range
loc :: !SL.Range
}
deriving ((forall x. Argument -> Rep Argument x)
-> (forall x. Rep Argument x -> Argument) -> Generic Argument
forall x. Rep Argument x -> Argument
forall x. Argument -> Rep Argument x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Argument -> Rep Argument x
from :: forall x. Argument -> Rep Argument x
$cto :: forall x. Rep Argument x -> Argument
to :: forall x. Rep Argument x -> Argument
Generic, Int -> Argument -> ShowS
[Argument] -> ShowS
Argument -> String
(Int -> Argument -> ShowS)
-> (Argument -> String) -> ([Argument] -> ShowS) -> Show Argument
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Argument -> ShowS
showsPrec :: Int -> Argument -> ShowS
$cshow :: Argument -> String
show :: Argument -> String
$cshowList :: [Argument] -> ShowS
showList :: [Argument] -> ShowS
Show)
data MethodSig = MethodSig
{ MethodSig -> Text
name :: !Name,
MethodSig -> Maybe Type
tpe :: !(Maybe Type),
MethodSig -> [Argument]
args :: ![Argument]
}
deriving ((forall x. MethodSig -> Rep MethodSig x)
-> (forall x. Rep MethodSig x -> MethodSig) -> Generic MethodSig
forall x. Rep MethodSig x -> MethodSig
forall x. MethodSig -> Rep MethodSig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MethodSig -> Rep MethodSig x
from :: forall x. MethodSig -> Rep MethodSig x
$cto :: forall x. Rep MethodSig x -> MethodSig
to :: forall x. Rep MethodSig x -> MethodSig
Generic, Int -> MethodSig -> ShowS
[MethodSig] -> ShowS
MethodSig -> String
(Int -> MethodSig -> ShowS)
-> (MethodSig -> String)
-> ([MethodSig] -> ShowS)
-> Show MethodSig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MethodSig -> ShowS
showsPrec :: Int -> MethodSig -> ShowS
$cshow :: MethodSig -> String
show :: MethodSig -> String
$cshowList :: [MethodSig] -> ShowS
showList :: [MethodSig] -> ShowS
Show)
mangle :: MethodSig -> Text
mangle :: MethodSig -> Text
mangle (MethodSig Text
name Maybe Type
_ [Argument]
args) =
Format Text (Text -> [Type] -> Text) -> Text -> [Type] -> Text
forall a. Format Text a -> a
sformat (Format ([Type] -> Text) (Text -> [Type] -> Text)
forall r. Format r (Text -> r)
stext Format ([Type] -> Text) (Text -> [Type] -> Text)
-> Format Text ([Type] -> Text)
-> Format Text (Text -> [Type] -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format ([Type] -> Text) ([Type] -> Text)
"@" Format ([Type] -> Text) ([Type] -> Text)
-> Format Text ([Type] -> Text) -> Format Text ([Type] -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Text
-> Format Builder (Type -> Builder) -> Format Text ([Type] -> Text)
forall (t :: * -> *) a r.
Foldable t =>
Text -> Format Builder (a -> Builder) -> Format r (t a -> r)
intercalated Text
"@" Format Builder (Type -> Builder)
forall a r. Show a => Format r (a -> r)
shown) Text
name ([Argument]
args [Argument] -> (Argument -> Type) -> [Type]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> Getting Type Argument Type -> Argument -> Type
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Type Argument Type
#tpe)
data MethodDecl = MethodDecl
{ MethodDecl -> MethodSig
sig :: !MethodSig,
MethodDecl -> Block
block :: !Block,
MethodDecl -> Range
loc :: !SL.Range
}
deriving ((forall x. MethodDecl -> Rep MethodDecl x)
-> (forall x. Rep MethodDecl x -> MethodDecl) -> Generic MethodDecl
forall x. Rep MethodDecl x -> MethodDecl
forall x. MethodDecl -> Rep MethodDecl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MethodDecl -> Rep MethodDecl x
from :: forall x. MethodDecl -> Rep MethodDecl x
$cto :: forall x. Rep MethodDecl x -> MethodDecl
to :: forall x. Rep MethodDecl x -> MethodDecl
Generic, Int -> MethodDecl -> ShowS
[MethodDecl] -> ShowS
MethodDecl -> String
(Int -> MethodDecl -> ShowS)
-> (MethodDecl -> String)
-> ([MethodDecl] -> ShowS)
-> Show MethodDecl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MethodDecl -> ShowS
showsPrec :: Int -> MethodDecl -> ShowS
$cshow :: MethodDecl -> String
show :: MethodDecl -> String
$cshowList :: [MethodDecl] -> ShowS
showList :: [MethodDecl] -> ShowS
Show)
data Statement = Statement
{ Statement -> Statement_
statement_ :: !Statement_,
Statement -> Range
loc :: !SL.Range
}
deriving ((forall x. Statement -> Rep Statement x)
-> (forall x. Rep Statement x -> Statement) -> Generic Statement
forall x. Rep Statement x -> Statement
forall x. Statement -> Rep Statement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Statement -> Rep Statement x
from :: forall x. Statement -> Rep Statement x
$cto :: forall x. Rep Statement x -> Statement
to :: forall x. Rep Statement x -> Statement
Generic, Int -> Statement -> ShowS
[Statement] -> ShowS
Statement -> String
(Int -> Statement -> ShowS)
-> (Statement -> String)
-> ([Statement] -> ShowS)
-> Show Statement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Statement -> ShowS
showsPrec :: Int -> Statement -> ShowS
$cshow :: Statement -> String
show :: Statement -> String
$cshowList :: [Statement] -> ShowS
showList :: [Statement] -> ShowS
Show)
data Statement_
= AssignStmt {Statement_ -> Assignment
assign :: !Assignment}
| IfStmt {Statement_ -> Expr
pred :: !Expr, Statement_ -> Block
ifBlock :: !Block, Statement_ -> Maybe Block
elseBlock :: !(Maybe Block)}
| ForStmt {Statement_ -> Maybe Assignment
init :: !(Maybe Assignment), pred :: !Expr, Statement_ -> Maybe Assignment
update :: !(Maybe Assignment), Statement_ -> Block
block :: !Block}
| ReturnStmt {Statement_ -> Maybe Expr
expr :: !(Maybe Expr)}
| MethodCallStmt {Statement_ -> MethodCall
methodCall :: !MethodCall}
| BreakStmt
| ContinueStmt
deriving ((forall x. Statement_ -> Rep Statement_ x)
-> (forall x. Rep Statement_ x -> Statement_) -> Generic Statement_
forall x. Rep Statement_ x -> Statement_
forall x. Statement_ -> Rep Statement_ x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Statement_ -> Rep Statement_ x
from :: forall x. Statement_ -> Rep Statement_ x
$cto :: forall x. Rep Statement_ x -> Statement_
to :: forall x. Rep Statement_ x -> Statement_
Generic, Int -> Statement_ -> ShowS
[Statement_] -> ShowS
Statement_ -> String
(Int -> Statement_ -> ShowS)
-> (Statement_ -> String)
-> ([Statement_] -> ShowS)
-> Show Statement_
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Statement_ -> ShowS
showsPrec :: Int -> Statement_ -> ShowS
$cshow :: Statement_ -> String
show :: Statement_ -> String
$cshowList :: [Statement_] -> ShowS
showList :: [Statement_] -> ShowS
Show)
data Expr = Expr
{ Expr -> Expr_
expr_ :: !Expr_,
Expr -> Type
tpe :: !Type,
Expr -> Range
loc :: !SL.Range
}
deriving ((forall x. Expr -> Rep Expr x)
-> (forall x. Rep Expr x -> Expr) -> Generic Expr
forall x. Rep Expr x -> Expr
forall x. Expr -> Rep Expr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Expr -> Rep Expr x
from :: forall x. Expr -> Rep Expr x
$cto :: forall x. Rep Expr x -> Expr
to :: forall x. Rep Expr x -> Expr
Generic, Int -> Expr -> ShowS
[Expr] -> ShowS
Expr -> String
(Int -> Expr -> ShowS)
-> (Expr -> String) -> ([Expr] -> ShowS) -> Show Expr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expr -> ShowS
showsPrec :: Int -> Expr -> ShowS
$cshow :: Expr -> String
show :: Expr -> String
$cshowList :: [Expr] -> ShowS
showList :: [Expr] -> ShowS
Show)
data Expr_
= LocationExpr {Expr_ -> Location
location :: !Location}
| MethodCallExpr {Expr_ -> MethodCall
methodCall :: !MethodCall}
| ExternCallExpr {Expr_ -> Text
name :: !Name, Expr_ -> [Expr]
args :: ![Expr]}
| IntLiteralExpr {Expr_ -> Int64
intVal :: !Int64}
| BoolLiteralExpr {Expr_ -> Bool
boolVal :: !Bool}
| CharLiteralExpr {Expr_ -> Char
charVal :: !Char}
| StringLiteralExpr {Expr_ -> Text
strVal :: !Text}
| ArithOpExpr {Expr_ -> ArithOp
arithOp :: !ArithOp, Expr_ -> Expr
lhs :: !Expr, Expr_ -> Expr
rhs :: !Expr}
| RelOpExpr {Expr_ -> RelOp
relOp :: !RelOp, lhs :: !Expr, rhs :: !Expr}
| CondOpExpr {Expr_ -> CondOp
condOp :: !CondOp, lhs :: !Expr, rhs :: !Expr}
| EqOpExpr {Expr_ -> EqOp
eqOp :: !EqOp, lhs :: !Expr, rhs :: !Expr}
| NegOpExpr {Expr_ -> NegOp
negOp :: !NegOp, Expr_ -> Expr
expr :: !Expr}
| NotOpExpr {Expr_ -> NotOp
notOp :: !NotOp, expr :: !Expr}
| ChoiceOpExpr {Expr_ -> ChoiceOp
choiceOp :: !ChoiceOp, Expr_ -> Expr
expr1 :: !Expr, Expr_ -> Expr
expr2 :: !Expr, Expr_ -> Expr
expr3 :: !Expr}
| LengthExpr {name :: !Name}
deriving ((forall x. Expr_ -> Rep Expr_ x)
-> (forall x. Rep Expr_ x -> Expr_) -> Generic Expr_
forall x. Rep Expr_ x -> Expr_
forall x. Expr_ -> Rep Expr_ x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Expr_ -> Rep Expr_ x
from :: forall x. Expr_ -> Rep Expr_ x
$cto :: forall x. Rep Expr_ x -> Expr_
to :: forall x. Rep Expr_ x -> Expr_
Generic, Int -> Expr_ -> ShowS
[Expr_] -> ShowS
Expr_ -> String
(Int -> Expr_ -> ShowS)
-> (Expr_ -> String) -> ([Expr_] -> ShowS) -> Show Expr_
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expr_ -> ShowS
showsPrec :: Int -> Expr_ -> ShowS
$cshow :: Expr_ -> String
show :: Expr_ -> String
$cshowList :: [Expr_] -> ShowS
showList :: [Expr_] -> ShowS
Show)
data Typed a = Typed {forall a. Typed a -> a
ele :: !a, forall a. Typed a -> Type
tpe :: !Type}
deriving ((forall x. Typed a -> Rep (Typed a) x)
-> (forall x. Rep (Typed a) x -> Typed a) -> Generic (Typed a)
forall x. Rep (Typed a) x -> Typed a
forall x. Typed a -> Rep (Typed a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Typed a) x -> Typed a
forall a x. Typed a -> Rep (Typed a) x
$cfrom :: forall a x. Typed a -> Rep (Typed a) x
from :: forall x. Typed a -> Rep (Typed a) x
$cto :: forall a x. Rep (Typed a) x -> Typed a
to :: forall x. Rep (Typed a) x -> Typed a
Generic, Int -> Typed a -> ShowS
[Typed a] -> ShowS
Typed a -> String
(Int -> Typed a -> ShowS)
-> (Typed a -> String) -> ([Typed a] -> ShowS) -> Show (Typed a)
forall a. Show a => Int -> Typed a -> ShowS
forall a. Show a => [Typed a] -> ShowS
forall a. Show a => Typed a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Typed a -> ShowS
showsPrec :: Int -> Typed a -> ShowS
$cshow :: forall a. Show a => Typed a -> String
show :: Typed a -> String
$cshowList :: forall a. Show a => [Typed a] -> ShowS
showList :: [Typed a] -> ShowS
Show)
data Block = Block
{ Block -> [FieldDecl]
vars :: ![FieldDecl],
Block -> [Statement]
stmts :: ![Statement],
Block -> Int
blockID :: !ScopeID
}
deriving ((forall x. Block -> Rep Block x)
-> (forall x. Rep Block x -> Block) -> Generic Block
forall x. Rep Block x -> Block
forall x. Block -> Rep Block x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Block -> Rep Block x
from :: forall x. Block -> Rep Block x
$cto :: forall x. Rep Block x -> Block
to :: forall x. Rep Block x -> Block
Generic, Int -> Block -> ShowS
[Block] -> ShowS
Block -> String
(Int -> Block -> ShowS)
-> (Block -> String) -> ([Block] -> ShowS) -> Show Block
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Block -> ShowS
showsPrec :: Int -> Block -> ShowS
$cshow :: Block -> String
show :: Block -> String
$cshowList :: [Block] -> ShowS
showList :: [Block] -> ShowS
Show)