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