{-# LANGUAGE NoImplicitPrelude #-} module Precursor.Numeric.Integral ( Integral(..) , even , odd )where import Data.Int (Int, Int16, Int32, Int64, Int8) import Precursor.Algebra.Semiring import Prelude (even, odd) import qualified Prelude -- | An integral domain. Members of this class must be 'Semiring's with -- commutative '*'. -- -- * @a '*' b = b '*' a@ -- * @(a '//' b) '*' b '+' (a '%' b) = a@ -- * @(a'+'k'*'b) '%' b = a '%' b@ -- * @'zero' '%' b = 'zero'@ class Semiring a => Integral a where {-# MINIMAL divMod | ((//), (%)) #-} -- | The divisor and modulo divMod :: a -> a -> (a, a) infixl 7 // -- | Integer division (//) :: a -> a -> a infixl 7 % -- | Modulo (%) :: a -> a -> a x // y = let (d,_) = divMod x y in d x % y = let (_,m) = divMod x y in m divMod x y = (x % y, x // y) instance Integral Int where divMod = Prelude.divMod instance Integral Int8 where divMod = Prelude.divMod instance Integral Int16 where divMod = Prelude.divMod instance Integral Int32 where divMod = Prelude.divMod instance Integral Int64 where divMod = Prelude.divMod instance Integral Prelude.Integer where divMod = Prelude.divMod