Flint2-0.1.0.5: Haskell bindings for the flint library for number theory
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Number.Flint.NMod.MPoly

Synopsis

Multivariate polynomials over integers mod n (word-size n)

Context object

nmod_mpoly_ctx_init :: Ptr CNModMPolyCtx -> CLong -> Ptr COrdering -> CMpLimb -> IO () Source #

nmod_mpoly_ctx_init ctx nvars ord n

Initialise a context object for a polynomial ring with the given number of variables and the given ordering. It will have coefficients modulo n. Setting \(n = 0\) will give undefined behavior. The possibilities for the ordering are ORD_LEX, ORD_DEGLEX and ORD_DEGREVLEX.

nmod_mpoly_ctx_nvars :: Ptr CNModMPolyCtx -> IO CLong Source #

nmod_mpoly_ctx_nvars ctx

Return the number of variables used to initialize the context.

nmod_mpoly_ctx_ord :: Ptr CNModMPolyCtx -> IO (Ptr COrdering) Source #

nmod_mpoly_ctx_ord ctx

Return the ordering used to initialize the context.

nmod_mpoly_ctx_modulus :: Ptr CNModMPolyCtx -> IO CMpLimb Source #

nmod_mpoly_ctx_modulus ctx

Return the modulus used to initialize the context.

nmod_mpoly_ctx_clear :: Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_ctx_clear ctx

Release any space allocated by ctx.

Memory management

nmod_mpoly_init :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_init A ctx

Initialise A for use with the given an initialised context object. Its value is set to zero.

nmod_mpoly_init2 :: Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_init2 A alloc ctx

Initialise A for use with the given an initialised context object. Its value is set to zero. It is allocated with space for alloc terms and at least MPOLY_MIN_BITS bits for the exponent widths.

nmod_mpoly_init3 :: Ptr CNModMPoly -> CLong -> CFBitCnt -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_init3 A alloc bits ctx

Initialise A for use with the given an initialised context object. Its value is set to zero. It is allocated with space for alloc terms and bits bits for the exponents.

nmod_mpoly_fit_length :: Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_fit_length A len ctx

Ensure that A has space for at least len terms.

nmod_mpoly_realloc :: Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_realloc A alloc ctx

Reallocate A to have space for alloc terms. Assumes the current length of the polynomial is not greater than alloc.

nmod_mpoly_clear :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_clear A ctx

Release any space allocated for A.

Input/Output

nmod_mpoly_get_str_pretty :: Ptr CNModMPoly -> Ptr (Ptr CChar) -> Ptr CNModMPolyCtx -> IO CString Source #

nmod_mpoly_get_str_pretty A x ctx

Return a string, which the user is responsible for cleaning up, representing A, given an array of variable strings x.

nmod_mpoly_fprint_pretty :: Ptr CFile -> Ptr CNModMPoly -> Ptr (Ptr CChar) -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_fprint_pretty file A x ctx

Print a string representing A to file.

nmod_mpoly_print_pretty :: Ptr CNModMPoly -> Ptr (Ptr CChar) -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_print_pretty A x ctx

Print a string representing A to stdout.

nmod_mpoly_set_str_pretty :: Ptr CNModMPoly -> CString -> Ptr (Ptr CChar) -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_set_str_pretty A str x ctx

Set A to the polynomial in the null-terminates string str given an array x of variable strings. If parsing str fails, A is set to zero, and \(-1\) is returned. Otherwise, \(0\) is returned. The operations +, -, *, and / are permitted along with integers and the variables in x. The character ^ must be immediately followed by the (integer) exponent. If any division is not exact, parsing fails.

Basic manipulation

nmod_mpoly_gen :: Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_gen A var ctx

Set A to the variable of index var, where \(var = 0\) corresponds to the variable with the most significance with respect to the ordering.

nmod_mpoly_is_gen :: Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_is_gen A var ctx

If \(var \ge 0\), return \(1\) if A is equal to the \(var\)-th generator, otherwise return \(0\). If \(var < 0\), return \(1\) if the polynomial is equal to any generator, otherwise return \(0\).

nmod_mpoly_set :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_set A B ctx

Set A to B.

nmod_mpoly_equal :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_equal A B ctx

Return \(1\) if A is equal to B, else return \(0\).

nmod_mpoly_swap :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_swap A B ctx

Efficiently swap A and B.

Constants

nmod_mpoly_is_ui :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_is_ui A ctx

Return \(1\) if A is a constant, else return \(0\).

nmod_mpoly_get_ui :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CULong Source #

nmod_mpoly_get_ui A ctx

Assuming that A is a constant, return this constant. This function throws if A is not a constant.

nmod_mpoly_set_ui :: Ptr CNModMPoly -> CULong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_set_ui A c ctx

Set A to the constant c.

nmod_mpoly_zero :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_zero A ctx

Set A to the constant \(0\).

nmod_mpoly_one :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_one A ctx

Set A to the constant \(1\).

nmod_mpoly_equal_ui :: Ptr CNModMPoly -> CULong -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_equal_ui A c ctx

Return \(1\) if A is equal to the constant c, else return \(0\).

nmod_mpoly_is_zero :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_is_zero A ctx

Return \(1\) if A is the constant \(0\), else return \(0\).

nmod_mpoly_is_one :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_is_one A ctx

Return \(1\) if A is the constant \(1\), else return \(0\).

Degrees

nmod_mpoly_degrees_fit_si :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_degrees_fit_si A ctx

Return \(1\) if the degrees of A with respect to each variable fit into an slong, otherwise return \(0\).

nmod_mpoly_degrees_fmpz :: Ptr (Ptr CFmpz) -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_degrees_fmpz degs A ctx

nmod_mpoly_degrees_si :: Ptr CLong -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_degrees_si degs A ctx

Set degs to the degrees of A with respect to each variable. If A is zero, all degrees are set to \(-1\).

nmod_mpoly_degree_fmpz :: Ptr CFmpz -> Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_degree_fmpz deg A var ctx

nmod_mpoly_degree_si :: Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO CLong Source #

nmod_mpoly_degree_si A var ctx

Either return or set deg to the degree of A with respect to the variable of index var. If A is zero, the degree is defined to be \(-1\).

nmod_mpoly_total_degree_fits_si :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_total_degree_fits_si A ctx

Return \(1\) if the total degree of A fits into an slong, otherwise return \(0\).

nmod_mpoly_total_degree_fmpz :: Ptr CFmpz -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_total_degree_fmpz tdeg A ctx

nmod_mpoly_total_degree_si :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CLong Source #

nmod_mpoly_total_degree_si A ctx

Either return or set tdeg to the total degree of A. If A is zero, the total degree is defined to be \(-1\).

nmod_mpoly_used_vars :: Ptr CInt -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_used_vars used A ctx

For each variable index i, set used[i] to nonzero if the variable of index i appears in A and to zero otherwise.

Coefficients

nmod_mpoly_get_coeff_ui_monomial :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CULong Source #

nmod_mpoly_get_coeff_ui_monomial A M ctx

Assuming that M is a monomial, return the coefficient of the corresponding monomial in A. This function throws if M is not a monomial.

nmod_mpoly_set_coeff_ui_monomial :: Ptr CNModMPoly -> CULong -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_set_coeff_ui_monomial A c M ctx

Assuming that M is a monomial, set the coefficient of the corresponding monomial in A to c. This function throws if M is not a monomial.

nmod_mpoly_get_coeff_ui_fmpz :: Ptr CNModMPoly -> Ptr (Ptr CFmpz) -> Ptr CNModMPolyCtx -> IO CULong Source #

nmod_mpoly_get_coeff_ui_fmpz A exp ctx

nmod_mpoly_get_coeff_ui_ui :: Ptr CNModMPoly -> Ptr CULong -> Ptr CNModMPolyCtx -> IO CULong Source #

nmod_mpoly_get_coeff_ui_ui A exp ctx

Return the coefficient of the monomial with exponent exp.

nmod_mpoly_set_coeff_ui_fmpz :: Ptr CNModMPoly -> CULong -> Ptr (Ptr CFmpz) -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_set_coeff_ui_fmpz A c exp ctx

nmod_mpoly_set_coeff_ui_ui :: Ptr CNModMPoly -> CULong -> Ptr CULong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_set_coeff_ui_ui A c exp ctx

Set the coefficient of the monomial with exponent exp to \(c\).

nmod_mpoly_get_coeff_vars_ui :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CLong -> Ptr CULong -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_get_coeff_vars_ui C A vars exps length ctx

Set C to the coefficient of A with respect to the variables in vars with powers in the corresponding array exps. Both vars and exps point to array of length length. It is assumed that 0 < length \le nvars(A) and that the variables in vars are distinct.

Comparison

nmod_mpoly_cmp :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_cmp A B ctx

Return \(1\) (resp. \(-1\), or \(0\)) if A is after (resp. before, same as) B in some arbitrary but fixed total ordering of the polynomials. This ordering agrees with the usual ordering of monomials when A and B are both monomials.

Container operations

nmod_mpoly_term_coeff_ref :: Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO (Ptr CMpLimb) Source #

nmod_mpoly_term_coeff_ref A i ctx

Return a reference to the coefficient of index i of A.

nmod_mpoly_is_canonical :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_is_canonical A ctx

Return \(1\) if A is in canonical form. Otherwise, return \(0\). To be in canonical form, all of the terms must have nonzero coefficients, and the terms must be sorted from greatest to least.

nmod_mpoly_length :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CLong Source #

nmod_mpoly_length A ctx

Return the number of terms in A. If the polynomial is in canonical form, this will be the number of nonzero coefficients.

nmod_mpoly_resize :: Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_resize A new_length ctx

Set the length of A to new_length. Terms are either deleted from the end, or new zero terms are appended.

nmod_mpoly_get_term_coeff_ui :: Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO CULong Source #

nmod_mpoly_get_term_coeff_ui A i ctx

Return the coefficient of the term of index i.

nmod_mpoly_set_term_coeff_ui :: Ptr CNModMPoly -> CLong -> CULong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_set_term_coeff_ui A i c ctx

Set the coefficient of the term of index i to c.

nmod_mpoly_term_exp_fits_si :: Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_term_exp_fits_si A i ctx

nmod_mpoly_term_exp_fits_ui :: Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_term_exp_fits_ui A i ctx

Return \(1\) if all entries of the exponent vector of the term of index i fit into an slong (resp. a ulong). Otherwise, return \(0\).

nmod_mpoly_get_term_exp_fmpz :: Ptr (Ptr CFmpz) -> Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_get_term_exp_fmpz exp A i ctx

nmod_mpoly_get_term_exp_ui :: Ptr CULong -> Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_get_term_exp_ui exp A i ctx

nmod_mpoly_get_term_exp_si :: Ptr CLong -> Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_get_term_exp_si exp A i ctx

Set exp to the exponent vector of the term of index i. The _ui (resp. _si) version throws if any entry does not fit into a ulong (resp. slong).

nmod_mpoly_get_term_var_exp_ui :: Ptr CNModMPoly -> CLong -> CLong -> Ptr CNModMPolyCtx -> IO CULong Source #

nmod_mpoly_get_term_var_exp_ui A i var ctx

nmod_mpoly_get_term_var_exp_si :: Ptr CNModMPoly -> CLong -> CLong -> Ptr CNModMPolyCtx -> IO CLong Source #

nmod_mpoly_get_term_var_exp_si A i var ctx

Return the exponent of the variable var of the term of index i. This function throws if the exponent does not fit into a ulong (resp. slong).

nmod_mpoly_set_term_exp_fmpz :: Ptr CNModMPoly -> CLong -> Ptr (Ptr CFmpz) -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_set_term_exp_fmpz A i exp ctx

nmod_mpoly_set_term_exp_ui :: Ptr CNModMPoly -> CLong -> Ptr CULong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_set_term_exp_ui A i exp ctx

Set the exponent of the term of index i to exp.

nmod_mpoly_get_term :: Ptr CNModMPoly -> Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_get_term M A i ctx

Set M to the term of index i in A.

nmod_mpoly_get_term_monomial :: Ptr CNModMPoly -> Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_get_term_monomial M A i ctx

Set M to the monomial of the term of index i in A. The coefficient of M will be one.

nmod_mpoly_push_term_ui_fmpz :: Ptr CNModMPoly -> CULong -> Ptr (Ptr CFmpz) -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_push_term_ui_fmpz A c exp ctx

nmod_mpoly_push_term_ui_ui :: Ptr CNModMPoly -> CULong -> Ptr CULong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_push_term_ui_ui A c exp ctx

Append a term to A with coefficient c and exponent vector exp. This function runs in constant average time.

nmod_mpoly_sort_terms :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_sort_terms A ctx

Sort the terms of A into the canonical ordering dictated by the ordering in ctx. This function simply reorders the terms: It does not combine like terms, nor does it delete terms with coefficient zero. This function runs in linear time in the bit size of A.

nmod_mpoly_combine_like_terms :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_combine_like_terms A ctx

Combine adjacent like terms in A and delete terms with coefficient zero. If the terms of A were sorted to begin with, the result will be in canonical form. This function runs in linear time in the bit size of A.

nmod_mpoly_reverse :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_reverse A B ctx

Set A to the reversal of B.

Random generation

nmod_mpoly_randtest_bound :: Ptr CNModMPoly -> Ptr CFRandState -> CLong -> CULong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_randtest_bound A state length exp_bound ctx

Generate a random polynomial with length up to length and exponents in the range [0, exp_bound - 1]. The exponents of each variable are generated by calls to n_randint(state, exp_bound).

nmod_mpoly_randtest_bounds :: Ptr CNModMPoly -> Ptr CFRandState -> CLong -> CULong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_randtest_bounds A state length exp_bounds ctx

Generate a random polynomial with length up to length and exponents in the range [0, exp_bounds[i] - 1]. The exponents of the variable of index i are generated by calls to n_randint(state, exp_bounds[i]).

nmod_mpoly_randtest_bits :: Ptr CNModMPoly -> Ptr CFRandState -> CLong -> CMpLimb -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_randtest_bits A state length exp_bits ctx

Generate a random polynomial with length up to length and exponents whose packed form does not exceed the given bit count.

Addition/Subtraction

nmod_mpoly_add_ui :: Ptr CNModMPoly -> Ptr CNModMPoly -> CULong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_add_ui A B c ctx

Set A to \(B + c\).

nmod_mpoly_sub_ui :: Ptr CNModMPoly -> Ptr CNModMPoly -> CULong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_sub_ui A B c ctx

Set A to \(B - c\).

nmod_mpoly_add :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_add A B C ctx

Set A to \(B + C\).

nmod_mpoly_sub :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_sub A B C ctx

Set A to \(B - C\).

Scalar operations

nmod_mpoly_neg :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_neg A B ctx

Set A to \(-B\).

nmod_mpoly_scalar_mul_ui :: Ptr CNModMPoly -> Ptr CNModMPoly -> CULong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_scalar_mul_ui A B c ctx

Set A to \(B \times c\).

nmod_mpoly_make_monic :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_make_monic A B ctx

Set A to B divided by the leading coefficient of B. This throws if B is zero or the leading coefficient is not invertible.

Differentiation

nmod_mpoly_derivative :: Ptr CNModMPoly -> Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_derivative A B var ctx

Set A to the derivative of B with respect to the variable of index var.

Evaluation

nmod_mpoly_evaluate_all_ui :: Ptr CNModMPoly -> Ptr CULong -> Ptr CNModMPolyCtx -> IO CULong Source #

nmod_mpoly_evaluate_all_ui A vals ctx

Return the evaluation of A where the variables are replaced by the corresponding elements of the array vals.

nmod_mpoly_evaluate_one_ui :: Ptr CNModMPoly -> Ptr CNModMPoly -> CULong -> CULong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_evaluate_one_ui A B var val ctx

Set A to the evaluation of B where the variable of index var is replaced by val.

nmod_mpoly_compose_nmod_poly :: Ptr CNModPoly -> Ptr CNModMPoly -> Ptr (Ptr (Ptr CNModPoly)) -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_compose_nmod_poly A B C ctx

Set A to the evaluation of B where the variables are replaced by the corresponding elements of the array C. The context object of B is ctxB. Return \(1\) for success and \(0\) for failure.

nmod_mpoly_compose_nmod_mpoly_geobucket :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr (Ptr (Ptr CNModMPoly)) -> Ptr CNModMPolyCtx -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_compose_nmod_mpoly_geobucket A B C ctxB ctxAC

nmod_mpoly_compose_nmod_mpoly_horner :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr (Ptr (Ptr CNModMPoly)) -> Ptr CNModMPolyCtx -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_compose_nmod_mpoly_horner A B C ctxB ctxAC

nmod_mpoly_compose_nmod_mpoly :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr (Ptr (Ptr CNModMPoly)) -> Ptr CNModMPolyCtx -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_compose_nmod_mpoly A B C ctxB ctxAC

Set A to the evaluation of B where the variables are replaced by the corresponding elements of the array C. Both A and the elements of C have context object ctxAC, while B has context object ctxB. Neither of A and B is allowed to alias any other polynomial. Return \(1\) for success and \(0\) for failure. The main method attempts to perform the calculation using matrices and chooses heuristically between the geobucket and horner methods if needed.

nmod_mpoly_compose_nmod_mpoly_gen :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CLong -> Ptr CNModMPolyCtx -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_compose_nmod_mpoly_gen A B c ctxB ctxAC

Set A to the evaluation of B where the variable of index i in ctxB is replaced by the variable of index c[i] in ctxAC. The length of the array C is the number of variables in ctxB. If any c[i] is negative, the corresponding variable of B is replaced by zero. Otherwise, it is expected that c[i] is less than the number of variables in ctxAC.

Multiplication

nmod_mpoly_mul :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_mul A B C ctx

Set A to \(B \times C\).

nmod_mpoly_mul_johnson :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_mul_johnson A B C ctx

nmod_mpoly_mul_heap_threaded :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_mul_heap_threaded A B C ctx

Set A to \(B \times C\) using Johnson's heap-based method. The first version always uses one thread.

nmod_mpoly_mul_array_threaded :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_mul_array_threaded A B C ctx

Try to set A to \(B \times C\) using arrays. If the return is \(0\), the operation was unsuccessful. Otherwise, it was successful, and the return is \(1\). The first version always uses one thread.

nmod_mpoly_mul_dense :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_mul_dense A B C ctx

Try to set A to \(B \times C\) using univariate arithmetic. If the return is \(0\), the operation was unsuccessful. Otherwise, it was successful and the return is \(1\).

Powering

nmod_mpoly_pow_fmpz :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CFmpz -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_pow_fmpz A B k ctx

Set A to B raised to the k-th power. Return \(1\) for success and \(0\) for failure.

nmod_mpoly_pow_ui :: Ptr CNModMPoly -> Ptr CNModMPoly -> CULong -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_pow_ui A B k ctx

Set A to B raised to the k-th power. Return \(1\) for success and \(0\) for failure.

Division

nmod_mpoly_divides :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_divides Q A B ctx

If A is divisible by B, set Q to the exact quotient and return \(1\). Otherwise, set Q to zero and return \(0\). Note that the function nmod_mpoly_div below may be faster if the quotient is known to be exact.

nmod_mpoly_div :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_div Q A B ctx

Set Q to the quotient of A by B, discarding the remainder.

nmod_mpoly_divrem :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_divrem Q R A B ctx

Set Q and R to the quotient and remainder of A divided by B.

nmod_mpoly_divrem_ideal :: Ptr (Ptr (Ptr CNModMPoly)) -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr (Ptr (Ptr CNModMPoly)) -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_divrem_ideal Q R A B len ctx

This function is as per nmod_mpoly_divrem except that it takes an array of divisor polynomials B and it returns an array of quotient polynomials Q. The number of divisor (and hence quotient) polynomials, is given by len.

nmod_mpoly_divides_dense :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_divides_dense Q A B ctx

Try to do the operation of nmod_mpoly_divides using univariate arithmetic. If the return is \(-1\), the operation was unsuccessful. Otherwise, it was successful and the return is \(0\) or \(1\).

nmod_mpoly_divides_monagan_pearce :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_divides_monagan_pearce Q A B ctx

Do the operation of nmod_mpoly_divides using the algorithm of Michael Monagan and Roman Pearce.

nmod_mpoly_divides_heap_threaded :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_divides_heap_threaded Q A B ctx

Do the operation of nmod_mpoly_divides using a heap and multiple threads. This function should only be called once global_thread_pool has been initialized.

Greatest Common Divisor

nmod_mpoly_term_content :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_term_content M A ctx

Set M to the GCD of the terms of A. If A is zero, M will be zero. Otherwise, M will be a monomial with coefficient one.

nmod_mpoly_content_vars :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CLong -> CLong -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_content_vars g A vars vars_length ctx

Set g to the GCD of the coefficients of A when viewed as a polynomial in the variables vars. Return \(1\) for success and \(0\) for failure. Upon success, g will be independent of the variables vars.

nmod_mpoly_gcd :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_gcd G A B ctx

Try to set G to the monic GCD of A and B. The GCD of zero and zero is defined to be zero. If the return is \(1\) the function was successful. Otherwise the return is \(0\) and G is left untouched.

nmod_mpoly_gcd_cofactors :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_gcd_cofactors G Abar Bbar A B ctx

Do the operation of nmod_mpoly_gcd and also compute \(Abar = A/G\) and \(Bbar = B/G\) if successful.

nmod_mpoly_gcd_zippel :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_gcd_zippel G A B ctx

Try to set G to the GCD of A and B using various algorithms.

nmod_mpoly_resultant :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_resultant R A B var ctx

Try to set R to the resultant of A and B with respect to the variable of index var.

nmod_mpoly_discriminant :: Ptr CNModMPoly -> Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_discriminant D A var ctx

Try to set D to the discriminant of A with respect to the variable of index var.

Square Root

nmod_mpoly_sqrt :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_sqrt Q A ctx

If \(Q^2=A\) has a solution, set Q to a solution and return \(1\), otherwise return \(0\) and set Q to zero.

nmod_mpoly_is_square :: Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_is_square A ctx

Return \(1\) if A is a perfect square, otherwise return \(0\).

nmod_mpoly_quadratic_root :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_quadratic_root Q A B ctx

If \(Q^2+AQ=B\) has a solution, set Q to a solution and return \(1\), otherwise return \(0\).

Univariate Functions

nmod_mpoly_univar_init :: Ptr CNModMPolyUnivar -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_univar_init A ctx

Initialize A.

nmod_mpoly_univar_clear :: Ptr CNModMPolyUnivar -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_univar_clear A ctx

Clear A.

nmod_mpoly_univar_swap :: Ptr CNModMPolyUnivar -> Ptr CNModMPolyUnivar -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_univar_swap A B ctx

Swap A and B.

nmod_mpoly_to_univar :: Ptr CNModMPolyUnivar -> Ptr CNModMPoly -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_to_univar A B var ctx

Set A to a univariate form of B by pulling out the variable of index var. The coefficients of A will still belong to the content ctx but will not depend on the variable of index var.

nmod_mpoly_from_univar :: Ptr CNModMPoly -> Ptr CNModMPolyUnivar -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_from_univar A B var ctx

Set A to the normal form of B by putting in the variable of index var. This function is undefined if the coefficients of B depend on the variable of index var.

nmod_mpoly_univar_degree_fits_si :: Ptr CNModMPolyUnivar -> Ptr CNModMPolyCtx -> IO CInt Source #

nmod_mpoly_univar_degree_fits_si A ctx

Return \(1\) if the degree of A with respect to the main variable fits an slong. Otherwise, return \(0\).

nmod_mpoly_univar_length :: Ptr CNModMPolyUnivar -> Ptr CNModMPolyCtx -> IO CLong Source #

nmod_mpoly_univar_length A ctx

Return the number of terms in A with respect to the main variable.

nmod_mpoly_univar_get_term_exp_si :: Ptr CNModMPolyUnivar -> CLong -> Ptr CNModMPolyCtx -> IO CLong Source #

nmod_mpoly_univar_get_term_exp_si A i ctx

Return the exponent of the term of index i of A.

nmod_mpoly_univar_get_term_coeff :: Ptr CNModMPoly -> Ptr CNModMPolyUnivar -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_univar_get_term_coeff c A i ctx

nmod_mpoly_univar_swap_term_coeff :: Ptr CNModMPoly -> Ptr CNModMPolyUnivar -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_univar_swap_term_coeff c A i ctx

Set (resp. swap) c to (resp. with) the coefficient of the term of index i of A.

Internal Functions

nmod_mpoly_pow_rmul :: Ptr CNModMPoly -> Ptr CNModMPoly -> CULong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_pow_rmul A B k ctx

Set A to B raised to the k-th power using repeated multiplications.

nmod_mpoly_div_monagan_pearce :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_div_monagan_pearce polyq poly2 poly3 ctx

Set polyq to the quotient of poly2 by poly3, discarding the remainder (with notional remainder coefficients reduced modulo the leading coefficient of poly3). Implements "Polynomial division using dynamic arrays, heaps and packed exponents" by Michael Monagan and Roman Pearce. This function is exceptionally efficient if the division is known to be exact.

nmod_mpoly_divrem_monagan_pearce :: Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_divrem_monagan_pearce q r poly2 poly3 ctx

Set polyq and polyr to the quotient and remainder of poly2 divided by poly3, (with remainder coefficients reduced modulo the leading coefficient of poly3). Implements "Polynomial division using dynamic arrays, heaps and packed exponents" by Michael Monagan and Roman Pearce.

nmod_mpoly_divrem_ideal_monagan_pearce :: Ptr (Ptr (Ptr CNModMPoly)) -> Ptr CNModMPoly -> Ptr CNModMPoly -> Ptr (Ptr (Ptr CNModMPoly)) -> CLong -> Ptr CNModMPolyCtx -> IO () Source #

nmod_mpoly_divrem_ideal_monagan_pearce q r poly2 poly3 len ctx

This function is as per nmod_mpoly_divrem_monagan_pearce except that it takes an array of divisor polynomials poly3, and it returns an array of quotient polynomials q. The number of divisor (and hence quotient) polynomials, is given by len. The function computes polynomials \(q_i = q[i]\) such that poly2 is \(r + \sum_{i=0}^{\mbox{len - 1}} q_ib_i\), where \(b_i =\) poly3[i].