1 {-# LANGUAGE UndecidableInstances #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 -- | Symantic for 'Eq'.
4 module Language.Symantic.Compiling.Eq where
7 import qualified Data.Eq as Eq
8 import Data.Proxy (Proxy(..))
9 import Data.Text (Text)
10 import Prelude hiding ((==), (/=))
12 import Language.Symantic.Parsing
13 import Language.Symantic.Typing
14 import Language.Symantic.Compiling.Term
15 import Language.Symantic.Interpreting
16 import Language.Symantic.Transforming.Trans
19 class Sym_Eq term where
20 (==) :: Eq a => term a -> term a -> term Bool
21 (/=) :: Eq a => term a -> term a -> term Bool
23 default (==) :: (Trans t term, Eq a) => t term a -> t term a -> t term Bool
24 default (/=) :: (Trans t term, Eq a) => t term a -> t term a -> t term Bool
26 (==) = trans_map2 (==)
27 (/=) = trans_map2 (/=)
32 type instance Sym_of_Iface (Proxy Eq) = Sym_Eq
33 type instance Consts_of_Iface (Proxy Eq) = Proxy Eq ': Consts_imported_by Eq
34 type instance Consts_imported_by Eq = '[]
36 instance Sym_Eq HostI where
39 instance Sym_Eq TextI where
40 (==) = textI_infix "==" (Precedence 4)
41 (/=) = textI_infix "/=" (Precedence 4)
42 instance (Sym_Eq r1, Sym_Eq r2) => Sym_Eq (DupI r1 r2) where
43 (==) = dupI2 (Proxy @Sym_Eq) (==)
44 (/=) = dupI2 (Proxy @Sym_Eq) (/=)
47 ( Read_TypeNameR Text cs rs
49 ) => Read_TypeNameR Text cs (Proxy Eq ': rs) where
50 read_typenameR _cs "Eq" k = k (ty @Eq)
51 read_typenameR _rs raw k = read_typenameR (Proxy @rs) raw k
52 instance Show_Const cs => Show_Const (Proxy Eq ': cs) where
53 show_const ConstZ{} = "Eq"
54 show_const (ConstS c) = show_const c
56 instance Proj_ConC cs (Proxy Eq)
57 data instance TokenT meta (ts::[*]) (Proxy Eq)
58 = Token_Term_Eq_eq (EToken meta ts)
59 | Token_Term_Eq_ne (EToken meta ts)
60 deriving instance Eq_Token meta ts => Eq (TokenT meta ts (Proxy Eq))
61 deriving instance Show_Token meta ts => Show (TokenT meta ts (Proxy Eq))
63 ( Inj_Const (Consts_of_Ifaces is) Bool
64 , Inj_Const (Consts_of_Ifaces is) (->)
65 , Inj_Const (Consts_of_Ifaces is) Eq
66 , Proj_Con (Consts_of_Ifaces is)
68 ) => CompileI is (Proxy Eq) where
71 Token_Term_Eq_eq tok_a -> from_op (==) tok_a
72 Token_Term_Eq_ne tok_a -> from_op (/=) tok_a
74 from_op (op::forall term a. (Sym_Eq term, Eq a) => term a -> term a -> term Bool) tok_a =
75 compileO tok_a ctx $ \ty_a (TermO a) ->
76 check_con (At (Just tok_a) (ty @Eq :$ ty_a)) $ \Con ->
77 k (ty_a ~> ty @Bool) $ TermO $