module Data.Modular (unMod, toMod, toMod', Mod, (/)(), ℤ) where
import Control.Arrow (first)
import Data.Proxy (Proxy (..))
import Data.Ratio ((%))
import GHC.TypeLits
newtype i `Mod` (n :: Nat) = Mod i deriving (Eq, Ord)
unMod :: i `Mod` n -> i
unMod (Mod i) = i
type (/) = Mod
type ℤ = Integer
_bound :: forall n i. (Integral i, KnownNat n) => i `Mod` n
_bound = Mod . fromInteger $ natVal (Proxy :: Proxy n)
toMod :: forall n i. (Integral i, KnownNat n) => i -> i `Mod` n
toMod i = Mod $ i `mod` unMod (_bound :: i `Mod` n)
toMod' :: forall n i j. (Integral i, Integral j, KnownNat n) => i -> j `Mod` n
toMod' i = toMod . fromIntegral $ i `mod` (fromInteger $ natVal (Proxy :: Proxy n))
instance Show i => Show (i `Mod` n) where show (Mod i) = show i
instance (Read i, Integral i, KnownNat n) => Read (i `Mod` n)
where readsPrec prec = map (first toMod) . readsPrec prec
instance (Integral i, KnownNat n) => Num (i `Mod` n) where
fromInteger = toMod . fromInteger
Mod i₁ + Mod i₂ = toMod $ i₁ + i₂
Mod i₁ * Mod i₂ = toMod $ i₁ * i₂
abs (Mod i) = toMod $ abs i
signum (Mod i) = toMod $ signum i
negate (Mod i) = toMod $ negate i
instance (Integral i, KnownNat n) => Enum (i `Mod` n) where
toEnum = fromInteger . toInteger
fromEnum = fromInteger . toInteger . unMod
enumFrom x = enumFromTo x maxBound
enumFromThen x y = enumFromThenTo x y bound
where
bound | fromEnum y >= fromEnum x = maxBound
| otherwise = minBound
instance (Integral i, KnownNat n) => Bounded (i `Mod` n) where
maxBound = pred _bound
minBound = 0
instance (Integral i, KnownNat n) => Real (i `Mod` n) where
toRational (Mod i) = toInteger i % 1
instance (Integral i, KnownNat n) => Integral (i `Mod` n) where
toInteger (Mod i) = toInteger i
Mod i₁ `quotRem` Mod i₂ = let (q, r) = i₁ `quotRem` i₂ in (toMod q, toMod r)