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