pub enum Value {
Root(Root),
Raw(Value),
}Expand description
Value wraps the native OCaml value type
Variants§
Root(Root)
Rooted value
Raw(Value)
Reference to a rooted value
NOTE: Value::Raw should NOT be used to convert arbitrary sys::Value into Value
Implementations§
Source§impl Value
impl Value
Sourcepub unsafe fn alloc(n: usize, tag: Tag) -> Value
pub unsafe fn alloc(n: usize, tag: Tag) -> Value
Allocate a new value with the given size and tag.
Sourcepub unsafe fn alloc_double_array(n: usize) -> Value
pub unsafe fn alloc_double_array(n: usize) -> Value
Allocate a new float array
Sourcepub unsafe fn alloc_tuple(n: usize) -> Value
pub unsafe fn alloc_tuple(n: usize) -> Value
Allocate a new tuple value
Sourcepub unsafe fn alloc_small(n: usize, tag: Tag) -> Value
pub unsafe fn alloc_small(n: usize, tag: Tag) -> Value
Allocate a new small value with the given size and tag
Sourcepub unsafe fn alloc_final<T>(
finalizer: unsafe extern "C" fn(Raw),
cfg: Option<(usize, usize)>,
) -> Value
pub unsafe fn alloc_final<T>( finalizer: unsafe extern "C" fn(Raw), cfg: Option<(usize, usize)>, ) -> Value
Allocate a new value with a finalizer
This calls caml_alloc_final under-the-hood, which can has less than ideal performance
behavior. In most cases you should prefer Pointer::alloc_custom when possible.
Sourcepub unsafe fn alloc_custom<T: Custom>() -> Value
pub unsafe fn alloc_custom<T: Custom>() -> Value
Allocate custom value
Sourcepub unsafe fn alloc_abstract_ptr<T>(ptr: *mut T) -> Value
pub unsafe fn alloc_abstract_ptr<T>(ptr: *mut T) -> Value
Allocate an abstract pointer value, it is best to ensure the value is
on the heap using Box::into_raw(Box::from(...)) to create the pointer
and Box::from_raw to free it
Sourcepub unsafe fn new<T: Into<Value>>(v: T) -> Value
pub unsafe fn new<T: Into<Value>>(v: T) -> Value
Create a new Value from an existing OCaml value
Sourcepub unsafe fn array_length(&self) -> usize
pub unsafe fn array_length(&self) -> usize
Get array length
Sourcepub unsafe fn register_global_root(&mut self)
pub unsafe fn register_global_root(&mut self)
See caml_register_global_root
Sourcepub unsafe fn remove_global_root(&mut self)
pub unsafe fn remove_global_root(&mut self)
Set caml_remove_global_root
Sourcepub unsafe fn of_str(s: &str) -> Value
pub unsafe fn of_str(s: &str) -> Value
Convert from a pointer to an OCaml string back to an OCaml value
§Safety
This function assumes that the str argument has been allocated by OCaml
Sourcepub unsafe fn of_bytes(s: &[u8]) -> Value
pub unsafe fn of_bytes(s: &[u8]) -> Value
Convert from a pointer to an OCaml string back to an OCaml value
§Safety
This function assumes that the &[u8] argument has been allocated by OCaml
Sourcepub unsafe fn variant(rt: &Runtime, tag: u8, value: Option<Value>) -> Value
pub unsafe fn variant(rt: &Runtime, tag: u8, value: Option<Value>) -> Value
Create a variant value
Sourcepub unsafe fn result<A: FromValue, B: FromValue>(&self) -> Result<A, B>
pub unsafe fn result<A: FromValue, B: FromValue>(&self) -> Result<A, B>
Convert OCaml ('a, 'b) Result.t to Rust Result<Value, Value>
Sourcepub unsafe fn result_error<T: ToValue>(rt: &Runtime, value: T) -> Value
pub unsafe fn result_error<T: ToValue>(rt: &Runtime, value: T) -> Value
Result.Error value
Sourcepub unsafe fn is_block(&self) -> bool
pub unsafe fn is_block(&self) -> bool
Check if a Value is an integer or block, returning true if the underlying value is a block
Sourcepub unsafe fn is_long(&self) -> bool
pub unsafe fn is_long(&self) -> bool
Check if a Value is an integer or block, returning true if the underlying value is an integer
Sourcepub unsafe fn double_field(&self, i: Size) -> f64
pub unsafe fn double_field(&self, i: Size) -> f64
Get index of underlying OCaml double array value
Sourcepub unsafe fn store_field<V: ToValue>(&mut self, rt: &Runtime, i: Size, val: V)
pub unsafe fn store_field<V: ToValue>(&mut self, rt: &Runtime, i: Size, val: V)
Set index of underlying OCaml block value
Sourcepub unsafe fn store_double_field(&mut self, i: Size, val: f64)
pub unsafe fn store_double_field(&mut self, i: Size, val: f64)
Set index of underlying OCaml double array value
Sourcepub unsafe fn double_val(&self) -> f64
pub unsafe fn double_val(&self) -> f64
Convert an OCaml Float to f64
Sourcepub unsafe fn store_double_val(&mut self, val: f64)
pub unsafe fn store_double_val(&mut self, val: f64)
Store f64 in OCaml Float
Sourcepub unsafe fn nativeint_val(&self) -> isize
pub unsafe fn nativeint_val(&self) -> isize
Convert an OCaml Nativeint to isize
Sourcepub unsafe fn custom_ptr_val<T>(&self) -> *const T
pub unsafe fn custom_ptr_val<T>(&self) -> *const T
Get pointer to data stored in an OCaml custom value
Sourcepub unsafe fn custom_ptr_val_mut<T>(&mut self) -> *mut T
pub unsafe fn custom_ptr_val_mut<T>(&mut self) -> *mut T
Get mutable pointer to data stored in an OCaml custom value
Sourcepub unsafe fn abstract_ptr_val<T>(&self) -> *const T
pub unsafe fn abstract_ptr_val<T>(&self) -> *const T
Get pointer to the pointer contained by Value
Sourcepub unsafe fn abstract_ptr_val_mut<T>(&self) -> *mut T
pub unsafe fn abstract_ptr_val_mut<T>(&self) -> *mut T
Get mutable pointer to the pointer contained by Value
Sourcepub unsafe fn string_val(&self) -> &str
pub unsafe fn string_val(&self) -> &str
Get underlying string pointer
Sourcepub unsafe fn string_val_mut(&mut self) -> &mut str
pub unsafe fn string_val_mut(&mut self) -> &mut str
Get mutable string pointer
Sourcepub unsafe fn bytes_val_mut(&mut self) -> &mut [u8] ⓘ
pub unsafe fn bytes_val_mut(&mut self) -> &mut [u8] ⓘ
Get mutable bytes pointer
Sourcepub unsafe fn call1<A: ToValue>(
&self,
rt: &Runtime,
arg1: A,
) -> Result<Value, Error>
pub unsafe fn call1<A: ToValue>( &self, rt: &Runtime, arg1: A, ) -> Result<Value, Error>
Call a closure with a single argument, returning an exception result
Sourcepub unsafe fn call2<A: ToValue, B: ToValue>(
&self,
rt: &Runtime,
arg1: A,
arg2: B,
) -> Result<Value, Error>
pub unsafe fn call2<A: ToValue, B: ToValue>( &self, rt: &Runtime, arg1: A, arg2: B, ) -> Result<Value, Error>
Call a closure with two arguments, returning an exception result
Sourcepub unsafe fn call3<A: ToValue, B: ToValue, C: ToValue>(
&self,
rt: &Runtime,
arg1: A,
arg2: B,
arg3: C,
) -> Result<Value, Error>
pub unsafe fn call3<A: ToValue, B: ToValue, C: ToValue>( &self, rt: &Runtime, arg1: A, arg2: B, arg3: C, ) -> Result<Value, Error>
Call a closure with three arguments, returning an exception result
Sourcepub unsafe fn call_n<A: AsRef<[Raw]>>(&self, args: A) -> Result<Value, Error>
pub unsafe fn call_n<A: AsRef<[Raw]>>(&self, args: A) -> Result<Value, Error>
Call a closure with n arguments, returning an exception result
Sourcepub unsafe fn call<const N: usize, T: FromValue>(
&self,
rt: &Runtime,
args: [impl ToValue; N],
) -> Result<T, Error>
pub unsafe fn call<const N: usize, T: FromValue>( &self, rt: &Runtime, args: [impl ToValue; N], ) -> Result<T, Error>
Call a closure with a variable number of arguments, returning and exception Result
Sourcepub unsafe fn modify_raw(&mut self, v: Raw)
pub unsafe fn modify_raw(&mut self, v: Raw)
Modify an OCaml value in place using a raw OCaml value as the new value
Sourcepub unsafe fn is_exception_result(&self) -> bool
pub unsafe fn is_exception_result(&self) -> bool
Determines if the current value is an exception
Sourcepub unsafe fn hash_variant<S: AsRef<str>>(
rt: &Runtime,
name: S,
a: Option<Value>,
) -> Value
pub unsafe fn hash_variant<S: AsRef<str>>( rt: &Runtime, name: S, a: Option<Value>, ) -> Value
Get hash variant as OCaml value
Sourcepub unsafe fn method<S: AsRef<str>>(
&self,
rt: &Runtime,
name: S,
) -> Option<Value>
pub unsafe fn method<S: AsRef<str>>( &self, rt: &Runtime, name: S, ) -> Option<Value>
Get object method
Sourcepub unsafe fn seq_next(&self) -> Result<Option<(Value, Value)>, Error>
pub unsafe fn seq_next(&self) -> Result<Option<(Value, Value)>, Error>
Returns the next item and the next Seq.t if available, otherwise Ok(None)
Sourcepub unsafe fn exception_to_string(&self) -> Result<String, Utf8Error>
pub unsafe fn exception_to_string(&self) -> Result<String, Utf8Error>
Convert an OCaml exception value to the string representation
Sourcepub unsafe fn initialize(&mut self, value: Value)
pub unsafe fn initialize(&mut self, value: Value)
Initialize OCaml value using caml_initialize
Sourcepub unsafe fn deep_clone_to_ocaml(self) -> Self
pub unsafe fn deep_clone_to_ocaml(self) -> Self
This will recursively clone any OCaml value The new value is allocated inside the OCaml heap, and may end up being moved or garbage collected.
Sourcepub unsafe fn deep_clone_to_rust(&self) -> Self
pub unsafe fn deep_clone_to_rust(&self) -> Self
This will recursively clone any OCaml value The new value is allocated outside of the OCaml heap, and should only be used for storage inside Rust structures.