{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} -- | Expression for 'Int'. module Language.Symantic.Expr.Int where import Prelude hiding ((+), (-), (*), abs, mod, negate) import Language.Symantic.Type import Language.Symantic.Expr.Common import Language.Symantic.Repr.Dup import Language.Symantic.Trans.Common -- * Class 'Sym_Int' -- | Symantic. class Sym_Int repr where int :: Int -> repr Int abs :: repr Int -> repr Int negate :: repr Int -> repr Int (+) :: repr Int -> repr Int -> repr Int (-) :: repr Int -> repr Int -> repr Int (*) :: repr Int -> repr Int -> repr Int mod :: repr Int -> repr Int -> repr Int default int :: Trans t repr => Int -> t repr Int default abs :: Trans t repr => t repr Int -> t repr Int default negate :: Trans t repr => t repr Int -> t repr Int default (+) :: Trans t repr => t repr Int -> t repr Int -> t repr Int default (-) :: Trans t repr => t repr Int -> t repr Int -> t repr Int default (*) :: Trans t repr => t repr Int -> t repr Int -> t repr Int default mod :: Trans t repr => t repr Int -> t repr Int -> t repr Int int = trans_lift . int abs = trans_map1 abs negate = trans_map1 negate (+) = trans_map2 (+) (-) = trans_map2 (-) (*) = trans_map2 (*) mod = trans_map2 mod infixl 6 + infixl 6 - infixl 7 * infixl 7 `mod` instance -- Sym_Int Dup ( Sym_Int r1 , Sym_Int r2 ) => Sym_Int (Dup r1 r2) where int x = int x `Dup` int x abs (x1 `Dup` x2) = abs x1 `Dup` abs x2 negate (x1 `Dup` x2) = negate x1 `Dup` negate x2 (+) (x1 `Dup` x2) (y1 `Dup` y2) = (+) x1 y1 `Dup` (+) x2 y2 (-) (x1 `Dup` x2) (y1 `Dup` y2) = (-) x1 y1 `Dup` (-) x2 y2 (*) (x1 `Dup` x2) (y1 `Dup` y2) = (*) x1 y1 `Dup` (*) x2 y2 mod (x1 `Dup` x2) (y1 `Dup` y2) = mod x1 y1 `Dup` mod x2 y2 -- * Type 'Expr_Int' -- | Expression. data Expr_Int (root:: *) type instance Root_of_Expr (Expr_Int root) = root type instance Type_of_Expr (Expr_Int root) = Type_Int type instance Sym_of_Expr (Expr_Int root) repr = Sym_Int repr type instance Error_of_Expr ast (Expr_Int root) = No_Error_Expr