1/*   bibtex_fields
    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(bibtex_fields, [
   24	      author_field/2,
   25              all_keywords/2,
   26	      bibentry_keywords/2
   27	  ]).

bibtex_fields: Parsing some BibTeX fields

Some fields can be parsed into smaller and simpler data. This module focus on some important and frequently used fields.

author
- Christian, Gimenez
license
- GPLv3 */
   37:- use_module(bibtex_dcg).
 author_field(+Field:term, Authors:list)
Parse an author field.
Arguments:
Field- a field/2 term: field(+Author:term, +Value: String).
Authors- a list of author/2 terms: author(+Surname: string, +Name: string). */
   47author_field(field(author, Value), AuthorList) :-
   48    string_codes(Value, ValueL),
   49    authors(AuthorList, ValueL, _Rest).
 all_keywords(+Codes:codes, -Keywords:list)
True if Keywords is a list with the keywords retrieved from Codes.

This predicate identify if the codes are separated by ",", ";" or spaces.

Arguments:
Codes- the value of a "keywords" field.
Keywords- a list of strings with the keywords. */
   63all_keywords(Codes, Keywords) :-
   64    k_sep(Sep),
   65    member(Sep, Codes),!,
   66    keyword_sep(Keywords, Codes, _).
   67all_keywords(Codes, Keywords) :-
   68    keyword_spaces(Keywords, Codes, _).
 bibentry_keywords(+BibEntry:term, -Keywords:list)
return from a BibTeX entry/3 all the keywords declared.

This predicate parse each "keywords" field's values.

Arguments:
Keywords- a list of strings.
BibEntry- an entry/3 compound term. */
   80bibentry_keywords(entry(_Name, _Label, Fields), Keywords) :-
   81    findall(Value,
   82	    member(field(keywords, Value), Fields),
   83 	    KeywordsList),
   84    flatten_lst_keywords(KeywordsList, Keywords).
 flatten_lst_keywords(+Lst:list, -Keywords:list)
Search for keywords in each string from the given list.
Arguments:
Lst- A list of string, each one is a list or one keyword.
Keywords- A list of strings. */
   94flatten_lst_keywords([],[]).
   95flatten_lst_keywords([Str|Rest], Lst) :-
   96    string_codes(Str, Codes),
   97    all_keywords(Codes, Keys),
   98    flatten_lst_keywords(Rest, RestKeys),
   99    append(Keys, RestKeys, Lst)