1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
4 {-# LANGUAGE TypeFamilies #-}
5 {-# LANGUAGE TypeOperators #-}
6 -- | Expression for 'Int'.
7 module Language.Symantic.Expr.Int where
9 import Language.Symantic.Type
10 import Language.Symantic.Expr.Root
11 import Language.Symantic.Expr.Error
12 import Language.Symantic.Expr.From
13 import Language.Symantic.Trans.Common
17 class Sym_Int repr where
18 int :: Int -> repr Int
19 default int :: Trans t repr => Int -> t repr Int
20 int = trans_lift . int
24 data Expr_Int (root:: *)
25 type instance Root_of_Expr (Expr_Int root) = root
26 type instance Type_of_Expr (Expr_Int root) = Type_Int
27 type instance Sym_of_Expr (Expr_Int root) repr = Sym_Int repr
28 type instance Error_of_Expr ast (Expr_Int root) = No_Error_Expr