Skip to content

Commit

Permalink
feature: Add Expr::{symbol, list_from_array} + doc examples on Expr::…
Browse files Browse the repository at this point in the history
…{mint, mreal, string}
  • Loading branch information
ConnorGray committed Nov 21, 2023
1 parent e2315f5 commit 062bd79
Show file tree
Hide file tree
Showing 3 changed files with 90 additions and 0 deletions.
10 changes: 10 additions & 0 deletions wolfram-library-link/RustLink/Tests/KernelExpr.wlt
Original file line number Diff line number Diff line change
Expand Up @@ -18,4 +18,14 @@ Test[
Global`$ReturnValue
),
{Global`Example1, Global`Example2, Example3`Example4}
]

Test[
(
LibraryFunctionLoad[
"liblibrary_tests", "test_kernel_expr_create_heterogenous", {}, "Void"
][];
Global`$ReturnValue
),
{1, 2.01, "three", Four, {"a", "b", "c"}}
]
14 changes: 14 additions & 0 deletions wolfram-library-link/examples/tests/test_kernel_expr.rs
Original file line number Diff line number Diff line change
Expand Up @@ -26,3 +26,17 @@ fn test_kernel_expr_create_symbols() {
// $ReturnValue = list
SymbolExpr::lookup("Global`$ReturnValue").set_to(&list.as_expr());
}

#[export]
fn test_kernel_expr_create_heterogenous() {
let result = NormalExpr::list_from_array([
Expr::mint(1),
Expr::mreal(2.01),
Expr::string("three"),
Expr::symbol("Global`Four"),
Expr::list_from_array([Expr::string("a"), Expr::string("b"), Expr::string("c")]),
]);

// $ReturnValue = list
SymbolExpr::lookup("Global`$ReturnValue").set_to(&result.as_expr());
}
66 changes: 66 additions & 0 deletions wolfram-library-link/src/kernel.rs
Original file line number Diff line number Diff line change
Expand Up @@ -32,20 +32,86 @@ pub struct Uninit<T>(ManuallyDrop<T>);

impl Expr {
/// Construct a machine-sized Integer expression.
///
/// # Examples
///
/// Construct the expression `42`:
///
/// ```no_run
/// use wolfram_library_link::kernel::Expr;
///
/// let e = Expr::mint(42);
/// ```
pub fn mint(value: mint) -> Expr {
MIntExpr::new(value).into_expr()
}

/// Construct a machine-sized Real expression.
///
/// # Examples
///
/// Construct the expression `1.23`:
///
/// ```no_run
/// use wolfram_library_link::kernel::Expr;
///
/// let e = Expr::mreal(1.23);
/// ```
pub fn mreal(value: mreal) -> Expr {
MRealExpr::new(value).into_expr()
}

/// Construct a String expression.
///
/// # Examples
///
/// Construct the expression `"Hello, Wolfram!"`:
///
/// ```no_run
/// use wolfram_library_link::kernel::Expr;
///
/// let e = Expr::string("Hello, Wolfram!");
/// ```
pub fn string(string: &str) -> Expr {
StringExpr::new(string).into_expr()
}

/// Construct a Symbol expression.
///
/// # Examples
///
/// Construct the expression `` System`Now ``:
///
/// ```no_run
/// use wolfram_library_link::kernel::Expr;
///
/// let e = Expr::symbol("System`Now");
/// ```
pub fn symbol(symbol: &str) -> Expr {
// FIXME: Validate that `symbol` is a valid symbol name or fully
// qualified symbol.
SymbolExpr::lookup(symbol).into_expr()
}

/// Construct a new `{...}` expression from an array of expressions.
///
/// # Examples
///
/// Construct the expression `{1, 2, 3}`:
///
/// ```no_run
/// use wolfram_library_link::kernel::{Expr, NormalExpr};
///
/// let list = NormalExpr::list_from_array([
/// Expr::mint(1),
/// Expr::mint(2),
/// Expr::mint(3)
/// ]);
/// ```
pub fn list_from_array<const N: usize>(array: [Expr; N]) -> Expr {
NormalExpr::list_from_array(array).into_expr()
}

/// Get the expression flags.
fn flags(&self) -> u16 {
unsafe { Flags_Expression_UnsignedInteger16(self.to_c_expr()) }
Expand Down

0 comments on commit 062bd79

Please sign in to comment.