besout-0.2.0.0: Extended GCD of polynomials over F_p[x]

Safe HaskellSafe-Inferred

Bezout

Contents

Synopsis

Extended gcd of integers

besout :: Integer -> Integer -> [Integer]Source

besout compute extended gcd of two integers. For example : besout 13 17 = [4,-3,1] , this means that gcd of 13 and 17 is 1 and 1 could be written as linear combination of 13 and 17 as 1 = 4*13 - 3*17.

Modular inverse of integer

inverseMod :: Integer -> Integer -> IntegerSource

From besout identity we derive the modular inverse of an integer x modulo an integer y . Integers x and y must be relatively prime , otherwise inverseMod returns zero. For example : inverseMod 13 17 = 4 , inverseMod 17 13 = 10.

shift

shift :: Num a => Int -> [a] -> [a]Source

padding left with n zeros

pad

pad :: Num a => Int -> [a] -> [a]Source

padding right with n zeros

trim

trim :: (Eq a, Num a) => [a] -> [a]Source

trim

trim'

trim' :: (Eq t, Num t) => [t] -> [t]Source

trim'

deg

deg :: (Eq a, Num a) => [a] -> IntSource

degree of polynomial

(+:)

(+:) :: (Num a, Num b) => (a -> b -> c) -> [a] -> [b] -> [c]Source

(+:) add or abstract two list of different length

mods

mods :: Integer -> Integer -> IntegerSource

mods return positve remainder of mod operator

mMod

mMod :: [Integer] -> Integer -> [Integer]Source

mMod map mods over list of integers

Multiplication of polynomials in F_p[x]

multPolyZ :: Integer -> [Integer] -> [Integer] -> [Integer]Source

multPolyZ compute the product of two polynomial P Q in F_p[x]. Write ploynom P of degree n as a sequence of coefficients P = [an, a_(n-1),.., a_0]. To compute the product of polynomials P,Q we borrow the Horner multiplication rules as described by the following chain. It consists to do n compositions of functions detailed in the following diagramm: Q -> anxQ + a_(n-1)Q

R -> xR + a_(n-2)Q

R -> xR + a_(n-3)Q

R -> xR + a-1Q

...

R -> xR + a_0Q

Let f = [2,0,3,2,1::Integer], g = [2,5,-3,1::Integer] in F_7[x]. multPolyZ 7 f g = [4,3,0,0,3,2,6,1] . That means that f*g = 4*x^7 + 3*x^6 + 3*x^3 + 2*x^2 + 6*x + 1 in F_7[x]. This function require writing polynoms in decreasing order .

Euclidean division of polynomials for F_p[x]

euclideanPolyMod :: Integer -> [Integer] -> [Integer] -> [[Integer]]Source

euclidanPolyMod compute the quotient and remainder of euclidean division of polynomial P by Q in the ring F_p[x] where p is a prime number. Let f = [2,0,3,2,1::Integer], g = [2,5,-3,1::Integer] in F_7[x]. euclideanPolyMod 7 f g = [[1,1],[1,4,0]]. That means f = (x + 1 )*g + (x^2 + 4*x ) in F_7[x].

Extended gcd of polynomials in F_p[x]

extendedgcdpoly :: Integer -> [Integer] -> [Integer] -> [[Integer]]Source

extendedgcdpoly compute the extended gcd of polynomials P and Q in the ring F_p[x] where p is a prime number. Let f = [2,0,3,2,1::Integer], g = [2,5,-3,1::Integer] in F_7[x]. extendedgcdpoly 7 f g = [[5,3],[2,6,5],[2,1]] . This means that the gcd of f and g in F_7[x] is the polynom 2*x+1 , and

2 * x + 1 = (5 * x + 3) * f + (2 * x^2 + 6 * x + 5) * g in F_7[x].

Inverse of polynomial P modulo polynomial Q in F_p[x]

inversePolyMod :: Integer -> [Integer] -> [Integer] -> [Integer]Source

inversePolyMod compute the modular inverse of polynomial P(x) modulo Q(x) in F_p[x] . Polynomials P and Q must be relatively prime , otherwise it return [0]. Let f = [2,0,3,2,1::Integer], g = [2,5,-3,1::Integer] in F_13[x]. extendedgcdpoly 13 f g =[[7,3,7],[6,8,4,7],[1]]. So f and g are relatively prime in F_13[x] , and the inverse of f modulo g in F_13[x] is given by inversePolyMod 13 f g = [7,3,7] .

Which says that the inverse of ploynomial f denoted f^(-1) is 7*x^2 + 3*x + 7 modulo g in F_13[x]

Pretty form polynom input

prettyFormPoly :: [[Integer]] -> [Integer]Source

This is a facility for writing non nul terms of polynomial , if f = 5*x^13 + 4*x^5 + (-3)*x^4 + 11*x + 19 , then

prettyFormPoly [[5,13],[4,5],[-3,4],[11,1],[19,0]] = [5,0,0,0,0,0,0,0,4,-3,0,0,11,19]