]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Compiling/Int.hs
Add Gram_Term.
[haskell/symantic.git] / Language / Symantic / Compiling / Int.hs
1 {-# LANGUAGE UndecidableInstances #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 {-# OPTIONS_GHC -fconstraint-solver-iterations=7 #-}
4 -- | Symantic for 'Int'.
5 module Language.Symantic.Compiling.Int where
6
7 import Data.Proxy
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_Int'
18 class Sym_Int term where
19 int :: Int -> term Int
20 default int :: Trans t term => Int -> t term Int
21 int = trans_lift . int
22
23 type instance Sym_of_Iface (Proxy Int) = Sym_Int
24 type instance Consts_of_Iface (Proxy Int) = Proxy Int ': Consts_imported_by Int
25 type instance Consts_imported_by Int =
26 [ Proxy Bounded
27 , Proxy Enum
28 , Proxy Eq
29 , Proxy Integral
30 , Proxy Num
31 , Proxy Ord
32 , Proxy Real
33 , Proxy Show
34 ]
35
36 instance Sym_Int HostI where
37 int = HostI
38 instance Sym_Int TextI where
39 int a = TextI $ \_p _v ->
40 Text.pack (show a)
41 instance (Sym_Int r1, Sym_Int r2) => Sym_Int (DupI r1 r2) where
42 int x = int x `DupI` int x
43
44 instance
45 ( Read_TypeNameR Type_Name cs rs
46 , Inj_Const cs Int
47 ) => Read_TypeNameR Type_Name cs (Proxy Int ': rs) where
48 read_typenameR _cs (Type_Name "Int") k = k (ty @Int)
49 read_typenameR _rs raw k = read_typenameR (Proxy @rs) raw k
50 instance Show_Const cs => Show_Const (Proxy Int ': cs) where
51 show_const ConstZ{} = "Int"
52 show_const (ConstS c) = show_const c
53
54 instance -- Proj_ConC
55 ( Proj_Const cs Int
56 , Proj_Consts cs (Consts_imported_by Int)
57 ) => Proj_ConC cs (Proxy Int) where
58 proj_conC _ (TyConst q :$ TyConst c)
59 | Just Refl <- eq_skind (kind_of_const c) SKiType
60 , Just Refl <- proj_const c (Proxy @Int)
61 = case () of
62 _ | Just Refl <- proj_const q (Proxy @Bounded) -> Just Con
63 | Just Refl <- proj_const q (Proxy @Enum) -> Just Con
64 | Just Refl <- proj_const q (Proxy @Eq) -> Just Con
65 | Just Refl <- proj_const q (Proxy @Integral) -> Just Con
66 | Just Refl <- proj_const q (Proxy @Num) -> Just Con
67 | Just Refl <- proj_const q (Proxy @Ord) -> Just Con
68 | Just Refl <- proj_const q (Proxy @Real) -> Just Con
69 | Just Refl <- proj_const q (Proxy @Show) -> Just Con
70 _ -> Nothing
71 proj_conC _c _q = Nothing
72 data instance TokenT meta (ts::[*]) (Proxy Int)
73 = Token_Term_Int Int
74 deriving instance Eq_Token meta ts => Eq (TokenT meta ts (Proxy Int))
75 deriving instance Show_Token meta ts => Show (TokenT meta ts (Proxy Int))
76 instance -- CompileI
77 Inj_Const (Consts_of_Ifaces is) Int =>
78 CompileI is (Proxy Int) where
79 compileI tok _ctx k =
80 case tok of
81 Token_Term_Int i -> k (ty @Int) $ TermO $ \_c -> int i
82 instance TokenizeT meta ts (Proxy Int)
83 instance Gram_Term_AtomsT meta ts (Proxy Int) g