modular-arithmetic-2.0.0.1: A type for integers modulo some constant.

Safe HaskellNone
LanguageHaskell2010

Data.Modular

Contents

Description

Types for working with integers modulo some constant.

Synopsis

Documentation

Mod and its synonym / let you wrap arbitrary numeric types in a modulus. To work with integers (mod 7) backed by Integer, you could use one of the following equivalent types:

Mod Integer 7
Integer `Mod` 7
Integer/7
ℤ/7

( is a synonym for Integer provided by this library. In Emacs, you can use the TeX input mode to type it with \Bbb{Z}.)

The usual numeric typeclasses are defined for these types. You can always extract the underlying value with unMod.

Here is a quick example:

>>> 10 * 11 :: ℤ/7
5

It also works correctly with negative numeric literals:

>>> (-10) * 11 :: ℤ/7
2

Modular division is an inverse of modular multiplication. It is defined when divisor is coprime to modulus:

>>> 7 / 3 :: ℤ/16
13
>>> 3 * 13 :: ℤ/16
7

Note that it raises an exception if the divisor is *not* coprime to the modulus:

>>> 7 / 4 :: ℤ/16
*** Exception: Cannot invert 4 (mod 16): not coprime to modulus.
...

To use type level numeric literals you need to enable the DataKinds extension and to use infix syntax for Mod or the / synonym, you need TypeOperators.

Preliminaries

To use type level numeric literals you need to enable the DataKinds extension:

>>> :set -XDataKinds

To use infix syntax for Mod or the / synonym, enable TypeOperators:

>>> :set -XTypeOperators

To use type applications with toMod and friends:

>>> :set -XTypeApplications

Modular arithmetic

data Mod i (n :: Nat) Source #

Wraps an underlying Integeral type i in a newtype annotated with the bound n.

Instances
(Integral i, Modulus n) => Bounded (Mod i n) Source # 
Instance details

Defined in Data.Modular

Methods

minBound :: Mod i n

maxBound :: Mod i n

(Integral i, Modulus n) => Enum (Mod i n) Source # 
Instance details

Defined in Data.Modular

Methods

succ :: Mod i n -> Mod i n

pred :: Mod i n -> Mod i n

toEnum :: Int -> Mod i n

fromEnum :: Mod i n -> Int

enumFrom :: Mod i n -> [Mod i n]

enumFromThen :: Mod i n -> Mod i n -> [Mod i n]

enumFromTo :: Mod i n -> Mod i n -> [Mod i n]

enumFromThenTo :: Mod i n -> Mod i n -> Mod i n -> [Mod i n]

Eq i => Eq (Mod i n) Source # 
Instance details

Defined in Data.Modular

Methods

(==) :: Mod i n -> Mod i n -> Bool

(/=) :: Mod i n -> Mod i n -> Bool

(Integral i, Modulus n) => Fractional (Mod i n) Source #

Division uses modular inverse inv so it is only possible to divide by numbers coprime to n.

>>> 1 / 3 :: ℤ/7
5
>>> 3 * 5 :: ℤ/7
1
>>> 2 / 5 :: ℤ/7
6
>>> 5 * 6 :: ℤ/7
2

Dividing by a number that is not coprime to n will raise an error. Use inv directly if you want to avoid this.

>>> 2 / 7 :: ℤ/7
*** Exception: Cannot invert 0 (mod 7): not coprime to modulus.
...
Instance details

Defined in Data.Modular

Methods

(/) :: Mod i n -> Mod i n -> Mod i n

recip :: Mod i n -> Mod i n

fromRational :: Rational -> Mod i n

(Integral i, Modulus n) => Num (Mod i n) Source # 
Instance details

Defined in Data.Modular

Methods

(+) :: Mod i n -> Mod i n -> Mod i n

(-) :: Mod i n -> Mod i n -> Mod i n

(*) :: Mod i n -> Mod i n -> Mod i n

negate :: Mod i n -> Mod i n

abs :: Mod i n -> Mod i n

signum :: Mod i n -> Mod i n

fromInteger :: Integer -> Mod i n

Ord i => Ord (Mod i n) Source # 
Instance details

Defined in Data.Modular

Methods

compare :: Mod i n -> Mod i n -> Ordering

(<) :: Mod i n -> Mod i n -> Bool

(<=) :: Mod i n -> Mod i n -> Bool

(>) :: Mod i n -> Mod i n -> Bool

(>=) :: Mod i n -> Mod i n -> Bool

max :: Mod i n -> Mod i n -> Mod i n

min :: Mod i n -> Mod i n -> Mod i n

(Read i, Integral i, Modulus n) => Read (Mod i n) Source # 
Instance details

Defined in Data.Modular

Methods

readsPrec :: Int -> ReadS (Mod i n)

readList :: ReadS [Mod i n]

readPrec :: ReadPrec (Mod i n)

readListPrec :: ReadPrec [Mod i n]

(Integral i, Modulus n) => Real (Mod i n) Source # 
Instance details

Defined in Data.Modular

Methods

toRational :: Mod i n -> Rational

Show i => Show (Mod i n) Source # 
Instance details

Defined in Data.Modular

Methods

showsPrec :: Int -> Mod i n -> ShowS

show :: Mod i n -> String

showList :: [Mod i n] -> ShowS

type Modulus n = (KnownNat n, 1 <= n) Source #

The modulus has to be a non-zero type-level natural number.

unMod :: (i `Mod` n) -> i Source #

Extract the underlying integral value from a modular type.

>>> unMod (10 :: ℤ/4)
2

toMod :: forall n i. (Integral i, Modulus n) => i -> i `Mod` n Source #

Injects a value of the underlying type into the modulus type, wrapping as appropriate.

If n is ambiguous, you can specify it with TypeApplications:

>>> toMod @6 10
4

Note that n cannot be 0.

toMod' :: forall n i j. (Integral i, Integral j, Modulus n) => i -> j `Mod` n Source #

Wraps an integral number, converting between integral types.

inv :: forall n i. (Modulus n, Integral i) => (i / n) -> Maybe (i / n) Source #

The modular inverse.

>>> inv 3 :: Maybe (ℤ/7)
Just 5
>>> 3 * 5 :: ℤ/7
1

Note that only numbers coprime to n have an inverse modulo n:

>>> inv 6 :: Maybe (ℤ/15)
Nothing

type (/) = Mod Source #

A synonym for Mod, inspired by the ℤ/n syntax from mathematics.

type = Integer Source #

A synonym for Integer, also inspired by the ℤ/n syntax.

modVal :: forall i proxy n. (Integral i, Modulus n) => i -> proxy n -> Mod i n Source #

Convert an integral number i into a Mod value with the type-level modulus n specified with a proxy argument.

This lets you use toMod without TypeApplications in contexts where n is ambiguous.

data SomeMod i Source #

A modular number with an unknown modulus.

Conceptually SomeMod i = ∃n. i/n.

Instances
Show i => Show (SomeMod i) Source #

Shows both the number *and* its modulus:

>>> show (someModVal 10 4)
"Just (someModVal 2 4)"

This doesn't *quite* follow the rule that the show instance should be a Haskell expression that evaluates to the given value—someModVal returns a Maybe—but this seems like the closest we can reasonably get.

Instance details

Defined in Data.Modular

Methods

showsPrec :: Int -> SomeMod i -> ShowS

show :: SomeMod i -> String

showList :: [SomeMod i] -> ShowS

someModVal Source #

Arguments

:: Integral i 
=> i

Underlying integer i

-> Integer

Modulus n

-> Maybe (SomeMod i) 

Convert an integral number i into SomeMod with the modulus given at runtime.

That is, given i :: ℤ, someModVal i modulus is equivalent to i :: ℤ/modulus except we don't know modulus statically.

>>> someModVal 10 4
Just (someModVal 2 4)

Will return Nothing if the modulus is 0 or negative:

>>> someModVal 10 (-10)
Nothing
>>> someModVal 10 0
Nothing