Skip to content

Commit

Permalink
Merge branch 'LogicalContracts:main' into main
Browse files Browse the repository at this point in the history
  • Loading branch information
joewatt95 authored May 8, 2024
2 parents 26039bc + 97c4200 commit fbdc4ba
Show file tree
Hide file tree
Showing 2 changed files with 28 additions and 15 deletions.
41 changes: 26 additions & 15 deletions le_answer.pl
Original file line number Diff line number Diff line change
Expand Up @@ -31,27 +31,24 @@
op(800,fx,user:responde), % to support querying in spanish
%op(1150,fx,user:show), % to support querying
op(850,xfx,user:of), % to support querying
%op(850,fx,user:'#pred'), % to support scasp
%op(800,xfx,user:'::'), % to support scasp
op(950, xfx, ::), % pred not x :: "...".
op(1200, fx, #),
op(1150, fx, pred),
op(1150, fx, show),
op(1150, fx, abducible),
dump/4, dump/3, dump/2, dump_scasp/3, split_module_name/3, just_saved_scasp/2,
prepare_query/6, assert_facts/2, retract_facts/2, parse_and_query/5, parse_and_query_and_explanation/5,
parse_and_query_and_explanation_text/5, le_expanded_terms/2, show/1, source_lang/1, targetBody/6
]).

%:- use_module(library(sandbox)).
:- if(exists_source(library(pengines_sandbox))).
:- use_module(library(pengines_sandbox)).
:- endif.

% required for sCASP justification (from ~/git/swish/pack/sCASP/examples)

% :- use_module(library(scasp)).
% :- use_module(library(scasp/html)).
% :- use_module(library(scasp/output)).
% :- use_module(library(scasp/json)).
:- if(exists_source(library(scasp))).
:- use_module(library(scasp)).
:- use_module(library(scasp/html)).
:- use_module(library(scasp/output)).
:- use_module(library(scasp/json)).
:- endif.

% :- use_module(library(http/http_server)).
% :- use_module(library(http/html_write)).
Expand All @@ -72,15 +69,19 @@

:- use_module('le_input.pl').
:- use_module('syntax.pl').
:- if(\+current_module(wasm)).
:- use_module('api.pl').
:- endif.
:- use_module('reasoner.pl').
:- use_module('./tokenize/prolog/tokenize.pl').


% html libs
:- use_module(library(http/html_write)).
:- use_module(library(http/term_html)).
:- if(exists_source(library(http/js_write))).
:- use_module(library(http/js_write)).
:- endif.

:- if(exists_source(library(r/r_call))).
:- use_module(library(r/r_call)).
Expand Down Expand Up @@ -147,7 +148,7 @@
unpack_tokens(Tokens, UTokens),
clean_comments(UTokens, CTokens),
phrase(conditions(0, [], _, Goals), CTokens) -> true
; ( error_notice(error, Me,Pos, ContextTokens), print_message(error, [Me,Pos,ContextTokens]), fail ).
; ( le_input:error_notice(error, Me,Pos, ContextTokens), print_message(error, [Me,Pos,ContextTokens]), fail ).

/* ----------------------------------------------------------------- Event Calculus */
% holds/2
Expand Down Expand Up @@ -444,7 +445,7 @@
unpack_tokens(Tokens, UTokens),
clean_comments(UTokens, CTokens), Scenario=noscenario, GoalName=nonamed,
(phrase(conditions(0, [], _, Goals), CTokens) -> true ;
( once(error_notice(error, Me,_, ContextTokens)), print_message(informational, "~w ~w"-[Me,ContextTokens]), CTokens=[], fail )
( once(le_input:error_notice(error, Me,_, ContextTokens)), print_message(informational, "~w ~w"-[Me,ContextTokens]), CTokens=[], fail )
).

command_(Goal, Scenario) -->
Expand Down Expand Up @@ -944,8 +945,9 @@
non_expanded_terms(File, TaxlogTerms, ExpandedTerms),
M:assertz(myDeclaredModule_(File)),
forall(member(T, [(:-module(File,[]))|ExpandedTerms]), assertz(M:T)), % simulating term expansion
hack_module_for_taxlog(M),
answer( Question, Scenario, le(LE_Explanation), _Result),
hack_module_for_taxlog(M),
(member(target(scasp),TaxlogTerms) -> answer(Question, Scenario);
answer( Question, Scenario, le(LE_Explanation), _Result)),
produce_text_explanation(LE_Explanation, Answer).

% non_expanded_terms/2 is just as the one above, but with semantics2prolog2 instead of semantics2prolog that has many other dependencies.
Expand Down Expand Up @@ -1050,7 +1052,15 @@
explanationLEText([C1|Cn],CH) :- explanationLEText(C1,CH1), explanationLEText(Cn,CHn), append(CH1,CHn,CH).
explanationLEText([],[]).

% Moved here so it loads in the wasm version, that doesn't have access to api.pl
:- if(current_module(wasm)).
hack_module_for_taxlog(M) :-
retractall(kp_loader:module_api_hack(_)),
assert(kp_loader:module_api_hack(M)).
:- endif.

%sandbox:safe_meta(term_singletons(X,Y), [X,Y]).
:- if(exists_source(library(pengines_sandbox))).
sandbox:safe_primitive(le_answer:answer( _EnText)).
sandbox:safe_primitive(le_answer:show( _Something)).
sandbox:safe_primitive(le_answer:show( _Something, _With)).
Expand All @@ -1065,5 +1075,6 @@
sandbox:safe_primitive(le_answer:parse_and_query(_,_,_,_,_)).
sandbox:safe_primitive(le_answer:parse_and_query_and_explanation(_,_,_,_,_)).
sandbox:safe_primitive(kp_loader:module_api_hack(_)).
:- endif.

%sandbox:safe_primitive(term_singletons(_,_)). % this would not work as term_singletons/2 is an undefined, C-based primitive
2 changes: 2 additions & 0 deletions syntax.pl
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,9 @@

:- use_module(library(prolog_xref)).
:- use_module(library(prolog_colour)).
:- if(exists_source(library(pengines))).
:- use_module(library(pengines)).
:- endif.


:- if(current_module(swish)).
Expand Down

0 comments on commit fbdc4ba

Please sign in to comment.