aboutsummaryrefslogtreecommitdiff
path: root/src/Language/SimpleShell/AST.hs
blob: 5a222c31de41073b41e4ece9876132caafceb14b (plain)
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
{-# LANGUAGE GADTs #-}

module Language.SimpleShell.AST
where

data SimpleType a where
  IntType :: SimpleType Integer
  StringType :: SimpleType String
  BoolType :: SimpleType Bool

data SimpleTypeList a where
  NilTs :: SimpleTypeList ()
  ConsTs :: SimpleType a -> SimpleTypeList as -> SimpleTypeList (a, as)

-- | Pure expression (no side effects).
data Expr a where
  Literal :: SimpleType a -> a -> Expr a
  VarE :: Var a -> Expr a
  FunctionCall :: FunctionRef a args -> ExprList args -> Expr a
  And :: Expr Bool -> Expr Bool -> Expr Bool
  Or  :: Expr Bool -> Expr Bool -> Expr Bool
  Not :: Expr Bool -> Expr Bool
  Eq  :: Expr a -> Expr a -> Expr Bool
  Neq :: Expr a -> Expr a -> Expr Bool
  Gt  :: Expr Integer -> Expr Integer -> Expr Bool
  Ge  :: Expr Integer -> Expr Integer -> Expr Bool
  Lt  :: Expr Integer -> Expr Integer -> Expr Bool
  Le  :: Expr Integer -> Expr Integer -> Expr Bool
  Ternary :: Expr Bool -> Expr a -> Expr a -> Expr a
  Length :: Expr String -> Expr Integer
  StrToInt :: Expr String -> Expr Integer
  IntToStr :: Expr Integer -> Expr String

data FunctionRef a args = FunctionRef String

data Function a args
  = Function
      (Args args)
      (Expr a)

data Function' where
  Function'
    :: SimpleType a
    -> SimpleTypeList as
    -> Function a as
    -> Function'

data ExprList a where
  NilE :: ExprList ()
  ConsE :: Expr a -> ExprList as -> ExprList (a, as)

data Var a = Var (SimpleType a) String

data Var' where
  Var' :: Var a -> Var'

data Args args where
  NilArgs :: Args ()
  ConsArgs :: Var a -> Args as -> Args (a, as)

data Statement ret
  = AssignExpr ExprAssignment'
  | Print (Expr String)
  | PrintErr (Expr String)
  | If (Expr Bool) [Statement ret] [Statement ret]
  | While (Expr Bool) [Statement ret]
  | RunCommand
      (Maybe (Var Integer))  -- shell return value
      (Maybe (Var String))   -- stdout
      (Maybe (Var String))   -- stderr
      (Command ret)
  | RunProcedure ProcAssignment'
  | Return (Expr ret)

data ExprAssignment' where
  ExprAssignment' :: Var a -> Expr a -> ExprAssignment'

data ProcAssignment' where
  ProcAssignment'
    :: Maybe (Var a)        -- procedure return value
    -> Maybe (Var String)   -- stdout
    -> Maybe (Var String)   -- stderr
    -> ProcRef a args
    -> Args args
    -> ProcAssignment'

data Command ret
  = ExtCmd (Expr String) [Expr String]
  | CompoundCmd [Statement ret]

data Procedure ret args
  = Procedure
      (Args args)
      [Var']    -- ^ variable declarations
      (Command ret)

data ProcRef ret args = ProcRef String

data Procedure' where
  Procedure'
    :: SimpleType ret
    -> SimpleTypeList args
    -> Procedure ret args
    -> Procedure'