summaryrefslogtreecommitdiff
path: root/src/SPL/Syntax.hs
blob: d4775a46979148132061282835faa768184d97e8 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
-- vim: et ts=2 sw=2 ai:
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE  DefaultSignatures #-}
module SPL.Syntax
where

import GHC.Generics
import Data.Serialize

type Name = String

data Program = Program
  { funs :: [Function]
  , vars :: [Variable]
  }
  deriving (Show, Generic)

data Function = Function
  { fname :: Name
  , ftype :: Maybe Type
  , fargs :: [Name]
  , fvars :: [Variable]
  , fcode :: Statement
  }
  deriving (Show, Generic)

data Variable = Variable
  { vname :: Name
  , vtype :: Maybe Type
  , vval  :: Expression
  }
  deriving (Show, Generic)

data Type
  = TInt
  | TBool
  | TChar
  | TVoid
  | TList Type
  | TTuple Type Type
  | TArrow [Type] Type
  | TVar Name
  deriving (Show, Generic)

data Statement
  = If Expression Statement (Maybe Statement)
  | While Expression Statement
  | Assign Name [Field] Expression
  | Eval Expression
  | Return (Maybe Expression)
  | Seq Statement Statement
  | Nop
  deriving (Show, Generic)

data Expression
  = Var Name
  | Field Expression Field
  | Op2 Expression Op2 Expression
  | Op1 Op1 Expression
  | Literal Literal
  | FunCall Name [Expression]
  | Tuple Expression Expression
  deriving (Show, Generic)

data Field
  = Hd
  | Tl
  | Fst
  | Snd
  deriving (Show, Generic)

data Op2
  = Add
  | Sub
  | Mul
  | Div
  | Mod
  | Eq
  | Lt
  | Gt
  | Le
  | Ge
  | Ne
  | And
  | Or
  | Cons
  deriving (Show, Generic)

data Op1
  = Not
  | Neg
  deriving (Show, Generic)

data Literal
  = LInt Int
  | LChar Char
  | LBool Bool
  | LNil
  deriving (Show, Generic)

instance Serialize Program
instance Serialize Function
instance Serialize Variable
instance Serialize Type
instance Serialize Statement
instance Serialize Expression
instance Serialize Field
instance Serialize Op2
instance Serialize Op1
instance Serialize Literal