]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Text.hs
Repr_Dup helpers
[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.Proxy
10 import Data.Text (Text)
11 import qualified Data.Text as Text
12
13 import Language.Symantic.Type
14 import Language.Symantic.Repr
15 import Language.Symantic.Expr.Root
16 import Language.Symantic.Expr.Error
17 import Language.Symantic.Expr.From
18 import Language.Symantic.Trans.Common
19
20 -- * Class 'Sym_Text'
21 -- | Symantic.
22 class Sym_Text repr where
23 text :: Text -> repr Text
24 default text :: Trans t repr => Text -> t repr Text
25 text = trans_lift . text
26 instance Sym_Text Repr_Host where
27 text = Repr_Host
28 instance Sym_Text Repr_Text where
29 text a = Repr_Text $ \_p _v -> Text.pack (show a)
30 instance (Sym_Text r1, Sym_Text r2) => Sym_Text (Repr_Dup r1 r2) where
31 text x = text x `Repr_Dup` text x
32
33 sym_Text :: Proxy Sym_Text
34 sym_Text = Proxy
35
36 -- * Type 'Expr_Text'
37 -- | Expression.
38 data Expr_Text (root:: *)
39 type instance Root_of_Expr (Expr_Text root) = root
40 type instance Type_of_Expr (Expr_Text root) = Type_Text
41 type instance Sym_of_Expr (Expr_Text root) repr = Sym_Text repr
42 type instance Error_of_Expr ast (Expr_Text root) = No_Error_Expr