Struct ocaml::OCaml[][src]

pub struct OCaml<'a, T> where
    T: 'a, 
{ /* fields omitted */ }

Representation of OCaml values.

Implementations

impl<'a, T> OCaml<'a, T>[src]

pub fn as_ref<'b>(&'b self) -> &'b OCamlCell<T> where
    'a: 'b, 
[src]

Obtains an OCamlRef<T> for this value.

pub fn root(self) -> BoxRoot<T>[src]

pub unsafe fn raw(&self) -> isize[src]

Gets the raw representation for this value reference (pointer or int).

Safety

The resulting raw pointer will not be tracked, and may become invalid after any call into the OCaml runtime. Great care must be taken when working with these values.

pub fn to_rust<RustT>(&self) -> RustT where
    RustT: FromOCaml<T>, 
[src]

Converts this OCaml value into a Rust value.

pub unsafe fn custom_ptr_val<U>(&self) -> *const U[src]

Meant to match Data_custom_val from mlvalues.h

Experimental

Safety

Casts to an arbitrary pointer type, take care before dereferencing

Similar to raw(), the resulting pointer can become invalid after any call into the OCaml runtime, for example allocating OCaml values or calling OCaml functions

impl<'a, T> OCaml<'a, DynBox<T>> where
    T: 'static, 
[src]

pub fn box_value(cr: &'a mut OCamlRuntime, v: T) -> OCaml<'a, DynBox<T>>[src]

Build an OCaml value wrapping a Rust value

The returned value will be opaque to the OCaml side, though you can provide functions using it and expose them to OCaml.

It will be dropped if it stops being referenced by the GC.

Experimental

impl OCaml<'static, ()>[src]

pub fn unit() -> OCaml<'static, ()>[src]

Returns a value that represent OCaml’s unit value.

impl<T> OCaml<'static, Option<T>>[src]

pub fn none() -> OCaml<'static, Option<T>>[src]

Returns a value that represent OCaml’s None value.

impl<'a> OCaml<'a, String>[src]

pub fn as_bytes(&self) -> &'a [u8][src]

Returns an [u8] reference to the internal bytes of this value.

pub fn as_str(&self) -> &'a str[src]

Returns a str reference to the internal bytes of this value.

Panics

Panics if the bytes do not form a valid utf8 string.

pub unsafe fn as_str_unchecked(&self) -> &'a str[src]

Returns a str reference to the internal bytes of this value.

Safety

No checks are performed to ensure that the returned value is a valid utf8 string.

impl<'a> OCaml<'a, OCamlBytes>[src]

pub fn as_bytes(&self) -> &'a [u8][src]

Returns an [u8] reference to the internal bytes of this value.

pub fn as_str(&self) -> &'a str[src]

Returns a str reference to the internal bytes of this value.

Panics

Panics if the bytes do not form a valid utf8 string.

pub unsafe fn as_str_unchecked(&self) -> &'a str[src]

Returns a str reference to the internal bytes of this value.

Safety

No checks are performed to ensure that the returned value is a valid utf8 string.

impl<'a> OCaml<'a, isize>[src]

pub fn to_i64(&self) -> i64[src]

Converts an OCaml int to an i64.

pub unsafe fn of_i64_unchecked(n: i64) -> OCaml<'static, isize>[src]

Creates an OCaml int from an i64 without checking that it fits in an OCaml fixnum.

Safety

OCaml ints are represented as 63bits + 1bit tag, so when converting from an i64, a bit of precision is lost.

pub fn of_i64(
    n: i64
) -> Result<OCaml<'static, isize>, OCamlFixnumConversionError>
[src]

pub fn of_i32(n: i32) -> OCaml<'static, isize>[src]

Creates an OCaml int from an i32.

impl<'a> OCaml<'a, bool>[src]

pub fn to_bool(&self) -> bool[src]

Converts an OCaml boolean into a Rust boolean.

pub fn of_bool(b: bool) -> OCaml<'static, bool>[src]

Creates an OCaml boolean from a Rust boolean.

impl<'a, A> OCaml<'a, Option<A>>[src]

pub fn is_none(&self) -> bool[src]

Returns true if this OCaml option value is an OCaml None.

pub fn is_some(&self) -> bool[src]

Returns true if this OCaml option value is an OCaml Some.

pub fn to_option(&self) -> Option<OCaml<'a, A>>[src]

Converts an OCaml Option<T> value into a Rust Option<OCaml<T>>.

impl<'a, A, Err> OCaml<'a, Result<A, Err>>[src]

pub fn is_ok(&self) -> bool[src]

Returns true if this OCaml result value is an OCaml Ok.

pub fn is_error(&self) -> bool[src]

Returns true if this OCaml result value is an OCaml Error.

pub fn to_result(&self) -> Result<OCaml<'a, A>, OCaml<'a, Err>>[src]

Converts an OCaml Result<T, E> value into a Rust Result<OCaml<T>, OCaml<E>>.

impl<'a, A> OCaml<'a, OCamlList<A>>[src]

pub fn nil() -> OCaml<'a, OCamlList<A>>[src]

Returns an OCaml nil (empty list) value.

pub fn is_empty(&self) -> bool[src]

Returns true if the value is OCaml’s nil (empty list).

pub fn hd(&self) -> Option<OCaml<'a, A>>[src]

Returns the head of an OCaml list.

pub fn tl(&self) -> Option<OCaml<'a, OCamlList<A>>>[src]

Returns the tail of an OCaml list.

pub fn uncons(&self) -> Option<(OCaml<'a, A>, OCaml<'a, OCamlList<A>>)>[src]

Returns a tuple of the head and tail of an OCaml list.

impl<'a, A, B> OCaml<'a, (A, B)>[src]

pub fn to_tuple(&self) -> (OCaml<'a, A>, OCaml<'a, B>)[src]

pub fn fst(&self) -> OCaml<'a, A>[src]

pub fn snd(&self) -> OCaml<'a, B>[src]

impl<'a, A, B, C> OCaml<'a, (A, B, C)>[src]

pub fn to_tuple(&self) -> (OCaml<'a, A>, OCaml<'a, B>, OCaml<'a, C>)[src]

pub fn fst(&self) -> OCaml<'a, A>[src]

pub fn snd(&self) -> OCaml<'a, B>[src]

pub fn tuple_3(&self) -> OCaml<'a, C>[src]

impl<'a, A, B, C, D> OCaml<'a, (A, B, C, D)>[src]

pub fn to_tuple(
    &self
) -> (OCaml<'a, A>, OCaml<'a, B>, OCaml<'a, C>, OCaml<'a, D>)
[src]

pub fn fst(&self) -> OCaml<'a, A>[src]

pub fn snd(&self) -> OCaml<'a, B>[src]

pub fn tuple_3(&self) -> OCaml<'a, C>[src]

pub fn tuple_4(&self) -> OCaml<'a, D>[src]

impl<'a, A, B, C, D, E> OCaml<'a, (A, B, C, D, E)>[src]

pub fn to_tuple(
    &self
) -> (OCaml<'a, A>, OCaml<'a, B>, OCaml<'a, C>, OCaml<'a, D>, OCaml<'a, E>)
[src]

pub fn fst(&self) -> OCaml<'a, A>[src]

pub fn snd(&self) -> OCaml<'a, B>[src]

pub fn tuple_3(&self) -> OCaml<'a, C>[src]

pub fn tuple_4(&self) -> OCaml<'a, D>[src]

pub fn tuple_5(&self) -> OCaml<'a, E>[src]

impl<'a, A, B, C, D, E, F> OCaml<'a, (A, B, C, D, E, F)>[src]

pub fn to_tuple(
    &self
) -> (OCaml<'a, A>, OCaml<'a, B>, OCaml<'a, C>, OCaml<'a, D>, OCaml<'a, E>, OCaml<'a, F>)
[src]

pub fn fst(&self) -> OCaml<'a, A>[src]

pub fn snd(&self) -> OCaml<'a, B>[src]

pub fn tuple_3(&self) -> OCaml<'a, C>[src]

pub fn tuple_4(&self) -> OCaml<'a, D>[src]

pub fn tuple_5(&self) -> OCaml<'a, E>[src]

pub fn tuple_6(&self) -> OCaml<'a, F>[src]

impl<'a, A, B, C, D, E, F, G> OCaml<'a, (A, B, C, D, E, F, G)>[src]

pub fn to_tuple(
    &self
) -> (OCaml<'a, A>, OCaml<'a, B>, OCaml<'a, C>, OCaml<'a, D>, OCaml<'a, E>, OCaml<'a, F>, OCaml<'a, G>)
[src]

pub fn fst(&self) -> OCaml<'a, A>[src]

pub fn snd(&self) -> OCaml<'a, B>[src]

pub fn tuple_3(&self) -> OCaml<'a, C>[src]

pub fn tuple_4(&self) -> OCaml<'a, D>[src]

pub fn tuple_5(&self) -> OCaml<'a, E>[src]

pub fn tuple_6(&self) -> OCaml<'a, F>[src]

pub fn tuple_7(&self) -> OCaml<'a, G>[src]

impl<'a, A, B, C, D, E, F, G, H> OCaml<'a, (A, B, C, D, E, F, G, H)>[src]

pub fn to_tuple(
    &self
) -> (OCaml<'a, A>, OCaml<'a, B>, OCaml<'a, C>, OCaml<'a, D>, OCaml<'a, E>, OCaml<'a, F>, OCaml<'a, G>, OCaml<'a, H>)
[src]

pub fn fst(&self) -> OCaml<'a, A>[src]

pub fn snd(&self) -> OCaml<'a, B>[src]

pub fn tuple_3(&self) -> OCaml<'a, C>[src]

pub fn tuple_4(&self) -> OCaml<'a, D>[src]

pub fn tuple_5(&self) -> OCaml<'a, E>[src]

pub fn tuple_6(&self) -> OCaml<'a, F>[src]

pub fn tuple_7(&self) -> OCaml<'a, G>[src]

pub fn tuple_8(&self) -> OCaml<'a, H>[src]

impl<'a, A, B, C, D, E, F, G, H, I> OCaml<'a, (A, B, C, D, E, F, G, H, I)>[src]

pub fn to_tuple(
    &self
) -> (OCaml<'a, A>, OCaml<'a, B>, OCaml<'a, C>, OCaml<'a, D>, OCaml<'a, E>, OCaml<'a, F>, OCaml<'a, G>, OCaml<'a, H>, OCaml<'a, I>)
[src]

pub fn fst(&self) -> OCaml<'a, A>[src]

pub fn snd(&self) -> OCaml<'a, B>[src]

pub fn tuple_3(&self) -> OCaml<'a, C>[src]

pub fn tuple_4(&self) -> OCaml<'a, D>[src]

pub fn tuple_5(&self) -> OCaml<'a, E>[src]

pub fn tuple_6(&self) -> OCaml<'a, F>[src]

pub fn tuple_7(&self) -> OCaml<'a, G>[src]

pub fn tuple_8(&self) -> OCaml<'a, H>[src]

pub fn tuple_9(&self) -> OCaml<'a, I>[src]

Trait Implementations

impl<'a, A> Borrow<A> for OCaml<'a, DynBox<A>> where
    A: 'static, 
[src]

pub fn borrow(&self) -> &A[src]

Immutably borrows from an owned value. Read more

impl<'a, T> Clone for OCaml<'a, T>[src]

pub fn clone(&self) -> OCaml<'a, T>[src]

Returns a copy of the value. Read more

fn clone_from(&mut self, source: &Self)1.0.0[src]

Performs copy-assignment from source. Read more

impl<'a, T> Deref for OCaml<'a, T>[src]

type Target = OCamlCell<T>

The resulting type after dereferencing.

pub fn deref(&self) -> &OCamlCell<T>[src]

Dereferences the value.

impl<'a, T> FromValue<'a> for OCaml<'a, T>[src]

fn from_value<'b>(v: Value) -> OCaml<'a, T>[src]

Convert from OCaml value

impl<'a, T> IntoValue for OCaml<'a, T>[src]

fn into_value(self, _rt: &Runtime) -> Value[src]

Convert to OCaml value

impl<'a, T> Copy for OCaml<'a, T>[src]

Auto Trait Implementations

impl<'a, T> RefUnwindSafe for OCaml<'a, T> where
    T: RefUnwindSafe

impl<'a, T> Send for OCaml<'a, T> where
    T: Sync

impl<'a, T> Sync for OCaml<'a, T> where
    T: Sync

impl<'a, T> Unpin for OCaml<'a, T>

impl<'a, T> UnwindSafe for OCaml<'a, T> where
    T: RefUnwindSafe

Blanket Implementations

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

pub fn type_id(&self) -> TypeId[src]

Gets the TypeId of self. Read more

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

pub fn borrow(&self) -> &T[src]

Immutably borrows from an owned value. Read more

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

pub fn borrow_mut(&mut self) -> &mut T[src]

Mutably borrows from an owned value. Read more

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

pub fn from(t: T) -> T[src]

Performs the conversion.

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

pub fn into(self) -> U[src]

Performs the conversion.

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

type Owned = T

The resulting type after obtaining ownership.

pub fn to_owned(&self) -> T[src]

Creates owned data from borrowed data, usually by cloning. Read more

pub fn clone_into(&self, target: &mut T)[src]

🔬 This is a nightly-only experimental API. (toowned_clone_into)

recently added

Uses borrowed data to replace owned data, usually by cloning. Read more

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.

pub fn try_from(value: U) -> Result<T, <T as TryFrom<U>>::Error>[src]

Performs the conversion.

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.

pub fn try_into(self) -> Result<U, <U as TryFrom<T>>::Error>[src]

Performs the conversion.