{-# LANGUAGE CPP #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
module Data.Euclidean
( Euclidean(..)
, Field
, GcdDomain(..)
, WrappedIntegral(..)
, WrappedFractional(..)
, gcdExt
) where
import Prelude hiding (quotRem, quot, rem, divMod, div, mod, gcd, lcm, negate, (*))
import qualified Prelude as P
import Control.Exception
import Data.Bits
import Data.Complex
import Data.Int (Int, Int8, Int16, Int32, Int64)
import Data.Maybe
import Data.Ratio
import Data.Semiring
import Data.Word (Word, Word8, Word16, Word32, Word64)
import Foreign.C.Types
import GHC.Exts
import GHC.Integer.GMP.Internals
import Numeric.Natural
class Semiring a => GcdDomain a where
divide :: a -> a -> Maybe a
default divide :: (Eq a, Euclidean a) => a -> a -> Maybe a
divide x y = let (q, r) = quotRem x y in
if isZero r then Just q else Nothing
gcd :: a -> a -> a
default gcd :: (Eq a, Euclidean a) => a -> a -> a
gcd a b
| isZero b = a
| otherwise = gcd b (a `rem` b)
lcm :: a -> a -> a
default lcm :: Eq a => a -> a -> a
lcm a b
| isZero a || isZero b = zero
| otherwise = case a `divide` gcd a b of
Nothing -> error "lcm: violated gcd invariant"
Just c -> c * b
coprime :: a -> a -> Bool
default coprime :: Eq a => a -> a -> Bool
coprime x y = isJust (one `divide` gcd x y)
infixl 7 `divide`
class GcdDomain a => Euclidean a where
quotRem :: a -> a -> (a, a)
quot :: a -> a -> a
quot x y = fst (quotRem x y)
rem :: a -> a -> a
rem x y = snd (quotRem x y)
degree :: a -> Natural
infixl 7 `quot`
infixl 7 `rem`
coprimeIntegral :: Integral a => a -> a -> Bool
coprimeIntegral x y = (odd x || odd y) && P.gcd x y == 1
gcdExt :: (Eq a, Euclidean a, Ring a) => a -> a -> (a, a)
gcdExt = go one zero
where
go s s' r r'
| r' == zero = (r, s)
| otherwise = case quotRem r r' of
(q, r'') -> go s' (minus s (times q s')) r' r''
{-# INLINABLE gcdExt #-}
class (Euclidean a, Ring a) => Field a
instance GcdDomain () where
divide = const $ const (Just ())
gcd = const $ const ()
lcm = const $ const ()
coprime = const $ const True
instance Euclidean () where
degree = const 0
quotRem = const $ const ((), ())
quot = const $ const ()
rem = const $ const ()
instance Field ()
instance GcdDomain Mod2 where
instance Euclidean Mod2 where
degree = const 0
quotRem x y
| isZero y = throw DivideByZero
| otherwise = (x, zero)
instance Field Mod2
newtype WrappedIntegral a = WrapIntegral { unwrapIntegral :: a }
deriving (Eq, Ord, Show, Num, Integral, Real, Enum, Bits)
instance Num a => Semiring (WrappedIntegral a) where
plus = (P.+)
zero = 0
times = (P.*)
one = 1
fromNatural = P.fromIntegral
instance Num a => Ring (WrappedIntegral a) where
negate = P.negate
instance Integral a => GcdDomain (WrappedIntegral a) where
gcd = P.gcd
lcm = P.lcm
coprime = coprimeIntegral
instance Integral a => Euclidean (WrappedIntegral a) where
degree = P.fromIntegral . abs . unwrapIntegral
quotRem = P.quotRem
quot = P.quot
rem = P.rem
instance GcdDomain Int where
#if MIN_VERSION_integer_gmp(0,5,1)
gcd (I# x) (I# y) = I# (gcdInt x y)
#else
gcd = P.gcd
#endif
lcm = P.lcm
coprime = coprimeIntegral
instance GcdDomain Word where
#if MIN_VERSION_integer_gmp(1,0,0)
gcd (W# x) (W# y) = W# (gcdWord x y)
#else
gcd = P.gcd
#endif
lcm = P.lcm
coprime = coprimeIntegral
instance GcdDomain Integer where
gcd = gcdInteger
lcm = lcmInteger
coprime = coprimeIntegral
#define deriveGcdDomain(ty) \
instance GcdDomain (ty) where { \
; gcd = P.gcd \
; lcm = P.lcm \
; coprime = coprimeIntegral \
}
deriveGcdDomain(Int8)
deriveGcdDomain(Int16)
deriveGcdDomain(Int32)
deriveGcdDomain(Int64)
deriveGcdDomain(Word8)
deriveGcdDomain(Word16)
deriveGcdDomain(Word32)
deriveGcdDomain(Word64)
deriveGcdDomain(Natural)
#define deriveEuclidean(ty) \
instance Euclidean (ty) where { \
; degree = P.fromIntegral . abs \
; quotRem = P.quotRem \
; quot = P.quot \
; rem = P.rem \
}
deriveEuclidean(Int)
deriveEuclidean(Int8)
deriveEuclidean(Int16)
deriveEuclidean(Int32)
deriveEuclidean(Int64)
deriveEuclidean(Integer)
deriveEuclidean(Word)
deriveEuclidean(Word8)
deriveEuclidean(Word16)
deriveEuclidean(Word32)
deriveEuclidean(Word64)
deriveEuclidean(Natural)
newtype WrappedFractional a = WrapFractional { unwrapFractional :: a }
deriving (Eq, Ord, Show, Num, Fractional)
instance Num a => Semiring (WrappedFractional a) where
plus = (P.+)
zero = 0
times = (P.*)
one = 1
fromNatural = P.fromIntegral
instance Num a => Ring (WrappedFractional a) where
negate = P.negate
instance Fractional a => GcdDomain (WrappedFractional a) where
divide x y = Just (x / y)
gcd = const $ const 1
lcm = const $ const 1
coprime = const $ const True
instance Fractional a => Euclidean (WrappedFractional a) where
degree = const 0
quotRem x y = (x / y, 0)
quot = (/)
rem = const $ const 0
instance Fractional a => Field (WrappedFractional a)
instance Integral a => GcdDomain (Ratio a) where
divide x y = Just (x / y)
gcd = const $ const 1
lcm = const $ const 1
coprime = const $ const True
instance Integral a => Euclidean (Ratio a) where
degree = const 0
quotRem x y = (x / y, 0)
quot = (/)
rem = const $ const 0
instance Integral a => Field (Ratio a)
instance GcdDomain Float where
divide x y = Just (x / y)
gcd = const $ const 1
lcm = const $ const 1
coprime = const $ const True
instance Euclidean Float where
degree = const 0
quotRem x y = (x / y, 0)
quot = (/)
rem = const $ const 0
instance Field Float
instance GcdDomain Double where
divide x y = Just (x / y)
gcd = const $ const 1
lcm = const $ const 1
coprime = const $ const True
instance Euclidean Double where
degree = const 0
quotRem x y = (x / y, 0)
quot = (/)
rem = const $ const 0
instance Field Double
instance GcdDomain CFloat where
divide x y = Just (x / y)
gcd = const $ const 1
lcm = const $ const 1
coprime = const $ const True
instance Euclidean CFloat where
degree = const 0
quotRem x y = (x / y, 0)
quot = (/)
rem = const $ const 0
instance Field CFloat
instance GcdDomain CDouble where
divide x y = Just (x / y)
gcd = const $ const 1
lcm = const $ const 1
coprime = const $ const True
instance Euclidean CDouble where
degree = const 0
quotRem x y = (x / y, 0)
quot = (/)
rem = const $ const 0
instance Field CDouble
conjQuotAbs :: Field a => Complex a -> Complex a
conjQuotAbs (x :+ y) = x `quot` norm :+ (negate y) `quot` norm
where
norm = (x `times` x) `plus` (y `times` y)
instance Field a => GcdDomain (Complex a) where
divide x y = Just (x `times` conjQuotAbs y)
gcd = const $ const one
lcm = const $ const one
coprime = const $ const True
instance Field a => Euclidean (Complex a) where
degree = const 0
quotRem x y = (quot x y, zero)
quot x y = x `times` conjQuotAbs y
rem = const $ const zero
instance Field a => Field (Complex a)