Skip to content

Commit

Permalink
ENHANCED: added unwrap() method and PlUnwrap()
Browse files Browse the repository at this point in the history
  • Loading branch information
kamahen committed Oct 22, 2023
1 parent 589f7c9 commit 790c664
Show file tree
Hide file tree
Showing 5 changed files with 344 additions and 316 deletions.
6 changes: 3 additions & 3 deletions SWI-cpp2-atommap.h
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,7 @@ class AtomMap
[[nodiscard]]
ValueType
find_inside_lock(PlAtom key)
{ const auto lookup = entries_.find(key.C_);
{ const auto lookup = entries_.find(key.unwrap());
ValueType value(ValueType::null);
if ( lookup != entries_.end() )
value.reset(ValueType(lookup->second));
Expand All @@ -119,15 +119,15 @@ class AtomMap
{ StoredValueType stored_value(StoredValueType::null);
register_value(value, &stored_value);
key.register_ref();
entries_.insert(std::make_pair(key.C_, stored_value));
entries_.insert(std::make_pair(key.unwrap(), stored_value));
} else if ( lookup != value )
{ throw PlPermissionError(insert_op_, insert_type_, PlTerm_atom(key));
}
}

void
erase_inside_lock(PlAtom key)
{ auto lookup = entries_.find(key.C_);
{ auto lookup = entries_.find(key.unwrap());
if ( lookup == entries_.end() )
return;
// TODO: As an alternative to removing the entry, leave it in place
Expand Down
77 changes: 38 additions & 39 deletions SWI-cpp2.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -230,7 +230,7 @@ const std::wstring
PlAtom::as_wstring() const
{ PlStringBuffers _string_buffers;
size_t len;
const wchar_t *s = Plx_atom_wchars(C_, &len);
const wchar_t *s = Plx_atom_wchars(unwrap(), &len);
return std::wstring(s, len);
}

Expand Down Expand Up @@ -297,8 +297,7 @@ bool PlTerm::unify_blob(std::unique_ptr<PlBlob>* blob) const
_SWI_CPP2_CPP_inline
PlTerm
PlTerm::copy_term_ref() const
{ PlTerm t(Plx_copy_term_ref(C_));
return t;
{ return PlTerm(Plx_copy_term_ref(unwrap()));
}

_SWI_CPP2_CPP_inline
Expand Down Expand Up @@ -363,7 +362,7 @@ PlTerm::record() const

_SWI_CPP2_CPP_inline
PlTerm::PlTerm(const PlRecord& r)
: WrappedC<term_t>(r.term().C_)
: WrappedC<term_t>(r.term().unwrap())
{ }


Expand All @@ -374,7 +373,7 @@ PlTerm::PlTerm(const PlRecord& r)
_SWI_CPP2_CPP_inline
PlTerm_tail::PlTerm_tail(const PlTerm& l)
{ if ( l.is_variable() || l.is_list() )
C_ = l.copy_term_ref().C_;
reset(l.copy_term_ref());
else
throw PlTypeError("list", l);
}
Expand All @@ -394,7 +393,7 @@ PlTerm_tail::append(PlTerm e)

_SWI_CPP2_CPP_inline
bool PlTerm_tail::next(PlTerm& t)
{ if ( Plx_get_list(C_, t.C_, C_) )
{ if ( Plx_get_list(unwrap(), t.unwrap(), unwrap()) )
return true;

if ( get_nil() )
Expand Down Expand Up @@ -463,18 +462,18 @@ PlTerm
PlTerm::operator [](size_t index) const
{ PlTerm t;

if ( Plx_get_arg(index, C_, t.C_) )
if ( Plx_get_arg(index, unwrap(), t.unwrap()) )
return t;

if ( !is_compound() )
throw PlTypeError("compound", *this);

/* Construct error term and throw it */
Plx_put_uint64(t.C_, index);
Plx_put_uint64(t.unwrap(), index);
if ( index < 1 )
throw PlDomainError("not_less_than_zero", t);
else
throw PlDomainError("arity", t); /* TODO: arity(t.C_) - see PlTermv::operator[] */
throw PlDomainError("arity", t); /* TODO: arity(t.unwrap()) - see PlTermv::operator[] */
}

_SWI_CPP2_CPP_inline
Expand All @@ -491,7 +490,7 @@ PlAtom
PlTerm::name() const
{ atom_t name;
size_t arity;
if ( Plx_get_name_arity(C_, &name, &arity) )
if ( Plx_get_name_arity(unwrap(), &name, &arity) )
return PlAtom(name);
throw PlTypeError("compound", *this);
}
Expand All @@ -500,7 +499,7 @@ _SWI_CPP2_CPP_inline
bool
PlTerm::name_arity(PlAtom *name, size_t *arity) const
{ atom_t name_a;
if ( Plx_get_name_arity(C_, &name_a, arity) )
if ( Plx_get_name_arity(unwrap(), &name_a, arity) )
{ if ( name )
*name = PlAtom(name_a);
return true;
Expand Down Expand Up @@ -578,7 +577,7 @@ bool
PlTerm::eq(const wchar_t *s) const
{ wchar_t *s0;

if ( Plx_get_wchars(C_, nullptr, &s0, CVT_ALL) )
if ( Plx_get_wchars(unwrap(), nullptr, &s0, CVT_ALL) )
return wcscmp(s0, s) == 0;

throw PlTypeError("text", *this);
Expand All @@ -600,8 +599,8 @@ bool
PlTerm::eq(const PlAtom& a) const
{ atom_t v;

if ( Plx_get_atom(C_, &v) )
return v == a.C_;
if ( Plx_get_atom(unwrap(), &v) )
return v == a.unwrap();

throw PlTypeError("atom", *this);
}
Expand All @@ -616,7 +615,7 @@ PlCompound::PlCompound(const wchar_t *text)
{ term_t t = Plx_new_term_ref();
if ( !Plx_wchars_to_term(text, t) )
throw PlException(PlTerm(t));
Plx_put_term(C_, t);
Plx_put_term(unwrap(), t);
}

_SWI_CPP2_CPP_inline
Expand All @@ -626,7 +625,7 @@ PlCompound::PlCompound(const std::string& text, PlEncoding enc)

// TODO: PL_put_term_from_chars() should take an unsigned int flags
PlEx<int>(Plx_put_term_from_chars(t, static_cast<int>(enc)|CVT_EXCEPTION, text.size(), text.data()));
Plx_put_term(C_, t);
Plx_put_term(unwrap(), t);
}

_SWI_CPP2_CPP_inline
Expand All @@ -637,33 +636,33 @@ PlCompound::PlCompound(const std::wstring& text)
// TODO: what is wchar_t equivalent of PL_put_term_from_chars()?
if ( !Plx_wchars_to_term(text.c_str(), t) ) // TODO: use text.size()
throw PlException(PlTerm(t));
Plx_put_term(C_, t);
Plx_put_term(unwrap(), t);
}

_SWI_CPP2_CPP_inline
PlCompound::PlCompound(const char *functor, const PlTermv& args)
{ functor_t f = Plx_new_functor(Plx_new_atom(functor), args.size());
PlEx<bool>(f != (functor_t)0);
Plx_cons_functor_v(C_, f, args.termv());
Plx_cons_functor_v(unwrap(), f, args.termv());
}

_SWI_CPP2_CPP_inline
PlCompound::PlCompound(const wchar_t *functor, const PlTermv& args)
{ functor_t f = Plx_new_functor(Plx_new_atom_wchars(wcslen(functor), functor), args.size());
PlEx<bool>(f != (functor_t)0);
Plx_cons_functor_v(C_, f, args.termv());
Plx_cons_functor_v(unwrap(), f, args.termv());
}

_SWI_CPP2_CPP_inline
PlCompound::PlCompound(const std::string& functor, const PlTermv& args)
{ functor_t f = Plx_new_functor(Plx_new_atom_nchars(functor.size(), functor.data()), args.size());
Plx_cons_functor_v(C_, f, args.termv());
Plx_cons_functor_v(unwrap(), f, args.termv());
}

_SWI_CPP2_CPP_inline
PlCompound::PlCompound(const std::wstring& functor, const PlTermv& args)
{ functor_t f = Plx_new_functor(Plx_new_atom_wchars(functor.size(), functor.data()), args.size());
Plx_cons_functor_v(C_, f, args.termv());
Plx_cons_functor_v(unwrap(), f, args.termv());
}

/*******************************
Expand All @@ -673,14 +672,14 @@ PlCompound::PlCompound(const std::wstring& functor, const PlTermv& args)
_SWI_CPP2_CPP_inline
PlTermv::PlTermv(const PlAtom& a)
: size_(1),
a0_(PlTerm_atom(a).C_)
a0_(PlTerm_atom(a).unwrap())
{ PlEx<bool>(a0_ != (term_t)0);
}

_SWI_CPP2_CPP_inline
PlTermv::PlTermv(const PlTerm& m0)
: size_(1),
a0_(m0.C_)
a0_(m0.unwrap())
{ // Assume that m0 is valid
}

Expand All @@ -689,29 +688,29 @@ PlTermv::PlTermv(const PlTerm& m0, const PlTerm& m1)
: size_(2),
a0_(Plx_new_term_refs(2))
{ PlEx<bool>(a0_ != (term_t)0);
Plx_put_term(a0_+0, m0.C_);
Plx_put_term(a0_+1, m1.C_);
Plx_put_term(a0_+0, m0.unwrap());
Plx_put_term(a0_+1, m1.unwrap());
}

_SWI_CPP2_CPP_inline
PlTermv::PlTermv(const PlTerm& m0, const PlTerm& m1, const PlTerm& m2)
: size_(3),
a0_(Plx_new_term_refs(3))
{ PlEx<bool>(a0_ != (term_t)0);
Plx_put_term(a0_+0, m0.C_);
Plx_put_term(a0_+1, m1.C_);
Plx_put_term(a0_+2, m2.C_);
Plx_put_term(a0_+0, m0.unwrap());
Plx_put_term(a0_+1, m1.unwrap());
Plx_put_term(a0_+2, m2.unwrap());
}

_SWI_CPP2_CPP_inline
PlTermv::PlTermv(const PlTerm& m0, const PlTerm& m1, const PlTerm& m2, const PlTerm& m3)
: size_(4),
a0_(Plx_new_term_refs(4))
{ PlEx<bool>(a0_ != (term_t)0);
Plx_put_term(a0_+0, m0.C_);
Plx_put_term(a0_+1, m1.C_);
Plx_put_term(a0_+2, m2.C_);
Plx_put_term(a0_+3, m3.C_);
Plx_put_term(a0_+0, m0.unwrap());
Plx_put_term(a0_+1, m1.unwrap());
Plx_put_term(a0_+2, m2.unwrap());
Plx_put_term(a0_+3, m3.unwrap());
}

_SWI_CPP2_CPP_inline
Expand All @@ -720,11 +719,11 @@ PlTermv::PlTermv(const PlTerm& m0, const PlTerm& m1, const PlTerm& m2,
: size_(5),
a0_(Plx_new_term_refs(5))
{ PlEx<bool>(a0_ != (term_t)0);
Plx_put_term(a0_+0, m0.C_);
Plx_put_term(a0_+1, m1.C_);
Plx_put_term(a0_+2, m2.C_);
Plx_put_term(a0_+3, m3.C_);
Plx_put_term(a0_+4, m4.C_);
Plx_put_term(a0_+0, m0.unwrap());
Plx_put_term(a0_+1, m1.unwrap());
Plx_put_term(a0_+2, m2.unwrap());
Plx_put_term(a0_+3, m3.unwrap());
Plx_put_term(a0_+4, m4.unwrap());
}

_SWI_CPP2_CPP_inline
Expand Down Expand Up @@ -800,7 +799,7 @@ PlException::what() const throw()
_SWI_CPP2_CPP_inline
int
PlQuery::next_solution()
{ int rval = PL_next_solution(C_);
{ int rval = PL_next_solution(unwrap());

if ( flags_ & PL_Q_EXT_STATUS )
{ // values are:
Expand Down Expand Up @@ -843,7 +842,7 @@ void PlWrapDebug(const char*msg) {

_SWI_CPP2_CPP_inline
PlStream::PlStream(PlTerm& stream, int flags)
{ Plx_get_stream(stream.C_, &s_, flags);
{ Plx_get_stream(stream.unwrap(), &s_, flags);
check_stream(); // Shouldn't happen
}

Expand Down

0 comments on commit 790c664

Please sign in to comment.