1use crate::error::{CamlError, Error};
2use crate::tag::Tag;
3use crate::{root::Root, sys, util, Pointer, Runtime};
4
5pub type Size = sys::Size;
7
8#[derive(Debug, Clone, PartialEq, PartialOrd, Eq)]
10pub enum Value {
11 Root(Root),
13
14 Raw(sys::Value),
17}
18
19#[derive(Debug, Clone, Copy, PartialEq, PartialOrd, Eq)]
21#[repr(transparent)]
22pub struct Raw(pub sys::Value);
23
24impl Raw {
25 pub unsafe fn as_value(&self) -> Value {
30 Value::Raw(self.0)
31 }
32
33 pub unsafe fn as_pointer<T>(&self) -> Pointer<T> {
35 Pointer::from_value(self.as_value())
36 }
37}
38
39impl AsRef<sys::Value> for Raw {
40 fn as_ref(&self) -> &sys::Value {
41 &self.0
42 }
43}
44
45impl From<sys::Value> for Raw {
46 fn from(x: sys::Value) -> Raw {
47 Raw(x)
48 }
49}
50
51impl From<Raw> for sys::Value {
52 fn from(x: Raw) -> sys::Value {
53 x.0
54 }
55}
56
57impl From<sys::Value> for Value {
58 fn from(v: sys::Value) -> Self {
59 unsafe { Value::Root(Root::new(v)) }
60 }
61}
62
63impl From<Raw> for Value {
64 fn from(v: Raw) -> Self {
65 Value::Raw(v.into())
66 }
67}
68
69pub unsafe trait ToValue {
75 fn to_value(&self, rt: &Runtime) -> Value;
77}
78
79pub unsafe trait FromValue {
85 fn from_value(v: Value) -> Self;
87}
88
89unsafe impl ToValue for Value {
90 fn to_value(&self, _rt: &Runtime) -> Value {
91 self.clone()
92 }
93}
94
95unsafe impl FromValue for Value {
96 fn from_value(v: Value) -> Value {
97 v
98 }
99}
100
101unsafe impl ToValue for Raw {
102 fn to_value(&self, _rt: &Runtime) -> Value {
103 unsafe { Value::new(self.0) }
104 }
105}
106
107unsafe impl FromValue for Raw {
108 #[inline]
109 fn from_value(v: Value) -> Raw {
110 v.raw()
111 }
112}
113
114impl Value {
115 pub fn raw(&self) -> Raw {
117 match self {
118 Value::Root(r) => unsafe { r.get().into() },
119 Value::Raw(r) => Raw(*r),
120 }
121 }
122
123 pub fn to<T: FromValue>(&self) -> T {
125 T::from_value(Value::Raw(self.raw().0))
126 }
127
128 pub fn into<T: FromValue>(self) -> T {
130 T::from_value(self)
131 }
132
133 pub unsafe fn named(name: &str) -> Option<Value> {
135 let s = match util::CString::new(name) {
136 Ok(s) => s,
137 Err(_) => return None,
138 };
139 let named = sys::caml_named_value(s.as_ptr());
140 if named.is_null() {
141 return None;
142 }
143
144 Some(Value::new(*named))
145 }
146
147 pub unsafe fn alloc(n: usize, tag: Tag) -> Value {
149 Value::new(sys::caml_alloc(n, tag.into()))
150 }
151
152 pub unsafe fn alloc_double_array(n: usize) -> Value {
154 Value::new(sys::caml_alloc_float_array(n))
155 }
156
157 pub unsafe fn alloc_tuple(n: usize) -> Value {
159 Value::new(sys::caml_alloc_tuple(n))
160 }
161
162 pub unsafe fn alloc_small(n: usize, tag: Tag) -> Value {
164 Value::new(sys::caml_alloc_small(n, tag.into()))
165 }
166
167 pub unsafe fn alloc_final<T>(
172 finalizer: unsafe extern "C" fn(Raw),
173 cfg: Option<(usize, usize)>,
174 ) -> Value {
175 let (used, max) = cfg.unwrap_or((0, 1));
176 Value::new(sys::caml_alloc_final(
177 core::mem::size_of::<T>(),
178 #[allow(clippy::missing_transmute_annotations)]
179 core::mem::transmute(finalizer),
180 used,
181 max,
182 ))
183 }
184
185 pub unsafe fn alloc_custom<T: crate::Custom>() -> Value {
187 let size = core::mem::size_of::<T>();
188 Value::new(sys::caml_alloc_custom(
189 T::ops() as *const _ as *const sys::custom_operations,
190 size,
191 T::USED,
192 T::MAX,
193 ))
194 }
195
196 pub unsafe fn alloc_abstract_ptr<T>(ptr: *mut T) -> Value {
200 let x = Self::alloc(1, Tag::ABSTRACT);
201 let dest = x.raw().0 as *mut *mut T;
202 *dest = ptr;
203 x
204 }
205
206 #[inline]
207 pub unsafe fn new<T: Into<Value>>(v: T) -> Value {
209 v.into()
210 }
211
212 pub unsafe fn array_length(&self) -> usize {
214 sys::caml_array_length(self.raw().into())
215 }
216
217 pub unsafe fn register_global_root(&mut self) {
219 sys::caml_register_global_root(&mut self.raw().0)
220 }
221
222 pub unsafe fn remove_global_root(&mut self) {
224 sys::caml_remove_global_root(&mut self.raw().0)
225 }
226
227 pub unsafe fn tag(&self) -> Tag {
229 sys::tag_val(self.raw().0).into()
230 }
231
232 pub unsafe fn bool(b: bool) -> Value {
234 Value::int(b as crate::Int)
235 }
236
237 pub unsafe fn string<S: AsRef<str>>(s: S) -> Value {
239 let s = s.as_ref();
240 Value::new(sys::caml_alloc_initialized_string(
241 s.len(),
242 s.as_ptr() as *const _,
243 ))
244 }
245
246 pub unsafe fn bytes<S: AsRef<[u8]>>(s: S) -> Value {
248 let s = s.as_ref();
249 Value::new(sys::caml_alloc_initialized_string(
250 s.len(),
251 s.as_ptr() as *const _,
252 ))
253 }
254
255 pub unsafe fn of_str(s: &str) -> Value {
260 Value::new(s.as_ptr() as isize)
261 }
262
263 pub unsafe fn of_bytes(s: &[u8]) -> Value {
268 Value::new(s.as_ptr() as isize)
269 }
270
271 pub unsafe fn some<V: ToValue>(rt: &Runtime, v: V) -> Value {
273 let v = v.to_value(rt);
274 let mut x = Value::new(sys::caml_alloc(1, 0));
275 x.store_field(rt, 0, &v);
276 x
277 }
278
279 #[inline(always)]
281 pub fn none() -> Value {
282 unsafe { Value::new(sys::NONE) }
283 }
284
285 #[inline(always)]
287 pub fn unit() -> Value {
288 unsafe { Value::new(sys::UNIT) }
289 }
290
291 pub unsafe fn variant(rt: &Runtime, tag: u8, value: Option<Value>) -> Value {
293 match value {
294 Some(v) => {
295 let mut value = Value::new(sys::caml_alloc(1, tag));
296 value.store_field(rt, 0, v);
297 value
298 }
299 None => Value::new(sys::caml_alloc(0, tag)),
300 }
301 }
302
303 pub unsafe fn result_ok<T: ToValue>(rt: &Runtime, value: T) -> Value {
305 Self::variant(rt, 0, Some(value.to_value(rt)))
306 }
307
308 pub unsafe fn result<A: FromValue, B: FromValue>(&self) -> Result<A, B> {
310 let tag = self.tag();
311 if tag.0 == 0 {
312 Ok(FromValue::from_value(self.field(0)))
313 } else {
314 Err(FromValue::from_value(self.field(0)))
315 }
316 }
317
318 pub unsafe fn result_error<T: ToValue>(rt: &Runtime, value: T) -> Value {
320 Self::variant(rt, 1, Some(value.to_value(rt)))
321 }
322
323 pub unsafe fn int(i: crate::Int) -> Value {
325 Value::new(sys::val_int(i))
326 }
327
328 pub unsafe fn uint(i: crate::Uint) -> Value {
330 Value::new(sys::val_int(i as crate::Int))
331 }
332
333 pub unsafe fn int64(i: i64) -> Value {
335 Value::new(sys::caml_copy_int64(i))
336 }
337
338 pub unsafe fn int32(i: i32) -> Value {
340 Value::new(sys::caml_copy_int32(i))
341 }
342
343 pub unsafe fn nativeint(i: isize) -> Value {
345 Value::new(sys::caml_copy_nativeint(i))
346 }
347
348 pub unsafe fn double(d: f64) -> Value {
350 Value::new(sys::caml_copy_double(d))
351 }
352
353 pub unsafe fn is_block(&self) -> bool {
356 sys::is_block(self.raw().0)
357 }
358
359 pub unsafe fn is_long(&self) -> bool {
362 sys::is_long(self.raw().0)
363 }
364
365 pub unsafe fn field(&self, i: Size) -> Value {
367 Value::new(*sys::field(self.raw().0, i))
368 }
369
370 pub unsafe fn double_field(&self, i: Size) -> f64 {
372 sys::caml_sys_double_field(self.raw().0, i)
373 }
374
375 pub unsafe fn store_field<V: ToValue>(&mut self, rt: &Runtime, i: Size, val: V) {
377 let v = val.to_value(rt);
378 sys::store_field(self.raw().0, i, v.raw().0)
379 }
380
381 pub unsafe fn store_double_field(&mut self, i: Size, val: f64) {
383 sys::caml_sys_store_double_field(self.raw().0, i, val)
384 }
385
386 pub unsafe fn int_val(&self) -> isize {
388 sys::int_val(self.raw().0)
389 }
390
391 pub unsafe fn double_val(&self) -> f64 {
393 sys::caml_sys_double_val(self.raw().0)
394 }
395
396 pub unsafe fn store_double_val(&mut self, val: f64) {
398 sys::caml_sys_store_double_val(self.raw().0, val)
399 }
400
401 pub unsafe fn int32_val(&self) -> i32 {
403 *self.custom_ptr_val::<i32>()
404 }
405
406 pub unsafe fn int64_val(&self) -> i64 {
408 *self.custom_ptr_val::<i64>()
409 }
410
411 pub unsafe fn nativeint_val(&self) -> isize {
413 *self.custom_ptr_val::<isize>()
414 }
415
416 pub unsafe fn custom_ptr_val<T>(&self) -> *const T {
418 sys::field(self.raw().0, 1) as *const T
419 }
420
421 pub unsafe fn custom_ptr_val_mut<T>(&mut self) -> *mut T {
423 sys::field(self.raw().0, 1) as *mut T
424 }
425
426 pub unsafe fn abstract_ptr_val<T>(&self) -> *const T {
428 *(self.raw().0 as *const *const T)
429 }
430
431 pub unsafe fn abstract_ptr_val_mut<T>(&self) -> *mut T {
433 *(self.raw().0 as *mut *mut T)
434 }
435
436 pub unsafe fn string_val(&self) -> &str {
438 let len = sys::caml_string_length(self.raw().0);
439 let ptr = sys::string_val(self.raw().0);
440 let slice = ::core::slice::from_raw_parts(ptr, len);
441 ::core::str::from_utf8(slice).expect("Invalid UTF-8")
442 }
443
444 pub unsafe fn bytes_val(&self) -> &[u8] {
446 let len = sys::caml_string_length(self.raw().0);
447 let ptr = sys::string_val(self.raw().0);
448 ::core::slice::from_raw_parts(ptr, len)
449 }
450
451 pub unsafe fn string_val_mut(&mut self) -> &mut str {
453 let len = sys::caml_string_length(self.raw().0);
454 let ptr = sys::string_val(self.raw().0);
455
456 let slice = ::core::slice::from_raw_parts_mut(ptr, len);
457 ::core::str::from_utf8_mut(slice).expect("Invalid UTF-8")
458 }
459
460 pub unsafe fn bytes_val_mut(&mut self) -> &mut [u8] {
462 let len = sys::caml_string_length(self.raw().0);
463 let ptr = sys::string_val(self.raw().0);
464 ::core::slice::from_raw_parts_mut(ptr, len)
465 }
466
467 pub unsafe fn exception(&self) -> Option<Value> {
469 if !self.is_exception_result() {
470 return None;
471 }
472
473 Some(Value::new(sys::extract_exception(self.raw().0)))
474 }
475
476 unsafe fn check_result(mut self) -> Result<Value, Error> {
478 if !self.is_exception_result() {
479 return Ok(self);
480 }
481
482 match &mut self {
483 Value::Root(r) => {
484 r.modify(sys::extract_exception(r.get()));
485 }
486 Value::Raw(mut r) => sys::caml_modify(&mut r, sys::extract_exception(r)),
487 }
488
489 Err(CamlError::Exception(self).into())
490 }
491
492 pub unsafe fn call1<A: ToValue>(&self, rt: &Runtime, arg1: A) -> Result<Value, Error> {
494 if self.tag() != Tag::CLOSURE {
495 return Err(Error::NotCallable);
496 }
497
498 let v = {
499 let arg1 = arg1.to_value(rt);
500 Value::new(sys::caml_callback_exn(self.raw().0, arg1.raw().0))
501 };
502 v.check_result()
503 }
504
505 pub unsafe fn call2<A: ToValue, B: ToValue>(
507 &self,
508 rt: &Runtime,
509 arg1: A,
510 arg2: B,
511 ) -> Result<Value, Error> {
512 if self.tag() != Tag::CLOSURE {
513 return Err(Error::NotCallable);
514 }
515
516 let v = {
517 let arg1 = arg1.to_value(rt);
518 let arg2 = arg2.to_value(rt);
519
520 Value::new(sys::caml_callback2_exn(
521 self.raw().0,
522 arg1.raw().0,
523 arg2.raw().0,
524 ))
525 };
526
527 v.check_result().map(Value::into)
528 }
529
530 pub unsafe fn call3<A: ToValue, B: ToValue, C: ToValue>(
532 &self,
533 rt: &Runtime,
534 arg1: A,
535 arg2: B,
536 arg3: C,
537 ) -> Result<Value, Error> {
538 if self.tag() != Tag::CLOSURE {
539 return Err(Error::NotCallable);
540 }
541
542 let v = {
543 let arg1 = arg1.to_value(rt);
544 let arg2 = arg2.to_value(rt);
545 let arg3 = arg3.to_value(rt);
546
547 Value::new(sys::caml_callback3_exn(
548 self.raw().0,
549 arg1.raw().0,
550 arg2.raw().0,
551 arg3.raw().0,
552 ))
553 };
554
555 v.check_result().map(Value::into)
556 }
557
558 pub unsafe fn call_n<A: AsRef<[Raw]>>(&self, args: A) -> Result<Value, Error> {
560 if self.tag() != Tag::CLOSURE {
561 return Err(Error::NotCallable);
562 }
563
564 let n = args.as_ref().len();
565
566 let v: Value = Value::new(sys::caml_callbackN_exn(
567 self.raw().0,
568 n,
569 args.as_ref().as_ptr() as *mut sys::Value,
570 ));
571
572 v.check_result()
573 }
574
575 #[cfg(not(feature = "no-std"))]
577 pub unsafe fn call<const N: usize, T: FromValue>(
578 &self,
579 rt: &Runtime,
580 args: [impl ToValue; N],
581 ) -> Result<T, Error> {
582 if self.tag() != Tag::CLOSURE {
583 return Err(Error::NotCallable);
584 }
585
586 let n = args.len();
587 let mut a = vec![];
588
589 for arg in args {
590 a.push(arg.to_value(rt));
591 }
592
593 if a.is_empty() {
594 a.push(Value::unit());
595 }
596
597 let b: Vec<Raw> = a.iter().map(|x| x.raw()).collect();
598
599 let v: Value = Value::new(sys::caml_callbackN_exn(
600 self.raw().0,
601 n,
602 b.as_ptr() as *mut sys::Value,
603 ));
604
605 FromValue::from_value(v.check_result()?)
606 }
607
608 pub unsafe fn modify<V: ToValue>(&mut self, rt: &Runtime, v: V) {
610 let v = v.to_value(rt);
611 match self {
612 Value::Root(r) => {
613 r.modify(v.raw().into());
614 }
615 Value::Raw(r) => sys::caml_modify(r, v.raw().into()),
616 }
617 }
618
619 pub unsafe fn modify_raw(&mut self, v: Raw) {
621 match self {
622 Value::Root(r) => r.modify(v.into()),
623 Value::Raw(r) => sys::caml_modify(r, v.into()),
624 }
625 }
626
627 pub unsafe fn is_exception_result(&self) -> bool {
629 sys::is_exception_result(self.raw().0)
630 }
631
632 pub unsafe fn hash_variant<S: AsRef<str>>(rt: &Runtime, name: S, a: Option<Value>) -> Value {
634 let s = util::CString::new(name.as_ref()).expect("Invalid C string");
635 let hash = Value::new(sys::caml_hash_variant(s.as_ptr() as *const u8));
636 match a {
637 Some(x) => {
638 let mut output = Value::alloc_small(2, Tag(0));
639 output.store_field(rt, 0, &hash);
640 output.store_field(rt, 1, &x);
641 output
642 }
643 None => hash,
644 }
645 }
646
647 pub unsafe fn method<S: AsRef<str>>(&self, rt: &Runtime, name: S) -> Option<Value> {
649 if self.tag() != Tag::OBJECT {
650 return None;
651 }
652
653 let variant = Self::hash_variant(rt, name, None);
654 let v = sys::caml_get_public_method(self.raw().0, variant.raw().0);
655
656 if v == 0 {
657 return None;
658 }
659
660 Some(Value::new(v))
661 }
662
663 pub unsafe fn seq_next(&self) -> Result<Option<(Value, Value)>, Error> {
665 let x = self.call_n([Value::unit().raw()])?;
666
667 if !x.is_block() {
668 return Ok(None);
669 }
670
671 let v = x.field(0);
672 let next = x.field(1);
673
674 Ok(Some((v, next)))
675 }
676
677 #[cfg(not(feature = "no-std"))]
679 pub unsafe fn exception_to_string(&self) -> Result<String, core::str::Utf8Error> {
680 let ptr = ocaml_sys::caml_format_exception(self.raw().0);
681 std::ffi::CStr::from_ptr(ptr).to_str().map(|x| x.to_owned())
682 }
683
684 pub unsafe fn initialize(&mut self, value: Value) {
686 sys::caml_initialize(&mut self.raw().0, value.raw().0)
687 }
688
689 #[doc(hidden)]
690 pub unsafe fn slice<'a>(&self) -> &'a [Raw] {
691 ::core::slice::from_raw_parts(
692 (self.raw().0 as *const Raw).offset(-1),
693 sys::wosize_val(self.raw().0) + 1,
694 )
695 }
696
697 #[doc(hidden)]
698 pub unsafe fn slice_mut<'a>(&self) -> &'a mut [Raw] {
699 ::core::slice::from_raw_parts_mut(
700 (self.raw().0 as *mut Raw).offset(-1),
701 sys::wosize_val(self.raw().0) + 1,
702 )
703 }
704
705 pub unsafe fn deep_clone_to_ocaml(self) -> Self {
709 if self.is_long() {
710 return self;
711 }
712 let wosize = sys::wosize_val(self.raw().0);
713 let val1 = Self::alloc(wosize, self.tag());
714 let ptr0 = self.raw().0 as *const sys::Value;
715 let ptr1 = val1.raw().0 as *mut sys::Value;
716 if self.tag() >= Tag::NO_SCAN {
717 ptr0.copy_to_nonoverlapping(ptr1, wosize);
718 return val1;
719 }
720 for i in 0..(wosize as isize) {
721 sys::caml_initialize(
722 ptr1.offset(i),
723 Value::new(ptr0.offset(i).read())
724 .deep_clone_to_ocaml()
725 .raw()
726 .0,
727 );
728 }
729 val1
730 }
731
732 #[cfg(not(feature = "no-std"))]
736 pub unsafe fn deep_clone_to_rust(&self) -> Self {
737 if self.is_long() {
738 return self.clone();
739 }
740 if self.tag() >= Tag::NO_SCAN {
741 let slice0 = self.slice();
742 let vec1 = slice0.to_vec();
743 let ptr1 = vec1.as_ptr();
744 core::mem::forget(vec1);
745 return Value::new(ptr1.offset(1) as isize);
746 }
747 let slice0 = self.slice();
748 Value::new(slice0.as_ptr().offset(1) as isize)
749 }
750
751 pub fn root(self) -> Value {
753 match self {
754 Value::Raw(raw) => unsafe { Value::Root(Root::new(raw)) },
755 _ => self,
756 }
757 }
758}