[][src]Struct ocaml::Value

#[repr(transparent)]pub struct Value(pub Value);

Value wraps the native OCaml value type transparently, this means it has the same representation as an ocaml_sys::Value

Methods

impl Value[src]

pub fn named<T: FromValue>(name: &str) -> Option<T>[src]

Returns a named value registered by OCaml

pub fn alloc(n: usize, tag: Tag) -> Value[src]

Allocate a new value with the given size and tag.

pub fn alloc_tuple(n: usize) -> Value[src]

Allocate a new tuple value

pub fn alloc_small(n: usize, tag: Tag) -> Value[src]

Allocate a new small value with the given size and tag

pub fn alloc_final<T>(
    finalizer: unsafe extern "C" fn(_: Value),
    cfg: Option<(usize, usize)>
) -> Value
[src]

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 Poiner::alloc_custom when possible.

pub fn alloc_custom<T: Custom>() -> Value[src]

Allocate custom value

pub const fn new(v: Value) -> Value[src]

Create a new Value from an existing OCaml value

pub fn array_length(self) -> usize[src]

Get array length

pub fn register_global_root(&mut self)[src]

See caml_register_global_root

pub fn remove_global_root(&mut self)[src]

Set caml_remove_global_root

pub fn tag(self) -> Tag[src]

Get the tag for the underlying OCaml value

pub const fn bool(b: bool) -> Value[src]

Convert a boolean to OCaml value

pub fn some<V: ToValue>(v: V) -> Value[src]

OCaml Some value

pub const fn none() -> Value[src]

OCaml None value

pub const fn unit() -> Value[src]

OCaml Unit value

pub fn variant(tag: u8, value: Option<Value>) -> Value[src]

Create a variant value

pub fn ptr<T>(p: *const T) -> Value[src]

Create a new opaque pointer Value

pub const fn int(i: Int) -> Value[src]

Create an OCaml int

pub const fn uint(i: Uint) -> Value[src]

Create an OCaml int

pub fn int64(i: i64) -> Value[src]

Create an OCaml Int64 from i64

pub fn int32(i: i32) -> Value[src]

Create an OCaml Int32 from i32

pub fn nativeint(i: isize) -> Value[src]

Create an OCaml Nativeint from isize

pub fn float(d: f64) -> Value[src]

Create an OCaml Float from f64

pub fn is_block(self) -> bool[src]

Check if a Value is an integer or block, returning true if the underlying value is a block

pub fn is_long(self) -> bool[src]

Check if a Value is an integer or block, returning true if the underlying value is an integer

pub fn field<T: FromValue>(self, i: Size) -> T[src]

Get index of underlying OCaml block value

pub fn store_field<V: ToValue>(&mut self, i: Size, val: V)[src]

Set index of underlying OCaml block value

pub const fn int_val(self) -> isize[src]

Convert an OCaml int to isize

pub fn float_val(self) -> f64[src]

Convert an OCaml Float to f64

pub fn int32_val(self) -> i32[src]

Convert an OCaml Int32 to i32

pub fn int64_val(self) -> i64[src]

Convert an OCaml Int64 to i64

pub fn nativeint_val(self) -> isize[src]

Convert an OCaml Nativeint to isize

pub fn custom_ptr_val<T>(self) -> *const T[src]

Get pointer to data stored in an OCaml custom value

pub fn custom_mut_ptr_val<T>(self) -> *mut T[src]

Get mutable pointer to data stored in an OCaml custom value

pub fn ptr_val<T>(self) -> *const T[src]

Get pointer to data stored in an opaque value

pub fn mut_ptr_val<T>(self) -> *mut T[src]

Get mutable pointer to data stored in an opaque value

pub fn exception<A: FromValue>(self) -> Option<A>[src]

Extract OCaml exception

pub fn call<A: ToValue>(self, arg: A) -> Result<Value, Error>[src]

Call a closure with a single argument, returning an exception value

pub fn call2<A: ToValue, B: ToValue>(
    self,
    arg1: A,
    arg2: B
) -> Result<Value, Error>
[src]

Call a closure with two arguments, returning an exception value

pub fn call3<A: ToValue, B: ToValue, C: ToValue>(
    self,
    arg1: A,
    arg2: B,
    arg3: C
) -> Result<Value, Error>
[src]

Call a closure with three arguments, returning an exception value

pub fn call_n<A: AsRef<[Value]>>(self, args: A) -> Result<Value, Error>[src]

Call a closure with n arguments, returning an exception value

pub fn modify<V: ToValue>(&mut self, v: V)[src]

Modify an OCaml value in place

pub fn is_exception_result(self) -> bool[src]

Determines if the current value is an exception

pub fn hash_variant<S: AsRef<str>>(name: S, a: Option<Value>) -> Value[src]

Get hash variant as OCaml value

pub fn method<S: AsRef<str>>(self, name: S) -> Option<Value>[src]

Get object method

pub fn deep_clone_to_ocaml(self) -> Self[src]

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.

Requires the deep-clone feature

pub fn deep_clone_to_rust(self) -> Self[src]

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.

Requires the deep-clone feature

Trait Implementations

impl Clone for Value[src]

impl Copy for Value[src]

impl Debug for Value[src]

impl FromValue for Value[src]

impl PartialEq<Value> for Value[src]

impl PartialOrd<Value> for Value[src]

impl StructuralPartialEq for Value[src]

impl<'_> ToValue for &'_ Value[src]

impl ToValue for Value[src]

Auto Trait Implementations

impl RefUnwindSafe for Value

impl Send for Value

impl Sync for Value

impl Unpin for Value

impl UnwindSafe for Value

Blanket Implementations

impl<T> Any for T where
    T: 'static + ?Sized
[src]

impl<T> Borrow<T> for T where
    T: ?Sized
[src]

impl<T> BorrowMut<T> for T where
    T: ?Sized
[src]

impl<T> From<T> for T[src]

impl<T, U> Into<U> for T where
    U: From<T>, 
[src]

impl<T> ToOwned for T where
    T: Clone
[src]

type Owned = T

The resulting type after obtaining ownership.

impl<T, U> TryFrom<U> for T where
    U: Into<T>, 
[src]

type Error = Infallible

The type returned in the event of a conversion error.

impl<T, U> TryInto<U> for T where
    U: TryFrom<T>, 
[src]

type Error = <U as TryFrom<T>>::Error

The type returned in the event of a conversion error.