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