module Language.Grammars.ZipperAG.Examples.LET.ExampleLet where
import Data.Generics.Zipper
import Language.Grammars.ZipperAG
import Language.Grammars.ZipperAG.Examples.LET.Let_DataTypes_Boilerplate
import Language.Grammars.ZipperAG.Examples.LET.Let_Bidi
import Language.Grammars.ZipperAG.Examples.LET.Let_Scope
import Language.Grammars.ZipperAG.Examples.LET.Let_Meaning_HO_NestedST_Circ
a1 = let a = b + 3
c = 8
w = let z = a * b
in z * b
b = (c * 3) c
in c * w a
a = RootC $
LetC ( ConsAssignC "a" (Add (Et $ Tf $ Var "b") (Tf $ Const 3))
$ ConsAssignC "c" (Et $ Tf $ Const 8)
$ ConsLetC "w" ( LetC ( ConsAssignC "z" (Et $ Mul (Tf $ Var "a") (Var "b")) EmptyListC)
$ InC (Et $ Mul (Tf $ Var "z") (Var "b"))
)
$ ConsAssignC "b" (Sub (Et $ (Mul (Tf $ Var "c") (Const 3))) (Tf $ Var "c"))
EmptyListC
)
$ InC (Sub (Et $ Mul (Tf $ Var "c") (Var "w")) (Tf $ Var "a"))
b1 = let c = 1
a = let b = c
in b
in a + c
b = RootC $
LetC ( ConsAssignC "c" (Et $ Tf $ Const 1)
$ ConsLetC "a" ( LetC ( ConsAssignC "b" (Et $ Tf $ Var "c") EmptyListC)
$ InC (Et $ Tf $ Var "b")
)
EmptyListC
)
$ InC (Add (Et $ Tf $ Var "a") (Tf $ Var "c"))
c1 = let a = 5
b = a
in b
c = RootC $
LetC ( ConsAssignC "a" (Et $ Tf $ Const 5)
$ ConsAssignC "b" (Et $ Tf $ Var "a")
EmptyListC
)
$ InC (Et $ Tf $ Var "b")
d1 = let a = b+3
c = 8
b = c*3 c
in c*5 a
d = RootC $
LetC ( ConsAssignC "a" (Add (Et $ Tf $ Var "b") (Tf $ Const 3))
$ ConsAssignC "c" (Et $ Tf $ Const 8)
$ ConsAssignC "b" (Sub (Et $ (Mul (Tf $ Var "c") (Const 3))) (Tf $ Var "c"))
EmptyListC
)
$ InC (Sub (Et $ Mul (Tf $ Var "c") (Const 5)) (Tf $ Var "a"))
e1 = let x = y
y = z
z = 2
in x
e = RootC $
LetC ( ConsAssignC "x" (Et $ Tf $ Var "y")
$ ConsAssignC "y" (Et $ Tf $ Var "z")
$ ConsAssignC "z" (Et $ Tf $ Const 2)
EmptyListC
)
$ InC (Et $ Tf $ Var "x")
f1 = let a = b + 3
c = 8
w = let z = a * b
in z * b
b = let c = 1
in c + 4
in c * w a
f = RootC $
LetC ( ConsAssignC "a" (Add (Et $ Tf $ Var "b") (Tf $ Const 3))
$ ConsAssignC "c" (Et $ Tf $ Const 8)
$ ConsLetC "w" ( LetC ( ConsAssignC "z" (Et $ Mul (Tf $ Var "a") (Var "b")) EmptyListC)
$ InC (Et $ Mul (Tf $ Var "z") (Var "b"))
)
$ ConsLetC "b" ( LetC ( ConsAssignC "c" (Et $ Tf $ Const 1) EmptyListC)
$ InC (Add (Et $ Tf $ Var "c") (Tf $ Const 4))
)
EmptyListC
)
$ InC (Sub (Et $ Mul (Tf $ Var "c") (Var "w")) (Tf $ Var "a"))
test_bidi p = do putStrLn ("**** CONCRETE -> " ++ show p)
let t1 = getRootC_RootA $ toZipper p
putStrLn ("**** ABSTRACT -> " ++ show t1)
let t2 = putRootA_RootC $ toZipper t1
putStrLn ("**** CONCRETE -> " ++ show t2)
test_scope_rules p = errs $ toZipper (getRootC_RootA $ toZipper p)
test_meaning p = solve $ toZipper (getRootC_RootA $ toZipper p)