]> Git — Sourcephile - haskell/symantic.git/blob - symantic-lib/Language/Symantic/Lib/Char.hs
Use AllowAmbiguousTypes to avoid Proxy uses.
[haskell/symantic.git] / symantic-lib / Language / Symantic / Lib / Char.hs
1 {-# LANGUAGE UndecidableInstances #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 -- | Symantic for 'Char'.
4 module Language.Symantic.Lib.Char where
5
6 import qualified Data.Char as Char
7 import qualified Data.Text as Text
8
9 import Language.Symantic.Grammar hiding (char, any)
10 import qualified Language.Symantic.Grammar as Gram
11 import Language.Symantic
12 import Language.Symantic.Lib.List (tyList)
13
14 -- * Class 'Sym_Char'
15 type instance Sym (Proxy Char) = Sym_Char
16 class Sym_Char term where
17 char :: Char -> term Char
18 char_toUpper :: term Char -> term Char
19 char_toLower :: term Char -> term Char
20
21 default char :: Sym_Char (UnT term) => Trans term => Char -> term Char
22 default char_toUpper :: Sym_Char (UnT term) => Trans term => term Char -> term Char
23 default char_toLower :: Sym_Char (UnT term) => Trans term => term Char -> term Char
24
25 char = trans . char
26 char_toUpper = trans1 char_toUpper
27 char_toLower = trans1 char_toLower
28
29 -- Interpreting
30 instance Sym_Char Eval where
31 char = Eval
32 char_toUpper = eval1 Char.toUpper
33 char_toLower = eval1 Char.toLower
34 instance Sym_Char View where
35 char a = View $ \_p _v ->
36 Text.pack (show a)
37 char_toUpper = view1 "Char.toUpper"
38 char_toLower = view1 "Char.toLower"
39 instance (Sym_Char r1, Sym_Char r2) => Sym_Char (Dup r1 r2) where
40 char x = char x `Dup` char x
41 char_toUpper = dup1 @Sym_Char char_toUpper
42 char_toLower = dup1 @Sym_Char char_toLower
43
44 -- Transforming
45 instance (Sym_Char term, Sym_Lambda term) => Sym_Char (BetaT term)
46
47 -- Typing
48 instance ClassInstancesFor Char where
49 proveConstraintFor _ (TyApp _ (TyConst _ _ q) z)
50 | Just HRefl <- proj_ConstKiTy @_ @Char z
51 = case () of
52 _ | Just Refl <- proj_Const @Bounded q -> Just Dict
53 | Just Refl <- proj_Const @Enum q -> Just Dict
54 | Just Refl <- proj_Const @Eq q -> Just Dict
55 | Just Refl <- proj_Const @Ord q -> Just Dict
56 | Just Refl <- proj_Const @Show q -> Just Dict
57 _ -> Nothing
58 proveConstraintFor _c _q = Nothing
59 instance TypeInstancesFor Char
60
61 -- Compiling
62 instance
63 ( Gram_Source src g
64 , Gram_Alt g
65 , Gram_Rule g
66 , Gram_Comment g
67 , Inj_Sym ss Char
68 ) => Gram_Term_AtomsFor src ss g Char where
69 g_term_atomsFor =
70 [ rule "teChar" $
71 lexeme $ g_source $
72 (\c src -> BinTree0 $ Token_Term $ TermAVT $ (`setSource` src) $ teChar c)
73 <$> between tickG tickG (
74 cf_of_Terminal (Gram.any `but` tickG) <+>
75 '\'' <$ string "\\'"
76 )
77 ]
78 where
79 tickG :: Gram_Terminal g' => g' Char
80 tickG = Gram.char '\''
81 instance (Source src, Inj_Sym ss Char) => ModuleFor src ss Char where
82 moduleFor = ["Char"] `moduleWhere`
83 [ "toLower" := teChar_toLower
84 , "toUpper" := teChar_toUpper
85 ]
86
87 -- ** 'Type's
88 tyChar :: Source src => Inj_Len vs => Type src vs Char
89 tyChar = tyConst @(K Char) @Char
90
91 tyString :: Source src => Inj_Len vs => Type src vs String
92 tyString = tyList tyChar
93
94 -- ** 'Term's
95 teChar :: Source src => Inj_Sym ss Char => Char -> Term src ss ts '[] (() #> Char)
96 teChar b = Term noConstraint tyChar $ teSym @Char $ char b
97
98 teChar_toUpper, teChar_toLower :: TermDef Char '[] (() #> (Char -> Char))
99 teChar_toUpper = Term noConstraint (tyChar ~> tyChar) $ teSym @Char $ lam1 char_toUpper
100 teChar_toLower = Term noConstraint (tyChar ~> tyChar) $ teSym @Char $ lam1 char_toLower