{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} -- | Expression for 'Int'. module Language.Symantic.Expr.Int where import qualified Data.Text as Text import Language.Symantic.Type import Language.Symantic.Repr import Language.Symantic.Expr.Root import Language.Symantic.Expr.Error import Language.Symantic.Expr.From import Language.Symantic.Trans.Common -- * Class 'Sym_Int' -- | Symantic. class Sym_Int repr where int :: Int -> repr Int default int :: Trans t repr => Int -> t repr Int int = trans_lift . int instance Sym_Int Repr_Host where int = Repr_Host instance Sym_Int Repr_Text where int a = Repr_Text $ \_p _v -> Text.pack (show a) instance (Sym_Int r1, Sym_Int r2) => Sym_Int (Repr_Dup r1 r2) where int x = int x `Repr_Dup` int x -- * Type 'Expr_Int' -- | Expression. data Expr_Int (root:: *) type instance Root_of_Expr (Expr_Int root) = root type instance Type_of_Expr (Expr_Int root) = Type_Int type instance Sym_of_Expr (Expr_Int root) repr = Sym_Int repr type instance Error_of_Expr ast (Expr_Int root) = No_Error_Expr