]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Text.hs
IO, Monoid, Foldable, Text
[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
11 import Language.Symantic.Type
12 import Language.Symantic.Expr.Root
13 import Language.Symantic.Expr.Error
14 import Language.Symantic.Expr.From
15 import Language.Symantic.Trans.Common
16
17 -- * Class 'Sym_Text'
18 -- | Symantic.
19 class Sym_Text repr where
20 text :: Text -> repr Text
21 default text :: Trans t repr => Text -> t repr Text
22 text = trans_lift . text
23
24 -- * Type 'Expr_Text'
25 -- | Expression.
26 data Expr_Text (root:: *)
27 type instance Root_of_Expr (Expr_Text root) = root
28 type instance Type_of_Expr (Expr_Text root) = Type_Text
29 type instance Sym_of_Expr (Expr_Text root) repr = Sym_Text repr
30 type instance Error_of_Expr ast (Expr_Text root) = No_Error_Expr