1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE ScopedTypeVariables #-}
5 {-# LANGUAGE TypeFamilies #-}
6 {-# LANGUAGE TypeOperators #-}
7 -- | Expression for 'Char'.
8 module Language.Symantic.Expr.Char where
11 import qualified Data.Char as Char
13 import qualified Data.Text as Text
15 import Language.Symantic.Type
16 import Language.Symantic.Repr
17 import Language.Symantic.Expr.Root
18 import Language.Symantic.Expr.Error
19 import Language.Symantic.Expr.From
20 import Language.Symantic.Trans.Common
24 class Sym_Char repr where
25 char :: Char -> repr Char
26 char_toUpper :: repr Char -> repr Char
28 default char :: Trans t repr => Char -> t repr Char
29 default char_toUpper :: Trans t repr => t repr Char -> t repr Char
31 char = trans_lift . char
32 char_toUpper = trans_map1 char_toUpper
33 instance Sym_Char Repr_Host where
35 char_toUpper = liftM Char.toUpper
36 instance Sym_Char Repr_Text where
37 char a = Repr_Text $ \_p _v ->
39 char_toUpper = repr_text_app1 "char_toUpper"
40 instance (Sym_Char r1, Sym_Char r2) => Sym_Char (Repr_Dup r1 r2) where
41 char x = char x `Repr_Dup` char x
42 char_toUpper = repr_dup1 sym_Char char_toUpper
44 sym_Char :: Proxy Sym_Char
49 data Expr_Char (root:: *)
50 type instance Root_of_Expr (Expr_Char root) = root
51 type instance Type_of_Expr (Expr_Char root) = Type_Char
52 type instance Sym_of_Expr (Expr_Char root) repr = Sym_Char repr
53 type instance Error_of_Expr ast (Expr_Char root) = No_Error_Expr