1:- module(owl_search_viz,
    2          [
    3           searchviz/1,
    4           searchviz/2,
    5
    6           owl_search_and_display/2
    7           %owl_search_and_display/6,
    8           %owl_search_and_display/7
    9           ]).

search and visualize results

Convenience wrapper that combines search_util and owl_edge/4 from owl_util

The main predicate is owl_search_and_display/2

requires og2dot - https://www.npmjs.com/package/obographviz */

   22:- use_module(library(semweb/rdfs)).   23:- use_module(library(semweb/rdf11)).   24:- use_module(library(sparqlprog/search_util)).   25:- use_module(library(sparqlprog/emulate_builtins)).   26:- use_module(library(sparqlprog/owl_util)).   27:- use_module(library(http/json)).   28:- use_module(library(regex)).
performs search on Term using lsearch/2 and draws results
   36searchviz(Term, Preds) :-
   37        setof(Obj,lsearch(Term,Obj),Objs),
   38        owl_subgraph(Objs, Preds, Quads, []),
   39        quads_dict(Quads, Dict),
   40        write_json_tmp(Dict, OgFile),
   41                                %write_json_tmp(stylemap{highlightIds: Objs}, StyleFile),
   42        atom_json_term(Style,stylemap{highlightIds: Objs}, []),
   43        style_file_args(StyleFileArgs),
   44        sformat(Cmd,'og2dot.js ~w -S \'~w\' -t png ~w',[StyleFileArgs,Style, OgFile]),
   45        debug(gv,'Cmd=~w',[Cmd]),
   46        shell(Cmd).
   47
   48searchviz(Term) :-
   49        searchviz(Term, _).
   50
   51% Default locations for style files
   52style_file('obograph-style.json').
   53style_file('style.json').
   54style_file('conf/obograph-style.json').
   55style_file('conf/style.json').
   56style_file('~/.obograph-style.json').
   57
   58style_file_args(A) :-
   59        style_file(File),
   60        expand_file_name(File,Files),
   61        member(F1,Files),
   62        exists_file(F1),
   63        sformat(A,'-s ~w',[F1]),
   64        !.
   65style_file_args('').
   66
   67
   68
   69write_json_tmp(Dict,File) :-
   70        atom_json_dict(JsonAtom, Dict, []),
   71        tmp_file(foo, File),
   72        open(File,write,IO,[]),
   73        format(IO,'~w',[JsonAtom]),
   74        debug(viz, 'j=~w', [JsonAtom]),
   75        close(IO).
   76
   77owl_search_and_display([SearchTerm], Opts) :-
   78        concat_atom([Pred,ST2],'=',SearchTerm),
   79        % e.g. id=GO:123456
   80        !,
   81        owl_search_and_display([ST2], [search_property(Pred)|Opts]).
 owl_search_and_display(+SearchTerms:list, +Opts:list) is semidet
perform a search over all SearchTerms and display

SearchTerms:

Each term in the list is an atom that is a regex used to search. Search is determined by search_property. By default this is label, to search using rdfs:label

In place of a regex, a prolog query term can be used, e.g 'q//label_of(shape,R),rdfs_subclass_of(Q,R)' to get all subclasses of 'shape'

Opts:

search_property(Prop)
one of: label, id, synonym, all only the first letter needs to be specified (l, i, s, a) default: label
relations(Rels)
list of object properties s is a shorthand for rdfs:subClassOf
output(File)
format(Fmt)
one of: disp, obo, viz, png, dot, ids
extend_lambda(File)

Examples:

  115owl_search_and_display(SearchTerms, Opts) :-
  116        debug(search, 'Opts  = ~q',[Opts]),
  117        option(search_property(P),Opts,l),
  118        option(extend_lambda(ExtendAtom),Opts,''),
  119        option(relations(RelAtom),Opts,''),
  120        option(format(OutFmt),Opts,info),
  121        normalize_predterm(P,P2),
  122        normalize_rels(RelAtom, Rels),
  123        debug(search, 'Rels(~q)  = ~q',[RelAtom, Rels]),
  124        findall(Obj,(member(T,SearchTerms),
  125                     search_to_objs(T, P2, Objs1, Opts),
  126                     member(Obj,Objs1)),
  127                Objs),
  128        debug(search, 'Search(~q) / ~q = ~q',[SearchTerms, P2, Objs]),
  129        concat_atom(PostTerms,',',ExtendAtom),
  130        findall(Obj2,(member(PostTerm,PostTerms),
  131                      normalize_extension_lambda(PostTerm, Lambda),
  132                      member(Obj,Objs),
  133                      call_lambda(Lambda,Obj,Obj2)),
  134                ObjsX),
  135        debug(search, 'PP(~q) = ~q',[PostTerms, ObjsX]),
  136        append(Objs,ObjsX,SeedObjs),
  137        debug(search, 'SG(~q)',[Rels]),
  138        owl_subgraph(SeedObjs, Rels, Quads, []),
  139        debug(search, 'SeedObjs = ~q',[SeedObjs]),
  140        (   option(output(OutFile),Opts)
  141        ->  true
  142        ;   OutFile=_),
  143        display_quads(Objs, Quads, OutFmt, OutFile, Opts).
  144
  145
  146% turn atomic search term into complex term if certain syntax is used
  147normalize_searchterm(X,Y/i) :-
  148        % if search term is =V, turn into exact regex
  149        atom(X),atom_concat('=',Term,X),concat_atom(['^',Term,'$'],Y).
  150normalize_searchterm(X,q(Q,Term)) :-
  151        % if search term is prolog query
  152        % e.g. subclasses of shape: "q//label_of(shape,R),rdfs_subclass_of(Q,R)"
  153        atom(X),atom_concat('q//',TermA,X),
  154        !,
  155        atom_to_term(TermA,Term,Bindings),
  156        member('Q'=Q,Bindings).
  157normalize_searchterm(X,X) :- X = _/_, !.
  158normalize_searchterm(X,X/i).
  159  
  160predterm(i,id).
  161predterm(l,label).
  162predterm(s,synonym).
  163predterm(a,all).
  164predterm('X',match_anything).
  165
  166normalize_predterm(S,X) :- predterm(S,X),!.
  167normalize_predterm(X,X).
  168
  169normalize_rels('.',_) :- !.
  170normalize_rels(L,L2) :- is_list(L), !, maplist(normalize_relterm,L,L2).
  171normalize_rels(X,L) :- concat_atom(L1,',',X),maplist(normalize_relterm,L1,L).
  172
  173normalize_relterm(X,^(P)) :- atom_concat('^',P1,X),!,normalize_relterm(P1,P).
  174normalize_relterm(X,P) :- normalize_rel(X,P1),ensure_uri(P1,P).
  175
  176normalize_rel(s,rdfs:subClassOf) :- !.
  177normalize_rel(e,owl:equivalentClass) :- !.
  178normalize_rel(t,rdf:type) :- !.
  179normalize_rel(N,R) :- \+ \+ lmatch(N,R), !, lmatch(N,R).
  180normalize_rel(N,R) :- concat_atom(L,'_',N), L=[_,_|_], concat_atom(L,' ',N1),!,normalize_rel(N1,R).
  181normalize_rel(X,X).
  182
  183% @Deprecated
  184/*
  185search_and_display1(SearchTerm, PredTerm, PostTerm, Rels, DispTerm, OutFile, Opts) :-
  186        search_to_objs(SearchTerm, PredTerm, Objs, Opts),
  187        debug(search, 'Search(~q) / ~q = ~q',[SearchTerm, PredTerm, Objs]),
  188        findall(Obj2,(member(Obj,Objs),
  189                      normalize_extension_lambda(PostTerm, Lambda),
  190                      call_lambda(Lambda,Obj,Obj2)),
  191                ObjsX),
  192        debug(search, 'PP(~q) = ~q',[PostTerm, ObjsX]),
  193        append(Objs,ObjsX,SeedObjs),
  194        owl_subgraph(SeedObjs, Rels, Quads, []),
  195        display_quads(Objs, Quads, DispTerm, OutFile, Opts).
  196*/
  197% TODO
  198%normalize_extension_lambda(_, X,X,_).
  199
  200normalize_extension_lambda(a, rdfs_subclass_of).
  201normalize_extension_lambda(d, [In,Out]>>rdfs_subclass_of(Out,In)).
  202normalize_extension_lambda(p, [In,Out]>>rdf(In,rdfs:subClassOf,Out)).
  203normalize_extension_lambda(c, [In,Out]>>rdf(Out,rdfs:subClassOf,In)).
  204normalize_extension_lambda(i, [In,Out]>>owl_edge(Out,_,In)).
  205normalize_extension_lambda(o, [In,Out]>>owl_edge(In,_,Out)).
  206normalize_extension_lambda(_,_) :- fail.
  207
  208call_lambda([In,Out]>>G,In,Out) :- !, G.
  209call_lambda(P,In,Out) :- atomic(P),!, G =.. [P,In,Out], G.
 search_to_objs(+SearchTerm, +PredTerm, ?Objs:list, +Opts:list) is det
given a SearchTerm and search predicate, find matching objects

SearchTerm = BaseSearchTerm / Flag

  218search_to_objs(SearchTerm, PredTerm, Objs, Opts) :-
  219        % normalize and redo search
  220        normalize_searchterm(SearchTerm,SearchTerm1),
  221        setof(Obj, search_to_obj(SearchTerm1, PredTerm, Obj, Opts), Objs),
  222        !.
  223search_to_objs(SearchTerm, PredTerm, [], _) :-
  224        debug(info, 'No matches for ~q ~q',[SearchTerm, PredTerm]).
  225 
  226search_to_obj(q(T,Query), _, Obj, _Opts) :-
  227        !,
  228        setof(T,Query,Objs),
  229        member(Obj,Objs).
  230search_to_obj(SearchTerm/_, id, Obj, _Opts) :-
  231        % if the term is already an entity, use it
  232        ensure_uri(SearchTerm, Obj),
  233        rdf_subject(Obj),
  234        !.
  235search_to_obj(SearchTerm/_, id, Obj, _Opts) :-
  236        % as above, but assume OBO expansion
  237        (   Sep=':' ; Sep='_'),
  238        concat_atom([Pre,Post],Sep,SearchTerm),
  239        concat_atom(['http://purl.obolibrary.org/obo/',Pre,'_',Post],Obj),
  240        rdf_subject(Obj),
  241        !.
  242search_to_obj(SearchTerm/FlagStr, id, Obj, _Opts) :-
  243        % slash indicates regex search; if search by id, do exact
  244        !,
  245        rdf_subject(Obj),
  246        regex(str(Obj),SearchTerm,FlagStr).
  247
  248search_to_obj(SearchTerm/FlagStr, all, Obj, _Opts) :-
  249        % regex over all
  250        !,
  251        rdf(Obj,_,Lit),
  252        regex(str(Lit),SearchTerm,FlagStr).
  253
  254search_to_obj(SearchTerm/FlagStr, label, Obj, _Opts) :-
  255        % regex over label
  256        !,
  257        rdf(Obj,rdfs:label,Lit),
  258        regex(str(Lit),SearchTerm,FlagStr).
  259
  260search_to_obj(SearchTerm/FlagStr, synonym, Obj, _Opts) :-
  261        %regex over syn
  262        !,
  263        label_or_synonym_pred_hook(Pred),
  264        rdf(Obj,Pred,Lit),
  265        regex(str(Lit),SearchTerm,FlagStr).
  266
  267search_to_obj(SearchTerm/FlagStr, Pred, Obj, _Opts) :-
  268        !,
  269        rdf(Obj,Pred,Lit),
  270        regex(str(Lit),SearchTerm,FlagStr).
  271
  272search_to_obj(_, match_anything, Obj, _Opts) :-
  273        rdf(Obj,_,_).
  274
  275gv_fmt(svg).
  276gv_fmt(png).
  277
  278magic_tell(F) :-
  279        var(F),
  280        !.
  281magic_tell(F) :- tell(F).
  282
  283opt_open_stream(F,user_output) :-
  284        var(F),
  285        !.
  286opt_open_stream(F,S) :-
  287        open(F,write,S,[]),
  288        !.
  289
  290create_style_json_term(FocusObjs, Style) :-
  291        maplist(ensure_curie, FocusObjs, IDs),
  292        atom_json_term(Style,stylemap{highlightIds: IDs}, []).
  293
  294
  295display_quads(Objs, Quads, Fmt, OutFile, _Opts) :-
  296        gv_fmt(Fmt),
  297        !,
  298        quads_dict(Quads, Dict),
  299        write_json_tmp(Dict, OgFile),
  300        atom_json_term(Style,stylemap{highlightIds: Objs}, []),
  301        style_file_args(StyleFileArgs),
  302        sformat(Cmd,'og2dot.js ~w -S \'~w\' -t ~w -o ~w ~w',[StyleFileArgs,Style, Fmt,OutFile,OgFile]),
  303        debug(gv,'cmd: ~w',[Cmd]),
  304        shell(Cmd).
  305
  306
  307display_quads(Objs, Quads, viz, _, _Opts) :-
  308        !,
  309        quads_dict(Quads, Dict),
  310        write_json_tmp(Dict, OgFile),
  311        create_style_json_term(Objs, Style),
  312        %atom_json_term(Style,stylemap{highlightIds: Objs}, []),
  313        style_file_args(StyleFileArgs),
  314        sformat(Cmd,'og2dot.js ~w -S \'~w\' -t png ~w',[StyleFileArgs,Style, OgFile]),
  315        debug(gv,'cmd: ~w',[Cmd]),
  316        shell(Cmd).
  317display_quads(Objs, Quads, dot, F, _Opts) :-
  318        !,
  319        quads_dict(Quads, Dict),
  320        write_json_tmp(Dict, OgFile),
  321        atom_json_term(Style,stylemap{highlightIds: Objs}, []),
  322        style_file_args(StyleFileArgs),
  323        (   nonvar(F)
  324        ->  sformat(Cmd,'og2dot.js ~w -S \'~w\' -o ~w ~w',[StyleFileArgs,Style, F, OgFile])
  325        ;   sformat(Cmd,'og2dot.js ~w -S \'~w\' ~w',[StyleFileArgs,Style, OgFile])),
  326        shell(Cmd).
  327display_quads(_, Quads, json, Dest, _Opts) :-
  328        !,
  329        quads_dict(Quads, Dict),
  330        atom_json_dict(JsonAtom, Dict, []),
  331        write_to(JsonAtom, Dest).
  332display_quads(_, Quads, ids, _, _Opts) :-
  333        !,
  334        quads_objects(Quads, Objs),
  335        maplist(writeln, Objs).
  336display_quads(_, Quads, info, F, Opts) :-
  337        !,
  338        magic_tell(F),
  339        quads_objects(Quads, Objs),
  340        forall(member(Obj, Objs),
  341               display_obj(Obj, Opts)),
  342        told.
  343display_quads(_, Quads, obo, F, Opts) :-
  344        !,
  345        opt_open_stream(F,S),
  346        quads_objects(Quads, Objs),
  347        ensure_loaded(library(sparqlprog/obo_util)),
  348        gen_header(S,_,Opts),
  349        nl(S),
  350        forall(member(Obj, Objs),
  351               gen_stanza(S,Obj,Opts)),
  352        close(S).
  353
  354display_quads(_, Quads, rdf, File, Opts) :-
  355        !,
  356        quads_objects(Quads, Objs),
  357        ensure_loaded(library(semweb/turtle)),
  358        G=x,
  359        extract_subontology(Objs,G,Opts),
  360        rdf_save_turtle(File,[graph(G)]).
  361
  362
  363display_obj(Uri, Opts) :-
  364        (   option(expand_uris(IsExp), Opts),
  365            ground(IsExp),
  366            IsExp=true
  367        ->  Id=Uri
  368        ;   ensure_curie(Uri, Id)),
  369        format('~w !',[Id]),
  370        forall((rdf(Uri,rdfs:label,Label),ensure_atom(Label,A)),
  371               format(' ~w',[A])),
  372        nl.
  373
  374
  375display_obo_stanza(Uri, Opts) :-
  376        gen_stanza(user_output,Uri,Opts).
  377
  378write_to(Atom, File) :-
  379        var(File),
  380        !,
  381        write(Atom).
  382write_to(Atom, stream(S)) :-
  383        !,
  384        format(S,Atom,[]).
  385write_to(Atom, F) :-
  386        !,
  387        open(F, write, S, []),
  388        format(S,Atom,[]),
  389        close(S)