1/*   bibtex
    2     Author: Giménez, Christian.
    3
    4     Copyright (C) 2017 Giménez, Christian
    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     02 jun 2017
   20*/
   21
   22
   23:- module(bibtex, [
   24	      bibtex_file/2,
   25	      nth_bibtex_file/3,
   26	      bibtex_author/3,
   27              bibtex_get_entries/3
   28	  ]).

bibtex: Parse a bibtex file or entry

Predicates that works on a whole BibTeX file. For example, return a particular entry, search for an author's entries or parse the file completely.

Useful compound terms

   42:- license(gplv3).   43
   44:- use_module(library(dcg/basics)).   45:- use_module(bibtex_dcg).
 bibtex_file(+Path:term, -LstEntries:list)
Parse a whole file and retrieve its entries.

This is a slower predicate because it reads all the file into string codes. For bigger files use nth_bibtex_file/3. */

   56bibtex_file(Path, LstEntries) :-
   57    read_file_to_codes(Path, Codes, []),
   58    parse_bibtex(Codes, LstEntries).
   59
   60parse_bibtex(``, []) :- !.
   61parse_bibtex(Codes, [Entry|Rest]) :-
   62    entry(Entry, Codes, RestCodes),!,
   63    parse_bibtex(RestCodes, Rest)
   63.
   64parse_bibtex(_Codes, []). 
 nth_bibtex_file(+Path:term, +Number:int, -Entry:term) is det
Search the nth arroba character and read that entry. This method is faster than parsing the whole file and retrieve then nth element of the list.
Arguments:
Number- An integer where 1 is the first entry. @return false if there's no nth entry or file couldn't be readed. */
   76nth_bibtex_file(Path, Number, Entry) :-
   77    open(Path, read, Stream),
   78    skip(Stream, `@`),
   79    nth_bibtex_file_s(Stream, Number, Entry),
   80    close(Stream).
 nth_bibtex_file_s(+Stream, +Number:int, -Entry:term) is det
Same as nth_bibtex_file/3, but using a stream. */
   87nth_bibtex_file_s(Stream, 1, Entry) :-
   88    (seek(Stream, 0, current, 0) ;
   89     seek(Stream, -1 , current, _NewPos))
   89,
   90    read_entry(Stream, Codes), !,
   91    entry(Entry, Codes, _Rest)
   91.
   92nth_bibtex_file_s(Stream, Number, Entry) :-
   93    Number > 1,
   94    seek(Stream, 1, current, _),
   95    skip(Stream, `@`),
   96    Number2 is Number - 1,
   97    nth_bibtex_file_s(Stream, Number2, Entry).
 skip_up_to_arroba(+Stream)
Move the stream up to arroba, ready for reading it. */
  104skip_up_to_arroba(Stream) :-
  105    skip(Stream, `@`),!,
  106    seek(Stream, -1, current, _NewPos).
 read_entry(+Stream, -Codes:list) is det
Read one entry from the stream (i.e. from '@' up to '@' or EOF). */
  113read_entry(Stream, [64|Rest]) :-
  114    peek_code(Stream, 64), !,
  115    get_code(Stream, 64),
  116    read_up_to_arroba(Stream, Rest).
  117
  118read_up_to_arroba(Stream, []) :-
  119    at_end_of_stream(Stream), !. % Red cut
  120read_up_to_arroba(Stream, []) :-
  121    peek_code(Stream, 64),!. % Red cut
  122read_up_to_arroba(Stream, [C|Rest]) :-
  123    get_code(Stream, C),
  124    read_up_to_arroba(Stream, Rest).
 bibtex_author(+File:term, +Author:string, -BibEntries:list)
Search in the BibTeX file all BibTeX entries related to the given author.
Arguments:
File- the filename.
Author- a string with the author name or surname word (just a word!).
BibEntries- a list of entry/3. */
  135bibtex_author(File, Author, BibEntries) :-
  136    string_codes(Author, AuthorC),
  137    bibtex_author_int(File, AuthorC, 1, BibEntries).
 has_word(+Word:codes, +Codes:codes) is det
True iff Word is part of Codes. */
  144has_word(Word, Codes) :-
  145    append([_, Word, _], Codes), !.
  146
  147bibtex_author_int(File, _Author, N, []) :-
  148    \+ nth_bibtex_file(File, N, _), !. 
  149bibtex_author_int(File, Author, N, [entry(Name, Label, LstFields)|Rest]) :-
  150    nth_bibtex_file(File, N, entry(Name, Label , LstFields)),
  151    member(field('author', Value), LstFields),
  152    string_codes(Value, ValueC),
  153    has_word(Author, ValueC),!,
  154    N2 is N + 1,
  155    bibtex_author_int(File, Author, N2, Rest)
  155.
  156bibtex_author_int(File, Author, N, Rest) :-
  158    N2 is N + 1,!,
  159    bibtex_author_int(File, Author, N2, Rest)
  159.
  160
 lst_entries(Lst:list)
The list of entries collected so far. */
  166:- dynamic lst_entries/1.
 add_entry_if_in_list(+Lst_keys:list, +Entry:term)
If the entry key is in the list of keys, then add it to the lst_entries/1 dynamic predicate. Else, just do not add it. Always return true.
Arguments:
Lst_keys- A list of string keys.
Entry- The BibTeX entry/3 term. */
  177add_entry_if_in_list(Lst_keys, entry(Key, Label, Fields)) :-
  178    atom_string(Label, LabelS),
  179    member(LabelS, Lst_keys),!,
  180    lst_entries(Lst),
  181    Lst2 = [entry(Key, Label, Fields)|Lst],
  182    retractall(lst_entries),
  183    asserta(lst_entries(Lst2)), !. 
  184add_entry_if_in_list(_Lst_keys, _Entry) :- !.
 collect_next_entry(+Stream:term, +Lst_keys:list)
Go to the next BibTeX entry on the stream and add it to lst_entries/1 if its key is on the Lst_keys string. */
  192collect_next_entry(Stream, _Lst_keys) :-
  193    at_end_of_stream(Stream), !. % red cut!
  194collect_next_entry(Stream, Lst_keys) :-
  195    % is not at EOF and...
  196    read_entry(Stream, Codes), !,
  197    entry(Entry, Codes, _Rest),
  198    add_entry_if_in_list(Lst_keys, Entry).
  199
  200jump_to_next_entry(Stream) :-
  201    skip(Stream, `@`),
  204    (at_end_of_stream(Stream), ! ;
  205     seek(Stream, -1, current, _New_pos))
  205.
  206
 bibtex_collect_entries(+Stream:term, +Lst_keys:list)
Get the next entry adding it to the lst_entries/1 if its key is on the list of keys. Repeat the process until the end of file. */
  213bibtex_collect_entries(Stream, Lst_keys) :-
  214    repeat,
  215
  216    jump_to_next_entry(Stream),
  217    collect_next_entry(Stream, Lst_keys),
  218    at_end_of_stream(Stream).
 bibtex_get_entries(+Path:term, +Lst_keys:list, -Lst_entries:list) is det
Search for the given BibTeX keys in the file and return their parsed entries.

Simmilar to nth_bibtex_file/3, walk through the file jumping from entry to entry and checking each one if its key is in the list. If the file is large, this is supposed to save more RAM memory than using bibtex_file/2.

Arguments:
Path- The filename path.
Lst_keys- A list of strings with the keys to search on the file.
Lst_entries- A list of entry/3 terms. */
  233bibtex_get_entries(Path, Lst_keys, Lst_entries) :-
  234    % lst_entries starts empty
  235    retractall(lst_entries),
  236    asserta(lst_entries([])),
  237
  238    open(Path, read, Stream),
  239    bibtex_collect_entries(Stream, Lst_keys),
  240    close(Stream),
  241
  242    % And the collected entries is Lst_entries
  243    lst_entries(Lst_entries1), !,
  244    reverse(Lst_entries1, Lst_entries)