{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} -- | Expression for 'Integral'. module Language.Symantic.Expr.Integral where import Control.Monad import Data.Monoid import Data.Proxy (Proxy(..)) import Data.Type.Equality ((:~:)(Refl)) import Prelude hiding (quot, rem, div, mod, quotRem, divMod, toInteger) import qualified Prelude import Language.Symantic.Type import Language.Symantic.Repr import Language.Symantic.Expr.Root import Language.Symantic.Expr.Error import Language.Symantic.Expr.From import Language.Symantic.Trans.Common -- * Class 'Sym_Integral' -- | Symantic. class Sym_Integral repr where quot :: Integral i => repr i -> repr i -> repr i rem :: Integral i => repr i -> repr i -> repr i div :: Integral i => repr i -> repr i -> repr i mod :: Integral i => repr i -> repr i -> repr i quotRem :: Integral i => repr i -> repr i -> repr (i, i) divMod :: Integral i => repr i -> repr i -> repr (i, i) toInteger :: Integral i => repr i -> repr Integer default quot :: (Trans t repr, Integral i) => t repr i -> t repr i -> t repr i default rem :: (Trans t repr, Integral i) => t repr i -> t repr i -> t repr i default div :: (Trans t repr, Integral i) => t repr i -> t repr i -> t repr i default mod :: (Trans t repr, Integral i) => t repr i -> t repr i -> t repr i default quotRem :: (Trans t repr, Integral i) => t repr i -> t repr i -> t repr (i, i) default divMod :: (Trans t repr, Integral i) => t repr i -> t repr i -> t repr (i, i) default toInteger :: (Trans t repr, Integral i) => t repr i -> t repr Integer quot = trans_map2 quot rem = trans_map2 rem div = trans_map2 div mod = trans_map2 mod quotRem = trans_map2 quotRem divMod = trans_map2 divMod toInteger = trans_map1 toInteger infixl 7 `quot` infixl 7 `rem` infixl 7 `div` infixl 7 `mod` instance Sym_Integral Repr_Host where quot = liftM2 Prelude.quot rem = liftM2 Prelude.rem div = liftM2 Prelude.div mod = liftM2 Prelude.mod quotRem = liftM2 Prelude.quotRem divMod = liftM2 Prelude.divMod toInteger = liftM Prelude.toInteger instance Sym_Integral Repr_Text where quot (Repr_Text x) (Repr_Text y) = Repr_Text $ \p v -> let p' = precedence_Integral in paren p p' $ x p' v <> " `quot` " <> y p' v rem (Repr_Text x) (Repr_Text y) = Repr_Text $ \p v -> let p' = precedence_Integral in paren p p' $ x p' v <> " `rem` " <> y p' v div (Repr_Text x) (Repr_Text y) = Repr_Text $ \p v -> let p' = precedence_Integral in paren p p' $ x p' v <> " `div` " <> y p' v mod (Repr_Text x) (Repr_Text y) = Repr_Text $ \p v -> let p' = precedence_Integral in paren p p' $ x p' v <> " `mod` " <> y p' v quotRem = repr_text_app2 "quotRem" divMod = repr_text_app2 "divMod" toInteger = repr_text_app1 "toInteger" instance ( Sym_Integral r1 , Sym_Integral r2 ) => Sym_Integral (Dup r1 r2) where quot (x1 `Dup` x2) (y1 `Dup` y2) = quot x1 y1 `Dup` quot x2 y2 div (x1 `Dup` x2) (y1 `Dup` y2) = div x1 y1 `Dup` div x2 y2 rem (x1 `Dup` x2) (y1 `Dup` y2) = rem x1 y1 `Dup` rem x2 y2 mod (x1 `Dup` x2) (y1 `Dup` y2) = mod x1 y1 `Dup` mod x2 y2 quotRem (x1 `Dup` x2) (y1 `Dup` y2) = quotRem x1 y1 `Dup` quotRem x2 y2 divMod (x1 `Dup` x2) (y1 `Dup` y2) = divMod x1 y1 `Dup` divMod x2 y2 toInteger (x1 `Dup` x2) = toInteger x1 `Dup` toInteger x2 -- * Type 'Expr_Integral' -- | Expression. data Expr_Integral (root:: *) type instance Root_of_Expr (Expr_Integral root) = root type instance Type_of_Expr (Expr_Integral root) = No_Type type instance Sym_of_Expr (Expr_Integral root) repr = Sym_Integral repr type instance Error_of_Expr ast (Expr_Integral root) = No_Error_Expr -- | Parse 'quotRem'. quotRem_from :: forall root ty ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Integral root) , Type0_Eq ty , Expr_From ast root , Type0_Lift Type_Tuple2 (Type_of_Expr root) , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast) (Error_of_Expr ast root) , Root_of_Expr root ~ root , Type0_Constraint Integral ty ) => ast -> ast -> ExprFrom ast (Expr_Integral root) hs ret quotRem_from ast_x ast_y ex ast ctx k = -- quotRem :: a -> a -> (a, a) expr_from (Proxy::Proxy root) ast_x ctx $ \(ty_x::ty h_x) (Forall_Repr_with_Context x) -> expr_from (Proxy::Proxy root) ast_y ctx $ \(ty_y::ty h_y) (Forall_Repr_with_Context y) -> check_type0_eq ex ast ty_x ty_y $ \Refl -> check_type0_constraint ex (Proxy::Proxy Integral) ast ty_x $ \Dict -> k (type_tuple2 ty_x ty_x) $ Forall_Repr_with_Context $ \c -> quotRem (x c) (y c) -- | Parse 'divMod'. divMod_from :: forall root ty ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Integral root) , Type0_Eq ty , Expr_From ast root , Type0_Lift Type_Tuple2 (Type_of_Expr root) , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast) (Error_of_Expr ast root) , Root_of_Expr root ~ root , Type0_Constraint Integral ty ) => ast -> ast -> ExprFrom ast (Expr_Integral root) hs ret divMod_from ast_x ast_y ex ast ctx k = -- divMod :: a -> a -> (a, a) expr_from (Proxy::Proxy root) ast_x ctx $ \(ty_x::ty h_x) (Forall_Repr_with_Context x) -> expr_from (Proxy::Proxy root) ast_y ctx $ \(ty_y::ty h_y) (Forall_Repr_with_Context y) -> check_type0_eq ex ast ty_x ty_y $ \Refl -> check_type0_constraint ex (Proxy::Proxy Integral) ast ty_x $ \Dict -> k (type_tuple2 ty_x ty_x) $ Forall_Repr_with_Context $ \c -> divMod (x c) (y c)