1/*   orgref_fixes
    2     Author: Christian Gimenez.
    3
    4     Copyright (C) 2020 Christian Gimenez
    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     11 Jul 2020
   20*/
   21
   22
   23:- module(orgref_fixes, [
   24              fix_citations/4,
   25              fix_references/3,
   26              fix_all/4,
   27
   28              generate_bibliography/3,
   29              generate_cites/4
   30	  ]).

orgref_fixes: Fix an org file with org-ref citations and references.

author
- Christian Gimenez */
license
- GPLv3
   38:- license(gplv3).   39
   40:- use_module(library(dcg/basics)).   41:- use_module(orgref_search).   42:- use_module(library(bibtex)).   43:- use_module(library(bibtex_fields)).
 fix_citations(+Org:term, +Bibtex:term, +Html:string, -Html_output:string)
Fix citation links and insert the bibliography at the end.
Arguments:
Org- The org file path.
Bibtex- The bibtex file path.
Html- the Html export string. Use read_file_to_string/3 to read a whole file. */
   59fix_citations(Org, Bibtex, Html, Html_output) :-
   60    read_file_to_string(Org, OrgText, []),
   61    
   62    search_citations(OrgText, Lst_cites),
   63    generate_cites(Bibtex, Lst_cites, Lst_citemaps, Lst_entries),
   64    
   65    html_fix_citations(Lst_citemaps, Html, Html1),
   66    insert_bibliography(Lst_entries, Html1, Html_output).
 fix_references(Org, Html, Html_output)
Fix references to a figure, table and/or section.
To be done
- */
   75fix_references(_Org, Html, Html).
   76% search_refs(Org, Lst_refs),
   77% replace_refs(Lst_refs, Html).
 fix_all(+Org_file:term, +Bibtex:term, +Html_file:term, +Result_file:term)
Fix the following items on the exported Html_file:
fix_references/3
fix_citations/4
@param Org_file The org file path. @param Bibtex The bibtex file path. @param Html_file The HTML exported file. @param Result_file The HTML output file which will be created. */
   92fix_all(Org_file, Bibtex, Html_file, Result_file) :-
   93    read_file_to_string(Html_file, Html, []),
   94    
   95    fix_references(Org_file, Html, Html1),
   96    fix_citations(Org_file, Bibtex, Html1, Html2),
   97
   98    tell(Result_file),
   99    write(Html2),
  100    told.
From a BibTeX author value return the abbreviated string, suitable for an APA-styled reference.

For example: from "Tania Tudorache and Csongor Nyulas and Natalya Fridman Noy and Mark A. Musen" return "Tudorache <i>et al.</i>".

The "et al." is added when more than one author is founded. Else, the author surname is used. */

  118et_alii(Author_value, Abbrv) :-
  119    author_field(field(author, Author_value), Authors),
  120    et_alii_int(Authors, Abbrv), !.
  121
  122et_alii_int([author(Surname, _Name)], Value) :-
  123    format(string(Value), "~s", [Surname]), !. % red cut.
  124et_alii_int([author(Surname, _Name)|_Rest], Value) :-
  125    format(string(Value), "~s <i>et al.</i>", [Surname]), !. % red cut.    
 accent(-Accent_type:string)//
Parse the next character and return the type of accent founded.
Arguments:
Accent_type- A string with the accent type. */
  134accent("'") --> [39].
  135accent("`") --> [96].
  136accent("\"") --> [34].
  137accent("~") --> `~`.
  138accent("c") --> `c`.
  139accent("s") --> `s`.                            
  140accent("a") --> `a`.
  141accent("A") --> `A`.
 accented_vowel(+Accent_type:string, -Accented_vowel:codes)//
Parse the next vowel and add the accent in Accent_type. Accent_type can be obtained from accent//1.
Arguments:
Accent_type- The LaTeX accent type. For instance, for the LaTeX "\'" accent use Accent_type = "'".
Accented_vowel- The resulting code: the vowel with the accent in one character.
See also
- accent//1 */
  156accented_vowel("'", `á`) --> "a".
  157accented_vowel("'", `é`) --> "e".
  158accented_vowel("'", `í`) --> "i".
  159accented_vowel("'", `ó`) --> "o".
  160accented_vowel("'", `ú`) --> "u".
  161accented_vowel("'", `Á`) --> "A".
  162accented_vowel("'", `É`) --> "E".
  163accented_vowel("'", `Í`) --> "I".
  164accented_vowel("'", `Ó`) --> "O".
  165accented_vowel("'", `Ú`) --> "U".
  166accented_vowel("`", `à`) --> "a".
  167accented_vowel("`", `è`) --> "e".
  168accented_vowel("`", `ì`) --> "i".
  169accented_vowel("`", `ò`) --> "o".
  170accented_vowel("`", `ù`) --> "u".
  171accented_vowel("`", `À`) --> "A".
  172accented_vowel("`", `È`) --> "E".
  173accented_vowel("`", `Ì`) --> "I".
  174accented_vowel("`", `Ò`) --> "O".
  175accented_vowel("`", `Ù`) --> "U".
  176accented_vowel("\"", `ä`) --> "a".
  177accented_vowel("\"", `ë`) --> "e".
  178accented_vowel("\"", `ï`) --> "i".
  179accented_vowel("\"", `ö`) --> "o".
  180accented_vowel("\"", `ü`) --> "u".
  181accented_vowel("\"", `Ä`) --> "A".
  182accented_vowel("\"", `Ë`) --> "E".
  183accented_vowel("\"", `Ï`) --> "I".
  184accented_vowel("\"", `Ö`) --> "O".
  185accented_vowel("\"", `Ü`) --> "U".
  186accented_vowel("~", `ñ`) --> "n".
  187accented_vowel("~", `Ñ`) --> "N".
  188accented_vowel("c", `ç`) --> "c".
  189accented_vowel("s", `ß`) --> "s".
  190accented_vowel("A", `Å`) --> "A".
  191accented_vowel("a", `å`) --> "a".
  192accented_vowel("a", `æ`) --> "e".
 parse_latex(-PlainText:codes)//
DCG rule to parse a LaTeX fragment and generate a plain text without:
  208parse_latex([B|Rest]) -->
  210    `\\`, accent(A), `{`, accented_vowel(A, [B]), `}`, !,
  211    parse_latex(Rest)
  211.
  212parse_latex([B|Rest]) -->
  214    `\\`, accent(A), accented_vowel(A, [B]), !,
  215    parse_latex(Rest)
  215.
  216parse_latex(Text) -->
  218    `{`, parse_latex(Nested), `}`, !, parse_latex(Rest),
  219    {append(Nested, Rest, Text)}
  219.
  220parse_latex([32|Rest]) -->
  222    blank, blanks, parse_latex(Rest)
  222.
  223parse_latex([C|Rest]) -->
  225    [C], parse_latex(Rest),
  226    {[C] \= `}`}, !
  226.
  227parse_latex([]) --> [].
Convert LaTeX accents, remove curly brackets and excesive spaces into text. For instance, convert the following LaTeX text
La   herramienta {Prot\'eg{\'{é}}} es utilizada para
        la   {W}eb  {Sem\'{a}ntica}.

into a plaint text as follows:

La herramienta Protégé es utilizada para la Web Semántica.

This is useful for generating the bibliography or reference text from the BibTeX's author names.

Arguments:
Latex- A string or codes to convert.
Text- The results of the convertion. */
  253latex2text(Latex, Text) :-
  254    is_of_type(string, Latex), !,
  255    
  256    string_codes(Latex, Latex_codes),
  257    phrase(parse_latex(Text1), Latex_codes),
  258    string_codes(Text, Text1).
  259
  260latex2text(Latex, Text) :-
  261    is_of_type(codes, Latex),
  262    phrase(parse_latex(Text1), Latex),
  263    string_codes(Text, Text1).
 get_field(+FieldName:atom, +Fields:list, -Value:string)
Return the field value from an entry/3's field/2 data.

This predicate always is succeds.

Arguments:
FieldName- The field name to retrieve. Ex.: author.
Fields- The list of field/2 terms.
Value- The string value. An empty string if the field does not exists. */
  276get_field(FieldName, Fields, Value) :-
  277    member(field(FieldName, Value), Fields), !. 
  278get_field(_Fieldname, _Fields, ""). % <- Couldn't find this field
 generate_cite(-Entry:term, -Cite_map:term) is det
Generate the cite/2 term from the given entry. The term consist of: cite(Entry_label: string, Reference_string: string).

For example, it generate the following "citemap" from an entry:

cite("schneider73:_cours_modul_applied", "(Schneider, Edward W, 1973)").
Arguments:
Entry- An entry/3 term.
Cite_map- A cite/2 term. */
  298generate_cite(entry(_Key, Label, Fields), cite(Label, Str)):-
  299    get_field(author, Fields, Author_value),
  300    latex2text(Author_value, Author_value2),
  301    et_alii(Author_value2, Auth_abbrv),
  302    get_field(year, Fields, Year),
  303    format(string(Str), "(~s, ~s)", [Auth_abbrv, Year]).
 fold_mapcites_pred(+Entry:term, +Lst_prev:list, -Lst_next:list)
Predicate used by a foldl/4 call. Generate the "citemap" from the given Entry and append it to the previous list Lst_prev.
Arguments:
Entry- An entry/3 term.
Lst_prev- A list of cite/2 citemaps.
Lst_next- A list of resulting cite/2 citemaps. */
  315fold_mapcites_pred(Entry, Lst_prev, [Map|Lst_prev]) :-
  316    generate_cite(Entry, Map).    
 generate_mapcites(+Lst_entries:list, -Lst_maps:list)
Generate citemaps from the given entry. Each citemap is used to generate the citation references in the middle of the text.

For instance, if a bibtex key is founded in the middle of the text, it should be replaced by the correct APA (or other style) citation reference.

Arguments:
Lst_entries- A list of entry/3 terms given by any bibtex predicate library.
Lst_maps- A list of cite/2 terms. */
  331generate_mapcites(Lst_entries, Lst_maps) :-
  332    foldl(fold_mapcites_pred, Lst_entries, [], Lst_maps).
 generate_cites(+Bibtex:term, +Lst_cites:list, -Map:list, -Lst_entries:list)
Given a list of bibtex citation keys, search each entry on the Bibtex file and create the citation maps.
Arguments:
Bibtex- The bibtex file path.
Lst_cites- A list of strings with cite keys.
Map- A cite/2 map between each key and the APA reference string.
Lst_entries- The list of bibtex entry/3 entries. */
  345generate_cites(Bibtex, Lst_cites, Map, Lst_entries) :-
  346    bibtex_get_entries(Bibtex, Lst_cites, Lst_entries),
  347    generate_mapcites(Lst_entries, Map).
 replace_cites(+Citemap:term, +Html:string, -Html_output:string)
For the Citemap = cite(Citekey, Labelstr), replace every anchor with href to with a proper formatted anchor with the Labelstr as text.
Arguments:
Citemap- A cite/2 mapping cite(+Citekey:string, +Labelstr:string).
Html- The org export as string.
Html_output- The replaced org. */
  359replace_cites(cite(Key, Str), Html, Html_output) :-
  360    format(string(Regexp), '<a href="([^"]+)">~s</a>', [Key]),
  361    format(string(Result),
  362           '<a href="#\\1" class="cite-link" data-ref="~s">~s</a>',
  363           [Key, Str]),
  364    re_replace(Regexp/g, Result, Html, Html_output).
 html_fix_citations(+Lst_citemaps:list, +Html:string, -Html_output:string)
Fix the citation references.
Arguments:
Lst_citemaps- A list of cite/2 mappings.
Html- A string with the exported org file.
Html_output- A string with the fixed anchors. */
  375html_fix_citations(Lst_citemaps, Html, Html_output) :-
  376    foldl(replace_cites, Lst_citemaps, Html, Html_output).
 process_field(+Fields:list, -Text:string)
Create the bibliography line by using the BibTeX field list.

For example, from an entry(Key, Label, Fields) create the following APA-styled bibliography line format:

AuthorSurname, AuthorName. Title (Year).

The fields taken from the Fields list are the following:

author
year
title
@param Fields The field list from the BibTeX entry/3 term. @param Text The string produced. */
  403process_field(Fields, Html) :-
  404    get_field(author, Fields, Author),
  405    get_field(year, Fields, Year),
  406    get_field(title, Fields, Title),
  407
  408    latex2text(Author, AuthorText),
  409    latex2text(Title, TitleText),
  410
  411    format(string(Html), '~s. ~s (~s).', [
  412               AuthorText, TitleText, Year
  413           ]).
 generate_html(+Entry:term, -Html:string)
Generate an HTML bibliography div from a BibTeX entry. The format produced is an HTML as follows:
  <div>
    <a name="Entry_label" class="org-bibitem" ></a>
    <p class="org-bibitem">
      -- APA-styled bibliography reference here --
    </p>
  </div>
Arguments:
Entry- A BibTeX entry/3 as the one produced by the bibtex library.
Html- The HTML filled with the BibTeX entry/3 data as described before. */
  433generate_html(entry(_Key, Label, Fields), Html) :-
  434    process_field(Fields, Fields_HTML),
  435    format(string(Html),
  436           '  <div>
  437    <a name="~s" class="org-bibitem" ></a>
  438    <p class="org-bibitem">
  439      ~s
  440    </p>
  441  </div>
  442',
  443           [
  444               Label,
  445               Fields_HTML
  446           ]).
 fold_bibs_pred(+Entry:term, +PrevHtml:string, -NextHtml:string)
Internal predicate. It is used by a foldl/4 predicate to generate all the bibliography HTML items.

Generate a bibliography APA-styled text from the given Entry. Use a HTML syntax.

Arguments:
Entry- A BibTeX entry/3 term where to take the author, title and year for the bibliography text.
PrevHtml- The previous HTML string generated by the previous call.
NextHtml- The output HTML for the next call.
See also
- generate_bibs_html/2 */
  464fold_bibs_pred(Entry, PrevHtml, NextHtml) :-
  465    generate_html(Entry, Html),
  466    string_concat(PrevHtml, Html, NextHtml).
 generate_bibs_html(+Lst_entries:list, -Html:string)
Generate an APA-styled bibliography from the given entry/3 BibTeX list. The output is formated using HTML syntax.
Arguments:
Lst_entries- A list of entry/3 BibTeX entries.
Html- The HTML bibliography text generated in HTML format. */
  477generate_bibs_html(Lst_entries, Html) :-
  478    foldl(fold_bibs_pred, Lst_entries, "\n<div class=\"org-bib\">\n", Html1),
  479    string_concat(Html1, "</div><!-- /org-bib -->\n", Html).
 generate_bibliography(+Bibtex:term, +Lst_cites:list, -Html:string)
Generate an APA-styled bibliography in HTML syntax from a list of citation labels.
Arguments:
Bibtex- The BibTeX file path.
Lst_cites- A list of strings. These must be citation labels (ex. ["giese15:optique", "chang18:_scaling_knowled_access"]).
Html- The HTML bibliography text generated in HTML format. */
  492generate_bibliography(Bibtex, Lst_cites, Html) :-
  493    bibtex_get_entries(Bibtex, Lst_cites, Lst_entries),
  494    generate_bibs_html(Lst_entries, Html).
 replace_printbibliography(+Html:string, +Bib_html:string, -Html_output:string)
Find all \printbibliography text in Html and replace it with Bib_Html.
Arguments:
Html- The input HTML text.
Bib_html- The bibliography in HTML format.
Html_output- The output HTML text */
  506replace_printbibliography(Html, Bib_html, Html_output) :-
  508    
  509    
  510    
  511    re_replace('\\\\'/g, "\\\\\\\\", Bib_html, Bib_html2), 
  512    re_replace('\n[[:space:]]*\\\\printbibliography[[:space:]]*\n'/g,
  513               Bib_html2, Html, Html_output)
  513.
  514
 insert_bibliography(+Lst_entries:list, +Html:string, -Html_output:string)
Replace the \printbibliography text in the Html string with the bibliography generated from the BibTeX entries given.

The bibliography text used is an HTML produced by the generate_bibs_html/2 predicate.

Arguments:
Lst_entries- A list of BibTeX entry/3 terms as returned by bibtex_get_entries/3 from the bibtex library.
Html- The HTML input.
Html_output- The HTML output with the bibliography inserted where the \printbibliography text were. */
  530insert_bibliography(Lst_entries, Html, Html_output) :-
  531    generate_bibs_html(Lst_entries, Bib_html),
  532    replace_printbibliography(Html, Bib_html, Html_output)