summaryrefslogtreecommitdiff
path: root/src/AST.hs
diff options
context:
space:
mode:
authorTom Smeding <tom@tomsmeding.com>2023-09-21 23:57:20 +0200
committerTom Smeding <tom@tomsmeding.com>2023-09-21 23:57:38 +0200
commit3266269f4636a491f74ccf72b02db7cbb5acf26c (patch)
treeace7ee902c01c8dd2e081afa28913399ce5da31d /src/AST.hs
parent302ca6fdb6d0a3ed764a99a3f42829a5a012b258 (diff)
WIP in merge mode only return free variables
The code typechecks and may well work, but is untested.
Diffstat (limited to 'src/AST.hs')
-rw-r--r--src/AST.hs8
1 files changed, 7 insertions, 1 deletions
diff --git a/src/AST.hs b/src/AST.hs
index e39c74f..9ee2405 100644
--- a/src/AST.hs
+++ b/src/AST.hs
@@ -12,6 +12,7 @@
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
+{-# LANGUAGE EmptyCase #-}
module AST (module AST, module AST.Weaken) where
import Data.Functor.Const
@@ -76,7 +77,7 @@ deriving instance Show (SScalTy t)
type TIx = TScal TI64
-type Idx :: [Ty] -> Ty -> Type
+type Idx :: [k] -> k -> Type
data Idx env t where
IZ :: Idx (t : env) t
IS :: Idx env t -> Idx (a : env) t
@@ -276,6 +277,11 @@ slistMap :: (forall t. f t -> g t) -> SList f list -> SList g list
slistMap _ SNil = SNil
slistMap f (SCons x list) = SCons (f x) (slistMap f list)
+slistIdx :: SList f list -> Idx list t -> f t
+slistIdx (SCons x _) IZ = x
+slistIdx (SCons _ list) (IS i) = slistIdx list i
+slistIdx SNil i = case i of {}
+
idx2int :: Idx env t -> Int
idx2int IZ = 0
idx2int (IS n) = 1 + idx2int n