padic-0.1.0.0: Fast, type-safe p-adic arithmetic
Copyright(c) Sergey Samoylenko 2022
LicenseGPL-3
Maintainersamsergey@yandex.ru
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Math.NumberTheory.Padic

Description

Module introduces p-adic integers and rationals with basic p-adic arithmetics and implments some specific functions (rational reconstruction, p-adic signum function, square roots etc.).

A truncated p-adic number \(x\) can be represented in three ways:

\[ \begin{align} x &= p^v u & (1)\\ & = d_0 + d_1 p + d_2 p^2 + ... d_k p^k & (2)\\ &= N\ \mathrm{mod}\ p^k, & (3) \end{align} \] where \(p > 1, k > 0, v \in \mathbb{Z},u \in \mathbb{Z_p},d_i \in \mathbb{Z}/p\mathbb{Z}, N \in \mathbb{Z}/p^k \mathbb{Z}\)

In order to gain efficiency the integer p-adic number with radix \(p\) is internally represented in form \((3)\) as only one digit \(N\), lifted to modulo \(p^k\), where \(k\) is chosen so that within working precision numbers belogning to Int and Ratio Int types could be reconstructed by extended Euclidean method. Form \((2)\) is used for textual output only, and form \((1)\) is used for transformations to and from rationals.

The documentation and the module bindings use following terminology:

  • radix -- modulus \(p\) of p-adic number,
  • precision -- maximal power \(k\) in p-adic expansion,
  • unit -- invertible muliplier \(u\) for prime \(p\),
  • valuation -- exponent \(v\),
  • digits -- list \(d_0,d_1,d_2,... d_k\) in the canonical p-adic expansion of a number,
  • lifted -- digit \(N\) lifted to modulo \(p^k\).

Rational p-adic number is represented as a unit (belonging to \(\mathbb{Z_p}\) ) and valuation, which may be negative.

The radix \(p\) of a p-adic number is specified at a type level via type-literals. In order to use them GHCi should be loaded with `-XDataKinds` extensions.

>>> :set -XDataKinds
>>> 45 :: Z 10
45
>>> 45 :: Q 5
140.0

Negative p-adic integers and rational p-adics have trailing periodic digit sequences, which are represented in parentheses.

>>> -45 :: Z 7
(6)04
>>> 1/7 :: Q 10
(285714)3.0

By default the precision of p-adics is computed so that it is possible to reconstruct integers and rationals using extended Euler's method. However precision could be specified explicitly via type-literal:

>>> sqrt 2 :: Q 7
…623164112011266421216213.0
>>> sqrt 2 :: Q' 7 5
…16213.0
>>> sqrt 2 :: Q' 7 50
…16244246442640361054365536623164112011266421216213.0

Between types defined in the module there are bijective mappings as shown in the diagram:

                       [Mod p]
                      /       \
             digits  /         \  digits
        fromDigits  /           \  fromDigits
                   /             \
    toInteger     /   fromUnit    \   fromRational
Z <-----------> Z p <----------> Q p <------------> Q
   fromInteger    \     unit      /    toRational
                   \             /
            lifted  \           /  lifted
             mkUnit  \         /  mkUnit
                      \       /
                      Integer
Synopsis

Data types

p-Adic integers

type Z p = Z' p (SufficientPrecision Word32 p) Source #

Integer p-adic number (an element of \(\mathbb{Z}_p\)) with default precision.

data Z' (p :: Nat) (prec :: Nat) Source #

Integer p-adic number with explicitly specified precision.

Instances

Instances details
Radix p prec => Enum (Z' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

Methods

succ :: Z' p prec -> Z' p prec #

pred :: Z' p prec -> Z' p prec #

toEnum :: Int -> Z' p prec #

fromEnum :: Z' p prec -> Int #

enumFrom :: Z' p prec -> [Z' p prec] #

enumFromThen :: Z' p prec -> Z' p prec -> [Z' p prec] #

enumFromTo :: Z' p prec -> Z' p prec -> [Z' p prec] #

enumFromThenTo :: Z' p prec -> Z' p prec -> Z' p prec -> [Z' p prec] #

Radix p prec => Eq (Z' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

Methods

(==) :: Z' p prec -> Z' p prec -> Bool #

(/=) :: Z' p prec -> Z' p prec -> Bool #

Radix p prec => Integral (Z' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

Methods

quot :: Z' p prec -> Z' p prec -> Z' p prec #

rem :: Z' p prec -> Z' p prec -> Z' p prec #

div :: Z' p prec -> Z' p prec -> Z' p prec #

mod :: Z' p prec -> Z' p prec -> Z' p prec #

quotRem :: Z' p prec -> Z' p prec -> (Z' p prec, Z' p prec) #

divMod :: Z' p prec -> Z' p prec -> (Z' p prec, Z' p prec) #

toInteger :: Z' p prec -> Integer #

Radix p prec => Num (Z' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

Methods

(+) :: Z' p prec -> Z' p prec -> Z' p prec #

(-) :: Z' p prec -> Z' p prec -> Z' p prec #

(*) :: Z' p prec -> Z' p prec -> Z' p prec #

negate :: Z' p prec -> Z' p prec #

abs :: Z' p prec -> Z' p prec #

signum :: Z' p prec -> Z' p prec #

fromInteger :: Integer -> Z' p prec #

Radix p prec => Ord (Z' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

Methods

compare :: Z' p prec -> Z' p prec -> Ordering #

(<) :: Z' p prec -> Z' p prec -> Bool #

(<=) :: Z' p prec -> Z' p prec -> Bool #

(>) :: Z' p prec -> Z' p prec -> Bool #

(>=) :: Z' p prec -> Z' p prec -> Bool #

max :: Z' p prec -> Z' p prec -> Z' p prec #

min :: Z' p prec -> Z' p prec -> Z' p prec #

Radix p prec => Real (Z' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

Methods

toRational :: Z' p prec -> Rational #

Radix p prec => Show (Z' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

Methods

showsPrec :: Int -> Z' p prec -> ShowS #

show :: Z' p prec -> String #

showList :: [Z' p prec] -> ShowS #

Radix p prec => PadicNum (Z' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

Associated Types

type Unit (Z' p prec) Source #

type Digit (Z' p prec) Source #

Methods

precision :: Integral i => Z' p prec -> i Source #

radix :: Integral i => Z' p prec -> i Source #

fromDigits :: [Digit (Z' p prec)] -> Z' p prec Source #

digits :: Z' p prec -> [Digit (Z' p prec)] Source #

lifted :: Z' p prec -> Integer Source #

mkUnit :: Integer -> Z' p prec Source #

fromUnit :: (Unit (Z' p prec), Int) -> Z' p prec Source #

splitUnit :: Z' p prec -> (Unit (Z' p prec), Int) Source #

isInvertible :: Z' p prec -> Bool Source #

inverse :: Z' p prec -> Maybe (Z' p prec) Source #

type Unit (Z' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

type Unit (Z' p prec) = Z' p prec
type Digit (Z' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

type Digit (Z' p prec) = Mod p

p-Adic rationals

type Q p = Q' p (SufficientPrecision Word32 p) Source #

Rational p-adic number (an element of \(\mathbb{Q}_p\)) with default precision.

data Q' (p :: Nat) (prec :: Nat) Source #

Rational p-adic number with explicitly specified precision.

Instances

Instances details
Radix p prec => Eq (Q' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

Methods

(==) :: Q' p prec -> Q' p prec -> Bool #

(/=) :: Q' p prec -> Q' p prec -> Bool #

Radix p prec => Floating (Q' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

Methods

pi :: Q' p prec #

exp :: Q' p prec -> Q' p prec #

log :: Q' p prec -> Q' p prec #

sqrt :: Q' p prec -> Q' p prec #

(**) :: Q' p prec -> Q' p prec -> Q' p prec #

logBase :: Q' p prec -> Q' p prec -> Q' p prec #

sin :: Q' p prec -> Q' p prec #

cos :: Q' p prec -> Q' p prec #

tan :: Q' p prec -> Q' p prec #

asin :: Q' p prec -> Q' p prec #

acos :: Q' p prec -> Q' p prec #

atan :: Q' p prec -> Q' p prec #

sinh :: Q' p prec -> Q' p prec #

cosh :: Q' p prec -> Q' p prec #

tanh :: Q' p prec -> Q' p prec #

asinh :: Q' p prec -> Q' p prec #

acosh :: Q' p prec -> Q' p prec #

atanh :: Q' p prec -> Q' p prec #

log1p :: Q' p prec -> Q' p prec #

expm1 :: Q' p prec -> Q' p prec #

log1pexp :: Q' p prec -> Q' p prec #

log1mexp :: Q' p prec -> Q' p prec #

Radix p prec => Fractional (Q' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

Methods

(/) :: Q' p prec -> Q' p prec -> Q' p prec #

recip :: Q' p prec -> Q' p prec #

fromRational :: Rational -> Q' p prec #

Radix p prec => Num (Q' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

Methods

(+) :: Q' p prec -> Q' p prec -> Q' p prec #

(-) :: Q' p prec -> Q' p prec -> Q' p prec #

(*) :: Q' p prec -> Q' p prec -> Q' p prec #

negate :: Q' p prec -> Q' p prec #

abs :: Q' p prec -> Q' p prec #

signum :: Q' p prec -> Q' p prec #

fromInteger :: Integer -> Q' p prec #

Radix p prec => Ord (Q' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

Methods

compare :: Q' p prec -> Q' p prec -> Ordering #

(<) :: Q' p prec -> Q' p prec -> Bool #

(<=) :: Q' p prec -> Q' p prec -> Bool #

(>) :: Q' p prec -> Q' p prec -> Bool #

(>=) :: Q' p prec -> Q' p prec -> Bool #

max :: Q' p prec -> Q' p prec -> Q' p prec #

min :: Q' p prec -> Q' p prec -> Q' p prec #

Radix p prec => Real (Q' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

Methods

toRational :: Q' p prec -> Rational #

Radix p prec => Show (Q' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

Methods

showsPrec :: Int -> Q' p prec -> ShowS #

show :: Q' p prec -> String #

showList :: [Q' p prec] -> ShowS #

Radix p prec => PadicNum (Q' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

Associated Types

type Unit (Q' p prec) Source #

type Digit (Q' p prec) Source #

Methods

precision :: Integral i => Q' p prec -> i Source #

radix :: Integral i => Q' p prec -> i Source #

fromDigits :: [Digit (Q' p prec)] -> Q' p prec Source #

digits :: Q' p prec -> [Digit (Q' p prec)] Source #

lifted :: Q' p prec -> Integer Source #

mkUnit :: Integer -> Q' p prec Source #

fromUnit :: (Unit (Q' p prec), Int) -> Q' p prec Source #

splitUnit :: Q' p prec -> (Unit (Q' p prec), Int) Source #

isInvertible :: Q' p prec -> Bool Source #

inverse :: Q' p prec -> Maybe (Q' p prec) Source #

type Unit (Q' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

type Unit (Q' p prec) = Z' p prec
type Digit (Q' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

type Digit (Q' p prec) = Digit (Z' p prec)

type family Padic num (p :: Nat) Source #

Type family for p-adic numbers with precision defined by reconstructable number type.

>>> 123456 :: Padic Int 7
1022634
>>> toInteger it
123456
>>> toRational (12345678987654321 :: Padic (Ratio Word16) 3)
537143292837 % 5612526479  -- insufficiend precision for proper reconstruction!!
>>> toRational (12345678987654321 :: Padic Rational 3)
12345678987654321 % 1

Instances

Instances details
type Padic Int p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

type Padic Integer p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

type Padic Rational p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

type Padic Word p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

type Padic Word8 p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

type Padic Word16 p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

type Padic Word32 p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

type Padic Word64 p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

type Padic (Ratio Int) p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

type Padic (Ratio Word) p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

type Padic (Ratio Word8) p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

type Padic (Ratio Word16) p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

type Padic (Ratio Word32) p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

type Padic (Ratio Word64) p Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

type family SufficientPrecision num (p :: Nat) :: Nat where ... Source #

Precision sufficient for rational reconstruction of number belonging to a type num. Used in a type declaration as follows:

>>> x = 1 `div` 1234567898765432123456789 :: Z 2 (Sufficientprecision Word32 2)
>>> toRational x
13822228938088947473 % 12702006275138148709
>>> x = 1 `div` 1234567898765432123456789 :: Z 2 (Sufficientprecision Int 2)
>>> toRational x
1 % 1234567898765432123456789

Classes and functions

Type synonyms and constraints

type family ValidRadix (m :: Nat) :: Constraint where ... Source #

Constraint for non-zero natural number which can be a radix.

Equations

ValidRadix 0 = TypeError ('Text "Zero radix!") 
ValidRadix 1 = TypeError ('Text "Radix should be more then 1!") 
ValidRadix m = () 

type KnownRadix m = (ValidRadix m, KnownNat m) Source #

Constraint for valid radix of a number

type family LiftedRadix p prec where ... Source #

Radix of the internal representation of integer p-adic number.

Equations

LiftedRadix p prec = p ^ ((2 * prec) + 1) 

type family Radix p prec :: Constraint where ... Source #

Constraint for known valid radix of p-adic number as well as it's lifted radix.

Equations

Radix p prec = (KnownNat prec, KnownRadix p, KnownRadix (LiftedRadix p prec)) 

p-adic numbers

class (Eq n, Num n) => PadicNum n Source #

Typeclass for p-adic numbers.

Instances

Instances details
KnownRadix p => PadicNum (Mod p) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Types

Associated Types

type Unit (Mod p) Source #

type Digit (Mod p) Source #

Methods

precision :: Integral i => Mod p -> i Source #

radix :: Integral i => Mod p -> i Source #

fromDigits :: [Digit (Mod p)] -> Mod p Source #

digits :: Mod p -> [Digit (Mod p)] Source #

lifted :: Mod p -> Integer Source #

mkUnit :: Integer -> Mod p Source #

fromUnit :: (Unit (Mod p), Int) -> Mod p Source #

splitUnit :: Mod p -> (Unit (Mod p), Int) Source #

isInvertible :: Mod p -> Bool Source #

inverse :: Mod p -> Maybe (Mod p) Source #

Radix p prec => PadicNum (Z' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

Associated Types

type Unit (Z' p prec) Source #

type Digit (Z' p prec) Source #

Methods

precision :: Integral i => Z' p prec -> i Source #

radix :: Integral i => Z' p prec -> i Source #

fromDigits :: [Digit (Z' p prec)] -> Z' p prec Source #

digits :: Z' p prec -> [Digit (Z' p prec)] Source #

lifted :: Z' p prec -> Integer Source #

mkUnit :: Integer -> Z' p prec Source #

fromUnit :: (Unit (Z' p prec), Int) -> Z' p prec Source #

splitUnit :: Z' p prec -> (Unit (Z' p prec), Int) Source #

isInvertible :: Z' p prec -> Bool Source #

inverse :: Z' p prec -> Maybe (Z' p prec) Source #

Radix p prec => PadicNum (Q' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

Associated Types

type Unit (Q' p prec) Source #

type Digit (Q' p prec) Source #

Methods

precision :: Integral i => Q' p prec -> i Source #

radix :: Integral i => Q' p prec -> i Source #

fromDigits :: [Digit (Q' p prec)] -> Q' p prec Source #

digits :: Q' p prec -> [Digit (Q' p prec)] Source #

lifted :: Q' p prec -> Integer Source #

mkUnit :: Integer -> Q' p prec Source #

fromUnit :: (Unit (Q' p prec), Int) -> Q' p prec Source #

splitUnit :: Q' p prec -> (Unit (Q' p prec), Int) Source #

isInvertible :: Q' p prec -> Bool Source #

inverse :: Q' p prec -> Maybe (Q' p prec) Source #

type family Unit n Source #

A type for p-adic unit.

Instances

Instances details
type Unit (Mod p) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Types

type Unit (Mod p) = Mod p
type Unit (Z' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

type Unit (Z' p prec) = Z' p prec
type Unit (Q' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

type Unit (Q' p prec) = Z' p prec

type family Digit n Source #

A type for digits of p-adic expansion. Associated type allows to assure that digits will agree with the radix p of the number.

Instances

Instances details
type Digit (Mod p) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Types

type Digit (Mod p) = Mod p
type Digit (Z' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Integer

type Digit (Z' p prec) = Mod p
type Digit (Q' p prec) Source # 
Instance details

Defined in Math.NumberTheory.Padic.Rational

type Digit (Q' p prec) = Digit (Z' p prec)

Functions and utilities

p-adic numbers and arithmetics

radix :: (PadicNum n, Integral i) => n -> i Source #

Returns the radix of a number

Examples:

>>> radix (5 :: Z 13)
13
>>> radix (-5 :: Q' 3 40)
3

precision :: (PadicNum n, Integral i) => n -> i Source #

Returns the precision of a number.

Examples:

>>> precision (123 :: Z 2)
20
>>> precision (123 :: Z' 2 40)
40

digits :: PadicNum n => n -> [Digit n] Source #

Returns digits of a digital object

Examples:

>>> digits (123 :: Z 10)
[(3 `modulo` 10),(2 `modulo` 10),(1 `modulo` 10),(0 `modulo` 10),(0 `modulo` 10)]
>>> take 5 $ digits (-123 :: Z 2)
[(1 `modulo` 2),(0 `modulo` 2),(1 `modulo` 2),(0 `modulo` 2),(0 `modulo` 2)]
>>> take 5 $ digits (1/300 :: Q 10)
[(7 `modulo` 10),(6 `modulo` 10),(6 `modulo` 10),(6 `modulo` 10),(6 `modulo` 10)]

firstDigit :: PadicNum n => n -> Digit n Source #

The least significant digit of a p-adic number. -- -- >>> firstDigit (123 :: Z 10) -- (3 modulo 10) -- >>> firstDigit (123 :: Z 257) -- (123 modulo 257)

reduce :: (KnownRadix p, PadicNum n) => n -> Mod p Source #

Returns p-adic number reduced modulo p

>>> reduce (123 :: Z 10) :: Mod 100
(23 `modulo` 100)

fromDigits :: PadicNum n => [Digit n] -> n Source #

Constructor for a digital object from it's digits

lifted :: PadicNum n => n -> Integer Source #

Returns lifted digits

Examples:

>>> lifted (123 :: Z 10)
123
>>> lifted (-123 :: Z 10)
9999999999999999999999999999999999999999877

mkUnit :: PadicNum n => Integer -> n Source #

Creates digital object from it's lifted digits.

splitUnit :: PadicNum n => n -> (Unit n, Int) Source #

Splits p-adic number into unit and valuation.

splitUnit (u * p^v) = (u, v)

fromUnit :: PadicNum n => (Unit n, Int) -> n Source #

Creates p-adic number from given unit and valuation.

fromUnit (u, v) = u * p^v

unit :: PadicNum n => n -> Unit n Source #

Returns the p-adic unit of a number

Examples:

>>> unit (120 :: Z 10)
12
>>> unit (75 :: Z 5)
3 

valuation :: PadicNum n => n -> Int Source #

Returns a p-adic valuation of a number

Examples:

>>> valuation (120 :: Z 10)
1
>>> valuation (75 :: Z 5)
2

Valuation of zero is equal to working precision

>>> valuation (0 :: Q 2)
64
>>> valuation (0 :: Q 10)
21 

norm :: (Integral i, PadicNum n) => n -> Ratio i Source #

Returns a rational p-adic norm of a number \(|x|_p\).

Examples:

>>> norm (120 :: Z 10)
0.1
>>> norm (75 :: Z 5)
4.0e-2

normalize :: PadicNum n => n -> n Source #

Adjusts unit and valuation of p-adic number, by removing trailing zeros from the right-side of the unit.

Examples:

>>> λ> x = 2313 + 1387 :: Q 10
>>> x
3700.0
>>> splitUnit x
(3700,0)
>>> splitUnit (normalize x)
(37,2) 

inverse :: PadicNum n => n -> Maybe n Source #

Partial multiplicative inverse of p-adic number (defined both for integer or rational p-adics).

isInvertible :: PadicNum n => n -> Bool Source #

Returns True for a p-adic number which is multiplicatively invertible.

isZero :: PadicNum n => n -> Bool Source #

Returns True for a p-adic number which is equal to zero (within it's precision).

getUnitZ :: (Integral p, Integral n) => p -> n -> (p, Int) Source #

Extracts p-adic unit from integer number. For radix \(p\) and integer \(n\) returns pair \((u, k)\) such that \(n = u \cdot p^k\).

Examples:

>>> getUnitZ  10 120
(12,1)
>>> getUnitZ 2 120
(15,3)
>>> getUnitZ 3 120
(40,1)

getUnitQ :: Integral p => p -> Ratio p -> (Ratio p, Int) Source #

Extracts p-adic unit from a rational number. For radix \(p\) and rational number \(x\) returns pair \((r/s, k)\) such that \(x = r/s \cdot p^k,\quad \gcd(r, s) = \gcd(s, p) = 1\) and \(p \nmid r\).

Examples:

>>> getUnitQ 3 (75/157)
(25 % 157, 1)
>>> getUnitQ 5 (75/157)
(3 % 157, 2)
>>> getUnitQ 157 (75/157)
(75 % 1, -1)
>>> getUnitQ 10 (1/60)
(5 % 3, -2)

p-adic analysis

findSolutionMod :: (PadicNum n, KnownRadix p, Digit n ~ Mod p) => (n -> n) -> [n] Source #

Returns solution of the equation \(f(x) = 0\ \mathrm{mod}\ p\) in p-adics. Used as a first step if henselLifting function and is usefull for introspection.

>>> findSolutionMod (\x -> x*x - 2) :: [Z 7]
[3,4]
>>> findSolutionMod (\x -> x*x - x) :: [Q 10]
[0.0,1.0,5.0,6.0]

henselLifting Source #

Arguments

:: (Eq n, PadicNum n, KnownRadix p, Digit n ~ Mod p) 
=> (n -> n)

Function to be vanished.

-> (n -> n)

Derivative of the function.

-> [n]

The result.

Returns p-adic solutions (if any) of the equation \(f(x) = 0\) using Hensel lifting method. First, solutions of \(f(x) = 0\ \mathrm{mod}\ p\) are found, then by Newton's method this solution is get lifted to p-adic number (up to specified precision).

Examples:

>>> henselLifting (\x -> x*x - 2) (\x -> 2*x) :: [Z 7]
[…64112011266421216213,…02554655400245450454]
>>> henselLifting (\x -> x*x - x) (\x -> 2*x-1) :: [Q 10]
[0,1,…92256259918212890625,…07743740081787109376]

unityRoots :: (KnownRadix p, PadicNum n, Digit n ~ Mod p) => Integer -> [n] Source #

Returns a list of m-th roots of unity.

pSqrt :: (Fractional n, PadicNum n, KnownRadix p, Digit n ~ Mod p) => n -> [n] Source #

Returns p-adic square root, calculated for odd radix via Hensel lifting, and for \(p=2\) by recurrent product.

pPow :: (PadicNum p, Fractional p) => p -> p -> Either String p Source #

Exponentiation for p-adic numbers, calculated as

\[ x^y = e^{y \log x}, \]

with convergence, corresponding to pExp and pLog functions.

zPow :: Radix p prec => Z' p prec -> Z' p prec -> Z' p prec Source #

Integer power function (analog of (^) operator )

pExp :: (Eq n, PadicNum n, Fractional n) => n -> Either String n Source #

Returns p-adic exponent function, calculated via Taylor series. For given radix \(p\) converges for numbers which satisfy inequality:

\[|x|_p < p^\frac{1}{1-p}.\]

pLog :: (Eq b, PadicNum b, Fractional b) => b -> Either String b Source #

Returns p-adic logarithm function, calculated via Taylor series. For given radix \(p\) converges for numbers which satisfy inequality:

\[|x|_p < 1.\]

pSin :: (PadicNum b, Fractional b) => b -> Either [Char] b Source #

Returns p-adic hyperbolic cosine function, calculated via Taylor series. For given radix \(p\) converges for numbers which satisfy inequality:

\[|x|_p < p^\frac{1}{1-p}.\]

pCos :: (PadicNum b, Fractional b) => b -> Either [Char] b Source #

Returns p-adic cosine function, calculated via Taylor series. For given radix \(p\) converges for numbers which satisfy inequality:

\[|x|_p < p^\frac{1}{1-p}.\]

pSinh :: (PadicNum b, Fractional b) => b -> Either [Char] b Source #

Returns p-adic hyperbolic sine function, calculated via Taylor series. For given radix \(p\) converges for numbers which satisfy inequality:

\[|x|_p < p^\frac{1}{1-p}.\]

pCosh :: (PadicNum b, Fractional b) => b -> Either [Char] b Source #

Returns p-adic hyperbolic cosine function, calculated via Taylor series. For given radix \(p\) converges for numbers which satisfy inequality:

\[|x|_p < p^\frac{1}{1-p}.\]

pTanh :: (Fractional b, PadicNum b) => b -> Either [Char] b Source #

Returns p-adic hyperbolic tan function, calculated as

\[\mathrm{tanh}\ x = \frac{\mathrm{sinh}\ x}{\mathrm{cosh}\ x},\]

with convergence, corresponding to pSinh and pCosh functions.

pAsin :: (Fractional b, PadicNum b) => b -> Either [Char] b Source #

Returns p-adic arcsine function, calculated via Taylor series. For given radix \(p\) converges for numbers which satisfy inequality:

\[|x|_p < 1.\]

pAsinh :: (PadicNum b, Fractional b) => b -> Either String b Source #

Returns p-adic inverse hyperbolic sine function, calculated as

\[\mathrm{sinh}^{ -1} x = \log(x + \sqrt{x^2+1})\]

with convergence, corresponding to pLog and pPow functions.

pAcosh :: (PadicNum b, Fractional b) => b -> Either String b Source #

Returns p-adic inverse hyperbolic cosine function, calculated as

\[\mathrm{cosh}^{ -1}\ x = \log(x + \sqrt{x^2-1}),\]

with convergence, corresponding to pLog and pPow functions.

pAtanh :: (PadicNum b, Fractional b) => b -> Either String b Source #

Returns p-adic inverse hyperbolic tan function, calculated as

\[\mathrm{tanh}^{ -1 }\ x = \frac{1}{2} \log\left(\frac{x + 1}{x - 1}\right)\]

with convergence, corresponding to pLog function.

Miscelleneos tools

fromRadix :: KnownRadix p => [Mod p] -> Integer Source #

Folds a list of digits (integers modulo p) to a number.

toRadix :: KnownRadix p => Integer -> [Mod p] Source #

Unfolds a number to a list of digits (integers modulo p).

findCycle :: Eq a => Int -> [a] -> Maybe ([a], [a]) Source #

For a given list extracts prefix and a cycle, limiting length of prefix and cycle by len. Uses the modified tortiose-and-hare method.

sufficientPrecision :: Integral a => Integer -> a -> Integer Source #

For given radix \(p\) and natural number \(m\) returns precision sufficient for rational reconstruction of fractions with numerator and denominator not exceeding \(m\).

Examples:

>>> sufficientPrecision 2 (maxBound :: Int)
64
>>> sufficientPrecision 3 (maxBound :: Int)
41
>>> sufficientPrecision 10 (maxBound :: Int)
20