summaryrefslogtreecommitdiff
path: root/src/Interpreter.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Interpreter.hs')
-rw-r--r--src/Interpreter.hs16
1 files changed, 6 insertions, 10 deletions
diff --git a/src/Interpreter.hs b/src/Interpreter.hs
index 316a423..4d1358f 100644
--- a/src/Interpreter.hs
+++ b/src/Interpreter.hs
@@ -19,17 +19,21 @@ module Interpreter (
) where
import Control.Monad (foldM, join)
+import Data.Char (isSpace)
import Data.Kind (Type)
import Data.Int (Int64)
import Data.IORef
import System.IO.Unsafe (unsafePerformIO)
+import Debug.Trace
+
import Array
import AST
import CHAD.Types
import Data
import Interpreter.Rep
import Data.Bifunctor (bimap)
+import GHC.Stack (HasCallStack)
newtype AcM s a = AcM { unAcM :: IO a }
@@ -41,17 +45,16 @@ runAcM (AcM m) = unsafePerformIO m
interpret :: Ex '[] t -> Rep t
interpret = interpretOpen SNil
-newtype Value t = Value (Rep t)
-
interpretOpen :: SList Value env -> Ex env t -> Rep t
interpretOpen env e = runAcM (interpret' env e)
-interpret' :: forall env t s. SList Value env -> Ex env t -> AcM s (Rep t)
+interpret' :: forall env t s. HasCallStack => SList Value env -> Ex env t -> AcM s (Rep t)
interpret' env = \case
EVar _ _ i -> case slistIdx env i of Value x -> return x
ELet _ a b -> do
x <- interpret' env a
interpret' (Value x `SCons` env) b
+ expr | False && trace ("<i> " ++ takeWhile (not . isSpace) (show expr)) False -> undefined
EPair _ a b -> (,) <$> interpret' env a <*> interpret' env b
EFst _ e -> fst <$> interpret' env e
ESnd _ e -> snd <$> interpret' env e
@@ -232,13 +235,6 @@ instance Shapey Shape where
shapeyCase ShNil k0 _ = k0
shapeyCase (ShCons sh n) _ k1 = k1 sh n
-enumInvShape :: InvShape n -> [InvIndex n]
-enumInvShape IShNil = [IIxNil]
-enumInvShape (n `IShCons` sh) = [i `IIxCons` ix | i <- [0 .. n - 1], ix <- enumInvShape sh]
-
-enumShape :: Shape n -> [Index n]
-enumShape = map uninvert . enumInvShape . invert
-
invert :: forall f n. Shapey f => f n -> Inverted f n
invert | Refl <- lemPlusZero @n = flip go InvNil
where