]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Text.hs
revamp Repr/*
[haskell/symantic.git] / Language / Symantic / Expr / Text.hs
1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
4 {-# LANGUAGE TypeFamilies #-}
5 {-# LANGUAGE TypeOperators #-}
6 -- | Expression for 'Text'.
7 module Language.Symantic.Expr.Text where
8
9 import Data.Text (Text)
10 import qualified Data.Text as Text
11
12 import Language.Symantic.Type
13 import Language.Symantic.Repr
14 import Language.Symantic.Expr.Root
15 import Language.Symantic.Expr.Error
16 import Language.Symantic.Expr.From
17 import Language.Symantic.Trans.Common
18
19 -- * Class 'Sym_Text'
20 -- | Symantic.
21 class Sym_Text repr where
22 text :: Text -> repr Text
23 default text :: Trans t repr => Text -> t repr Text
24 text = trans_lift . text
25 instance Sym_Text Repr_Host where
26 text = Repr_Host
27 instance Sym_Text Repr_Text where
28 text a = Repr_Text $ \_p _v -> Text.pack (show a)
29 instance
30 ( Sym_Text r1
31 , Sym_Text r2
32 ) => Sym_Text (Dup r1 r2) where
33 text x = text x `Dup` text x
34
35 -- * Type 'Expr_Text'
36 -- | Expression.
37 data Expr_Text (root:: *)
38 type instance Root_of_Expr (Expr_Text root) = root
39 type instance Type_of_Expr (Expr_Text root) = Type_Text
40 type instance Sym_of_Expr (Expr_Text root) repr = Sym_Text repr
41 type instance Error_of_Expr ast (Expr_Text root) = No_Error_Expr