]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Compiling/Text.hs
Clarify names, and add commentaries.
[haskell/symantic.git] / Language / Symantic / Compiling / Text.hs
1 {-# LANGUAGE UndecidableInstances #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 -- | Symantic for 'Text'.
4 module Language.Symantic.Compiling.Text where
5
6 import Data.Proxy
7 import Data.Text (Text)
8 import qualified Data.Text as Text
9 import Data.Type.Equality ((:~:)(Refl))
10
11 import Language.Symantic.Parsing
12 import Language.Symantic.Typing
13 import Language.Symantic.Compiling.Term
14 import Language.Symantic.Interpreting
15 import Language.Symantic.Transforming.Trans
16
17 -- * Class 'Sym_Text'
18 class Sym_Text term where
19 text :: Text -> term Text
20 default text :: Trans t term => Text -> t term Text
21 text = trans_lift . text
22
23 type instance Sym_of_Iface (Proxy Text) = Sym_Text
24 type instance Consts_of_Iface (Proxy Text) = Proxy Text ': Consts_imported_by Text
25 type instance Consts_imported_by Text =
26 [ Proxy Eq
27 , Proxy Monoid
28 , Proxy Ord
29 , Proxy Show
30 ]
31
32 instance Sym_Text HostI where
33 text = HostI
34 instance Sym_Text TextI where
35 text a = TextI $ \_p _v ->
36 Text.pack (show a)
37 instance (Sym_Text r1, Sym_Text r2) => Sym_Text (DupI r1 r2) where
38 text x = text x `DupI` text x
39
40 instance Const_from Text cs => Const_from Text (Proxy Text ': cs) where
41 const_from "Text" k = k (ConstZ kind)
42 const_from s k = const_from s $ k . ConstS
43 instance Show_Const cs => Show_Const (Proxy Text ': cs) where
44 show_const ConstZ{} = "Text"
45 show_const (ConstS c) = show_const c
46
47 instance -- Proj_ConC
48 ( Proj_Const cs Text
49 , Proj_Consts cs (Consts_imported_by Text)
50 ) => Proj_ConC cs (Proxy Text) where
51 proj_conC _ (TyConst q :$ TyConst c)
52 | Just Refl <- eq_skind (kind_of_const c) SKiType
53 , Just Refl <- proj_const c (Proxy::Proxy Text)
54 = case () of
55 _ | Just Refl <- proj_const q (Proxy::Proxy Eq) -> Just Con
56 | Just Refl <- proj_const q (Proxy::Proxy Monoid) -> Just Con
57 | Just Refl <- proj_const q (Proxy::Proxy Ord) -> Just Con
58 | Just Refl <- proj_const q (Proxy::Proxy Show) -> Just Con
59 _ -> Nothing
60 proj_conC _c _q = Nothing
61 data instance TokenT meta (ts::[*]) (Proxy Text)
62 = Token_Term_Text Text
63 deriving instance Eq_Token meta ts => Eq (TokenT meta ts (Proxy Text))
64 deriving instance Show_Token meta ts => Show (TokenT meta ts (Proxy Text))
65 instance -- CompileI
66 Inj_Const (Consts_of_Ifaces is) Text =>
67 CompileI is (Proxy Text) where
68 compileI tok _ctx k =
69 case tok of
70 Token_Term_Text i -> k tyText $ TermO $ \_c -> text i
71
72 -- | The 'Text' 'Type'
73 tyText :: Inj_Const cs Text => Type cs Text
74 tyText = TyConst inj_const
75
76 sym_Text :: Proxy Sym_Text
77 sym_Text = Proxy