summaryrefslogtreecommitdiff
path: root/src/Language/SimpleShell/AST.hs
blob: 75496260e4a3dc69a9bdcb0dbb2cfaa4ad08f039 (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
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}

module Language.SimpleShell.AST
where

class SimpleType a
instance SimpleType Integer
instance SimpleType String
instance SimpleType Bool

class Castable a b
instance Castable Integer String
instance Castable String Integer

data Expr a where
  Literal :: (SimpleType a) => a -> Expr a
  VarE :: Var a -> Expr a
  FunctionCall :: Function 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 :: (SimpleType a) => Expr Bool -> Expr a -> Expr a -> Expr a
  Cast :: (Castable a b) => Expr a -> Expr b

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

data Var a where
  Var :: (SimpleType a) => String -> Var a

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

data Statement a where
  Declare :: Var a -> Statement b
  Assign :: Var a -> Expr a -> Statement b
  Print :: Expr String -> Statement b
  Command
    :: (Maybe (Var Integer))  -- shell return value
    -> (Maybe (Var String))   -- stdout
    -> (Maybe (Var String))   -- stderr
    -> Command a
    -> Statement a
  Return :: Expr a -> Statement a

data Command a where
  ExtCmd :: Expr String -> [Expr String] -> Command b
  CompundCmd :: [Statement a] -> Command a

data Function a args where
  Function :: (SimpleType a) => Args args -> Command a -> Function a args