{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -- | Expression for 'Ord'. module Language.Symantic.Expr.Ord where import Control.Monad import qualified Data.Ord as Ord import Data.Proxy (Proxy(..)) import Data.Type.Equality ((:~:)(Refl)) import Data.Ord (Ord) import Prelude hiding (Ord(..)) import Language.Symantic.Type import Language.Symantic.Repr import Language.Symantic.Expr.Root import Language.Symantic.Expr.Error import Language.Symantic.Expr.From import Language.Symantic.Expr.Eq import Language.Symantic.Trans.Common -- * Class 'Sym_Ord' -- | Symantic. class Sym_Eq repr => Sym_Ord repr where compare :: Ord a => repr a -> repr a -> repr Ordering (<) :: Ord a => repr a -> repr a -> repr Bool (<=) :: Ord a => repr a -> repr a -> repr Bool (>) :: Ord a => repr a -> repr a -> repr Bool (>=) :: Ord a => repr a -> repr a -> repr Bool max :: Ord a => repr a -> repr a -> repr a min :: Ord a => repr a -> repr a -> repr a default compare :: (Trans t repr, Ord a) => t repr a -> t repr a -> t repr Ordering default (<) :: (Trans t repr, Ord a) => t repr a -> t repr a -> t repr Bool default (<=) :: (Trans t repr, Ord a) => t repr a -> t repr a -> t repr Bool default (>) :: (Trans t repr, Ord a) => t repr a -> t repr a -> t repr Bool default (>=) :: (Trans t repr, Ord a) => t repr a -> t repr a -> t repr Bool default max :: (Trans t repr, Ord a) => t repr a -> t repr a -> t repr a default min :: (Trans t repr, Ord a) => t repr a -> t repr a -> t repr a compare = trans_map2 compare (<) = trans_map2 (<) (<=) = trans_map2 (<=) (>) = trans_map2 (>) (>=) = trans_map2 (>=) min = trans_map2 min max = trans_map2 max infix 4 < infix 4 <= infix 4 > infix 4 >= instance Sym_Ord Repr_Host where compare = liftM2 Ord.compare (<) = liftM2 (Ord.<) (<=) = liftM2 (Ord.<=) (>) = liftM2 (Ord.>) (>=) = liftM2 (Ord.>=) min = liftM2 Ord.min max = liftM2 Ord.max instance Sym_Ord Repr_Text where compare = repr_text_app2 "compare" (<) = repr_text_infix "<" (Precedence 4) (<=) = repr_text_infix "<=" (Precedence 4) (>) = repr_text_infix ">" (Precedence 4) (>=) = repr_text_infix ">=" (Precedence 4) min = repr_text_app2 "min" max = repr_text_app2 "max" instance (Sym_Ord r1, Sym_Ord r2) => Sym_Ord (Repr_Dup r1 r2) where compare = repr_dup2 sym_Ord compare (<) = repr_dup2 sym_Ord (<) (<=) = repr_dup2 sym_Ord (<=) (>) = repr_dup2 sym_Ord (>) (>=) = repr_dup2 sym_Ord (>=) min = repr_dup2 sym_Ord min max = repr_dup2 sym_Ord max sym_Ord :: Proxy Sym_Ord sym_Ord = Proxy -- * Type 'Expr_Ord' -- | Expression. data Expr_Ord (root:: *) type instance Root_of_Expr (Expr_Ord root) = root type instance Type_of_Expr (Expr_Ord root) = Type_Ordering type instance Sym_of_Expr (Expr_Ord root) repr = Sym_Ord repr type instance Error_of_Expr ast (Expr_Ord root) = No_Error_Expr -- | Parse 'compare'. compare_from :: forall root ty ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Ord root) , Type0_Eq ty , Expr_From ast root , Type0_Lift Type_Ordering (Type_of_Expr root) , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast) (Error_of_Expr ast root) , Root_of_Expr root ~ root , Type0_Constraint Ord ty ) => ast -> ast -> ExprFrom ast (Expr_Ord root) hs ret compare_from ast_x ast_y ex ast ctx k = expr_from (Proxy::Proxy root) ast_x ctx $ \(ty_x::ty h_x) (Forall_Repr_with_Context x) -> expr_from (Proxy::Proxy root) ast_y ctx $ \(ty_y::ty h_y) (Forall_Repr_with_Context y) -> check_type0_eq ex ast ty_x ty_y $ \Refl -> check_type0_constraint ex (Proxy::Proxy Ord) ast ty_x $ \Dict -> k type_ordering $ Forall_Repr_with_Context $ \c -> x c `compare` y c -- | Parse 'compare', partially applied. compare_from1 :: forall root ty ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Ord root) , Type0_Eq ty , Expr_From ast root , Type0_Lift Type_Ordering (Type_of_Expr root) , Type0_Lift Type_Fun (Type_of_Expr root) , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast) (Error_of_Expr ast root) , Root_of_Expr root ~ root , Type0_Constraint Ord ty ) => ast -> ExprFrom ast (Expr_Ord root) hs ret compare_from1 ast_x ex ast ctx k = expr_from (Proxy::Proxy root) ast_x ctx $ \(ty_x::ty h_x) (Forall_Repr_with_Context x) -> check_type0_constraint ex (Proxy::Proxy Ord) ast ty_x $ \Dict -> k (type_fun ty_x type_ordering) $ Forall_Repr_with_Context $ \c -> lam $ \y -> x c `compare` y -- | Parse '<', '<=', '>', or '>='. ord_from :: forall root ty ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Ord root) , Type0_Lift Type_Bool (Type_of_Expr root) , Type0_Eq ty , Expr_From ast root , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast) (Error_of_Expr ast root) , Root_of_Expr root ~ root , Type0_Constraint Ord ty ) => (forall repr a. (Sym_Ord repr, Ord a) => repr a -> repr a -> repr Bool) -> ast -> ast -> ExprFrom ast (Expr_Ord root) hs ret ord_from test ast_x ast_y ex ast ctx k = expr_from (Proxy::Proxy root) ast_x ctx $ \(ty_x::ty h_x) (Forall_Repr_with_Context x) -> expr_from (Proxy::Proxy root) ast_y ctx $ \(ty_y::ty h_y) (Forall_Repr_with_Context y) -> check_type0_eq ex ast ty_x ty_y $ \Refl -> check_type0_constraint ex (Proxy::Proxy Ord) ast ty_x $ \Dict -> k type_bool $ Forall_Repr_with_Context $ \c -> x c `test` y c -- | Parse '<', '<=', '>', or '>=', partially applied. ord_from1 :: forall root ty ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Ord root) , Type0_Lift Type_Bool (Type_of_Expr root) , Type0_Lift Type_Fun (Type_of_Expr root) , Type0_Eq ty , Expr_From ast root , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast) (Error_of_Expr ast root) , Root_of_Expr root ~ root , Type0_Constraint Ord ty ) => (forall repr a. (Sym_Ord repr, Ord a) => repr a -> repr a -> repr Bool) -> ast -> ExprFrom ast (Expr_Ord root) hs ret ord_from1 test ast_x ex ast ctx k = expr_from (Proxy::Proxy root) ast_x ctx $ \(ty_x::ty h_x) (Forall_Repr_with_Context x) -> check_type0_constraint ex (Proxy::Proxy Ord) ast ty_x $ \Dict -> k (type_fun ty_x type_bool) $ Forall_Repr_with_Context $ \c -> lam $ \y -> x c `test` y