Skip to content

Commit

Permalink
works for hermit
Browse files Browse the repository at this point in the history
  • Loading branch information
cmungall committed Jul 2, 2010
1 parent 7f9f22f commit d69b34d
Show file tree
Hide file tree
Showing 5 changed files with 66 additions and 28 deletions.
8 changes: 2 additions & 6 deletions bin/thea-jpl
Expand Up @@ -5,11 +5,8 @@ DIRNAME=`dirname $0`
# These will be resolved into absolute pathnames
# Wildcards are allowed
CLASSPATH_RELATIVE=$DIRNAME/../jars/*.jar
echo $CLASSPATH_RELATIVE

for ARG in "$CLASSPATH_RELATIVE"
do
DEREFERENCED_CLASSPATH=`ls -1 -L $ARG`
DEREFERENCED_CLASSPATH=`ls -1 -L $CLASSPATH_RELATIVE`
echo A = $DEREFERENCED_CLASSPATH
for CP_ENTRY in $DEREFERENCED_CLASSPATH
do
Expand All @@ -20,8 +17,7 @@ do
CLASSPATH="$CLASSPATH:$CP_ENTRY"
fi
done
done

#echo CP = $CLASSPATH
echo CP = $CLASSPATH
#CLASSPATH="jars/owlapi-bin.jar:" thea --ensure_loaded "library(thea2/owl2_java_owlapi)" "$@"
thea --ensure_loaded "library(thea2/owl2_java_owlapi)" "$@"
15 changes: 15 additions & 0 deletions bin/thea-owl-i
Expand Up @@ -35,6 +35,11 @@ main :-
get_time(T2),
LoadTime is T2-T1,
debug(bench,'load_time: ~w',[LoadTime]),
( member(reasonername(RN),Opts)
-> ensure_loaded(library(thea2/owl2_reasoner)),
initialize_reasoner(RN,Reasoner),
nb_setval(reasoner,Reasoner)
; true),
forall(member(goal(G),Opts),
G),
forall(member(popl(G),Opts),
Expand All @@ -57,6 +62,9 @@ main :-
-> save_axioms(OutFile,OutFmt,SaveOpts)
; save_axioms(_,OutFmt,SaveOpts))
; true),
forall(member(reasonerquery(T,G),Opts),
forall(reasoner_ask(Reasoner,G),
show_term(T,Opts))),
forall(member(query(T,G),Opts),
forall(G,show_term(T,Opts))),
( member(qsave(QSF),Opts)
Expand Down Expand Up @@ -186,6 +194,13 @@ parse_arg(['--query',select,TA,where,GA|L],L,query(T,G)) :- sformat(A,'q((~w),(~
parse_arg(['--query',GA|L],L,query(T,G)) :- atom_to_term(GA,G-T,_).
arg_info(query,goal,'execute prolog query').

parse_arg(['--reasoner',A|L],L,reasonername(RN)) :-
atom_to_term(A,RN,_).

parse_arg(['--reasoner-ask-all'|L],L,reasonerquery( A, A)).



parse_arg(['--load-catalog'|L],L,null) :- load_catalog.

parse_arg(['--qsave',File|L],L,qsave(File)).
Expand Down
Binary file added jars/org.semanticweb.HermiT.jar
Binary file not shown.
53 changes: 33 additions & 20 deletions owl2_java_owlapi.pl
Expand Up @@ -141,8 +141,8 @@
jpl_call(RFac,createReasoner,[Ont],Reasoner).

reasoner_factory(pellet,'com.clarkparsia.pellet.owlapiv3.PelletReasonerFactory').
reasoner_factory(hermit,'org.semanticweb.HermiT.Reasoner').
reasoner_factory(factpp,'uk.ac.manchester.cs.factplusplus.owlapiv3.Reasoner').
reasoner_factory(hermit,'org.semanticweb.HermiT.Reasoner$ReasonerFactory').
reasoner_factory(factpp,'uk.ac.manchester.cs.factplusplus.owlapiv3.FaCTPlusPlusReasonerFactory').

% DEPRECATED
reasoner_classify(Reasoner) :-
Expand Down Expand Up @@ -262,6 +262,7 @@

% reasoner_nr_subClassOf(+R,+Fac,?C,?P)
reasoner_nr_subClassOf(R,Fac,C,P) :-
throw(not_implemented),
var(C),
var(P),
!,
Expand All @@ -270,6 +271,7 @@

% reasoner_nr_subClassOf(+R,+Fac,+C,?P)
reasoner_nr_subClassOf(R,Fac,C,P) :-
throw(not_implemented),
nonvar(C),
!,
pl2javaref(Fac,C,JC),
Expand All @@ -278,10 +280,11 @@

% reasoner_nr_subClassOf(+R,+Fac,?C,+P)
reasoner_nr_subClassOf(R,Fac,C,P) :-
throw(not_implemented),
nonvar(P),
!,
pl2javaref(Fac,P,JP),
jpl_call(R,getSubClasses,[JP,(@false)],JCSetSet),
jpl_call(R,getSubClasses,[JP,(@true)],JCSetSet),
nodeset_entity(JCSetSet,C).

%% reasoner_subClassOf(+R,+Fac,?C,?P)
Expand Down Expand Up @@ -340,9 +343,8 @@
( IsDirect
-> Bool='@'(true)
; Bool='@'(false)),
jpl_call(R,getIndividuals,[JC,Bool],ISet),
jset_member(ISet,JI),
java_namedentity(JI,I).
jpl_call(R,getInstances,[JC,Bool],ISet),
nodeset_entity(ISet,I).

reasoner_individualOf(R,Fac,I,C,IsDirect) :-
nonvar(I),
Expand All @@ -354,12 +356,15 @@
jpl_call(R,getTypes,[JI,Bool],JCSetSet),
ecsets_class(JCSetSet,C).

reasoner_objectPropertyAssertion(R,Fac,I,P,I2) :-
reasoner_objectPropertyAssertion(R,Fac,P,I,I2) :-
( var(I)
-> classAssertion(_,I), % TODO - better way to get enumerate individuals?
\+ objectProperty(I), % see issue 16 - hack for now
\+ class(I)
; true),
( var(P)
-> objectProperty(P)
; true),
debug(reasoner,'I=~w',[I]),
pl2javaref(Fac,I,JI),
pl2javaref(Fac,P,JP),
Expand Down Expand Up @@ -770,32 +775,40 @@
:- multifile owl2_reasoner:reasoner_ask_hook/2.

wrapped_reasoner(pellet).
wrapped_reasoner(hermit).
wrapped_reasoner(factpp).

initialize_reasoner_hook(Type,R,Opts) :-
wrapped_reasoner(Type),
initialize_reasoner_hook(owlapi(Type),R,Opts).
initialize_reasoner_hook(owlapi(Type),owlapi(R-Man-Fac),_Opts) :-
owl2_reasoner:initialize_reasoner_hook(Type,R,Opts) :-
wrapped_reasoner(Type), % choose arbitrary if not defined
!,
owl2_reasoner:initialize_reasoner_hook(owlapi(Type),R,Opts).
owl2_reasoner:initialize_reasoner_hook(owlapi(Type),owlapi_reasoner(R,Fac,Opts),Opts) :-
!,
require_manager(Man),
create_factory(Man,Fac),
create_reasoner(Man,Type,R).
build_ontology(Man,Fac,Ont),
create_reasoner(Ont,Type,R).

%reasoner_tell_hook(R,Axiom) :- foo.

reasoner_tell_all_hook(owlapi(OWLReasoner,Fac)) :-
owl2_reasoner:reasoner_tell_all_hook(owlapi_reasoner(OWLReasoner,Fac,_Opts)) :-
build_ontology(Man,Fac,Ont),
reasoner_classify(OWLReasoner,Man,Ont).


reasoner_ask_hook(R,Axiom) :-
var(Axiom), % allow all?
!,
throw(error(reasoner(R,Axiom))).
%owl2_reasoner:reasoner_ask_hook(R,Axiom) :-
% var(Axiom), % allow all?
% !,
% throw(error(reasoner(R,Axiom))).

reasoner_ask_hook(R,subClassOf(A,B)) :-
reasoner_subClassOf(R,_,A,B). % TODO

owl2_reasoner:reasoner_ask_hook(owlapi_reasoner(R,Fac,_Opts),subClassOf(A,B)) :-
reasoner_subClassOf(R,Fac,A,B).

owl2_reasoner:reasoner_ask_hook(owlapi_reasoner(R,Fac,_Opts),classAssertion(C,I)) :-
reasoner_individualOf(R,Fac,I,C).

owl2_reasoner:reasoner_ask_hook(owlapi_reasoner(R,Fac,_Opts),propertyAssertion(P,A,B)) :-
reasoner_objectPropertyAssertion(R,Fac,P,A,B).

/** <module> bridge to java OWLAPI
Expand Down
18 changes: 16 additions & 2 deletions owl2_reasoner.pl
Expand Up @@ -2,6 +2,7 @@

:- module(owl2_reasoner,
[
initialize_reasoner/2,
initialize_reasoner/3,
reasoner_tell/2,
reasoner_tell_all/1,
Expand Down Expand Up @@ -30,9 +31,13 @@
% ==
% initialize_reasoner(pellet,R,[])
% ==
initialize_reasoner(Type,Reasoner,Opts) :-
initialize_reasoner(Type,Reasoner,Opts) :-
load_handler(Type,Opts),
initialize_reasoner_hook(Type,Reasoner,Opts).
initialize_reasoner_hook(Type,Reasoner,Opts),
debug(reasoner,'Initialized reasoner: ~w',[Reasoner]),
!.
initialize_reasoner(Type,_,Opts) :-
throw(error(initialize_reasoner(Type,Opts))).

%% reasoner_tell(+Reasoner,+Axiom)
% feed an axiom to the reasoner
Expand All @@ -57,6 +62,7 @@
% that contain variables.
% TODO - isConsistent
reasoner_ask(Reasoner,Axiom) :-
debug(reasoner,'Reasoner query: ~w',[Axiom]),
reasoner_ask_hook(Reasoner,Axiom).

%% reasoner_check_consistency(+Reasoner)
Expand All @@ -66,6 +72,14 @@

% --

load_handler(Type,_Opts) :-
forall(reasoner_module(Type,Mod),
ensure_loaded(library(thea2/Mod))).

reasoner_module(pellet,owl2_java_owlapi).
reasoner_module(factpp,owl2_java_owlapi).
reasoner_module(hermit,owl2_java_owlapi).
reasoner_module(owlapi(_),owl2_java_owlapi).


/** <module> reasoner API - NOT YET IN USE
Expand Down

0 comments on commit d69b34d

Please sign in to comment.