aboutsummaryrefslogtreecommitdiff
path: root/src/HSVIS/AST.hs
diff options
context:
space:
mode:
authorTom Smeding <tom@tomsmeding.com>2024-02-26 22:59:54 +0100
committerTom Smeding <tom@tomsmeding.com>2024-02-26 22:59:54 +0100
commit307919760c58e037ec3260fcd0c3c7f7227fd7aa (patch)
tree2d4451b230a243f4dec60d80b6e9557c2e486749 /src/HSVIS/AST.hs
parent49f4a26867eb81eb59cfea78374bb09dd45edfa3 (diff)
WIP typecheck and other stuff
Diffstat (limited to 'src/HSVIS/AST.hs')
-rw-r--r--src/HSVIS/AST.hs30
1 files changed, 22 insertions, 8 deletions
diff --git a/src/HSVIS/AST.hs b/src/HSVIS/AST.hs
index 5a90205..f606d22 100644
--- a/src/HSVIS/AST.hs
+++ b/src/HSVIS/AST.hs
@@ -1,3 +1,7 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE StandaloneDeriving #-}
module HSVIS.AST where
import Data.List.NonEmpty (NonEmpty)
@@ -17,18 +21,27 @@ data DataDef = DataDef Name [Name] [(Name, [Type])]
data FunDef t = FunDef Name (Maybe Type) (NonEmpty (FunEq t))
deriving (Show)
-data FunEq t = FunEq Name [Pattern t] (RHS t)
+data FunEq t = FunEq t Name [Pattern t] (RHS t)
deriving (Show)
-data Type
- = TApp Type [Type]
- | TTup [Type]
- | TList Type
- | TFun Type Type
- | TCon Name
- | TVar Name
+data TypeStage = TSTC | TSNormal
deriving (Show)
+data GType (stage :: TypeStage) where
+ TApp :: GType s -> [GType s] -> GType s
+ TTup :: [GType s] -> GType s
+ TList :: GType s -> GType s
+ TFun :: GType s -> GType s -> GType s
+ TCon :: Name -> GType s
+ TVar :: Name -> GType s
+
+ -- Type constructor used only while type checking
+ TUniVar :: Int -> GType 'TSTC
+deriving instance Show (GType stage)
+
+type TCType = GType 'TSTC
+type Type = GType 'TSNormal
+
data Pattern t
= PWildcard t
| PVar t Name
@@ -55,6 +68,7 @@ data Expr t
| EIf t (Expr t) (Expr t) (Expr t)
| ECase t (Expr t) [(Pattern t, RHS t)]
| ELet t [FunDef t] (Expr t)
+ | EParseError
deriving (Show)
data Literal = LInt Integer | LFloat Rational | LChar Char | LString String