Pointer

Struct Pointer 

Source
#[repr(transparent)]
pub struct Pointer<T>(pub Value, _);
Expand description

A handle to a Rust value/reference owned by the OCaml heap.

This should only be used with values allocated with alloc_final or alloc_custom, for abstract pointers see Value::alloc_abstract_ptr and Value::abstract_ptr_val

Tuple Fields§

§0: Value

Implementations§

Source§

impl<T: Custom> Pointer<T>

Source

pub fn alloc_custom(x: T) -> Pointer<T>
where T: Custom,

Allocate a Custom value

Source§

impl<T> Pointer<T>

Source

pub fn alloc_final( x: T, finalizer: Option<unsafe extern "C" fn(Raw)>, used_max: Option<(usize, usize)>, ) -> Pointer<T>

Allocate a new value with an optional custom finalizer and used/max

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.

Source

pub fn alloc(x: T) -> Pointer<T>

Allocate a new abstract value

Source

pub unsafe fn drop_in_place(self)

Drop pointer in place

§Safety

This should only be used when you’re in control of the underlying value and want to drop it. It should only be called once.

Source

pub fn set(&mut self, x: T)

Replace the inner value with the provided argument

Source

pub fn as_ptr(&self) -> *const T

Access the underlying pointer

Source

pub fn as_mut_ptr(&mut self) -> *mut T

Access the underlying mutable pointer

Trait Implementations§

Source§

impl<T> AsMut<T> for Pointer<T>

Source§

fn as_mut(&mut self) -> &mut T

Converts this type into a mutable reference of the (usually inferred) input type.
Source§

impl<T> AsRef<T> for Pointer<T>

Source§

fn as_ref(&self) -> &T

Converts this type into a shared reference of the (usually inferred) input type.
Source§

impl<T: Clone> Clone for Pointer<T>

Source§

fn clone(&self) -> Pointer<T>

Returns a duplicate of the value. Read more
1.0.0 · Source§

fn clone_from(&mut self, source: &Self)

Performs copy-assignment from source. Read more
Source§

impl<T: Custom> From<T> for Pointer<T>

Source§

fn from(x: T) -> Self

Converts to this type from the input type.
Source§

impl<T> FromValue for Pointer<T>

Source§

fn from_value(value: Value) -> Self

Convert from OCaml value
Source§

impl<T: PartialEq> PartialEq for Pointer<T>

Source§

fn eq(&self, other: &Pointer<T>) -> bool

Tests for self and other values to be equal, and is used by ==.
1.0.0 · Source§

fn ne(&self, other: &Rhs) -> bool

Tests for !=. The default implementation is almost always sufficient, and should not be overridden without very good reason.
Source§

impl<T: PartialOrd> PartialOrd for Pointer<T>

Source§

fn partial_cmp(&self, other: &Pointer<T>) -> Option<Ordering>

This method returns an ordering between self and other values if one exists. Read more
1.0.0 · Source§

fn lt(&self, other: &Rhs) -> bool

Tests less than (for self and other) and is used by the < operator. Read more
1.0.0 · Source§

fn le(&self, other: &Rhs) -> bool

Tests less than or equal to (for self and other) and is used by the <= operator. Read more
1.0.0 · Source§

fn gt(&self, other: &Rhs) -> bool

Tests greater than (for self and other) and is used by the > operator. Read more
1.0.0 · Source§

fn ge(&self, other: &Rhs) -> bool

Tests greater than or equal to (for self and other) and is used by the >= operator. Read more
Source§

impl<T> ToValue for Pointer<T>

Source§

fn to_value(&self, _rt: &Runtime) -> Value

Convert to OCaml value
Source§

impl<T: Eq> Eq for Pointer<T>

Source§

impl<T> StructuralPartialEq for Pointer<T>

Auto Trait Implementations§

§

impl<T> Freeze for Pointer<T>

§

impl<T> !RefUnwindSafe for Pointer<T>

§

impl<T> !Send for Pointer<T>

§

impl<T> !Sync for Pointer<T>

§

impl<T> Unpin for Pointer<T>
where T: Unpin,

§

impl<T> !UnwindSafe for Pointer<T>

Blanket Implementations§

Source§

impl<T> Any for T
where T: 'static + ?Sized,

Source§

fn type_id(&self) -> TypeId

Gets the TypeId of self. Read more
Source§

impl<T> Borrow<T> for T
where T: ?Sized,

Source§

fn borrow(&self) -> &T

Immutably borrows from an owned value. Read more
Source§

impl<T> BorrowMut<T> for T
where T: ?Sized,

Source§

fn borrow_mut(&mut self) -> &mut T

Mutably borrows from an owned value. Read more
Source§

impl<T> CloneToUninit for T
where T: Clone,

Source§

unsafe fn clone_to_uninit(&self, dest: *mut u8)

🔬This is a nightly-only experimental API. (clone_to_uninit)
Performs copy-assignment from self to dest. Read more
Source§

impl<T> From<T> for T

Source§

fn from(t: T) -> T

Returns the argument unchanged.

Source§

impl<T, U> Into<U> for T
where U: From<T>,

Source§

fn into(self) -> U

Calls U::from(self).

That is, this conversion is whatever the implementation of From<T> for U chooses to do.

Source§

impl<T> ToOwned for T
where T: Clone,

Source§

type Owned = T

The resulting type after obtaining ownership.
Source§

fn to_owned(&self) -> T

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

fn clone_into(&self, target: &mut T)

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

impl<T, U> TryFrom<U> for T
where U: Into<T>,

Source§

type Error = Infallible

The type returned in the event of a conversion error.
Source§

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

Performs the conversion.
Source§

impl<T, U> TryInto<U> for T
where U: TryFrom<T>,

Source§

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

The type returned in the event of a conversion error.
Source§

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

Performs the conversion.