]> 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.Root
13 import Language.Symantic.Expr.Error
14 import Language.Symantic.Expr.From
15 import Language.Symantic.Trans.Common
16
17 -- * Class 'Sym_Int'
18 -- | Symantic.
19 class Sym_Int repr where
20 int :: Int -> repr Int
21 abs :: repr Int -> repr Int
22 negate :: repr Int -> repr Int
23 (+) :: repr Int -> repr Int -> repr Int
24 (-) :: repr Int -> repr Int -> repr Int
25 (*) :: repr Int -> repr Int -> repr Int
26 mod :: repr Int -> repr Int -> repr Int
27
28 default int :: Trans t repr => Int -> t repr Int
29 default abs :: Trans t repr => t repr Int -> t repr Int
30 default negate :: Trans t repr => t repr Int -> t repr Int
31 default (+) :: Trans t repr => t repr Int -> t repr Int -> t repr Int
32 default (-) :: Trans t repr => t repr Int -> t repr Int -> t repr Int
33 default (*) :: Trans t repr => t repr Int -> t repr Int -> t repr Int
34 default mod :: Trans t repr => t repr Int -> t repr Int -> t repr Int
35 int = trans_lift . int
36 abs = trans_map1 abs
37 negate = trans_map1 negate
38 (+) = trans_map2 (+)
39 (-) = trans_map2 (-)
40 (*) = trans_map2 (*)
41 mod = trans_map2 mod
42 infixl 6 +
43 infixl 6 -
44 infixl 7 *
45 infixl 7 `mod`
46
47 -- * Type 'Expr_Int'
48 -- | Expression.
49 data Expr_Int (root:: *)
50 type instance Root_of_Expr (Expr_Int root) = root
51 type instance Type_of_Expr (Expr_Int root) = Type_Int
52 type instance Sym_of_Expr (Expr_Int root) repr = Sym_Int repr
53 type instance Error_of_Expr ast (Expr_Int root) = No_Error_Expr