1/*  Part of SWI-Prolog odf-sheet pack
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org/pack/list?p=odf-sheet
    6
    7    Copyright (c) 2012-2014, VU University of Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions are
   12    met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15    notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18    notice, this list of conditions and the following disclaimer in the
   19    documentation and/or other materials provided with the distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS
   22    IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
   23    TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A
   24    PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
   25    HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
   26    SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED
   27    TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR
   28    PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
   29    LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING
   30    NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
   31    SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
   32*/
   33
   34:- module(ods_sheet,
   35	  [ ods_load/1,			% :File
   36	    ods_current/1,		% :URL
   37	    ods_unload/0,
   38	    ods_unload_all/0,
   39	    ods_compile/0,
   40	    ods_compile_all/0,
   41	    ods_eval/2,			% +Expression, -Value
   42	    ods_style_property/2,	% :Style, ?Property
   43	    cell_value/4,		% :Sheet, ?X, ?Y, ?Value
   44	    cell_type/4,		% :Sheet, ?X, ?Y, ?Type
   45	    cell_formula/4,		% :Sheet, ?X, ?Y, ?Formula
   46	    cell_eval/4,		% :Sheet, ?X, ?Y, -Value
   47	    cell_style/4,		% :Sheet, ?X, ?Y, ?Property
   48	    cell/8,			% :Sheet, ?X, ?Y, ?V, ?T, ?F, ?S, ?A
   49
   50	    column_name/2,		% ?Index, ?Name
   51	    ods_DOM/3,			% :Source, -DOM, +Options
   52
   53	    cell_id/3,			% ?X, ?Y, ?Id
   54
   55	    sheet_name_need_quotes/1,	% +SheetName
   56	    ods_reference//2		% -Expr, +Table
   57	  ]).   58:- use_module(library(xpath)).   59:- use_module(library(sgml)).   60:- use_module(library(uri)).   61:- use_module(library(archive)).   62:- use_module(library(apply_macros)).   63:- use_module(library(lists)).   64:- use_module(library(dcg/basics)).   65:- use_module(library(aggregate)).   66:- use_module(functions).   67:- use_module(bisect).   68
   69:- set_prolog_flag(optimise, true).

Load Open Document Spreadsheets

This module loads an Open Document spreadsheet into the Prolog database. The primary call is ods_load/1, which adds the following facts into the calling module:

In addition, it provides the following high-level query primitives: cell_value/4, cell_type/4, cell_formula/4, cell_eval/4 and cell_style/4. All these predicates use the same calling convention, e.g.,

cell_value(Sheet, X, Y, Value)

where Sheet is the name of the sheet, X is the column (an integer) and Y is the row (an integer). Value is the current value of the cell. Although integer columns are easier for computation, these predicates do allow specifying the column as an atom. E.g., the value of cell WindOffshore.D43 can be requested using the call below. This is mainly intended for querying from the toplevel.

?- cell_value('WindOffshore', d, 43, X).
X = 0.07629.

Values are represented using the following conventions:

To be done
- Add interface to query cell spanning
- Correctly report cell boolean and error values. */
  115:- meta_predicate
  116	ods_load(:),
  117	ods_current(:),
  118	ods_eval(:, -),
  119	ods_style_property(:, ?),
  120	cell_value(:, ?, ?, ?),
  121	cell_type(:, ?, ?, ?),
  122	cell_formula(:, ?, ?, ?),
  123	cell_eval(:, ?, ?, ?),
  124	cell_style(:, ?, ?, ?),
  125	cell(:, ?, ?, ?, ?, ?, ?, ?).  126
  127:- dynamic
  128	ods_spreadsheet/2.		% URL, Module
 ods_DOM(+File, -DOM, +Options) is det
DOM is the XML domtree of the content file of the given ODS document.
  135ods_DOM(File, DOM, Options) :-
  136	setup_call_cleanup(
  137	    archive_open(File, Archive, []),
  138	    archive_dom(Archive, DOM, Options),
  139	    archive_close(Archive)).
  140
  141archive_dom(Archive, DOM, Options) :-
  142	select_option(member(Member), Options, XMLOptions, 'content.xml'),
  143	archive_next_header(Archive, Member),
  144	setup_call_cleanup(
  145	    archive_open_entry(Archive, Stream),
  146	    load_structure(Stream, DOM, XMLOptions),
  147	    close(Stream)).
 ods_load(:Data)
Load a spreadsheet. Data is either a parsed XML DOM, a file name or a URI. Tables in the spreadsheet are converted into a set of Prolog predicates in the calling module. The generated predicates are:

Does nothing if the spreadsheet is already loaded in the target module. To force reloading, first use ods_unload/0.

  166ods_load(Module:DOM) :-
  167	nonvar(DOM),
  168	DOM = [element(_,_,_)], !,
  169	load_styles(DOM, Module),
  170	load_tables(DOM, Module).
  171ods_load(Module:Spec) :-
  172	(   uri_is_global(Spec)
  173	->  uri_file_name(Spec, File),
  174	    URI = Spec
  175	;   uri_file_name(URI, Spec),
  176	    File = Spec
  177	),
  178	(   ods_spreadsheet(URI, Module)
  179	->  true
  180	;   statistics(cputime, CPU0),
  181	    ods_DOM(File, DOM, []),
  182	    dynamic_decls(Module),
  183	    ods_load(Module:DOM),
  184	    statistics(cputime, CPU1),
  185	    CPU is CPU1-CPU0,
  186	    predicate_property(Module:sheet(_,_),
  187			       number_of_clauses(Sheets)),
  188	    predicate_property(Module:cell(_,_,_,_,_,_,_),
  189			       number_of_clauses(Cells)),
  190	    print_message(informational,
  191			  ods(loaded(Module:Spec, CPU, Sheets, Cells))),
  192	    retractall(ods_spreadsheet(URI, _)),
  193	    assertz(ods_spreadsheet(URI, Module))
  194	).
 ods_ensure_loaded(+URL, -Module) is semidet
True when the spreadsheet in URL is loaded into Module.
  200ods_ensure_loaded(URI, Module) :-
  201	ods_spreadsheet(URI, Module), !,
  202	Module \= #(_).
  203ods_ensure_loaded(URI, Module) :-
  204	uri_file_name(URI, File),
  205	(   access_file(File, read)
  206	->  ods_load(URI:File),
  207	    Module = URI
  208	;   assertz(ods_spreadsheet(URI, #('REF!')))
  209	).
 cell_id(+X, +Y, -ID) is det
cell_id(-X, -Y, +ID) is det
  215cell_id(X, Y, ID) :-
  216	nonvar(X), nonvar(Y), !,
  217	(   integer(X)
  218	->  ID is Y*10000+X
  219	;   upcase_atom(X, XU),
  220	    column_name(I, XU),
  221	    ID is Y*10000+I
  222	).
  223cell_id(X, Y, ID) :-
  224	nonvar(ID), !,
  225	Y is ID//10000,
  226	X is ID mod 10000.
  227
  228load_tables(DOM, Module) :-
  229	forall(xpath(DOM, //'table:table'(@'table:name'=Name,
  230					  @'table:style-name'=Style), Table),
  231	       load_table(Table, Name, Style, Module)).
  232
  233load_table(DOM, Name, TStyle, Module) :-
  234	assertz(Module:sheet(Name, TStyle)),
  235	State = state(1,1,Name,_),
  236	forall(xpath(DOM, 'table:table-column'(@'table:style-name'=Style), Col),
  237	       load_column(Col, Style, State, Module)),
  238	forall(xpath(DOM, 'table:table-row'(@'table:style-name'=Style), Col),
  239	       load_row(Col, Style, State, Module)).
  240
  241load_column(element(_, CollAttrs, []), Style, State, Module) :-
  242	arg(1, State, X0),
  243	arg(3, State, Table),
  244	(   memberchk('table:number-columns-repeated'=RepA, CollAttrs),
  245	    atom_number(RepA, Rep)
  246	->  true
  247	;   Rep = 1
  248	),
  249	End is X0+Rep-1,
  250	forall(between(X0, End, X),
  251	       assertz(Module:col(Table, X, Style))),
  252	NextX is End+1,
  253	nb_setarg(1, State, NextX).
  254
  255load_row(DOM, Style, State, Module) :-
  256	DOM = element(_, RowAttrs, _),
  257	nb_setarg(1, State, 1),
  258	arg(2, State, Y0),
  259	arg(3, State, Table),
  260	(   memberchk('table:number-rows-repeated'=RepA, RowAttrs),
  261	    atom_number(RepA, Rep)
  262	->  true
  263	;   Rep = 1
  264	),
  265	End is Y0+Rep-1,
  266	(   nonempty_row(DOM)
  267	->  forall(between(Y0, End, Y),
  268		   ( assertz(Module:row(Table, Y, Style)),
  269		     debug(ods(row), 'Processing row ~q', [Y]),
  270		     forall(xpath(DOM, 'table:table-cell'(self), Cell),
  271			    load_cell(Cell, State, Module))
  272		   ))
  273	;   true
  274	),
  275	NextY is End + 1,
  276	nb_setarg(2, State, NextY).
  277
  278nonempty_row(DOM) :-
  279	xpath(DOM, 'table:table-cell'(content), Content),
  280	Content \== [].
  281
  282load_cell(DOM, State, Module) :-
  283	DOM = element(_, CellAttrs, Content),
  284	arg(1, State, X0),
  285	arg(2, State, Y),
  286	arg(3, State, Table),
  287	(   memberchk('table:number-columns-repeated'=RepA, CellAttrs),
  288	    atom_number(RepA, Rep)
  289	->  Columns = Rep,  Repeat = Rep, Span = 1
  290	;   memberchk('table:number-columns-spanned'=SpanA, CellAttrs),
  291	    atom_number(SpanA, Span)
  292	->  Columns = Span, Repeat = 1
  293	;   Columns = 1,    Repeat = 1, Span = 1
  294	),
  295	(   memberchk('table:number-rows-spanned'=VSpanA, CellAttrs),
  296	    atom_number(VSpanA, VSpan)
  297	->  true
  298	;   VSpan = 1
  299	),
  300	EndRep is X0+Repeat-1,
  301	(   Content == []
  302	->  debug(ods(cell), '~w empty cells', [Columns]),
  303	    (	cell_style(DOM, Style),
  304		Style \== default
  305	    ->	forall(between(X0, EndRep, X),
  306		       ( debug(ods(cell), '~q,~q: ~q', [X,Y,Value]),
  307			 cell_id(X,Y,Id),
  308			 assertz(Module:cell(Table,Id,
  309					     @empty,
  310					     no_type,
  311					     -,
  312					     Style,
  313					     []))
  314		       ))
  315	    ;	true
  316	    )
  317	;   Content = [Annotation],
  318	    xpath(Annotation, /'office:annotation'(self), _)
  319	->  (   cell_style(DOM, Style),
  320	        cell_annotations(DOM, Annotations)
  321	    ->	forall(between(X0, EndRep, X),
  322		       ( debug(ods(cell), '~q,~q: ~q', [X,Y,Value]),
  323			 cell_id(X,Y,Id),
  324			 assertz(Module:cell(Table,Id,
  325					     @empty,
  326					     no_type,
  327					     -,
  328					     Style,
  329					     Annotations))
  330		       ))
  331	    ;	ods_warning(convert_failed(cell, DOM))
  332	    )
  333	;   (   cell_type(DOM, Type),
  334	        cell_style(DOM, Style),
  335		cell_value(DOM, Type, Value),
  336		cell_formula(DOM, Table, Formula),
  337		cell_annotations(DOM, Annotations)
  338	    ->  forall(between(X0, EndRep, X),
  339		       ( debug(ods(cell), '~q,~q: ~q', [X,Y,Value]),
  340			 cell_id(X,Y,Id),
  341			 assertz(Module:cell(Table,Id,
  342					     Value,
  343					     Type,
  344					     Formula,
  345					     Style,
  346					     Annotations))
  347		       ))
  348	    ;	ods_warning(convert_failed(cell, DOM))
  349	    )
  350	),
  351	(   (Span > 1 ; VSpan > 1)
  352	->  cell_id(X0,Y,Id0),
  353	    EndSpanX is X0+Columns-1,
  354	    EndSpanY is Y+VSpan-1,
  355	    forall(between(Y, EndSpanY, YS),
  356		   forall(between(X0, EndSpanX, XS),
  357			  ( cell_id(XS,YS,IDS),
  358			    (	IDS \== Id0
  359			    ->	assertz(Module:span(IDS, Id0))
  360			    ;	true
  361			    )
  362			  )))
  363	;   true
  364	),
  365	NextX is X0+Columns,
  366	nb_setarg(1, State, NextX).
  367
  368
  369cell_type(DOM, Type) :-
  370	xpath(DOM, /'table:table-cell'(@'office:value-type'), OfficeType),
  371	OfficeType = Type.
  372
  373cell_style(DOM, Style) :-
  374	xpath(DOM, /'table:table-cell'(@'table:style-name'), Style), !.
  375cell_style(_, default).			% TBD: Use default column style
  376
  377cell_value(DOM, Type, Value) :-
  378	xpath(DOM, /'table:table-cell'(@'office:value'), OfficeValue), !,
  379	convert_value(Type, OfficeValue, Value).
  380cell_value(DOM, date, Value) :-
  381	xpath(DOM, /'table:table-cell'(@'office:date-value'), OfficeValue), !,
  382	convert_date(OfficeValue, Value).
  383cell_value(DOM, string, Value) :-
  384	findall(T, xpath(DOM, 'text:p'(normalize_space), T), List),
  385	atomic_list_concat(List, Value).
  386
  387convert_value(float, Text, Value) :- !,
  388	(   atom_number(Text, Value0)
  389	->  Value is float(Value0)
  390	;   type_error(float, Text)
  391	).
  392convert_value(percentage, Text, Value) :- !,
  393	(   atom_number(Text, Value0)
  394	->  Value is float(Value0)
  395	;   type_error(percentage, Text)
  396	).
  397convert_value(Type, Value, Value) :-
  398	ods_warning(unknown_type(Type)).
  399
  400convert_date(Text, date(Y,M,D)) :-
  401	atom_codes(Text, Codes),
  402	phrase(date(Y,M,D), Codes), !.
  403convert_date(Text, Text) :-
  404	ods_warning(convert_failed(date, Text)).
  405
  406date(Y,M,D) -->
  407	integer(Y), "-", integer(M), "-", integer(D),
  408	{ between(1, 12, M),
  409	  between(1, 31, D)
  410	}.
 cell_annotations(+DOM, -Annotations:list) is det
  414cell_annotations(DOM, Annotations) :-
  415	findall(Annot, cell_annotation(DOM, Annot), Annotations).
  416
  417cell_annotation(DOM, Term) :-
  418	xpath(DOM, 'office:annotation'(self), Annotation),
  419	(   convert_annotation(Annotation, Term)
  420	->  true
  421	;   ods_warning(convert_failed(annotation, DOM))
  422	).
  423
  424convert_annotation(DOM, annotation(Date, Author, Text)) :-
  425	xpath(DOM, 'dc:date'(text), DateText),
  426	parse_time(DateText, Date),
  427	!,
  428	findall(T, xpath(DOM, 'text:p'(text), T), List),
  429	List = [Author|Rest],
  430	atomic_list_concat(Rest, Text).
  431convert_annotation(DOM, annotation(0,'',Text)) :-
  432	findall(T, xpath(DOM, 'text:p'(text), T), List),
  433	atomic_list_concat(List, Text).
  434
  435%%	cell_formula(+DOM, +Table, -Formula) is det.
  436
  437cell_formula(DOM, Table, Formula) :-
  438	xpath(DOM, /'table:table-cell'(@'table:formula'), OfficeFormula), !,
  439	(   compile_formula(OfficeFormula, Table, Formula)
  440	->  true
  441	;   ods_warning(convert_failed(formula, OfficeFormula)),
  442	    Formula = OfficeFormula
  443	).
  444cell_formula(_, _, -).
  445
  446
  447		 /*******************************
  448		 *	      STYLES		*
  449		 *******************************/
  450
  451%%	load_styles(+DOM, +Module) is det.
  452%
  453%	Load the style information for the  spreadsheet. We simply store
  454%	the DOM content of the style,   leaving the high-level reasoning
  455%	to other predicates. One  advantage  of   this  is  that  we can
  456%	re-generate the style info.
  457%
  458%	@tbd	Styles defined here may refer to styles in =|styles.xml|=.
  459
  460load_styles(DOM, Module) :-
  461	xpath(DOM, //'office:automatic-styles'(self), StylesDOM), !,	forall(xpath(StylesDOM, 'style:style'(@'style:name' = Name), SDOM),	       assertz(Module:style(Name, SDOM))).
 ods_style_property(:Style, ?Property) is nondet
True when Property is a property of Style. Currently extracted styles are:
font_weight(Weight)
Font weight (e.g., bold)
font_name(Name)
Name of the font used for the text
font_size(Size)
Size of the font. See below for size representations.
column_width(Width)
Width of the column
cell_color(Color)
Color of the cell background
name(Name)
Name of the style.

Sizes are expressed as one of pt(Points), cm(Centimeters) or mm(Millimeters)

See also
- http://docs.oasis-open.org/office/v1.2/OpenDocument-v1.2-part1.html
To be done
- Normalize sizes?
  489ods_style_property(Module:Style, Property) :-
  490	Module:style(Style, DOM),
  491	(   nonvar(Property)
  492	->  once(style_property(Property, DOM))
  493	;   style_property(Property, DOM)
  494	).
  495
  496style_property(font_weight(W), DOM) :-
  497	xpath(DOM, 'style:text-properties'(@'fo:font-weight'=W), _).
  498style_property(font_name(Name), DOM) :-
  499	xpath(DOM, 'style:text-properties'(@'style:font-name'=Name), _).
  500style_property(name(Name), DOM) :-
  501	xpath(DOM, /'style:style'(@'style:name'=Name), _).
  502style_property(font_size(Size), DOM) :-
  503	xpath(DOM, 'style:text-properties'(@'fo:font-size'=Size0), _),
  504	convert_size(Size0, Size).
  505style_property(column_width(Size), DOM) :-
  506	xpath(DOM, 'style:table-column-properties'(@'style:column-width'=Size0), _),
  507	convert_size(Size0, Size).
  508style_property(cell_color(Color), DOM) :-
  509	xpath(DOM, 'style:table-cell-properties'(@'fo:background-color'=Color),_),
  510	Color \== transparent.
  511
  512convert_size(Atom, Term) :-
  513	size_suffix(Suffix),
  514	atom_concat(NumA, Suffix, Atom),
  515	atom_number(NumA, Num), !,
  516	Term =.. [Suffix,Num].
  517convert_size(Atom, Atom) :-
  518	ods_warning(unknown_size(Atom)).
  519
  520size_suffix(pt).
  521size_suffix(cm).
  522size_suffix(mm).
  523
  524		 /*******************************
  525		 *	      FORMULAS		*
  526		 *******************************/
 compile_formula(OfficeFormula, Table, Formula) is det
Compile a formula into a Prolog expression. Cells are of the form cell(X,Y).
See also
- http://en.wikipedia.org/wiki/OpenFormula
- http://docs.oasis-open.org/office/v1.2/OpenDocument-v1.2-part2.html
  536compile_formula(Text, Table, Formula) :-
  537	atom_codes(Text, Codes),
  538	phrase(formula(Formula, Table), Codes), !.
  539
  540formula(Formula, Table) -->
  541	"of:=",
  542	expression(Formula, 1200, _, Table).
  543
  544expression(Expr, Pri, RPri, Table) -->
  545	blanks,
  546	(   ods_number(Expr0)
  547	;   ods_string(Expr0)
  548%	;   ods_array(Expr0)
  549	;   ods_prefix_func(Expr0, Pri, RPri0, Table)
  550	;   "(", expression(Expr0, 1200, _, Table), ")"
  551	;   ods_function_call(Expr0, Table)
  552	;   ods_reference(Expr0, Table)
  553%	;   ods_quoted_label(Expr0)
  554%	;   ods_automatic_intersection(Expr0)
  555%	;   ods_named_expression(Expr0)
  556%	;   ods_error(Expr0)
  557	), blanks, !,
  558	{ var(RPri0) -> RPri0 = 0 ; true },
  559	ods_op_func(Expr0, Pri, RPri0, RPri, Expr, Table).
  560
  561ods_prefix_func(Expr, Pri, OpPri, Table) -->
  562	ods_op(Op, prefix(OpPri, ArgPri)),
  563	{ OpPri =< Pri },
  564	expression(Expr0, ArgPri, _, Table),
  565	{ Expr =.. [Op,Expr0] }.
 ods_op_func(+LeftExpr, +MaxPri, +LeftExprPri, -Expr) is semidet
  569ods_op_func(Left, Pri, PriL, RPri, Expr, Table) -->
  570	ods_op(Op, infix(OpPri, LeftPri, RightPri)),
  571	{ PriL =< LeftPri, OpPri =< Pri },
  572	expression(Right, RightPri, _, Table),
  573	{ Expr1 =.. [Op,Left,Right] },
  574	ods_op_func(Expr1, Pri, OpPri, RPri, Expr, Table).
  575ods_op_func(Left, Pri, PriL, RPri, Expr, Table) -->
  576	ods_op(Op, postfix(OpPri, LeftPri)),
  577	{ PriL =< LeftPri, OpPri =< Pri },
  578	{ Expr1 =.. [Op,Left] },
  579	ods_op_func(Expr1, Pri, OpPri, RPri, Expr, Table).
  580ods_op_func(Expr, _, Pri, Pri, Expr, _) -->
  581	"".
  582
  583ods_op(Op, Type) -->
  584	ods_op(Op),
  585	{ ods_op(Op, Type) }.
  586
  587ods_op(':') --> ":".
  588ods_op('!') --> "!".
  589ods_op('~') --> "~".
  590ods_op('+') --> "+".
  591ods_op('-') --> "-".
  592ods_op('%') --> "%".
  593ods_op('^') --> "^".
  594ods_op('*') --> "*".
  595ods_op('/') --> "/".
  596ods_op('&') --> "&".
  597ods_op('=') --> "=".
  598ods_op('<>') --> "<>".
  599ods_op('<=') --> "<=".
  600ods_op('<') --> "<".
  601ods_op('>=') --> ">=".
  602ods_op('>') --> ">".
  603
  604ods_op(':', infix(10, 10, 9)).
  605ods_op('!', infix(20, 20, 19)).
  606ods_op('~', infix(30, 30, 29)).
  607ods_op('+', prefix(40, 40)).
  608ods_op('-', prefix(40, 40)).
  609ods_op('%', postfix(50, 50)).
  610ods_op('^', infix(60, 60, 59)).
  611ods_op('*', infix(70, 70, 69)).
  612ods_op('/', infix(70, 70, 69)).
  613ods_op('+', infix(80, 80, 79)).
  614ods_op('-', infix(80, 80, 79)).
  615ods_op('&', infix(90, 90, 89)).
  616ods_op('=', infix(100, 100, 99)).
  617ods_op('<>', infix(100, 100, 99)).
  618ods_op('<', infix(100, 100, 99)).
  619ods_op('<=', infix(100, 100, 99)).
  620ods_op('>', infix(100, 100, 99)).
  621ods_op('>=', infix(100, 100, 99)).
 ods_number(-Number)// is semidet
Deal with numbers that start with . instead of 0.
  627ods_number(N) -->
  628	number(N), !.
  629ods_number(N) -->
  630	dot,
  631	digit(DF0),
  632	digits(DF),
  633	{ F = [0'0, 0'., DF0|DF] },
  634	(   exp
  635	->  int_codes(DI),
  636	    {E=[0'e|DI]}
  637	;   {E = ""}
  638	),
  639	{ append([F, E], Codes),
  640	  number_codes(N, Codes)
  641	}.
  642
  643int_codes([C,D0|D]) -->
  644	sign(C), !,
  645	digit(D0),
  646	digits(D).
  647int_codes([D0|D]) -->
  648	digit(D0),
  649	digits(D).
  650
  651sign(0'-) --> "-".
  652sign(0'+) --> "+".
  653
  654dot --> ".".
  655
  656exp --> "e".
  657exp --> "E".
 ods_string(-Atom)//
  661ods_string(String) -->
  662	"\"", str_codes(Codes), "\"",
  663	{ atom_codes(String, Codes) }.
  664
  665str_codes([H|T]) -->
  666	str_code(H), !,
  667	str_codes(T).
  668str_codes([]) -->
  669	"".
  670
  671str_code(0'") --> "\"\"", !.
  672str_code(C) --> [C], { C \== 0'" }.
 ods_function_call(Expr0)// is semidet
  676ods_function_call(eval(Expr), Table) -->
  677	function_name(Name),
  678	blanks, "(", parameter_list(Args, Table),
  679	{ Expr =.. [Name|Args] }.
  680
  681parameter_list([], _) -->
  682	")", !.
  683parameter_list([H|T], Table) -->
  684	expression(H, 1200, _, Table), !, blanks,
  685	(   ";"
  686	->  blanks,
  687	    parameter_list(T, Table)
  688	;   ")"
  689	->  { T = [] }
  690	).
  691
  692function_name(Name) -->
  693	letter_xml(C0),
  694	function_name_codes(C),
  695	{ atom_codes(Name, [C0|C]) }.
  696
  697function_name_codes([H|T]) -->
  698	function_name_code(H), !,
  699	function_name_codes(T).
  700function_name_codes([]) --> "".
  701
  702function_name_code(C) -->
  703	[C],
  704	{ xml_basechar(C)
  705	; xml_digit(C)
  706	; C == 0'_
  707	; C == 0'.
  708	; xml_ideographic(C)
  709	; xml_combining_char(C)
  710	}, !.
  711
  712
  713letter_xml(C) --> [C], { xml_basechar(C) ;
  714			 xml_ideographic(C)
  715		       }, !.
 ods_reference(Expr0, Table)
  719ods_reference(Expr, Table) -->
  720	"[", reference(Expr, Table), "]", !.
  721
  722reference(ext(IRI, Range), Table) -->
  723	"'", !, string(Codes), "'#",
  724	{ atom_codes(IRI0, Codes),
  725	  fixup_reference(IRI0, IRI)
  726	},
  727	range_address(Range, Table).
  728reference(Range, Table) -->
  729	range_address(Range, Table).
  730reference(#('REF!'), _) -->
  731	"#REF!".
  732
  733:- dynamic
  734	fixed_up/2.  735
  736fixup_reference(IRI0, IRI) :-
  737	fixed_up(IRI0, IRI), !.
  738fixup_reference(IRI0, IRI) :-
  739	uri_file_name(IRI0, File),
  740	(   access_file(File, read)
  741	->  IRI = IRI0
  742	;   file_base_name(File, Base),
  743	    file_name_extension(Plain, _, Base),
  744	    file_name_extension(Plain, ods, Local),
  745	    access_file(Local, read)
  746	->  uri_file_name(IRI, Local),
  747	    print_message(informational, ods(updated_ext(IRI0, IRI)))
  748	;   print_message(warning, ods(no_ext(IRI0))),
  749	    IRI = IRI0
  750	),
  751	assertz(fixed_up(IRI0, IRI)).
  752
  753clean_fixup :-
  754	retractall(fixed_up(_,_)).
 range_address(-Ref, +DefaultTable)
  758range_address(Ref, Table) -->
  759	sheet_locator_or_empty(Sheet, Table),
  760	".",
  761	(   cell(SX,SY)
  762	->  (   ":."
  763	    ->  cell(EX,EY),
  764		{ Ref = cell_range(Sheet, SX, SY, EX, EY) }
  765	    ;   { Ref = cell(Sheet, SX, SY) }
  766	    )
  767	;   column(Start)
  768	->  ":.",
  769	    column(End),
  770	    { Ref = col_range(Sheet, Start, End) }
  771	;   row(Start)
  772	->  ":.",
  773	    row(End),
  774	    { Ref = row_range(Sheet, Start, End) }
  775	).
  776range_address(Ref, _Table) -->
  777	sheet_locator(Sheet),
  778	".",
  779	(   cell(SX, SY)
  780	->  ":",
  781	    sheet_locator(Sheet2), cell(EX, EY),
  782	    { Ref = xcell_range(Sheet, SX, SY, Sheet2, EX, EY) }
  783	;   column(Start)
  784	->  ":",
  785	    sheet_locator(Sheet2), column(End),
  786	    { Ref = xcol_range(Sheet, Start, Sheet2, End) }
  787	;   row(Start)
  788	->  ":",
  789	    sheet_locator(Sheet2), row(End),
  790	    { Ref = xrow_range(Sheet, Start, Sheet2, End) }
  791	).
  792
  793sheet_locator_or_empty(Sheet, _) -->
  794	sheet_locator(Sheet).
  795sheet_locator_or_empty(Table, Table) --> "".
  796
  797sheet_locator(Sheet) -->
  798	sheet_name(Name),
  799	subtable_path(Name, Sheet).
  800
  801subtable_path(Name, Locator) -->
  802	".",
  803	subtable_cell(One),
  804	{ Path0 = Name/One },
  805	subtable_path(Path0, Locator).
  806subtable_path(Path, Path) --> "".
  807
  808subtable_cell(Cell) -->
  809	cell(Cell), !.
  810subtable_cell(Sheet) -->
  811	sheet_name(Sheet).
  812
  813sheet_name(Name) -->
  814	( "$" ->  "" ; "" ),
  815	(   single_quoted(Name)
  816	;   sheet_name_code(C0),
  817	    sheet_name_codes(Codes)
  818	->  { atom_codes(Name, [C0|Codes]) }
  819	).
  820
  821cell(cell(X,Y)) -->
  822	column(X),
  823	row(Y).
  824
  825cell(X, Y) -->
  826	column(X),
  827	row(Y).
  828
  829column(Col) -->
  830	( "$" ->  "" ; "" ),
  831	coln(0, Col).
  832
  833coln(C0, C) -->
  834	[D],
  835	{ between(0'A, 0'Z, D), !,
  836	  C1 is C0*26+D-0'A+1
  837	},
  838	coln(C1, C).
  839coln(C, C) --> "".
  840
  841row(Row) -->
  842	( "$" ->  "" ; "" ),
  843	rown(0, Row).
  844
  845rown(R0, R) -->
  846	[D],
  847	{ between(0'0, 0'9, D), !,
  848	  R1 is R0*10+D-0'0
  849	},
  850	rown(R1, R).
  851rown(R, R) --> "".
 single_quoted(-Atom)
  856single_quoted(String) -->
  857	"'", sq_codes(Codes), "'",
  858	{ atom_codes(String, Codes) }.
  859
  860sq_codes([H|T]) -->
  861	sq_code(H), !,
  862	sq_codes(T).
  863sq_codes([]) -->
  864	"".
  865
  866sq_code(0'\') --> "''", !.
  867sq_code(C) --> [C], { C \== 0'\' }.
  868
  869sheet_name_codes([H|T]) -->
  870	sheet_name_code(H), !,
  871	sheet_name_codes(T).
  872sheet_name_codes([]) --> "".
  873
  874sheet_name_code(C) -->
  875	[C],
  876	{ \+ not_in_sheet_name(C) }.
  877
  878not_in_sheet_name(0']).
  879not_in_sheet_name(0'.).
  880not_in_sheet_name(0'\s).
  881not_in_sheet_name(0'#).
  882not_in_sheet_name(0'$).
 sheet_name_need_quotes(+Name) is semidet
True when Name is a sheet name that needs (single) quotes.
  888sheet_name_need_quotes(Name) :-
  889	atom_codes(Name, Codes),
  890	member(Code, Codes),
  891	not_in_sheet_name(Code), !.
  892
  893
  894		 /*******************************
  895		 *	 CELL PROPERTIES	*
  896		 *******************************/
 cell_value(:Sheet, ?X, ?Y, ?Value)
True when cell X,Y in Sheet has Value.
  902cell_value(Module:Sheet, X, Y, Value) :-
  903	(   ground(cell(Sheet,X,Y))
  904	->  cell_id(X,Y,Id),
  905	    once(Module:cell(Sheet, Id, Value, _, _, _, _))
  906	;   Module:cell(Sheet, Id, Value, _, _, _, _),
  907	    cell_id(X,Y,Id)
  908	),
  909	Value \== @empty.
 cell_type(:Sheet, ?X, ?Y, ?Type)
True when cell X,Y in Sheet has Type.
  915cell_type(Module:Sheet, X, Y, Type) :-
  916	(   ground(cell(Sheet,X,Y))
  917	->  cell_id(X,Y,Id),
  918	    once(Module:cell(Sheet, Id, _, Type, _, _, _))
  919	;   Module:cell(Sheet, Id, _, Type, _, _, _),
  920	    cell_id(X,Y,Id)
  921	).
 cell_formula(:Sheet, ?X, ?Y, ?Formula)
True when cell X,Y in Sheet has Formula.
  927cell_formula(Module:Sheet, X, Y, Formula) :-
  928	(   ground(cell(Sheet,X,Y))
  929	->  cell_id(X,Y,Id),
  930	    once(Module:cell(Sheet, Id, _, _, Formula, _, _))
  931	;   Module:cell(Sheet, Id, _, _, Formula, _, _),
  932	    cell_id(X,Y,Id)
  933	),
  934	Formula \== (-).
 cell_eval(:Sheet, ?X, ?Y, ?Value)
True when the formula of cell X,Y in Sheet evaluates to Value
  940cell_eval(Sheet, X, Y, Value) :-
  941	cell_formula(Sheet, X, Y, Formula),
  942	cell_type(Sheet, X, Y, Type),
  943	Sheet = Module:_,
  944	ods_eval_typed(Formula, Type, Value, Module).
 cell_style(:Sheet, ?X, ?Y, ?Style)
True when cell X,Y in Sheet has style property Style. See ods_style_property/2 for supported styles.
  951cell_style(Sheet, X, Y, Property) :-
  952	nonvar(Property), !,
  953	style_property_level(Property, Where),
  954	cell_style(Where, Sheet, X, Y, Property).
  955cell_style(Sheet, X, Y, Property) :-
  956	cell_style(_, Sheet, X, Y, Property).
  957
  958cell_style(cell, Module:Sheet, X, Y, Property) :-
  959	(   ground(cell(Sheet,X,Y))
  960	->  cell_id(X,Y,Id),
  961	    once(Module:cell(Sheet, Id, _, _, _, Style, _))
  962	;   Module:cell(Sheet, Id, _, _, _, Style, _),
  963	    cell_id(X,Y,Id)
  964	),
  965	ods_style_property(Module:Style, Property).
  966cell_style(column, Module:Sheet, Col, _, Property) :-
  967	(   ground(cell(Sheet,Col))
  968	->  column_id(Col, X),
  969	    once(Module:col(Sheet, X, Style))
  970	;   Module:col(Sheet, Col, Style)
  971	),
  972	ods_style_property(Module:Style, Property).
  973
  974column_id(Col, X) :-
  975	(   integer(Col)
  976	->  X = Col
  977	;   upcase_atom(Col, Up),
  978	    column_name(X, Up)
  979	).
  980
  981style_property_level(column_width(_),	column).
  982style_property_level(font_weight(_),	cell).
  983style_property_level(font_name(_),	cell).
  984style_property_level(font_size(_),	cell).
  985style_property_level(cell_color(_),	cell).
  986style_property_level(name(_),		cell).
 cell(:Sheet, ?X, ?Y, ?Value, ?Type, ?Formula, ?Style, ?Annotations)
Query raw cells.
  992cell(M:Sheet, X, Y, Value, Type, Formula, Style, Annot) :-
  993	(   ground(cell(Sheet,X,Y))
  994	->  cell_id(X,Y,Id),
  995	    once(M:cell(Sheet, Id, Value, Type, Formula, Style, Annot))
  996        ;   M:cell(Sheet, Id, Value, Type, Formula, Style, Annot),
  997	    cell_id(X,Y,Id)
  998	).
  999
 1000
 1001		 /*******************************
 1002		 *    EXPRESSION EVALUATION	*
 1003		 *******************************/
 ods_eval(:Expression, -Value) is det
Evaluate an expression.
 1009ods_eval(Module:Expression, Value) :-
 1010	ods_eval(Expression, Value, Module).
 1011
 1012ods_eval(cell(Sheet,X,Y), Value, Module) :- !,
 1013	cell_value(Sheet,X,Y, _Type, Value, Module).
 1014ods_eval(cell_range(Sheet, SX,SY, EX,EY), List, M) :- !,
 1015	(   SX =:= EX
 1016	->  col_array(Sheet, SX, SY, EY, List, M)
 1017	;   SY =:= EY
 1018	->  row_array(Sheet, SY, SX, EX, List, M)
 1019	;   array(Sheet, SX,SY, EX,EY, List, M)
 1020	).
 1021ods_eval(Ref1:Ref2, Value, Module) :- !,
 1022	eval_reference(Ref1, cell(S,SX,SY), Module),
 1023	eval_reference(Ref2, cell(S,EX,EY), Module),
 1024	ods_eval(cell_range(S,SX,SY,EX,EY), Value, Module).
 1025ods_eval(ext(URL, Ref), Value, _Module) :- !,
 1026	(   ods_ensure_loaded(URL, MExt)
 1027	->  ods_eval(Ref, Value, MExt)
 1028	;   ods_warning(no_ext(URL)),
 1029	    Value = #('REF!')
 1030	).
 1031ods_eval(eval(Expr), Value, M) :- !,
 1032	eval_function(Expr, Value, M).
 1033ods_eval(A+B, Value, M) :- !,
 1034	ods_eval_typed(A, number, VA, M),
 1035	ods_eval_typed(B, number, VB, M),
 1036	Value is VA+VB.
 1037ods_eval(A-B, Value, M) :- !,
 1038	ods_eval_typed(A, number, VA, M),
 1039	ods_eval_typed(B, number, VB, M),
 1040	Value is VA-VB.
 1041ods_eval(A*B, Value, M) :- !,
 1042	ods_eval_typed(A, number, VA, M),
 1043	ods_eval_typed(B, number, VB, M),
 1044	Value is VA*VB.
 1045ods_eval(A/B, Value, M) :- !,
 1046	ods_eval_typed(A, number, VA, M),
 1047	ods_eval_typed(B, number, VB, M),
 1048	(   VB =:= 0
 1049	->  Value = #('DIV/0!')
 1050	;   Value is VA/VB
 1051	).
 1052ods_eval(-A, Value, M) :- !,
 1053	ods_eval_typed(A, number, VA, M),
 1054	Value is -VA.
 1055ods_eval(+A, Value, M) :- !,
 1056	ods_eval_typed(A, number, Value, M).
 1057ods_eval(A=B, Value, M) :- !,
 1058	ods_eval(A, VA, M),
 1059	ods_eval(B, VB, M),
 1060	(   ods_equal(VA, VB)
 1061	->  Value = @true
 1062	;   Value = @false
 1063	).
 1064ods_eval(A>B, Value, M) :- !,		% compare numbers, text, boolean
 1065	ods_eval(A, VA, M),		% different types: undefined.
 1066	ods_eval(B, VB, M),
 1067	(   VA @> VB
 1068	->  Value = @true
 1069	;   Value = @false
 1070	).
 1071ods_eval(A>=B, Value, M) :- !,
 1072	ods_eval(A, VA, M),
 1073	ods_eval(B, VB, M),
 1074	(   VA @>= VB
 1075	->  Value = @true
 1076	;   Value = @false
 1077	).
 1078ods_eval(A<B, Value, M) :- !,
 1079	ods_eval(A, VA, M),
 1080	ods_eval(B, VB, M),
 1081	(   VA @< VB
 1082	->  Value = @true
 1083	;   Value = @false
 1084	).
 1085ods_eval('<='(A,B), Value, M) :- !,
 1086	ods_eval(A, VA, M),
 1087	ods_eval(B, VB, M),
 1088	(   VA @=< VB
 1089	->  Value = @true
 1090	;   Value = @false
 1091	).
 1092ods_eval('%'(A), Value, M) :- !,
 1093	ods_eval(A, VA, M),
 1094	(   VA >= 0, VA =< 100
 1095	->  Value is VA/100.0
 1096	;   domain_error(percentage, VA)
 1097	).
 1098ods_eval(#(Error), #(Error), _) :- !.
 1099ods_eval(X, X, _).
 1100
 1101ods_eval_typed(cell(Sheet, X, Y), Type, Value, M) :- !,
 1102	cell_value(Sheet,X,Y, Type, Value, M).
 1103ods_eval_typed(Expr, Type, Value, M) :-
 1104	ods_eval(Expr, Value0, M),
 1105	type_convert(Type, Value0, Value).
 1106
 1107cell_value(Sheet,X,Y, Type, Value, M) :-
 1108	(   cell_id(X,Y,Id),
 1109	    M:cell(Sheet, Id, Value0, _Type, _, _, _)
 1110	->  type_convert(Type, Value0, Value)
 1111	;   no_cell(Sheet,X,Y),
 1112	    type_default(Type, Value0)
 1113	->  Value = Value0
 1114	).
 eval_reference(+Spec, -Ref, +Module)
Evaluate an expression to a reference.
 1120eval_reference(Ref, Ref, _) :-
 1121	is_reference(Ref), !.
 1122eval_reference(eval('OFFSET'(Ref0, OXExpr, OYExpr)), Ref, M) :-
 1123	ods_eval_typed(OXExpr, integer, OX, M),
 1124	ods_eval_typed(OYExpr, integer, OY, M),
 1125	offset_reference(Ref0, OX, OY, Ref).
 1126
 1127is_reference(#(_)).
 1128is_reference(cell(_,_,_)).
 1129is_reference(cell_range(_,_,_,_,_)).
 offset_reference(+Ref0, +OX, +OY, -Ref)
 1133offset_reference(cell(S,X0,Y0), OffX, OffY, cell(S,X,Y)) :- !,
 1134	X is X0 + OffX,
 1135	Y is Y0 + OffY.
 1136offset_reference(cell_range(S,SX0,SY0,EX0,EY0), OffX, OffY,
 1137		 cell_range(S,SX,SY,EX,EY)) :- !,
 1138	SX is SX0 + OffX,
 1139	SY is SY0 + OffY,
 1140	EX is EX0 + OffX,
 1141	EY is EY0 + OffY.
 1142offset_reference(_, _, _, #('REF!')).
 col_array(+Sheet, +X, +SY, +EY, -Array, +Module) is det
Produce an array of values for a column, represented as a list.
 1148col_array(Sheet, X, Y0, Y, [V0|VL], M) :-
 1149	Y0 =< Y, !,
 1150	cell_id(X,Y0,Id),
 1151	(   M:cell(Sheet, Id, V0, _Type, _, _, _)
 1152	->  true
 1153	;   V0 = @empty
 1154	),
 1155	Y1 is Y0+1,
 1156	col_array(Sheet, X, Y1, Y, VL, M).
 1157col_array(_, _, _, _, [], _).
 row_array(+Sheet, +Y, +SX, +EX, -Array, +Module) is det
Produce an array of values for a row, represented as a list.
 1164row_array(Sheet, Y, X0, X, [V0|VL], M) :-
 1165	X0 =< X, !,
 1166	cell_id(X0,Y,Id),
 1167	(   M:cell(Sheet, Id, V0, _Type, _, _, _)
 1168	->  true
 1169	;   V0 = @empty
 1170	),
 1171	X1 is X0+1,
 1172	row_array(Sheet, Y, X1, X, VL, M).
 1173row_array(_, _, _, _, [], _).
 array(+Sheet, +SX, +SY, +EX, +EY, -Array, +Module) is det
Array is a two-dimenional list of values in the range SXSY:EXEY.
 1179array(Sheet, SX, Y0, EX, Y, [R1|RL], Module) :-
 1180	Y0 =< Y, !,
 1181	row_array(Sheet, Y0, SX, EX, R1, Module),
 1182	Y1 is Y0+1,
 1183	array(Sheet, SX, Y1, EX, Y, RL, Module).
 1184array(_, _, _, _, _, [], _).
 eval_function(+FunctionTerm, -Value, +Module)
 1190eval_function('IF'(Cond, Then, Else), Value, M) :- !,
 1191	ods_eval(Cond, VC, M),
 1192	(   VC == @true
 1193	->  ods_eval(Then, Value, M)
 1194	;   ods_eval(Else, Value, M)
 1195	).
 1196eval_function('VLOOKUP'(VExpr, DataSource, ColExpr), Value, M) :- !,
 1197	ods_eval(VExpr, V, M),
 1198	(   DataSource = cell_range(Sheet, SX,SY, EX,EY),
 1199	    ods_eval_typed(ColExpr, integer, Column, M),
 1200	    Column \= #(_),
 1201	    TX is SX+Column-1,
 1202	    TX =< EX
 1203	->  (   bisect(range_vtest(V, Sheet, SX), SY, EY, TY)
 1204	    ->	cell_value(Sheet, TX, TY, Value)
 1205	    ;	Value = #('N/A')
 1206	    )
 1207	;   print_message(error, ods(invalid_vlookup)),
 1208	    Value = #('N/A')
 1209	).
 1210eval_function('VLOOKUP'(VExpr, DataSource, ColExpr, Sorted), Value, M) :- !,
 1211	(   ods_eval(Sorted, @false, M)
 1212	->  ods_eval(VExpr, V, M),
 1213	    (	DataSource = cell_range(Sheet, SX,SY, EX,EY)
 1214	    ->	(   ods_eval_typed(ColExpr, integer, Column, M),
 1215		    TX is SX+Column-1,
 1216		    TX =< EX,		% TBD: range error
 1217		    between(SY, EY, Y),
 1218		    cell_value(Sheet, SX, Y, V)
 1219		->  cell_value(Sheet, TX, Y, Value)
 1220		;   Value = #('N/A')
 1221		)
 1222	    ;	print_message(error, ods(unsupported_datasource, DataSource)),
 1223		Value = #('N/A')
 1224	    )
 1225	;   eval_function('VLOOKUP'(VExpr, DataSource, ColExpr), Value, M)
 1226	).
 1227eval_function('HLOOKUP'(VExpr, DataSource, RowExpr), Value, M) :- !,
 1228	ods_eval(VExpr, V, M),
 1229	(   DataSource = cell_range(Sheet, SX,SY, EX,EY),
 1230	    ods_eval_typed(RowExpr, integer, Row, M),
 1231	    Row \= #(_),
 1232	    TY is SY+Row-1,
 1233	    TY =< EY
 1234	->  (   bisect(range_vtest(V, Sheet, SY), SX, EX, TX)
 1235	    ->	cell_value(Sheet, TX, TY, Value)
 1236	    ;	Value = #('N/A')
 1237	    )
 1238	;   print_message(error, ods(invalid_vlookup)),
 1239	    Value = #('N/A')
 1240	).
 1241eval_function('HLOOKUP'(VExpr, DataSource, ColExpr, Sorted), Value, M) :- !,
 1242	(   ods_eval(Sorted, @false, M)
 1243	->  ods_eval(VExpr, V, M),
 1244	    (	DataSource = cell_range(Sheet, SX,SY, EX,EY)
 1245	    ->	(   ods_eval_typed(ColExpr, integer, Column, M),
 1246		    TY is SY+Column-1,
 1247		    TY =< EY,		% TBD: range error
 1248		    between(SX, EX, X),
 1249		    cell_value(Sheet, X, SY, V)
 1250		->  cell_value(Sheet, X, TY, Value)
 1251		;   Value = #('N/A')
 1252		)
 1253	    ;	print_message(error, ods(unsupported_datasource, DataSource)),
 1254		Value = #('N/A')
 1255	    )
 1256	;   eval_function('HLOOKUP'(VExpr, DataSource, ColExpr), Value, M)
 1257	).
 1258eval_function('MATCH'(VExpr, Values), Value, M) :- !,
 1259	eval_function('MATCH'(VExpr, Values, 1), Value, M).
 1260eval_function('MATCH'(VExpr, ValuesExpr, How), Value, M) :- !,
 1261	ods_eval(VExpr, Target, M),
 1262	ods_eval(ValuesExpr, Values),
 1263	(   \+ is_list(Values)
 1264	->  Value = #('N/A')
 1265	;   How =:= 1
 1266	->  (   Values = [H|_],
 1267	        ods_before(Target, H)
 1268	    ->	Value = #('N/A')
 1269	    ;	nth1(Index, Values, V),
 1270		ods_before(V, Target)
 1271	    ->	Value is Index-1
 1272	    ;	length(Values, Value)
 1273	    )
 1274	;   How =:= 0
 1275	->  (   nth1(Index, Values, Target)
 1276	    ->	Value = Index
 1277	    ;	Value = #('N/A')
 1278	    )
 1279	;   How =:= -1
 1280	->  (   Values = [H|_],
 1281	        ods_before(H, Target)
 1282	    ->	Value = #('N/A')
 1283	    ;	nth1(Index, Values, V),
 1284		ods_before(Target, V)
 1285	    ->	Value is Index-1
 1286	    ;	length(Values, Value)
 1287	    )
 1288	;   Value = #('N/A')
 1289	).
 1290eval_function('ISBLANK'(Expr), Value, M) :- !,
 1291	(   Expr = cell(Sheet,X,Y)
 1292	->  cell_id(X,Y,Id),
 1293	    (	M:cell(Sheet, Id, CellValue, _Type, _, _, _),
 1294		CellValue \== @empty
 1295	    ->	Value = @false
 1296	    ;	Value = @true
 1297	    )
 1298	;   Expr = #('REF!')		% Error reference
 1299	->  Value = @true
 1300	;   Value = @false
 1301	).
 1302eval_function('COUNTIF'(In, &(Op,To)), Value, M) :- !,
 1303	range_goal(In, V, Goal, M),	% TBD: What about &?
 1304	ods_eval(To, VTo),		% TBD: Comparison to empty cells
 1305	Func =.. [Op,V,VTo],
 1306	same_type_condition(VTo, V, TypeCond),
 1307	aggregate_all(count,
 1308		      ( Goal, TypeCond,
 1309			ods_eval(Func, @true, M)
 1310		      ),
 1311		      Value).
 1312eval_function(Expr, Value, M) :-
 1313	Expr =.. [Func|ArgExprs],
 1314	maplist(ods_evalm(M), ArgExprs, Args),
 1315	(   eval_varargs(Func, Args, Value)
 1316	->  true
 1317	;   Expr1 =.. [Func|Args],
 1318	    (   eval(Expr1, Value)
 1319	    ->  true
 1320	    ;   ods_error(eval(Expr1)),
 1321		Value = #('N/A')
 1322	    )
 1323	).
 1324
 1325ods_evalm(M, Expr, Value) :-
 1326	ods_eval(Expr, Value, M).
 eval(+Expr, -Value) is det
 1330eval('SUM'(List), Value) :-
 1331	ods_sum_list(List, Value).
 1332eval('AVERAGE'(List), Value) :-
 1333	length(List, Len),		% should length include @empty?
 1334	(   Len > 0
 1335	->  ods_sum_list(List, Sum),
 1336	    Value is Sum/Len
 1337	;   Value = #('N/A')
 1338	).
 1339eval('RANK'(V, List), Rank) :-
 1340	msort(List, Sorted),
 1341	reverse(Sorted, Descending),
 1342	(   nth1(Rank, Descending, V)
 1343	->  true
 1344	;   Rank = #('N/A')
 1345	).
 1346eval('RANK'(V, List, Order), Rank) :-
 1347	(   Order =:= 0
 1348	->  eval('RANK'(V, List), Rank)
 1349	;   msort(List, Ascending),
 1350	    nth1(Rank, Ascending, V)
 1351	->  true
 1352	;   Rank = #('N/A')
 1353	).
 1354eval('ISERROR'(T), True) :-
 1355	(   T = #(_)
 1356	->  True = @true
 1357	;   True = @false
 1358	).
 1359eval('PMT'(Rate, Nper, Pv, Fv, PayType), Value) :-
 1360	pmt(Rate, Nper, Pv, Fv, PayType, Value).
 1361eval('PMT'(Rate, Nper, Pv, Fv), Value) :-
 1362	pmt(Rate, Nper, Pv, Fv, 0, Value).
 1363eval('PMT'(Rate, Nper, Pv), Value) :-
 1364	pmt(Rate, Nper, Pv, 0, 0, Value).
 1365eval('ROUND'(Float), Value) :-
 1366	Value is round(Float).
 1367eval('ROUND'(Float, Digits), Value) :-
 1368	(   Digits =:= 0
 1369	->  Value is round(Float)
 1370	;   Digits > 0
 1371	->  Mult is 10^integer(Digits),
 1372	    Value is round(Float*Mult)/Mult
 1373	;   Div is 10^(-integer(Digits)),
 1374	    Value is round(Float/Div)*Div
 1375	).
 1376eval('ROUNDDOWN'(Float), Value) :-
 1377	Value is truncate(Float).
 1378eval('ROUNDDOWN'(Float, Digits), Value) :-
 1379	(   Digits =:= 0
 1380	->  Value is truncate(Float)
 1381	;   Digits > 0
 1382	->  Mult is 10^integer(Digits),
 1383	    Value is truncate(Float*Mult)/Mult
 1384	;   Div is 10^(-integer(Digits)),
 1385	    Value is truncate(Float/Div)*Div
 1386	).
 1387eval('EXP'(Float), Value) :-
 1388	Value is exp(Float).
 1389eval('FALSE', @false).
 1390eval('TRUE', @true).
 eval_varargs(+Func, +Args, -Value) is semidet
 1394eval_varargs('MAX', Args, Value) :-
 1395	(   Args = [List],		% MAX(DataSource)
 1396	    is_list(List)
 1397	->  true
 1398	;   List = Args			% MAX(A;B;...)
 1399	),
 1400	(   List \== []
 1401	->  include(number, List, Numbers),
 1402	    max_list(Numbers, Value)
 1403	;   Value = 0
 1404	).
 1405eval_varargs('MIN', Args, Value) :-
 1406	(   Args = [List],
 1407	    is_list(List)
 1408	->  true
 1409	;   List = Args
 1410	),
 1411	(   List \== []
 1412	->  include(number, List, Numbers),
 1413	    min_list(Numbers, Value)
 1414	;   Value = 0
 1415	).
 1416eval_varargs('CONCATENATE', List, Value) :-
 1417	maplist(normalize_value, List, Normalized),
 1418	atomic_list_concat(Normalized, Value0),
 1419	normalize_space(atom(Value), Value0). % Seems to be used.
 normalize_value(+Raw, -Normalized)
Normalizes floats that happen to be int to integers.
 1425normalize_value(Float, Int) :-
 1426	float(Float),
 1427	float_fractional_part(Float) =:= 0.0, !,
 1428	Int is integer(Float).
 1429normalize_value(Value, Value).
 type_default(+Type, -Default)
 1434type_default(string, '').
 1435type_default(number, 0).
 1436type_default(float, 0.0).
 1437type_default(integer, 0).
 type_convert(+Type, +V0, -V)
 1441type_convert(Type, V0, V) :-
 1442	var(Type), !,
 1443	V = V0.
 1444type_convert(_, #(Error), #(Error)) :- !.
 1445type_convert(number, V0, V) :-
 1446	(   number(V0)
 1447	->  V = V0
 1448	;   ods_warning(convert(number, V0)),
 1449	    (	V0 == ''
 1450	    ->	V = 0.0
 1451	    ;	atom_number(V0, V)
 1452	    )
 1453	).
 1454type_convert(float, V0, V) :-
 1455	(   number(V0)
 1456	->  V is float(V0)
 1457	;   ods_warning(convert(number, V0)),
 1458	    (	V0 == ''
 1459	    ->	V = 0.0
 1460	    ;	atom_number(V0, V1),
 1461		V is float(V1)
 1462	    )
 1463	).
 1464type_convert(percentage, V0, V) :-
 1465	type_convert(float, V0, V).
 1466type_convert(integer, V0, V) :-
 1467	(   number(V0)
 1468	->  V is integer(V0)
 1469	;   ods_warning(convert(number, V0)),
 1470	    (	V0 == ''
 1471	    ->	V = 0
 1472	    ;	atom_number(V0, V1),
 1473		V is integer(V1)
 1474	    )
 1475	).
 1476type_convert(string, V0, V) :-
 1477	(   atom(V0)
 1478	->  V = V0
 1479	;   ods_warning(convert(string, V0)),
 1480	    atom_number(V, V0)
 1481	).
 1482
 1483
 1484no_cell(Sheet, X, Y) :-
 1485	ods_warning(no_cell(Sheet,X,Y)).
 range_goal(+Spec, -Goal, +Module) is det
 1489range_goal(cell_range(Sheet, SX,SY, EX,EY), V, Goal, M) :- !,
 1490	(   SX == EX
 1491	->  Goal = ( between(SY,EY,Y),
 1492	             ods_eval_if_exists(cell(Sheet,SX,Y), V, M)
 1493		   )
 1494	;   SY == EY
 1495	->  Goal = ( between(SX,EX,X),
 1496		     ods_eval_if_exists(cell(Sheet,X,SY), V, M)
 1497		   )
 1498	;   ods_warning(eval(cell_range(Sheet, SX,SY, EX,EY))),
 1499	    Goal = fail
 1500	).
 1501range_goal(Expr, _, fail, _) :-
 1502	ods_warning(range_expected(Expr)).
 range_vtest(+Value, +Sheet, +X, +Y) is semidet
True if cell_value(Sheet,X,Y,V) and V is before Value.
 1508range_vtest(Value, Sheet, X, Y) :-
 1509	cell_value(Sheet, X, Y, V2),
 1510	ods_before(V2, Value).
 ods_before(+Value1, +Value2) is semidet
True if Value1 is before Value2 in the spreadsheet order of terms. Meaning numbers < text < logical, @false < @true.
 1517ods_before(@X, @Y) :- !,
 1518	ods_before_special(X,Y).
 1519ods_before(N1, N2) :-
 1520	number(N1), number(N2),
 1521	N1 < N2.
 1522ods_before(V1, V2) :-
 1523	V1 @< V2.			% @<: number < atom < compound
 1524
 1525ods_before_special(false, true).
 ods_equal(+Value1, +Value2) is semidet
True if Value1 and Value2 have the same value.
 1531ods_equal(X, X) :- !.
 1532ods_equal(N1, N2) :-
 1533	number(N1), number(N2), !,
 1534	N1 =:= N2.
 same_type_condition(+Value, +Var, -Goal) is det
True when Goal is a goal that succeeds if Var is of the same type as Value.
 1541same_type_condition(Ref, V, number(V)) :-
 1542	number(Ref), !.
 1543same_type_condition(Ref, V, atom(V)) :-
 1544	atom(Ref), !.
 1545same_type_condition(Ref, _, true) :-
 1546	ods_warning(same_type_condition(Ref)).
 ods_sum_list(+List, -Sum) is det
 1551ods_sum_list(List, Sum) :-
 1552	ods_sum_list(List, 0, Sum).
 1553
 1554ods_sum_list([], Sum, Sum).
 1555ods_sum_list([H|T], Sum0, Sum) :-
 1556	ods_add(H, Sum0, Sum1),
 1557	ods_sum_list(T, Sum1, Sum).
 1558
 1559ods_add(N1, N2, N) :-
 1560	number(N1),
 1561	number(N2), !,
 1562	N is N1 + N2.
 1563ods_add(@empty, Sum, Sum) :- !.
 1564ods_add(_, #(E), #(E)) :- !.
 1565ods_add(#(E), _, #(E)) :- !.
 1566
 1567
 1568		 /*******************************
 1569		 *	       UTIL		*
 1570		 *******************************/
 column_name(?Index, ?Name) is det
Name is the alplanumerical name of column Col. Column 1 is 'A', 26 = 'Z', 27 = 'AA'.
 1578column_name(N, Col) :-
 1579	integer(N), !,
 1580	col_chars(N, Chars, []),
 1581	atom_codes(Col, Chars).
 1582column_name(N, Col) :-
 1583	atom_codes(Col, Codes),
 1584	phrase(column(N), Codes).
 1585
 1586
 1587col_chars(Col, [C|T], T) :-
 1588	Col =< 26, !,
 1589	C is Col+0'A-1.
 1590col_chars(Col, List, T) :-
 1591	High is Col//26,
 1592	Last is (Col mod 26) + 0'A - 1,
 1593	col_chars(High, List, [Last|T]).
 1594
 1595
 1596
 1597		 /*******************************
 1598		 *	      CLEANUP		*
 1599		 *******************************/
 ods_unload
Remove saved facts from the database
 1605:- module_transparent
 1606	ods_unload/0,
 1607	ods_compile/0. 1608
 1609ods_unload :-
 1610	context_module(M),
 1611	clean_fixup,
 1612	retractall(ods_sheet:ods_spreadsheet(_, M)),
 1613	(   predicate_property(M:sheet(_,_), dynamic)
 1614	->  forall(data_predicate(Name/Arity),
 1615		   ( functor(Head, Name, Arity),
 1616		     retractall(M:Head)))
 1617	;   forall(data_predicate(P),
 1618		   abolish(M:P))
 1619	).
 1620
 1621dynamic_decls(M) :-
 1622	forall(data_predicate(P),
 1623	       dynamic(M:P)).
 1624
 1625data_predicate(sheet/2).
 1626data_predicate(col/3).
 1627data_predicate(row/3).
 1628data_predicate(cell/7).
 1629data_predicate(span/2).
 1630data_predicate(style/2).
 ods_unload_all is det
Unload all currently loaded spreadsheets.
 1637ods_unload_all :-
 1638	forall(ods_spreadsheet(_, M),
 1639	       M:ods_unload).
 ods_compile
Lock the spreadsheet predicates as static to make them faster.
 1646ods_compile :-
 1647	context_module(M),
 1648	compile_predicates(M:[ sheet/2,
 1649			       col/3,
 1650			       row/3,
 1651			       cell/7,
 1652			       style/2
 1653			     ]).
 ods_compile_all is det
Compile all loaded spreadsheets
 1659ods_compile_all :-
 1660	forall(ods_spreadsheet(_, M),
 1661	       M:ods_compile).
 ods_current(:URL) is nondet
True when URL is the currently loaded spreadsheet.
 1668ods_current(Module:URL) :-
 1669	ods_spreadsheet(URL, Module).
 1670
 1671
 1672		 /*******************************
 1673		 *	       MESSAGES		*
 1674		 *******************************/
 ods_warning(+Term)
Print message if ods(warnings) topic is enabled
 1680ods_warning(Term) :-
 1681	(   debugging(ods(warnings))
 1682	->  print_message(warning, ods(Term))
 1683	;   true
 1684	).
 1685
 1686ods_error(Term) :-
 1687	print_message(error, ods(Term)).
 1688
 1689
 1690:- multifile
 1691	prolog:message//1. 1692
 1693prolog:message(ods(Msg)) -->
 1694	message(Msg).
 1695
 1696message(updated_ext(IRI0, IRI)) -->
 1697	[ 'Updated external reference:'-[], nl,
 1698	  '   ~w --> ~w'-[IRI0, IRI]
 1699	].
 1700message(no_ext(IRI)) -->
 1701	[ 'Missing external reference: ~q'-[IRI] ].
 1702message(loaded(Module:File, CPU, Sheets, Cells)) -->
 1703	[ 'Loaded ~q into ~q; ~3f sec; ~D cells in ~D sheets'-
 1704	  [File, Module, CPU, Cells, Sheets]
 1705	]