| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Data.Modular
Description
Types for working with integers modulo some constant.
and its synonym Mod/ let you wrap arbitrary numeric types
in a modulus. To work with integers (mod 7) backed by Integer,
you could write:
Integer `Mod` 7 Integer/7 ℤ/7
(The last 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 extrac the underlying value with .unMod
Here is a quick example:
*Data.Modular> (10 :: ℤ/7) * (11 :: ℤ/7) 5
It also works correctly with negative numeric literals:
*Data.Modular> (-10 :: ℤ/7) * (11 :: ℤ/7) 2
To us type level numeric literals you need to enable the
DataKinds extension and to use infix syntax for Mod or the /
synonym, you need TypeOperators.
- unMod :: (i `Mod` n) -> i
- toMod :: forall n i. (Integral i, KnownNat n) => i -> i `Mod` n
- toMod' :: forall n i j. (Integral i, Integral j, KnownNat n) => i -> j `Mod` n
- data Mod i n
- inv :: forall n i. (KnownNat n, Integral i) => Mod i n -> Mod i n
- type (/) = Mod
- type ℤ = Integer
- modVal :: forall i proxy n. (Integral i, KnownNat n) => i -> proxy n -> Mod i n
- data SomeMod i
- someModVal :: Integral i => i -> Integer -> Maybe (SomeMod i)
Documentation
toMod :: forall n i. (Integral i, KnownNat n) => i -> i `Mod` n Source
Wraps the underlying type into the modular type, wrapping as appropriate.
toMod' :: forall n i j. (Integral i, Integral j, KnownNat n) => i -> j `Mod` n Source
Wraps an integral number to a mod, converting between integral types.
The actual type, wrapping an underlying Integeral type i in a
newtype annotated with the bound.
Instances
| (Integral i, KnownNat n) => Bounded (Mod i n) | |
| (Integral i, KnownNat n) => Enum (Mod i n) | |
| Eq i => Eq (Mod i n) | |
| (Integral i, KnownNat n) => Integral (Mod i n) | Integer division uses modular inverse |
| (Integral i, KnownNat n) => Num (Mod i n) | |
| Ord i => Ord (Mod i n) | |
| (Read i, Integral i, KnownNat n) => Read (Mod i n) | |
| (Integral i, KnownNat n) => Real (Mod i n) | |
| Show i => Show (Mod i n) |
inv :: forall n i. (KnownNat n, Integral i) => Mod i n -> Mod i n Source
The modular inverse.
Note that only numbers coprime to n have an inverse modulo n.
modVal :: forall i proxy n. (Integral i, KnownNat n) => i -> proxy n -> Mod i n Source
Convert an integral number i into a value given
modular bound Modn at type level.
This type represents a modular number with unknown bound.