summaryrefslogtreecommitdiff
path: root/src/Analysis/Identity.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Analysis/Identity.hs')
-rw-r--r--src/Analysis/Identity.hs10
1 files changed, 9 insertions, 1 deletions
diff --git a/src/Analysis/Identity.hs b/src/Analysis/Identity.hs
index 54f7cd2..186ab71 100644
--- a/src/Analysis/Identity.hs
+++ b/src/Analysis/Identity.hs
@@ -2,10 +2,12 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE StandaloneDeriving #-}
module Analysis.Identity (
- ValId(..),
identityAnalysis,
identityAnalysis',
+ ValId(..),
+ validSplitEither,
) where
import Data.Foldable (toList)
@@ -31,6 +33,7 @@ data ValId t where
VIArr :: Int -> Vec n Int -> ValId (TArr n t)
VIScal :: Int -> ValId (TScal t)
VIAccum :: Int -> ValId (TAccum t)
+deriving instance Show (ValId t)
instance PrettyX ValId where
prettyX = \case
@@ -46,6 +49,11 @@ instance PrettyX ValId where
VIScal i -> show i
VIAccum i -> 'C' : show i
+validSplitEither :: ValId (TEither a b) -> (Maybe (ValId a), Maybe (ValId b))
+validSplitEither (VIEither (Left v)) = (Just v, Nothing)
+validSplitEither (VIEither (Right v)) = (Nothing, Just v)
+validSplitEither (VIEither' v1 v2) = (Just v1, Just v2)
+
-- | Symbolic partial evaluation.
identityAnalysis :: SList STy env -> Expr x env t -> Expr ValId env t
identityAnalysis env term = runIdGen 0 $ do