{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} -- | Expression for 'Text'. module Language.Symantic.Expr.Text where import Data.Proxy import Data.Text (Text) 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_Text' -- | Symantic. class Sym_Text repr where text :: Text -> repr Text default text :: Trans t repr => Text -> t repr Text text = trans_lift . text instance Sym_Text Repr_Host where text = Repr_Host instance Sym_Text Repr_Text where text a = Repr_Text $ \_p _v -> Text.pack (show a) instance (Sym_Text r1, Sym_Text r2) => Sym_Text (Repr_Dup r1 r2) where text x = text x `Repr_Dup` text x sym_Text :: Proxy Sym_Text sym_Text = Proxy -- * Type 'Expr_Text' -- | Expression. data Expr_Text (root:: *) type instance Root_of_Expr (Expr_Text root) = root type instance Type_of_Expr (Expr_Text root) = Type_Text type instance Sym_of_Expr (Expr_Text root) repr = Sym_Text repr type instance Error_of_Expr ast (Expr_Text root) = No_Error_Expr