1/*   orgref_search.pl
    2     Author: cnngimenez.
    3
    4     Copyright (C) 2020 cnngimenez
    5
    6     This program is free software: you can redistribute it and/or modify
    7     it under the terms of the GNU General Public License as published by
    8     the Free Software Foundation, either version 3 of the License, or
    9     at your option) any later version.
   10
   11     This program is distributed in the hope that it will be useful,
   12     but WITHOUT ANY WARRANTY; without even the implied warranty of
   13     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   14     GNU General Public License for more details.
   15
   16     You should have received a copy of the GNU General Public License
   17     along with this program.  If not, see <http://www.gnu.org/licenses/>.
   18
   19     06 Jun 2020
   20*/
   21
   22
   23:- module(orgref_search, [
   24              search_citations/2,
   25              search_refs/2
   26	  ]).

orgref_search: Search citations and references on an org file.

author
- Christian Gimenez */
license
- GPLv3
   34:- license(gplv3).   35
   36:- use_module(library(bibtex)).   37
   38
   39:- dynamic bibs/1.   40
   41load_bibtex(File) :-
   42    bibtex_file(File, L),
   43    retractall(bibs/1),
   44    assertz(bibs(L)).
   45
   46:- use_module(library(dcg/basics)).
 citation(-Link:codes)//
How the citation is formatted by ox-twbs or ox-html export. */
   53citation(Link) --> "<a href=\"", string_without("\"", Link), "\" >".
   54
   55a_tag_regexp(CiteKey, Tag) :-
   56    string_concat("<a href=\"", CiteKey, S1),
   57    string_concat(S1, "\">([^<]+)</a>", Tag).    
   58
   59a_tag_converted(CiteKey, CiteLabel, New_tag) :-
   60    format(string(New_tag), "<a href=\"~s\">~s</a>", [CiteKey, CiteLabel]).
   68citation_regexp("(parencite|cite):([^\\s\\.,;]+)").
   69ref_regexp("(ref):([^\\s\\.,;]+)").
 join(+Match, +V0, -V1)
Predicate used to join matches used by re_foldl/6.
Arguments:
Match- A re_match.
V0- The previous collected list.
V1- The next list with the Match included. */
   80join(Match, V0, [Match|V0]).
 search_regcites(+Org:string, -Lst_matches:list)
Arguments:
Org- The string where to search for citations.
Lst_matches- A list of dicts of number to string. Each number is the group matched. The zero number is the global match. */
   90search_regcites(Org, Lst_matches) :-
   91    citation_regexp(Regexp),
   92    re_foldl(join, Regexp, Org, [], Lst_matches, []).
   93
   94search_references(Org, Lst_matches) :-
   95    ref_regexp(Regexp),
   96    re_foldl(join, Regexp, Org, [], Lst_matches, []).
 get_keys(+Lst_matches:list, -Lst_keys:list)
Collect the citation or reference keys from the re_match dicts.

The second group of the dict match must be the key.

Arguments:
Lst_matches- A re_match dict list.
Lst_keys- A list of strings with the citation keys. */
  109get_keys([], []) :- !.
  110get_keys([Match|RM], [Key|RL]) :-
  111    .(Match, 2, Key),
  112    get_keys(RM, RL).
 search_citations(+Org:string, -Lst_cites:list)
Search for the citation keys used in the Org text. This citations have got the format expressed by the regexp citation_regexp/1.

Look for all of those "cite" and "parencite" and return only the key strings on Lst_cites.

Arguments:
Org- The whole Org file in string format.
Lst_cites- A list of citation key strings. */
  126search_citations(Org, Lst_cites) :-
  127    search_regcites(Org, Matches),
  128    get_keys(Matches, Lst_cites1),
  130    reverse(Lst_cites1, Lst_cites)
  130.
  131
 search_refs(+Org:string, -Lst_refs:list)
Search for all the references and return their keys on Lst_refs.
Arguments:
Org- The whole Org file in string format.
Lst_refs- A list of reference key strings */
  140search_refs(Org, Lst_refs) :-
  141    search_references(Org, Matches),
  142    get_keys(Matches, Lst_cites1),
  143    reverse(Lst_cites1, Lst_refs)