]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Num.hs
Integer, Integral, Num
[haskell/symantic.git] / Language / Symantic / Expr / Num.hs
1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
4 {-# LANGUAGE TypeFamilies #-}
5 {-# LANGUAGE TypeOperators #-}
6 -- | Expression for 'Num'.
7 module Language.Symantic.Expr.Num where
8
9 import Prelude hiding ((+), (-), (*), abs, mod, negate)
10
11 import Language.Symantic.Type
12 import Language.Symantic.Expr.Root
13 import Language.Symantic.Expr.Error
14 import Language.Symantic.Expr.From
15 import Language.Symantic.Trans.Common
16
17 -- * Class 'Sym_Num'
18 -- | Symantic.
19 class Sym_Num repr where
20 abs :: Num n => repr n -> repr n
21 negate :: Num n => repr n -> repr n
22 (+) :: Num n => repr n -> repr n -> repr n
23 (-) :: Num n => repr n -> repr n -> repr n
24 (*) :: Num n => repr n -> repr n -> repr n
25 default abs :: (Trans t repr, Num n) => t repr n -> t repr n
26 default negate :: (Trans t repr, Num n) => t repr n -> t repr n
27 default (+) :: (Trans t repr, Num n) => t repr n -> t repr n -> t repr n
28 default (-) :: (Trans t repr, Num n) => t repr n -> t repr n -> t repr n
29 default (*) :: (Trans t repr, Num n) => t repr n -> t repr n -> t repr n
30 abs = trans_map1 abs
31 negate = trans_map1 negate
32 (+) = trans_map2 (+)
33 (-) = trans_map2 (-)
34 (*) = trans_map2 (*)
35 infixl 6 +
36 infixl 6 -
37 infixl 7 *
38
39 -- * Type 'Expr_Num'
40 -- | Expression.
41 data Expr_Num (root:: *)
42 type instance Root_of_Expr (Expr_Num root) = root
43 type instance Type_of_Expr (Expr_Num root) = No_Type
44 type instance Sym_of_Expr (Expr_Num root) repr = Sym_Num repr
45 type instance Error_of_Expr ast (Expr_Num root) = No_Error_Expr