Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module supports working with symbolic expressions.
Introduction
Formally, a symbolic expression is either:
An atom being one of
- An integer, for example 0 or -34.
- A symbol, for example x, Mul, SomeUserNamedSymbol. Symbols should be valid C identifiers (containing only the characters A-Z, a-z, 0-9, _, and not starting with a digit).
- A string, for example "Hello, world!". For the moment, we only consider ASCII strings, but there is no obstacle in principle to supporting UTF-8.
- A non-atomic expression, \(e_0(e_1,e_2,\ldots e_n)\) representing a function call where \((e_1,\ldots,e_n)\) are symbolic expressions.
The meaning of an expression depends on the interpretation of symbols
in a given context. For example, with a standard interpretation (used
within Calcium) of the symbols Mul
, Add
and Neg
, the expression
Mul(3, Add(Neg(x), y))
encodes the formula \(3 \cdot ((-x)+y)\)
where x
and y
are symbolic variables. See fexpr-builtin
for
documentation of builtin symbols.
Computing and embedding data
Symbolic expressions are usually not the best data structure to use directly for heavy-duty computations. Functions acting on symbolic expressions will typically convert to a dedicated data structure (e.g. polynomials) internally and (optionally) convert the final result back to a symbolic expression.
Symbolic expressions do not allow embedding arbitrary binary objects such as Flint/Arb/Antic/Calcium types as atoms. This is done on purpose to make symbolic expressions easy to use as a data exchange format. To embed an object in an expression, one has the following options:
- Represent the object structurally using atoms supported natively by symbolic expressions (for example, an integer polynomial can be represented as a list of coefficients or as an arithmetic expression tree).
- Introduce a dummy symbol to represent the object, maintaining an external translation table mapping this symbol to the intended value.
- Encode the object using a string or symbol name. This is generally not recommended, as it requires parsing; properly used, symbolic expressions have the benefit of being able to represent the parsed structure.
Flat-packed representation
Symbolic expressions are often implemented using trees of pointers
(often together with hash tables for uniqueness), requiring some form of
memory management. The fexpr_t
type, by contrast, stores a symbolic
expression using a "flat-packed" representation without internal
pointers. The expression data is just an array of words (ulong
). The
first word is a header encoding type information (whether the expression
is a function call or an atom, and the type of the atom) and the total
number of words in the expression. For atoms, the data is stored either
in the header word itself (small integers and short symbols/strings) or
in the following words. For function calls, the header is followed by
the expressions \(e_0\), ..., \(e_n\) packed contiguously in memory.
Pros:
- Memory management is trivial.
- Copying an expression is just copying an array of words.
- Comparing expressions for equality is just comparing arrays of words.
- Merging expressions is basically just concatenating arrays of words.
- Expression data can be shared freely in binary form between threads and even between machines (as long as all machines have the same word size and endianness).
Cons:
- Repeated instances of the same subexpression cannot share memory (a workaround is to introduce local dummy symbols for repeated subexpressions).
- Extracting a subexpression for modification generally requires making a complete copy of that subxepression (however, for read-only access to subexpressions, one can use “view” expressions which have zero overhead).
- Manipulating a part of an expression generally requires rebuilding the whole expression.
- Building an expression incrementally is typically \(O\left(n^2\right)\). As a workaround, it is a good idea to work with balanced (low-depth) expressions and try to construct an expression in one go (for example, to create a sum, create a single Add expression with many arguments instead of chaining binary Add operations).
Synopsis
- data Fexpr = Fexpr !(ForeignPtr CFexpr)
- data CFexpr
- newFexpr :: IO Fexpr
- withFexpr :: Fexpr -> (Ptr CFexpr -> IO a) -> IO (Fexpr, a)
- withNewFexpr :: (Ptr CFexpr -> IO a) -> IO (Fexpr, a)
- fexpr_init :: Ptr CFexpr -> IO ()
- fexpr_clear :: Ptr CFexpr -> IO ()
- _fexpr_vec_init :: CLong -> IO (Ptr Fexpr)
- _fexpr_vec_clear :: Ptr Fexpr -> CLong -> IO ()
- fexpr_fit_size :: Ptr CFexpr -> CLong -> IO ()
- fexpr_set :: Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_swap :: Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_type_small_int :: FexprType
- fexpr_type_small_symbol :: FexprType
- fexpr_type_small_string :: FexprType
- fexpr_type_big_int_pos :: FexprType
- fexpr_type_big_int_neg :: FexprType
- fexpr_type_big_symbol :: FexprType
- fexpr_type_big_string :: FexprType
- fexpr_type_call0 :: FexprType
- fexpr_type_call1 :: FexprType
- fexpr_type_call2 :: FexprType
- fexpr_type_call3 :: FexprType
- fexpr_type_call4 :: FexprType
- fexpr_type_calln :: FexprType
- fexpr_depth :: Ptr CFexpr -> IO CLong
- fexpr_num_leaves :: Ptr CFexpr -> IO CLong
- fexpr_size :: Ptr CFexpr -> IO CLong
- fexpr_size_bytes :: Ptr CFexpr -> IO CLong
- fexpr_allocated_bytes :: Ptr CFexpr -> IO CLong
- fexpr_equal :: Ptr CFexpr -> Ptr CFexpr -> IO CInt
- fexpr_equal_si :: Ptr CFexpr -> CLong -> IO CInt
- fexpr_equal_ui :: Ptr CFexpr -> CULong -> IO CInt
- fexpr_hash :: Ptr CFexpr -> IO CULong
- fexpr_cmp_fast :: Ptr CFexpr -> Ptr CFexpr -> IO CInt
- fexpr_is_integer :: Ptr CFexpr -> IO CInt
- fexpr_is_symbol :: Ptr CFexpr -> IO CInt
- fexpr_is_string :: Ptr CFexpr -> IO CInt
- fexpr_is_atom :: Ptr CFexpr -> IO CInt
- fexpr_zero :: Ptr CFexpr -> IO ()
- fexpr_is_zero :: Ptr CFexpr -> IO CInt
- fexpr_is_neg_integer :: Ptr CFexpr -> IO CInt
- fexpr_set_si :: Ptr CFexpr -> CLong -> IO ()
- fexpr_set_ui :: Ptr CFexpr -> CULong -> IO ()
- fexpr_set_fmpz :: Ptr CFexpr -> Ptr CFmpz -> IO ()
- fexpr_get_fmpz :: Ptr CFmpz -> Ptr CFexpr -> IO CInt
- fexpr_set_symbol_builtin :: Ptr CFexpr -> CLong -> IO ()
- fexpr_is_builtin_symbol :: Ptr CFexpr -> CLong -> IO CInt
- fexpr_is_any_builtin_symbol :: Ptr CFexpr -> IO CInt
- fexpr_set_symbol_str :: Ptr CFexpr -> CString -> IO ()
- fexpr_get_symbol_str :: Ptr CFexpr -> IO CString
- fexpr_set_string :: Ptr CFexpr -> CString -> IO ()
- fexpr_get_string :: Ptr CFexpr -> IO CString
- fexpr_write :: Ptr CCalciumStream -> Ptr CFexpr -> IO ()
- fexpr_print :: Ptr CFexpr -> IO ()
- fexpr_get_str :: Ptr CFexpr -> IO CString
- fexpr_write_latex :: Ptr CCalciumStream -> Ptr CFexpr -> CULong -> IO ()
- fexpr_print_latex :: Ptr CFexpr -> CULong -> IO ()
- fexpr_get_str_latex :: Ptr CFexpr -> CULong -> IO CString
- fexpr_latex_small :: FexprLatexFlag
- fexpr_latex_logic :: FexprLatexFlag
- fexpr_nargs :: Ptr CFexpr -> IO CLong
- fexpr_func :: Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_view_func :: Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_arg :: Ptr CFexpr -> Ptr CFexpr -> CLong -> IO ()
- fexpr_view_arg :: Ptr CFexpr -> Ptr CFexpr -> CLong -> IO ()
- fexpr_view_next :: Ptr CFexpr -> IO ()
- fexpr_is_builtin_call :: Ptr CFexpr -> CLong -> IO CInt
- fexpr_is_any_builtin_call :: Ptr CFexpr -> IO CInt
- fexpr_call0 :: Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_call1 :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_call2 :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_call3 :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_call4 :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_call_vec :: Ptr CFexpr -> Ptr CFexpr -> Ptr Fexpr -> CLong -> IO ()
- fexpr_call_builtin1 :: Ptr CFexpr -> CLong -> Ptr CFexpr -> IO ()
- fexpr_call_builtin2 :: Ptr CFexpr -> CLong -> Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_contains :: Ptr CFexpr -> Ptr CFexpr -> IO CInt
- fexpr_replace :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO CInt
- fexpr_replace2 :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO CInt
- fexpr_replace_vec :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexprVec -> Ptr CFexprVec -> IO CInt
- fexpr_set_fmpq :: Ptr CFexpr -> Ptr CFmpq -> IO ()
- fexpr_set_arf :: Ptr CFexpr -> Ptr CArf -> IO ()
- fexpr_set_d :: Ptr CFexpr -> CDouble -> IO ()
- fexpr_set_re_im_d :: Ptr CFexpr -> CDouble -> CDouble -> IO ()
- fexpr_neg :: Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_add :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_sub :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_mul :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_div :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_pow :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO ()
- fexpr_is_arithmetic_operation :: Ptr CFexpr -> IO CInt
- fexpr_arithmetic_nodes :: Ptr CFexprVec -> Ptr CFexpr -> IO ()
- fexpr_get_fmpz_mpoly_q :: Ptr CFmpzMPolyQ -> Ptr CFexpr -> Ptr CFexprVec -> Ptr CFmpzMPolyCtx -> IO CInt
- fexpr_set_fmpz_mpoly :: Ptr CFexpr -> Ptr CFmpzMPoly -> Ptr CFexprVec -> Ptr CFmpzMPolyCtx -> IO ()
- fexpr_set_fmpz_mpoly_q :: Ptr CFexpr -> Ptr CFmpzMPolyQ -> Ptr CFexprVec -> Ptr CFmpzMPolyCtx -> IO ()
- fexpr_expanded_normal_form :: Ptr CFexpr -> Ptr CFexpr -> CULong -> IO CInt
- newFexprVec :: CLong -> IO FexprVec
- withFexprVec :: FexprVec -> (Ptr CFexprVec -> IO a) -> IO (FexprVec, a)
- withNewFexprVec :: CLong -> (Ptr CFexprVec -> IO a) -> IO (FexprVec, a)
- fexpr_vec_init :: Ptr CFexprVec -> CLong -> IO ()
- fexpr_vec_clear :: Ptr CFexprVec -> IO ()
- fexpr_vec_print :: Ptr CFexprVec -> IO ()
- fexpr_vec_swap :: Ptr CFexprVec -> Ptr CFexprVec -> IO ()
- fexpr_vec_fit_length :: Ptr CFexprVec -> CLong -> IO ()
- fexpr_vec_set :: Ptr CFexprVec -> Ptr CFexprVec -> IO ()
- fexpr_vec_append :: Ptr CFexprVec -> Ptr CFexpr -> IO ()
- fexpr_vec_insert_unique :: Ptr CFexprVec -> Ptr CFexpr -> IO CLong
- fexpr_vec_set_length :: Ptr CFexprVec -> CLong -> IO ()
- _fexpr_vec_sort_fast :: Ptr Fexpr -> CLong -> IO ()
Flat-packed symbolic expressions
Introduction
Computing and embedding data
Flat-packed representation
Memory management
Instances
fexpr_init :: Ptr CFexpr -> IO () Source #
fexpr_init expr
Initializes expr for use. Its value is set to the atomic integer 0.
fexpr_clear :: Ptr CFexpr -> IO () Source #
fexpr_clear expr
Clears expr, freeing its allocated memory.
_fexpr_vec_init :: CLong -> IO (Ptr Fexpr) Source #
_fexpr_vec_init len
Returns a heap-allocated vector of len initialized expressions.
_fexpr_vec_clear :: Ptr Fexpr -> CLong -> IO () Source #
_fexpr_vec_clear vec len
Clears the len expressions in vec and frees vec itself.
fexpr_fit_size :: Ptr CFexpr -> CLong -> IO () Source #
fexpr_fit_size expr size
Ensures that expr has room for size words.
fexpr_set :: Ptr CFexpr -> Ptr CFexpr -> IO () Source #
fexpr_set res expr
Sets res to the a copy of expr.
Types
fexpr_type_small_int :: FexprType Source #
fexpr_type_small_symbol :: FexprType Source #
fexpr_type_small_string :: FexprType Source #
fexpr_type_big_int_pos :: FexprType Source #
fexpr_type_big_int_neg :: FexprType Source #
fexpr_type_big_symbol :: FexprType Source #
fexpr_type_big_string :: FexprType Source #
fexpr_type_call0 :: FexprType Source #
fexpr_type_call1 :: FexprType Source #
fexpr_type_call2 :: FexprType Source #
fexpr_type_call3 :: FexprType Source #
fexpr_type_call4 :: FexprType Source #
fexpr_type_calln :: FexprType Source #
Size information
fexpr_depth :: Ptr CFexpr -> IO CLong Source #
fexpr_depth expr
Returns the depth of expr as a symbolic expression tree.
fexpr_num_leaves :: Ptr CFexpr -> IO CLong Source #
fexpr_num_leaves expr
Returns the number of leaves (atoms, counted with repetition) in the expression expr.
fexpr_size :: Ptr CFexpr -> IO CLong Source #
fexpr_size expr
Returns the number of words in the internal representation of expr.
fexpr_size_bytes :: Ptr CFexpr -> IO CLong Source #
fexpr_size_bytes expr
Returns the number of bytes in the internal representation of expr.
The count excludes the size of the structure itself. Add
sizeof(fexpr_struct)
to get the size of the object as a whole.
fexpr_allocated_bytes :: Ptr CFexpr -> IO CLong Source #
fexpr_allocated_bytes expr
Returns the number of allocated bytes in the internal representation of
expr. The count excludes the size of the structure itself. Add
sizeof(fexpr_struct)
to get the size of the object as a whole.
Comparisons
fexpr_equal :: Ptr CFexpr -> Ptr CFexpr -> IO CInt Source #
fexpr_equal a b
Checks if a and b are exactly equal as expressions.
fexpr_equal_ui :: Ptr CFexpr -> CULong -> IO CInt Source #
fexpr_equal_ui expr c
Checks if expr is an atomic integer exactly equal to c.
fexpr_hash :: Ptr CFexpr -> IO CULong Source #
fexpr_hash expr
Returns a hash of the expression expr.
fexpr_cmp_fast :: Ptr CFexpr -> Ptr CFexpr -> IO CInt Source #
fexpr_cmp_fast a b
Compares a and b using an ordering based on the internal representation, returning -1, 0 or 1. This can be used, for instance, to maintain sorted arrays of expressions for binary search; the sort order has no mathematical significance.
Atoms
fexpr_is_integer :: Ptr CFexpr -> IO CInt Source #
fexpr_is_integer expr
Returns whether expr is an atomic integer
fexpr_is_symbol :: Ptr CFexpr -> IO CInt Source #
fexpr_is_symbol expr
Returns whether expr is an atomic symbol.
fexpr_is_string :: Ptr CFexpr -> IO CInt Source #
fexpr_is_string expr
Returns whether expr is an atomic string.
fexpr_is_zero :: Ptr CFexpr -> IO CInt Source #
fexpr_is_zero expr
Returns whether expr is the atomic integer 0.
fexpr_is_neg_integer :: Ptr CFexpr -> IO CInt Source #
fexpr_is_neg_integer expr
Returns whether expr is any negative atomic integer.
fexpr_set_fmpz :: Ptr CFexpr -> Ptr CFmpz -> IO () Source #
fexpr_set_fmpz res c
Sets res to the atomic integer c.
fexpr_get_fmpz :: Ptr CFmpz -> Ptr CFexpr -> IO CInt Source #
fexpr_get_fmpz res expr
Sets res to the atomic integer in expr. This aborts if expr is not an atomic integer.
fexpr_set_symbol_builtin :: Ptr CFexpr -> CLong -> IO () Source #
fexpr_set_symbol_builtin res id
Sets res to the builtin symbol with internal index id (see
fexpr-builtin
).
fexpr_is_builtin_symbol :: Ptr CFexpr -> CLong -> IO CInt Source #
fexpr_is_builtin_symbol expr id
Returns whether expr is the builtin symbol with index id (see
fexpr-builtin
).
fexpr_is_any_builtin_symbol :: Ptr CFexpr -> IO CInt Source #
fexpr_is_any_builtin_symbol expr
Returns whether expr is any builtin symbol (see fexpr-builtin
).
fexpr_set_symbol_str :: Ptr CFexpr -> CString -> IO () Source #
fexpr_set_symbol_str res s
Sets res to the symbol given by s.
fexpr_get_symbol_str :: Ptr CFexpr -> IO CString Source #
fexpr_get_symbol_str expr
Returns the symbol in expr as a string. The string must be freed with
flint_free
. This aborts if expr is not an atomic symbol.
fexpr_set_string :: Ptr CFexpr -> CString -> IO () Source #
fexpr_set_string res s
Sets res to the atomic string s.
fexpr_get_string :: Ptr CFexpr -> IO CString Source #
fexpr_get_string expr
Assuming that expr is an atomic string, returns a copy of this string.
The string must be freed with flint_free
.
Input and output
fexpr_write :: Ptr CCalciumStream -> Ptr CFexpr -> IO () Source #
fexpr_write stream expr
Writes expr to stream.
fexpr_get_str :: Ptr CFexpr -> IO CString Source #
fexpr_get_str expr
Returns a string representation of expr. The string must be freed with
flint_free
.
Warning: string literals appearing in expressions are currently not escaped.
LaTeX output
fexpr_write_latex :: Ptr CCalciumStream -> Ptr CFexpr -> CULong -> IO () Source #
fexpr_write_latex stream expr flags
Writes the LaTeX representation of expr to stream.
fexpr_print_latex :: Ptr CFexpr -> CULong -> IO () Source #
fexpr_print_latex expr flags
Prints the LaTeX representation of expr to standard output.
fexpr_get_str_latex :: Ptr CFexpr -> CULong -> IO CString Source #
fexpr_get_str_latex expr flags
Returns a string of the LaTeX representation of expr. The string must
be freed with flint_free
.
Warning: string literals appearing in expressions are currently not escaped.
The flags parameter allows specifying options for LaTeX output. The following flags are supported:
fexpr_latex_small :: FexprLatexFlag Source #
fexpr_latex_small
Generate more compact formulas, most importantly by printing fractions inline as \(p/q\) instead of as \(\frac{p}{q}\). This flag is automatically activated within subscripts and superscripts and in certain other parts of formulas.
fexpr_latex_logic :: FexprLatexFlag Source #
fexpr_latex_logic
Use symbols for logical operators such as Not, And, Or, which by default are rendered as words for legibility.
Function call structure
fexpr_nargs :: Ptr CFexpr -> IO CLong Source #
fexpr_nargs expr
Returns the number of arguments n in the function call \(f(e_1,\ldots,e_n)\) represented by expr. If expr is an atom, returns -1.
fexpr_func :: Ptr CFexpr -> Ptr CFexpr -> IO () Source #
fexpr_func res expr
Assuming that expr represents a function call \(f(e_1,\ldots,e_n)\), sets res to the function expression f.
fexpr_view_func :: Ptr CFexpr -> Ptr CFexpr -> IO () Source #
fexpr_view_func view expr
As fexpr_func
, but sets view to a shallow view instead of copying
the expression. The variable view must not be initialized before use
or cleared after use, and expr must not be modified or cleared as long
as view is in use.
fexpr_arg :: Ptr CFexpr -> Ptr CFexpr -> CLong -> IO () Source #
fexpr_arg res expr i
Assuming that expr represents a function call \(f(e_1,\ldots,e_n)\), sets res to the argument \(e_{i+1}\). Note that indexing starts from 0. The index must be in bounds, with \(0 \le i < n\).
fexpr_view_arg :: Ptr CFexpr -> Ptr CFexpr -> CLong -> IO () Source #
fexpr_view_arg view expr i
As fexpr_arg
, but sets view to a shallow view instead of copying the
expression. The variable view must not be initialized before use or
cleared after use, and expr must not be modified or cleared as long as
view is in use.
fexpr_view_next :: Ptr CFexpr -> IO () Source #
fexpr_view_next view
Assuming that view is a shallow view of a function argument \(e_i\) in a function call \(f(e_1,\ldots,e_n)\), sets view to a view of the next argument \(e_{i+1}\). This function can be called when view refers to the last argument \(e_n\), provided that view is not used afterwards. This function can also be called when view refers to the function f, in which case it will make view point to \(e_1\).
fexpr_is_builtin_call :: Ptr CFexpr -> CLong -> IO CInt Source #
fexpr_is_builtin_call expr id
Returns whether expr has the form \(f(\ldots)\) where f is a builtin
function defined by id (see fexpr-builtin
).
fexpr_is_any_builtin_call :: Ptr CFexpr -> IO CInt Source #
fexpr_is_any_builtin_call expr
Returns whether expr has the form \(f(\ldots)\) where f is any
builtin function (see fexpr-builtin
).
Composition
fexpr_call2 :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO () Source #
fexpr_call2 res f x1 x2
fexpr_call3 :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO () Source #
fexpr_call3 res f x1 x2 x3
fexpr_call4 :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO () Source #
fexpr_call4 res f x1 x2 x3 x4
fexpr_call_vec :: Ptr CFexpr -> Ptr CFexpr -> Ptr Fexpr -> CLong -> IO () Source #
fexpr_call_vec res f args len
Creates the function call \(f(x_1,\ldots,x_n)\). The vec version takes the arguments as an array args and n is given by len. Warning: aliasing between inputs and outputs is not implemented.
fexpr_call_builtin1 :: Ptr CFexpr -> CLong -> Ptr CFexpr -> IO () Source #
fexpr_call_builtin1 res f x1
fexpr_call_builtin2 :: Ptr CFexpr -> CLong -> Ptr CFexpr -> Ptr CFexpr -> IO () Source #
fexpr_call_builtin2 res f x1 x2
Creates the function call \(f(x_1,\ldots,x_n)\), where f defines a builtin symbol.
Subexpressions and replacement
fexpr_contains :: Ptr CFexpr -> Ptr CFexpr -> IO CInt Source #
fexpr_contains expr x
Returns whether expr contains the expression x as a subexpression (this includes the case where expr and x are equal).
fexpr_replace :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO CInt Source #
fexpr_replace res expr x y
Sets res to the expression expr with all occurrences of the subexpression x replaced by the expression y. Returns a boolean value indicating whether any replacements have been performed. Aliasing is allowed between res and expr but not between res and x or y.
fexpr_replace2 :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO CInt Source #
fexpr_replace2 res expr x1 y1 x2 y2
Like fexpr_replace
, but simultaneously replaces x1 by y1 and x2
by y2.
fexpr_replace_vec :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexprVec -> Ptr CFexprVec -> IO CInt Source #
fexpr_replace_vec res expr xs ys
Sets res to the expression expr with all occurrences of the subexpressions given by entries in xs replaced by the corresponding expressions in ys. It is required that xs and ys have the same length. Returns a boolean value indicating whether any replacements have been performed. Aliasing is allowed between res and expr but not between res and the entries of xs or ys.
Arithmetic expressions
fexpr_set_fmpq :: Ptr CFexpr -> Ptr CFmpq -> IO () Source #
fexpr_set_fmpq res x
Sets res to the rational number x. This creates an atomic integer if the denominator of x is one, and otherwise creates a division expression.
fexpr_set_d :: Ptr CFexpr -> CDouble -> IO () Source #
fexpr_set_d res x
Sets res to an expression for the value of the floating-point number
x. NaN is represented as Undefined
. For a regular value, this
creates an atomic integer or a rational fraction if the exponent is
small, and otherwise creates an expression of the form
Mul(m, Pow(2, e))
.
fexpr_set_re_im_d :: Ptr CFexpr -> CDouble -> CDouble -> IO () Source #
fexpr_set_re_im_d res x y
Sets res to an expression for the complex number with real part x and imaginary part y.
fexpr_pow :: Ptr CFexpr -> Ptr CFexpr -> Ptr CFexpr -> IO () Source #
fexpr_pow res a b
Constructs an arithmetic expression with given arguments. No simplifications whatsoever are performed.
fexpr_is_arithmetic_operation :: Ptr CFexpr -> IO CInt Source #
fexpr_is_arithmetic_operation expr
Returns whether expr is of the form \(f(e_1,\ldots,e_n)\) where f is
one of the arithmetic operators Pos
, Neg
, Add
, Sub
, Mul
,
Div
.
fexpr_arithmetic_nodes :: Ptr CFexprVec -> Ptr CFexpr -> IO () Source #
fexpr_arithmetic_nodes nodes expr
Sets nodes to a vector of subexpressions of expr such that expr is
an arithmetic expression with nodes as leaves. More precisely, expr
will be constructed out of nested application the arithmetic operators
Pos
, Neg
, Add
, Sub
, Mul
, Div
with integers and expressions
in nodes as leaves. Powers Pow
with an atomic integer exponent are
also allowed. The nodes are output without repetition but are not
automatically sorted in a canonical order.
fexpr_get_fmpz_mpoly_q :: Ptr CFmpzMPolyQ -> Ptr CFexpr -> Ptr CFexprVec -> Ptr CFmpzMPolyCtx -> IO CInt Source #
fexpr_get_fmpz_mpoly_q res expr vars ctx
Sets res to the expression expr as a formal rational function of the
subexpressions in vars. The vector vars must have the same length as
the number of variables specified in ctx. To build vars
automatically for a given expression, fexpr_arithmetic_nodes
may be
used.
Returns 1 on success and 0 on failure. Failure can occur for the following reasons:
- A subexpression is encountered that cannot be interpreted as an arithmetic operation and does not appear (exactly) in vars.
- Overflow (too many terms or too large exponent).
- Division by zero (a zero denominator is encountered).
It is important to note that this function views expr as a formal rational function with vars as formal indeterminates. It does thus not check for algebraic relations between vars and can implicitly divide by zero if vars are not algebraically independent.
fexpr_set_fmpz_mpoly :: Ptr CFexpr -> Ptr CFmpzMPoly -> Ptr CFexprVec -> Ptr CFmpzMPolyCtx -> IO () Source #
fexpr_set_fmpz_mpoly res poly vars ctx
fexpr_set_fmpz_mpoly_q :: Ptr CFexpr -> Ptr CFmpzMPolyQ -> Ptr CFexprVec -> Ptr CFmpzMPolyCtx -> IO () Source #
fexpr_set_fmpz_mpoly_q res frac vars ctx
Sets res to an expression for the multivariate polynomial poly (or rational function frac), using the expressions in vars as the variables. The length of vars must agree with the number of variables in ctx. If NULL is passed for vars, a default choice of symbols is used.
fexpr_expanded_normal_form :: Ptr CFexpr -> Ptr CFexpr -> CULong -> IO CInt Source #
fexpr_expanded_normal_form res expr flags
Sets res to expr converted to expanded normal form viewed as a
formal rational function with its non-arithmetic subexpressions as
terminal nodes. This function first computes nodes with
fexpr_arithmetic_nodes
, sorts the nodes, evaluates to a rational
function with fexpr_get_fmpz_mpoly_q
, and then converts back to an
expression with fexpr_set_fmpz_mpoly_q
. Optional flags are reserved
for future use.
Vectors
newFexprVec :: CLong -> IO FexprVec Source #
fexpr_vec_init :: Ptr CFexprVec -> CLong -> IO () Source #
fexpr_vec_init vec len
Initializes vec to a vector of length len. All entries are set to the atomic integer 0.
fexpr_vec_clear :: Ptr CFexprVec -> IO () Source #
fexpr_vec_clear vec
Clears the vector vec.
fexpr_vec_print :: Ptr CFexprVec -> IO () Source #
fexpr_vec_print vec
Prints vec to standard output.
fexpr_vec_swap :: Ptr CFexprVec -> Ptr CFexprVec -> IO () Source #
fexpr_vec_swap x y
Swaps x and y efficiently.
fexpr_vec_fit_length :: Ptr CFexprVec -> CLong -> IO () Source #
fexpr_vec_fit_length vec len
Ensures that vec has space for len entries.
fexpr_vec_set :: Ptr CFexprVec -> Ptr CFexprVec -> IO () Source #
fexpr_vec_set dest src
Sets dest to a copy of src.
fexpr_vec_append :: Ptr CFexprVec -> Ptr CFexpr -> IO () Source #
fexpr_vec_append vec expr
Appends expr to the end of the vector vec.
fexpr_vec_insert_unique :: Ptr CFexprVec -> Ptr CFexpr -> IO CLong Source #
fexpr_vec_insert_unique vec expr
Inserts expr without duplication into vec, returning its position. If this expression already exists, vec is unchanged. If this expression does not exist in vec, it is appended.