summaryrefslogtreecommitdiffstats
path: root/src/uscxml/plugins/datamodel/prolog/swi/SWIDataModel.cpp
diff options
context:
space:
mode:
Diffstat (limited to 'src/uscxml/plugins/datamodel/prolog/swi/SWIDataModel.cpp')
-rw-r--r--src/uscxml/plugins/datamodel/prolog/swi/SWIDataModel.cpp525
1 files changed, 275 insertions, 250 deletions
diff --git a/src/uscxml/plugins/datamodel/prolog/swi/SWIDataModel.cpp b/src/uscxml/plugins/datamodel/prolog/swi/SWIDataModel.cpp
index 4786903..9d9dda8 100644
--- a/src/uscxml/plugins/datamodel/prolog/swi/SWIDataModel.cpp
+++ b/src/uscxml/plugins/datamodel/prolog/swi/SWIDataModel.cpp
@@ -30,6 +30,14 @@
#include <Pluma/Connector.hpp>
#endif
+#define RETHROW_PLEX_AS_EVENT \
+catch (PlException plex) { \
+ Event e; \
+ e.name = "error.execution"; \
+ e.data.compound["cause"] = (char*)plex; \
+ throw e; \
+} \
+
#define SET_PL_CONTEXT \
_dmPtr = this;
@@ -66,121 +74,127 @@ SWIDataModel::SWIDataModel() {
}
SWIDataModel::~SWIDataModel() {
- if (_swiEngines.find(this) != _swiEngines.end()) {
- PL_destroy_engine(_swiEngines[this]);
- _swiEngines.erase(this);
- }
+ try {
+ if (_swiEngines.find(this) != _swiEngines.end()) {
+ PL_destroy_engine(_swiEngines[this]);
+ _swiEngines.erase(this);
+ }
+ } RETHROW_PLEX_AS_EVENT;
}
boost::shared_ptr<DataModelImpl> SWIDataModel::create(InterpreterImpl* interpreter) {
- boost::shared_ptr<SWIDataModel> dm = boost::shared_ptr<SWIDataModel>(new SWIDataModel());
- dm->_interpreter = interpreter;
-
- const char* swibin = getenv("SWI_BINARY");
- if (swibin == NULL)
- swibin = SWI_BINARY;
- const char* quiet = "--quiet";
-
- int argc = 2;
- static char * av[] = {
- (char*)swibin,
- (char*)quiet,
- NULL
- };
-
- PL_engine_t engine;
-
- if (!PL_is_initialised(NULL, NULL)) {
- if(!PL_initialise(argc,av)) {
- LOG(ERROR) << "Error intializing prolog engine";
- PL_halt(1);
- return boost::shared_ptr<DataModelImpl>();
- }
+ try {
+ boost::shared_ptr<SWIDataModel> dm = boost::shared_ptr<SWIDataModel>(new SWIDataModel());
+ dm->_interpreter = interpreter;
+
+ const char* swibin = getenv("SWI_BINARY");
+ if (swibin == NULL)
+ swibin = SWI_BINARY;
+ const char* quiet = "--quiet";
+
+ int argc = 2;
+ static char * av[] = {
+ (char*)swibin,
+ (char*)quiet,
+ NULL
+ };
+
+ PL_engine_t engine;
+
+ if (!PL_is_initialised(NULL, NULL)) {
+ if(!PL_initialise(argc,av)) {
+ LOG(ERROR) << "Error intializing prolog engine";
+ PL_halt(1);
+ return boost::shared_ptr<DataModelImpl>();
+ }
- PL_set_engine(PL_ENGINE_CURRENT, &engine);
+ PL_set_engine(PL_ENGINE_CURRENT, &engine);
- // load SWI XML parser
- try {
- PlCall("use_module", PlCompound("library", PlTerm("sgml")));
- } catch (PlException plex) {
+ // load SWI XML parser
+ try {
+ PlCall("use_module", PlCompound("library", PlTerm("sgml")));
+ } catch (PlException plex) {
- LOG(ERROR) << "Cannot load prolog sgml module - make sure you have it installed in your prolog runtime: " << (char*)plex;
- throw plex;
- }
+ LOG(ERROR) << "Cannot load prolog sgml module - make sure you have it installed in your prolog runtime: " << (char*)plex;
+ throw plex;
+ }
- // load json parser
- try {
- PlCall("use_module", PlCompound("library", PlTerm("http/json")));
- PlCall("use_module", PlCompound("library", PlTerm("http/json_convert")));
- } catch (PlException plex) {
- LOG(ERROR) << "Cannot load prolog json module or json_convert - make sure you have it installed in your prolog runtime: " << (char*)plex;
- throw plex;
+ // load json parser
+ try {
+ PlCall("use_module", PlCompound("library", PlTerm("http/json")));
+ PlCall("use_module", PlCompound("library", PlTerm("http/json_convert")));
+ } catch (PlException plex) {
+ LOG(ERROR) << "Cannot load prolog json module or json_convert - make sure you have it installed in your prolog runtime: " << (char*)plex;
+ throw plex;
+ }
+
+ } else {
+ LOG(WARNING) << "Instantiating more than one SWI prolog datamodel will lead to weird effects as I cannot seperate the environments";
+ engine = PL_create_engine(NULL);
}
- } else {
- LOG(WARNING) << "Instantiating more than one SWI prolog datamodel will lead to weird effects as I cannot seperate the environments";
- engine = PL_create_engine(NULL);
- }
+ assert(engine);
+ _swiEngines[dm.get()] = engine;
+ _dmPtr = dm.get();
+
+ int rc = PL_set_engine(engine, NULL);
+ assert(rc == PL_ENGINE_SET);
+ (void)rc;
+
+ _plModule = boost::replace_all_copy(interpreter->getSessionId(), "-", "");
+ boost::replace_all(_plModule, "0", "g");
+ boost::replace_all(_plModule, "1", "h");
+ boost::replace_all(_plModule, "2", "i");
+ boost::replace_all(_plModule, "3", "j");
+ boost::replace_all(_plModule, "4", "k");
+ boost::replace_all(_plModule, "5", "l");
+ boost::replace_all(_plModule, "6", "m");
+ boost::replace_all(_plModule, "7", "n");
+ boost::replace_all(_plModule, "8", "o");
+ boost::replace_all(_plModule, "9", "p");
+
+ // use atoms for double quoted
+ PlCall("set_prolog_flag(double_quotes,atom).");
+
+ // set system variables
+ PlCall("assert", PlCompound("sessionid", PlTerm(PlString(dm->_interpreter->getSessionId().c_str()))));
+ PlCall("assert", PlCompound("name", PlTerm(PlString(dm->_interpreter->getName().c_str()))));
+
+ std::map<std::string, IOProcessor>::const_iterator ioProcIter = dm->_interpreter->getIOProcessors().begin();
+ while(ioProcIter != dm->_interpreter->getIOProcessors().end()) {
+ Data ioProcData = ioProcIter->second.getDataModelVariables();
+
+ if (ioProcIter->first.find_first_of(":/'") == std::string::npos) {
+ std::stringstream ioProcShortCall;
+ ioProcShortCall << "assert(ioprocessors(" << ioProcIter->first << "(location('" << ioProcData.compound["location"].atom << "'))))";
+ PlCall(ioProcShortCall.str().c_str());
+ }
+ std::stringstream ioProcCall;
+ ioProcCall << "assert(ioprocessors(name('" << ioProcIter->first << "'), location('" << ioProcData.compound["location"].atom << "')))";
+ PlCall(ioProcCall.str().c_str());
- assert(engine);
- _swiEngines[dm.get()] = engine;
- _dmPtr = dm.get();
-
- int rc = PL_set_engine(engine, NULL);
- assert(rc == PL_ENGINE_SET);
- (void)rc;
-
- _plModule = boost::replace_all_copy(interpreter->getSessionId(), "-", "");
- boost::replace_all(_plModule, "0", "g");
- boost::replace_all(_plModule, "1", "h");
- boost::replace_all(_plModule, "2", "i");
- boost::replace_all(_plModule, "3", "j");
- boost::replace_all(_plModule, "4", "k");
- boost::replace_all(_plModule, "5", "l");
- boost::replace_all(_plModule, "6", "m");
- boost::replace_all(_plModule, "7", "n");
- boost::replace_all(_plModule, "8", "o");
- boost::replace_all(_plModule, "9", "p");
-
- // use atoms for double quoted
- PlCall("set_prolog_flag(double_quotes,atom).");
-
- // set system variables
- PlCall("assert", PlCompound("sessionid", PlTerm(PlString(dm->_interpreter->getSessionId().c_str()))));
- PlCall("assert", PlCompound("name", PlTerm(PlString(dm->_interpreter->getName().c_str()))));
-
- std::map<std::string, IOProcessor>::const_iterator ioProcIter = dm->_interpreter->getIOProcessors().begin();
- while(ioProcIter != dm->_interpreter->getIOProcessors().end()) {
- Data ioProcData = ioProcIter->second.getDataModelVariables();
-
- if (ioProcIter->first.find_first_of(":/'") == std::string::npos) {
- std::stringstream ioProcShortCall;
- ioProcShortCall << "assert(ioprocessors(" << ioProcIter->first << "(location('" << ioProcData.compound["location"].atom << "'))))";
- PlCall(ioProcShortCall.str().c_str());
+ ioProcIter++;
}
- std::stringstream ioProcCall;
- ioProcCall << "assert(ioprocessors(name('" << ioProcIter->first << "'), location('" << ioProcData.compound["location"].atom << "')))";
- PlCall(ioProcCall.str().c_str());
-
- ioProcIter++;
- }
- // the in predicate
- PlRegister("user", "in", 1, SWIDataModel::inPredicate);
- return dm;
+ // the in predicate
+ PlRegister("user", "in", 1, SWIDataModel::inPredicate);
+ return dm;
+ } RETHROW_PLEX_AS_EVENT;
}
foreign_t SWIDataModel::inPredicate(term_t a0, int arity, void* context) {
- char *s;
- if ( PL_get_atom_chars(a0, &s) ) {
- NodeSet<std::string> config = _dmPtr->_interpreter->getConfiguration();
- for (int i = 0; i < config.size(); i++) {
- if (HAS_ATTR(config[i], "id") && strcmp(ATTR(config[i], "id").c_str(), s) == 0) {
- return TRUE;
+ try {
+ char *s;
+ if ( PL_get_atom_chars(a0, &s) ) {
+ NodeSet<std::string> config = _dmPtr->_interpreter->getConfiguration();
+ for (int i = 0; i < config.size(); i++) {
+ if (HAS_ATTR(config[i], "id") && strcmp(ATTR(config[i], "id").c_str(), s) == 0) {
+ return TRUE;
+ }
}
}
- }
- return FALSE;
+ return FALSE;
+ } RETHROW_PLEX_AS_EVENT;
}
void SWIDataModel::registerIOProcessor(const std::string& name, const IOProcessor& ioprocessor) {
@@ -210,6 +224,7 @@ void SWIDataModel::initialize() {
}
void SWIDataModel::setEvent(const Event& event) {
+
SET_PL_CONTEXT;
// remove old event
try {
@@ -287,9 +302,7 @@ void SWIDataModel::setEvent(const Event& event) {
paramIter = lastValueIter;
}
}
- } catch(PlException e) {
- LOG(ERROR) << e.operator const char *();
- }
+ } RETHROW_PLEX_AS_EVENT;
}
Data SWIDataModel::getStringAsData(const std::string& content) {
@@ -307,16 +320,18 @@ bool SWIDataModel::validate(const std::string& location, const std::string& sche
uint32_t SWIDataModel::getLength(const std::string& expr) {
SET_PL_CONTEXT
- PlCompound compound(expr.c_str());
- PlTermv termv(compound.arity());
- for (int i = 0; i < compound.arity(); i++) {
- termv[i] = compound[i + 1];
- }
- PlQuery query(compound.name(), termv);
- uint32_t length = 0;
- while(query.next_solution() > 0)
- length++;
- return length;
+ try {
+ PlCompound compound(expr.c_str());
+ PlTermv termv(compound.arity());
+ for (int i = 0; i < compound.arity(); i++) {
+ termv[i] = compound[i + 1];
+ }
+ PlQuery query(compound.name(), termv);
+ uint32_t length = 0;
+ while(query.next_solution() > 0)
+ length++;
+ return length;
+ } RETHROW_PLEX_AS_EVENT;
}
void SWIDataModel::setForeach(const std::string& item,
@@ -324,40 +339,44 @@ void SWIDataModel::setForeach(const std::string& item,
const std::string& index,
uint32_t iteration) {
SET_PL_CONTEXT
- PlCompound compound(array.c_str());
- PlCompound orig(array.c_str());
- PlTermv termv(compound.arity());
- for (int i = 0; i < compound.arity(); i++) {
- termv[i] = compound[i + 1];
- }
- {
- int tmp = iteration + 1;
- PlQuery query(compound.name(), termv);
- while (tmp) {
- query.next_solution();
- tmp--;
+ try {
+ PlCompound compound(array.c_str());
+ PlCompound orig(array.c_str());
+ PlTermv termv(compound.arity());
+ for (int i = 0; i < compound.arity(); i++) {
+ termv[i] = compound[i + 1];
}
- }
- PlCall("retractall", PlCompound(index.c_str(), 1));
- PlCall("retractall", PlCompound(item.c_str(), 1));
- PlCall("assert", PlCompound(index.c_str(), PlTerm((long)iteration)));
-
- std::map<std::string, PlTerm> vars = resolveAtoms(compound, orig);
- std::map<std::string, PlTerm>::iterator varIter = vars.begin();
- while(varIter != vars.end()) {
- PlCall("assert", PlCompound(item.c_str(), varIter->second));
- varIter++;
- }
+ {
+ int tmp = iteration + 1;
+ PlQuery query(compound.name(), termv);
+ while (tmp) {
+ query.next_solution();
+ tmp--;
+ }
+ }
+ PlCall("retractall", PlCompound(index.c_str(), 1));
+ PlCall("retractall", PlCompound(item.c_str(), 1));
+ PlCall("assert", PlCompound(index.c_str(), PlTerm((long)iteration)));
+
+ std::map<std::string, PlTerm> vars = resolveAtoms(compound, orig);
+ std::map<std::string, PlTerm>::iterator varIter = vars.begin();
+ while(varIter != vars.end()) {
+ PlCall("assert", PlCompound(item.c_str(), varIter->second));
+ varIter++;
+ }
+ } RETHROW_PLEX_AS_EVENT;
}
void SWIDataModel::eval(const Element<std::string>& scriptElem, const std::string& expr) {
SET_PL_CONTEXT
- if (scriptElem && HAS_ATTR(scriptElem, "type") && iequals(ATTR(scriptElem, "type"), "query")) {
- evalAsBool(expr);
- } else {
- URL localPLFile = URL::toLocalFile(expr, ".pl");
- PlCall("user", "load_files", PlTermv(localPLFile.asLocalFile(".pl").c_str())) || LOG(ERROR) << "Could not execute prolog from file";
- }
+ try {
+ if (scriptElem && HAS_ATTR(scriptElem, "type") && iequals(ATTR(scriptElem, "type"), "query")) {
+ evalAsBool(expr);
+ } else {
+ URL localPLFile = URL::toLocalFile(expr, ".pl");
+ PlCall("user", "load_files", PlTermv(localPLFile.asLocalFile(".pl").c_str())) || LOG(ERROR) << "Could not execute prolog from file";
+ }
+ } RETHROW_PLEX_AS_EVENT;
}
bool SWIDataModel::evalAsBool(const std::string& expr) {
@@ -381,136 +400,142 @@ bool SWIDataModel::evalAsBool(const Arabica::DOM::Node<std::string>& node, const
std::string SWIDataModel::evalAsString(const std::string& expr) {
SET_PL_CONTEXT
- PlCompound orig(expr.c_str()); // keep the original to find variables
- PlCompound compound(expr.c_str());
- if (strlen(compound.name())) {
- PlTermv termv(compound.arity());
- for (int i = 0; i < compound.arity(); i++) {
- termv[i] = compound[i + 1];
- }
- PlQuery query(compound.name(), termv);
-
- std::stringstream ss;
- const char* separator = "";
- while (query.next_solution()) {
- std::map<std::string, PlTerm> vars = resolveAtoms(compound, orig);
- if (vars.size() == 1) {
- ss << (char *)vars.begin()->second;
- } else {
- std::map<std::string, PlTerm>::const_iterator varIter = vars.begin();
- while(varIter != vars.end()) {
- ss << separator << (char *)varIter->second;
- separator = ", ";
- varIter++;
+ try {
+ PlCompound orig(expr.c_str()); // keep the original to find variables
+ PlCompound compound(expr.c_str());
+ if (strlen(compound.name())) {
+ PlTermv termv(compound.arity());
+ for (int i = 0; i < compound.arity(); i++) {
+ termv[i] = compound[i + 1];
+ }
+ PlQuery query(compound.name(), termv);
+
+ std::stringstream ss;
+ const char* separator = "";
+ while (query.next_solution()) {
+ std::map<std::string, PlTerm> vars = resolveAtoms(compound, orig);
+ if (vars.size() == 1) {
+ ss << (char *)vars.begin()->second;
+ } else {
+ std::map<std::string, PlTerm>::const_iterator varIter = vars.begin();
+ while(varIter != vars.end()) {
+ ss << separator << (char *)varIter->second;
+ separator = ", ";
+ varIter++;
+ }
}
}
+ return ss.str();
}
- return ss.str();
- }
- return std::string(compound);
+ return std::string(compound);
+ } RETHROW_PLEX_AS_EVENT
}
// this is similar to http://etalis.googlecode.com/svn/eEtalis/src/term.c
std::map<std::string, PlTerm> SWIDataModel::resolveAtoms(PlTerm& term, PlTerm& orig) {
SET_PL_CONTEXT
- std::map<std::string, PlTerm> atoms;
- switch (orig.type()) {
- case PL_VARIABLE: {
- atoms[(char *)orig] = term;
- break;
- }
- case PL_ATOM:
- break;
- case PL_STRING:
- break;
- case PL_INTEGER:
- break;
- case PL_TERM:
- for (int i = 1; i <= orig.arity(); i++) {
- PlTerm newTerm = term[i];
- PlTerm newOrig = orig[i];
- std::map<std::string, PlTerm> result = resolveAtoms(newTerm, newOrig);
- atoms.insert(result.begin(), result.end());
+ try {
+ std::map<std::string, PlTerm> atoms;
+ switch (orig.type()) {
+ case PL_VARIABLE: {
+ atoms[(char *)orig] = term;
+ break;
}
- break;
- }
- return atoms;
+ case PL_ATOM:
+ break;
+ case PL_STRING:
+ break;
+ case PL_INTEGER:
+ break;
+ case PL_TERM:
+ for (int i = 1; i <= orig.arity(); i++) {
+ PlTerm newTerm = term[i];
+ PlTerm newOrig = orig[i];
+ std::map<std::string, PlTerm> result = resolveAtoms(newTerm, newOrig);
+ atoms.insert(result.begin(), result.end());
+ }
+ break;
+ }
+ return atoms;
+ } RETHROW_PLEX_AS_EVENT
}
void SWIDataModel::assign(const Element<std::string>& assignElem,
const Node<std::string>& node,
const std::string& content) {
SET_PL_CONTEXT
- std::string expr = content;
- std::string predicate;
- if (HAS_ATTR(assignElem, "expr")) {
- expr = ATTR(assignElem, "expr");
- }
- if (HAS_ATTR(assignElem, "id"))
- predicate = ATTR(assignElem, "id");
- if (HAS_ATTR(assignElem, "location"))
- predicate = ATTR(assignElem, "location");
-
- if (predicate.size() > 0) {
- std::string callAssert = "assert";
- std::string type;
- if (HAS_ATTR(assignElem, "type")) {
- type = ATTR(assignElem, "type");
- if(iequals(type, "append")) {
- callAssert = "assertz";
- } else if(iequals(type, "prepend")) {
- callAssert = "asserta";
- }
+ try {
+ std::string expr = content;
+ std::string predicate;
+ if (HAS_ATTR(assignElem, "expr")) {
+ expr = ATTR(assignElem, "expr");
}
-
- URL domUrl;
- Data json;
- if (!node)
- json = Data::fromJSON(expr);
- if (node) {
- std::stringstream dataInitStr;
- std::stringstream xmlDoc;
- Node<std::string> child = node;
- while(child) {
- xmlDoc << child;
- child = child.getNextSibling();
+ if (HAS_ATTR(assignElem, "id"))
+ predicate = ATTR(assignElem, "id");
+ if (HAS_ATTR(assignElem, "location"))
+ predicate = ATTR(assignElem, "location");
+
+ if (predicate.size() > 0) {
+ std::string callAssert = "assert";
+ std::string type;
+ if (HAS_ATTR(assignElem, "type")) {
+ type = ATTR(assignElem, "type");
+ if(iequals(type, "append")) {
+ callAssert = "assertz";
+ } else if(iequals(type, "prepend")) {
+ callAssert = "asserta";
+ }
}
- domUrl = URL::toLocalFile(xmlDoc.str(), ".pl");
- if (iequals(type, "retract"))
- PlCall("retractall", PlCompound(predicate.c_str(), 1));
- dataInitStr << "load_xml_file('" << domUrl.asLocalFile(".pl") << "', XML), copy_term(XML,DATA), " << callAssert << "(" << predicate << "(DATA))";
- PlCall(dataInitStr.str().c_str());
- } else if (json) {
- std::stringstream dataInitStr;
- if (iequals(type, "retract"))
- PlCall("retractall", PlCompound(predicate.c_str(), 1));
- dataInitStr << "json_to_prolog(" << expr << ", JSON), assert(" << predicate << "(JSON))";
- PlCall(dataInitStr.str().c_str());
- } else {
- // treat content as . seperated facts
- std::stringstream factStream(content);
- std::string item;
- while(std::getline(factStream, item, '.')) {
- std::string fact = boost::trim_copy(item);
- if (fact.length() == 0)
- continue;
- PlCall((callAssert + "(" + predicate + "(" + fact + "))").c_str());
+
+ URL domUrl;
+ Data json;
+ if (!node)
+ json = Data::fromJSON(expr);
+ if (node) {
+ std::stringstream dataInitStr;
+ std::stringstream xmlDoc;
+ Node<std::string> child = node;
+ while(child) {
+ xmlDoc << child;
+ child = child.getNextSibling();
+ }
+ domUrl = URL::toLocalFile(xmlDoc.str(), ".pl");
+ if (iequals(type, "retract"))
+ PlCall("retractall", PlCompound(predicate.c_str(), 1));
+ dataInitStr << "load_xml_file('" << domUrl.asLocalFile(".pl") << "', XML), copy_term(XML,DATA), " << callAssert << "(" << predicate << "(DATA))";
+ PlCall(dataInitStr.str().c_str());
+ } else if (json) {
+ std::stringstream dataInitStr;
+ if (iequals(type, "retract"))
+ PlCall("retractall", PlCompound(predicate.c_str(), 1));
+ dataInitStr << "json_to_prolog(" << expr << ", JSON), assert(" << predicate << "(JSON))";
+ PlCall(dataInitStr.str().c_str());
+ } else {
+ // treat content as . seperated facts
+ std::stringstream factStream(content);
+ std::string item;
+ while(std::getline(factStream, item, '.')) {
+ std::string fact = boost::trim_copy(item);
+ if (fact.length() == 0)
+ continue;
+ PlCall((callAssert + "(" + predicate + "(" + fact + "))").c_str());
+ }
}
- }
- } else if (expr.length() > 0) {
- if (boost::equals(TAGNAME(assignElem), "data")) {
- eval(assignElem, expr);
- } else {
- std::stringstream exprStream(expr);
- std::string item;
- while(std::getline(exprStream, item, '.')) {
- std::string plExpr = boost::trim_copy(item);
- if (plExpr.length() == 0)
- continue;
- PlCall(plExpr.c_str());
+ } else if (expr.length() > 0) {
+ if (boost::equals(TAGNAME(assignElem), "data")) {
+ eval(assignElem, expr);
+ } else {
+ std::stringstream exprStream(expr);
+ std::string item;
+ while(std::getline(exprStream, item, '.')) {
+ std::string plExpr = boost::trim_copy(item);
+ if (plExpr.length() == 0)
+ continue;
+ PlCall(plExpr.c_str());
+ }
}
}
- }
+ } RETHROW_PLEX_AS_EVENT
}
void SWIDataModel::assign(const std::string& location, const Data& data) {