{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# OPTIONS_GHC -Wno-missing-signatures #-}
+{-# OPTIONS_GHC -Wno-orphans #-}
+
-- {-# OPTIONS_GHC -Wno-monomorphism-restriction #-}
-{-# OPTIONS_GHC -freduction-depth=400 #-}
module Symantic.Syntaxes where
import Data.Monoid (Monoid (..))
import Data.Semigroup (Semigroup (..))
import Data.Void (Void)
-import Debug.Trace
+
+-- import Debug.Trace
import Text.Show (Show (..))
import Type.Reflection (eqTypeRep, typeRep, (:~~:) (..))
import Prelude (error)
-- tree1 = mul (add (lit 8) (neg (add (lit 1) (lit 2)))) (lit 2)
tree2 = lam (typeOf @()) (\(x :: sem Int) -> add .@ x .@ lit 0)
+tree3 = lam (typeOf @()) (\(x :: sem Int) -> add .@ x .@ x)
tree0Print = print tree0
-- tree1Print = print tree1
tree2Print = print tree2
+tree3Print = print tree3
tree0ParsePrint :: TermAST ()
tree0ParsePrint = case parse @(FinalSyntaxes ()) @() tree0Print of
tree2ParsePrint = case parse @(FinalSyntaxes ()) @() tree2Print of
Left e -> error e
Right (TermVT _ty (runOTerm -> ForallSem sem)) -> print sem
+
+tree3ParsePrint :: TermAST ()
+tree3ParsePrint = case parse @(FinalSyntaxes ()) @() tree3Print of
+ Left e -> error e
+ Right (TermVT _ty (runOTerm -> ForallSem sem)) -> print sem