]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Ord.hs
polish names
[haskell/symantic.git] / Language / Symantic / Expr / Ord.hs
1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE MultiParamTypeClasses #-}
5 {-# LANGUAGE OverloadedStrings #-}
6 {-# LANGUAGE ScopedTypeVariables #-}
7 {-# LANGUAGE TypeFamilies #-}
8 {-# LANGUAGE TypeOperators #-}
9 {-# OPTIONS_GHC -fno-warn-orphans #-}
10 -- | Expression for 'Ord'.
11 module Language.Symantic.Expr.Ord where
12
13 import Control.Monad
14 import Data.Monoid
15 import qualified Data.Ord as Ord
16 import Data.Proxy (Proxy(..))
17 import Data.Type.Equality ((:~:)(Refl))
18 import Prelude hiding (compare)
19
20 import Language.Symantic.Type
21 import Language.Symantic.Repr
22 import Language.Symantic.Expr.Root
23 import Language.Symantic.Expr.Error
24 import Language.Symantic.Expr.From
25 import Language.Symantic.Expr.Eq
26 import Language.Symantic.Trans.Common
27
28 -- * Class 'Sym_Ord'
29 -- | Symantic.
30 class Sym_Eq repr => Sym_Ord repr where
31 compare :: Ord a => repr a -> repr a -> repr Ordering
32 default compare :: (Trans t repr, Ord a) => t repr a -> t repr a -> t repr Ordering
33 compare = trans_map2 compare
34 instance Sym_Ord Repr_Host where
35 compare = liftM2 Ord.compare
36 instance Sym_Ord Repr_Text where
37 compare (Repr_Text x) (Repr_Text y) =
38 Repr_Text $ \p v ->
39 let p' = precedence_Eq in
40 paren p p' $
41 "compare " <> x p' v <> " " <> y p' v
42 instance
43 ( Sym_Ord r1
44 , Sym_Ord r2
45 ) => Sym_Ord (Dup r1 r2) where
46 compare (x1 `Dup` x2) (y1 `Dup` y2) =
47 compare x1 y1 `Dup` compare x2 y2
48
49 -- * Type 'Expr_Ord'
50 -- | Expression.
51 data Expr_Ord (root:: *)
52 type instance Root_of_Expr (Expr_Ord root) = root
53 type instance Type_of_Expr (Expr_Ord root) = Type_Ordering
54 type instance Sym_of_Expr (Expr_Ord root) repr = (Sym_Ord repr)
55 type instance Error_of_Expr ast (Expr_Ord root) = No_Error_Expr
56
57 compare_from
58 :: forall root ty ast hs ret.
59 ( ty ~ Type_Root_of_Expr (Expr_Ord root)
60 , Type0_Eq ty
61 , Expr_From ast root
62 , Type0_Lift Type_Ordering (Type_of_Expr root)
63 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
64 (Error_of_Expr ast root)
65 , Root_of_Expr root ~ root
66 , Type0_Constraint Ord ty
67 ) => ast -> ast
68 -> ExprFrom ast (Expr_Ord root) hs ret
69 compare_from ast_x ast_y ex ast ctx k =
70 expr_from (Proxy::Proxy root) ast_x ctx $
71 \(ty_x::ty h_x) (Forall_Repr_with_Context x) ->
72 expr_from (Proxy::Proxy root) ast_y ctx $
73 \(ty_y::ty h_y) (Forall_Repr_with_Context y) ->
74 check_type0_eq ex ast ty_x ty_y $ \Refl ->
75 check_type0_constraint ex (Proxy::Proxy Ord) ast ty_x $ \Dict ->
76 k type_ordering $ Forall_Repr_with_Context $
77 \c -> x c `compare` y c