module Wave.Ast where
import qualified Data.Text as T
import Wave.Common
import Wave.Types
type Var = T.Text
data Lit
= LInt Int
| LFloat Float
| LString T.Text
deriving (Int -> Lit -> ShowS
[Lit] -> ShowS
Lit -> String
(Int -> Lit -> ShowS)
-> (Lit -> String) -> ([Lit] -> ShowS) -> Show Lit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Lit] -> ShowS
$cshowList :: [Lit] -> ShowS
show :: Lit -> String
$cshow :: Lit -> String
showsPrec :: Int -> Lit -> ShowS
$cshowsPrec :: Int -> Lit -> ShowS
Show, Lit -> Lit -> Bool
(Lit -> Lit -> Bool) -> (Lit -> Lit -> Bool) -> Eq Lit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Lit -> Lit -> Bool
$c/= :: Lit -> Lit -> Bool
== :: Lit -> Lit -> Bool
$c== :: Lit -> Lit -> Bool
Eq)
data Expr a
= EAnnotated a (Expr a)
| ELit Lit
| EVar Var
| EFun [Var] (Sub a)
| EFunCall (Expr a) [Expr a]
| ERecord (Record (Expr a))
| EFfi T.Text [Expr a]
| EVariant (Variant (Expr a))
| ECase (Expr a) [(Pattern, Expr a)]
| ERecordAccess (Expr a) Label
deriving (Int -> Expr a -> ShowS
[Expr a] -> ShowS
Expr a -> String
(Int -> Expr a -> ShowS)
-> (Expr a -> String) -> ([Expr a] -> ShowS) -> Show (Expr a)
forall a. Show a => Int -> Expr a -> ShowS
forall a. Show a => [Expr a] -> ShowS
forall a. Show a => Expr a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Expr a] -> ShowS
$cshowList :: forall a. Show a => [Expr a] -> ShowS
show :: Expr a -> String
$cshow :: forall a. Show a => Expr a -> String
showsPrec :: Int -> Expr a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Expr a -> ShowS
Show, Expr a -> Expr a -> Bool
(Expr a -> Expr a -> Bool)
-> (Expr a -> Expr a -> Bool) -> Eq (Expr a)
forall a. Eq a => Expr a -> Expr a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Expr a -> Expr a -> Bool
$c/= :: forall a. Eq a => Expr a -> Expr a -> Bool
== :: Expr a -> Expr a -> Bool
$c== :: forall a. Eq a => Expr a -> Expr a -> Bool
Eq)
data DataType
= DataType Constr [TypeVar] [Variant Type]
deriving (Int -> DataType -> ShowS
[DataType] -> ShowS
DataType -> String
(Int -> DataType -> ShowS)
-> (DataType -> String) -> ([DataType] -> ShowS) -> Show DataType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataType] -> ShowS
$cshowList :: [DataType] -> ShowS
show :: DataType -> String
$cshow :: DataType -> String
showsPrec :: Int -> DataType -> ShowS
$cshowsPrec :: Int -> DataType -> ShowS
Show, DataType -> DataType -> Bool
(DataType -> DataType -> Bool)
-> (DataType -> DataType -> Bool) -> Eq DataType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataType -> DataType -> Bool
$c/= :: DataType -> DataType -> Bool
== :: DataType -> DataType -> Bool
$c== :: DataType -> DataType -> Bool
Eq)
data Definition a
= TypeDef DataType
| TermDef (TermDef a)
deriving (Int -> Definition a -> ShowS
[Definition a] -> ShowS
Definition a -> String
(Int -> Definition a -> ShowS)
-> (Definition a -> String)
-> ([Definition a] -> ShowS)
-> Show (Definition a)
forall a. Show a => Int -> Definition a -> ShowS
forall a. Show a => [Definition a] -> ShowS
forall a. Show a => Definition a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Definition a] -> ShowS
$cshowList :: forall a. Show a => [Definition a] -> ShowS
show :: Definition a -> String
$cshow :: forall a. Show a => Definition a -> String
showsPrec :: Int -> Definition a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Definition a -> ShowS
Show, Definition a -> Definition a -> Bool
(Definition a -> Definition a -> Bool)
-> (Definition a -> Definition a -> Bool) -> Eq (Definition a)
forall a. Eq a => Definition a -> Definition a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Definition a -> Definition a -> Bool
$c/= :: forall a. Eq a => Definition a -> Definition a -> Bool
== :: Definition a -> Definition a -> Bool
$c== :: forall a. Eq a => Definition a -> Definition a -> Bool
Eq)
data TermDef a
= Variable Var (Expr a)
| Function Var [Var] (Sub a)
deriving (Int -> TermDef a -> ShowS
[TermDef a] -> ShowS
TermDef a -> String
(Int -> TermDef a -> ShowS)
-> (TermDef a -> String)
-> ([TermDef a] -> ShowS)
-> Show (TermDef a)
forall a. Show a => Int -> TermDef a -> ShowS
forall a. Show a => [TermDef a] -> ShowS
forall a. Show a => TermDef a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TermDef a] -> ShowS
$cshowList :: forall a. Show a => [TermDef a] -> ShowS
show :: TermDef a -> String
$cshow :: forall a. Show a => TermDef a -> String
showsPrec :: Int -> TermDef a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> TermDef a -> ShowS
Show, TermDef a -> TermDef a -> Bool
(TermDef a -> TermDef a -> Bool)
-> (TermDef a -> TermDef a -> Bool) -> Eq (TermDef a)
forall a. Eq a => TermDef a -> TermDef a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TermDef a -> TermDef a -> Bool
$c/= :: forall a. Eq a => TermDef a -> TermDef a -> Bool
== :: TermDef a -> TermDef a -> Bool
$c== :: forall a. Eq a => TermDef a -> TermDef a -> Bool
Eq)
data Statement a
= SExpr (Expr a)
| SDef (TermDef a)
deriving (Int -> Statement a -> ShowS
[Statement a] -> ShowS
Statement a -> String
(Int -> Statement a -> ShowS)
-> (Statement a -> String)
-> ([Statement a] -> ShowS)
-> Show (Statement a)
forall a. Show a => Int -> Statement a -> ShowS
forall a. Show a => [Statement a] -> ShowS
forall a. Show a => Statement a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Statement a] -> ShowS
$cshowList :: forall a. Show a => [Statement a] -> ShowS
show :: Statement a -> String
$cshow :: forall a. Show a => Statement a -> String
showsPrec :: Int -> Statement a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Statement a -> ShowS
Show, Statement a -> Statement a -> Bool
(Statement a -> Statement a -> Bool)
-> (Statement a -> Statement a -> Bool) -> Eq (Statement a)
forall a. Eq a => Statement a -> Statement a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Statement a -> Statement a -> Bool
$c/= :: forall a. Eq a => Statement a -> Statement a -> Bool
== :: Statement a -> Statement a -> Bool
$c== :: forall a. Eq a => Statement a -> Statement a -> Bool
Eq)
type Sub a = [Statement a]
data Pattern
= PWildcard
| PVar Var
| PLit Lit
| PRecord (Record Pattern)
| PVariant (Variant Pattern)
deriving (Int -> Pattern -> ShowS
[Pattern] -> ShowS
Pattern -> String
(Int -> Pattern -> ShowS)
-> (Pattern -> String) -> ([Pattern] -> ShowS) -> Show Pattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Pattern] -> ShowS
$cshowList :: [Pattern] -> ShowS
show :: Pattern -> String
$cshow :: Pattern -> String
showsPrec :: Int -> Pattern -> ShowS
$cshowsPrec :: Int -> Pattern -> ShowS
Show, Pattern -> Pattern -> Bool
(Pattern -> Pattern -> Bool)
-> (Pattern -> Pattern -> Bool) -> Eq Pattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Pattern -> Pattern -> Bool
$c/= :: Pattern -> Pattern -> Bool
== :: Pattern -> Pattern -> Bool
$c== :: Pattern -> Pattern -> Bool
Eq)
newtype File a
= File [Definition a]
deriving (Int -> File a -> ShowS
[File a] -> ShowS
File a -> String
(Int -> File a -> ShowS)
-> (File a -> String) -> ([File a] -> ShowS) -> Show (File a)
forall a. Show a => Int -> File a -> ShowS
forall a. Show a => [File a] -> ShowS
forall a. Show a => File a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [File a] -> ShowS
$cshowList :: forall a. Show a => [File a] -> ShowS
show :: File a -> String
$cshow :: forall a. Show a => File a -> String
showsPrec :: Int -> File a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> File a -> ShowS
Show, File a -> File a -> Bool
(File a -> File a -> Bool)
-> (File a -> File a -> Bool) -> Eq (File a)
forall a. Eq a => File a -> File a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: File a -> File a -> Bool
$c/= :: forall a. Eq a => File a -> File a -> Bool
== :: File a -> File a -> Bool
$c== :: forall a. Eq a => File a -> File a -> Bool
Eq)