summaryrefslogtreecommitdiff
path: root/src/AST.hs
diff options
context:
space:
mode:
authorTom Smeding <tom@tomsmeding.com>2023-09-16 12:32:56 +0200
committerTom Smeding <tom@tomsmeding.com>2023-09-16 12:32:56 +0200
commit35cc10682f35dafba98000bf35191896a6432624 (patch)
tree7fbe9080ec502f3398a5329e15e5d263182d91a3 /src/AST.hs
parente52a3e7e89f6ad41d4291a467e4c1d3571614b0a (diff)
CHAD ops
Diffstat (limited to 'src/AST.hs')
-rw-r--r--src/AST.hs7
1 files changed, 7 insertions, 0 deletions
diff --git a/src/AST.hs b/src/AST.hs
index b1f3e5d..7c5de11 100644
--- a/src/AST.hs
+++ b/src/AST.hs
@@ -13,6 +13,8 @@
{-# LANGUAGE DeriveFoldable #-}
module AST (module AST, module AST.Weaken) where
+import Data.Functor.Const
+
import Data.Kind (Type)
import Data.Int
@@ -126,6 +128,11 @@ data Expr x env t where
EError :: STy a -> String -> Expr x env a
deriving instance (forall ty. Show (x ty)) => Show (Expr x env t)
+type Ex = Expr (Const ())
+
+ext :: Const () a
+ext = Const ()
+
type SOp :: Ty -> Ty -> Type
data SOp a t where
OAdd :: SScalTy a -> SOp (TPair (TScal a) (TScal a)) (TScal a)