]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Eq.hs
IO, Monoid, Foldable, Text
[haskell/symantic.git] / Language / Symantic / Expr / Eq.hs
1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE MultiParamTypeClasses #-}
5 {-# LANGUAGE PolyKinds #-}
6 {-# LANGUAGE ScopedTypeVariables #-}
7 {-# LANGUAGE TypeFamilies #-}
8 {-# LANGUAGE TypeOperators #-}
9 {-# LANGUAGE NoMonomorphismRestriction #-}
10 {-# OPTIONS_GHC -fno-warn-orphans #-}
11 -- | Expression for 'Eq'.
12 module Language.Symantic.Expr.Eq where
13
14 import Data.Proxy (Proxy(..))
15 import Data.Type.Equality ((:~:)(Refl))
16 import Prelude hiding ((==))
17
18 import Language.Symantic.Trans.Common
19 import Language.Symantic.Type
20 import Language.Symantic.Expr.Root
21 import Language.Symantic.Expr.Error
22 import Language.Symantic.Expr.From
23
24 -- * Class 'Sym_Eq'
25 -- | Symantic.
26 class Sym_Eq repr where
27 (==) :: Eq a => repr a -> repr a -> repr Bool
28 default (==) :: (Trans t repr, Eq a)
29 => t repr a -> t repr a -> t repr Bool
30 (==) = trans_map2 (==)
31 infix 4 ==
32
33 -- * Type 'Expr_Eq'
34 -- | Expression.
35 data Expr_Eq (root:: *)
36 type instance Root_of_Expr (Expr_Eq root) = root
37 type instance Type_of_Expr (Expr_Eq root) = No_Type
38 type instance Sym_of_Expr (Expr_Eq root) repr = (Sym_Eq repr)
39 type instance Error_of_Expr ast (Expr_Eq root) = No_Error_Expr
40
41 instance Constraint_Type Eq (Type_Var0 root)
42 instance Constraint_Type Eq (Type_Var1 root)
43
44 eq_from
45 :: forall root ty ast hs ret.
46 ( ty ~ Type_Root_of_Expr (Expr_Eq root)
47 , Lift_Type Type_Bool (Type_of_Expr root)
48 , Eq_Type ty
49 , Expr_from ast root
50 , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast)
51 (Error_of_Expr ast root)
52 , Root_of_Expr root ~ root
53 , Constraint_Type Eq ty
54 ) => ast -> ast
55 -> Expr_From ast (Expr_Eq root) hs ret
56 eq_from ast_x ast_y ex ast ctx k =
57 expr_from (Proxy::Proxy root) ast_x ctx $
58 \(ty_x::ty h_x) (Forall_Repr_with_Context x) ->
59 expr_from (Proxy::Proxy root) ast_y ctx $
60 \(ty_y::ty h_y) (Forall_Repr_with_Context y) ->
61 check_eq_type ex ast ty_x ty_y $ \Refl ->
62 check_constraint_type ex (Proxy::Proxy Eq) ast ty_x $ \Dict ->
63 k type_bool $ Forall_Repr_with_Context $
64 \c -> x c == y c