]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Integral.hs
Integer, Integral, Num
[haskell/symantic.git] / Language / Symantic / Expr / Integral.hs
1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
4 {-# LANGUAGE TypeFamilies #-}
5 {-# LANGUAGE TypeOperators #-}
6 -- | Expression for 'Integral'.
7 module Language.Symantic.Expr.Integral where
8
9 import Data.Proxy (Proxy(..))
10 import Data.Type.Equality ((:~:)(Refl))
11 import Prelude hiding (quot, rem, div, mod, quotRem, divMod, toInteger)
12
13 import Language.Symantic.Type
14 import Language.Symantic.Expr.Root
15 import Language.Symantic.Expr.Error
16 import Language.Symantic.Expr.From
17 import Language.Symantic.Trans.Common
18
19 -- * Class 'Sym_Integral'
20 -- | Symantic.
21 class Sym_Integral repr where
22 quot :: Integral i => repr i -> repr i -> repr i
23 rem :: Integral i => repr i -> repr i -> repr i
24 div :: Integral i => repr i -> repr i -> repr i
25 mod :: Integral i => repr i -> repr i -> repr i
26 quotRem :: Integral i => repr i -> repr i -> repr (i, i)
27 divMod :: Integral i => repr i -> repr i -> repr (i, i)
28 toInteger :: Integral i => repr i -> repr Integer
29
30 default quot :: (Trans t repr, Integral i) => t repr i -> t repr i -> t repr i
31 default rem :: (Trans t repr, Integral i) => t repr i -> t repr i -> t repr i
32 default div :: (Trans t repr, Integral i) => t repr i -> t repr i -> t repr i
33 default mod :: (Trans t repr, Integral i) => t repr i -> t repr i -> t repr i
34 default quotRem :: (Trans t repr, Integral i) => t repr i -> t repr i -> t repr (i, i)
35 default divMod :: (Trans t repr, Integral i) => t repr i -> t repr i -> t repr (i, i)
36 default toInteger :: (Trans t repr, Integral i) => t repr i -> t repr Integer
37
38 quot = trans_map2 quot
39 rem = trans_map2 rem
40 div = trans_map2 div
41 mod = trans_map2 mod
42 quotRem = trans_map2 quotRem
43 divMod = trans_map2 divMod
44 toInteger = trans_map1 toInteger
45
46 infixl 7 `quot`
47 infixl 7 `rem`
48 infixl 7 `div`
49 infixl 7 `mod`
50
51 -- * Type 'Expr_Integral'
52 -- | Expression.
53 data Expr_Integral (root:: *)
54 type instance Root_of_Expr (Expr_Integral root) = root
55 type instance Type_of_Expr (Expr_Integral root) = No_Type
56 type instance Sym_of_Expr (Expr_Integral root) repr = Sym_Integral repr
57 type instance Error_of_Expr ast (Expr_Integral root) = No_Error_Expr
58
59 -- | Parse 'quotRem'.
60 quotRem_from
61 :: forall root ty ast hs ret.
62 ( ty ~ Type_Root_of_Expr (Expr_Integral root)
63 , Eq_Type ty
64 , Expr_from ast root
65 , Lift_Type Type_Tuple2 (Type_of_Expr root)
66 , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast)
67 (Error_of_Expr ast root)
68 , Root_of_Expr root ~ root
69 , Constraint_Type Integral ty
70 ) => ast -> ast
71 -> Expr_From ast (Expr_Integral root) hs ret
72 quotRem_from ast_x ast_y ex ast ctx k =
73 -- quotRem :: a -> a -> (a, a)
74 expr_from (Proxy::Proxy root) ast_x ctx $
75 \(ty_x::ty h_x) (Forall_Repr_with_Context x) ->
76 expr_from (Proxy::Proxy root) ast_y ctx $
77 \(ty_y::ty h_y) (Forall_Repr_with_Context y) ->
78 check_eq_type ex ast ty_x ty_y $ \Refl ->
79 check_constraint_type ex (Proxy::Proxy Integral) ast ty_x $ \Dict ->
80 k (type_tuple2 ty_x ty_x) $ Forall_Repr_with_Context $
81 \c -> quotRem (x c) (y c)
82
83 -- | Parse 'divMod'.
84 divMod_from
85 :: forall root ty ast hs ret.
86 ( ty ~ Type_Root_of_Expr (Expr_Integral root)
87 , Eq_Type ty
88 , Expr_from ast root
89 , Lift_Type Type_Tuple2 (Type_of_Expr root)
90 , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast)
91 (Error_of_Expr ast root)
92 , Root_of_Expr root ~ root
93 , Constraint_Type Integral ty
94 ) => ast -> ast
95 -> Expr_From ast (Expr_Integral root) hs ret
96 divMod_from ast_x ast_y ex ast ctx k =
97 -- divMod :: a -> a -> (a, a)
98 expr_from (Proxy::Proxy root) ast_x ctx $
99 \(ty_x::ty h_x) (Forall_Repr_with_Context x) ->
100 expr_from (Proxy::Proxy root) ast_y ctx $
101 \(ty_y::ty h_y) (Forall_Repr_with_Context y) ->
102 check_eq_type ex ast ty_x ty_y $ \Refl ->
103 check_constraint_type ex (Proxy::Proxy Integral) ast ty_x $ \Dict ->
104 k (type_tuple2 ty_x ty_x) $ Forall_Repr_with_Context $
105 \c -> divMod (x c) (y c)