GC: refactored Ptr specific test implementation into Mate/Tests/MockRefs;
[mate.git] / scratch / Analysis.hs
index fb50ea13bd542c538f8b6ed8a9b0333dc4a843fd..df60ed05f9cf19bca2b529cb5218a4a2096182c1 100644 (file)
@@ -1,10 +1,12 @@
+{-# LANGUAGE GADTs #-}
 module Analysis where
 
+import Compiler.Hoopl
 import Control.Monad.State
 
 type Addr = Int
 
-data StackIL = Dup | Ld Addr Type | Add Type | Store Addr Type
+data StackIL = Dup | Ld Addr Type | Add Type | Store Addr Type deriving Show
 
 type Target = (Int,Type)
 type Source = (Int,Type)
@@ -21,7 +23,7 @@ type StackElem = (Int,Type)
 type Stack = [StackElem]
 
 dup :: State Stack ()
-dup = modify (\(top@(i,t):x) -> (i+1,t) : top : xs)
+dup = modify (\(top@(i,t):xs) -> (i+1,t) : top : xs)
 
 push :: Type -> State Stack Int
 push t = do tos <- get
@@ -57,4 +59,26 @@ generateRegisterIR :: [StackIL] -> [RegIL]
 generateRegisterIR = (`evalState` []) . aInterpret
 
 --data StackIL = Dup | Ld Addr Type | Add Type | Store Addr Type
-testCase1 = [ Ld 0 Int, Ld 1 Int, Dup , Add Int, Add Int, Store 0 Int]
+testCase1 =  [ Ld 0 Int, Ld 1 Int, Dup , Add Int, Add Int, Store 0 Int]
+
+bench = concat . replicate 100000 
+
+type TLabel = Int
+type Var = String
+data Expr = VarE Var | AddE Var Var | Lit Int | CLe Expr Expr
+
+data Node e x where
+  Label  :: TLabel -> Node C O
+  Assign :: Var -> Expr -> Node O O
+  If :: Expr -> TLabel -> TLabel -> Node O C
+  Ret :: Node O C
+  Nop :: Node O O
+  Branch :: TLabel -> Node C C
+
+{-testProgram = [ Assign "x" (Lit 3),
+                Assign "y" (Lit 5),  
+                If (CLe (VarE "x") (VarE "y")) 1 2,
+                Assign "x" (VarE "y")
+                ] -}
+
+