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(recognise,
   35	  [ anchor/2,			% :DataSource, Type
   36	    unassigned_anchor/2,	% :DataSource, ?Type
   37
   38	    block/2,			% :DataSource, Type
   39	    row/2,			% :DataSource, Type
   40	    col/2,			% :DataSource, Type
   41
   42	    row/6,			% :Sheet, SX,SY, EX,SY, Type
   43	    col/6,			% :Sheet, SX,SY, EX,SY, Type
   44	    block/6,			% :Sheet, SX,SY, EX,SY, Type
   45
   46	    cell_class/1,		% ?Class
   47	    cell_class/4,		% :Sheet, ?SX, ?SY, ?Class
   48
   49	    sheet_bb/2			% :Sheet, -DataSource
   50%	    ds_join/2			% +DataSources, -Joined
   51	  ]).
   52:- use_module(sheet).   53:- use_module(datasource).   54:- use_module(data).   55:- use_module(library(apply)).   56:- use_module(library(lists)).   57
   58:- meta_predicate
   59	anchor(:, ?),
   60	unassigned_anchor(:, ?),
   61
   62	block(:,?),
   63	row(:,?),
   64	col(:,?),
   65
   66	block(:,?,?,?,?,?),
   67	row(:,?,?,?,?,?),
   68	col(:,?,?,?,?,?),
   69
   70	cell_class(:, ?, ?, ?),
   71
   72	sheet_bb(:,?).

Inference over spreadsheets

To be done
- Use constraints for types? E.g., allow for float or empty */
 anchor(:DataSource, ?Type) is nondet
True when the top-level of DataSource is an anchor of Type. This implies it is a cell the given Type and the cells left and above it are of different types.

The anchor/2 predicate is used to generate candidates for creating larger units of cells. For example, to generate all blocks of floats, use this:

?- anchor(D, float), once(block(D, float)).
   94anchor(M:cell_range(Sheet, SX,SY, _EX,_EY), Type) :-
   95	cell_class(M:Sheet, SX,SY, Type),
   96	(   SX =:= 0
   97	->  true
   98	;   LX is SX-1,
   99	    cell_class(M:Sheet, LX,SY, TLeft), TLeft \== Type
  100	),
  101	(   SY =:= 0
  102	->  true
  103	;   AY is SY-1,
  104	    cell_class(M:Sheet, SX,AY, TAbove), TAbove \== Type
  105	).
 unassigned_anchor(:DataSource, ?Type) is nondet
  109unassigned_anchor(M:cell_range(Sheet, SX,SY, _EX,_EY), Type) :-
  110	MSheet = M:Sheet,
  111	cell_class(MSheet, SX,SY, Type),
  112	\+ assigned(MSheet, SX,SY),
  113	(   SX =:= 0
  114	->  true
  115	;   LX is SX-1,
  116	    (	cell_class(MSheet, LX,SY, TLeft), TLeft \== Type
  117	    ->	true
  118	    ;	assigned(MSheet, LX,SY)
  119	    )
  120	),
  121	(   SY =:= 0
  122	->  true
  123	;   AY is SY-1,
  124	    (	cell_class(MSheet, SX,AY, TAbove), TAbove \== Type
  125	    ->	true
  126	    ;	assigned(MSheet, SX,AY)
  127	    )
  128	).
  129
  130assigned(Sheet, X, Y) :-
  131	cell_property(Sheet, X, Y, P),
  132	assigned(P).
  133
  134assigned(table(_)).
  135assigned(block(_)).
 block(:DataSource, ?Type) is nondet
  140block(M:cell_range(Sheet, SX,SY, EX,EY), Type) :-
  141	block(M:Sheet, SX,SY, EX,EY, Type).
  142
  143row(M:cell_range(Sheet, SX,SY, EX,EY), Type) :-
  144	row(M:Sheet, SX,SY, EX,EY, Type).
  145
  146col(M:cell_range(Sheet, SX,SY, EX,EY), Type) :-
  147	col(M:Sheet, SX,SY, EX,EY, Type).
 block(?Sheet, ?SX, ?SY, ?EX, ?EY, ?Type) is nondet
A block is the largest rectangular area of cells of the same Type that starts at SX,SY. A block consists minimally of two cells, stacked either horizontally or vertically.
  156block(Sheet, SX,SY, EX,EY, Type) :-
  157	row(Sheet, SX,SY, EX,SY, Type), !,		% dubious cut
  158	block2(Sheet, SX,SY,EX,EY, Type).
  159block(Sheet, SX,SY, EX,EY, Type) :-
  160	col(Sheet, SX,SY, EX,EY, Type).
  161
  162block2(Sheet, SX,SY,EX,EY, Type) :-
  163	(   Y2 is SY+1,
  164	    row(Sheet, SX,Y2, EX,Y2, Type),
  165	    block2(Sheet, SX,Y2,EX,EY, Type)
  166	;   EY=SY
  167	).
  168
  169row(Sheet, SX,SY, EX,SY, Type) :-
  170	cell_class(Sheet, SX,SY, Type),
  171	X2 is SX+1,
  172	row2(Sheet, X2,SY, EX,SY, Type).
  173
  174row2(Sheet, SX,SY, EX,SY, Type) :-
  175	cell_class(Sheet, SX,SY, Type),
  176	X2 is SX+1,
  177	(   row2(Sheet, X2,SY, EX,SY, Type)
  178	;   EX=SX
  179	).
  180
  181
  182col(Sheet, SX,SY, SX,EY, Type) :-
  183	cell_class(Sheet, SX,SY, Type),
  184	Y2 is SY+1,
  185	col2(Sheet, SX,Y2, SX,EY, Type).
  186
  187col2(Sheet, SX,SY, SX,EY, Type) :-
  188	cell_class(Sheet, SX,SY, Type),
  189	Y2 is SY+1,
  190	(   col2(Sheet, SX,Y2, SX,EY, Type)
  191	;   EY=SY
  192	).
  193
  194
  195		 /*******************************
  196		 *	   BLANK PARTS		*
  197		 *******************************/
  198
  199cell_class(float).
  200cell_class(percentage).
  201cell_class(string).
 cell_class(:Sheet, ?X, ?Y, ?Class) is nondet
Classification of cells. Defined classes are:
  214cell_class(Sheet, X,Y, Type) :-
  215	ground(cell(Sheet,X,Y)), !,
  216	(   cell_type(Sheet, X,Y, Type0),
  217	    Type0 \== no_type,
  218	    \+ cell_value(Sheet, X, Y, '')
  219	->  Type = Type0
  220	;   Type = empty
  221	->  sheet_bb(Sheet, SheetDS),
  222	    ds_grow(SheetDS, 1, ExtendedDS),
  223	    ds_inside(ExtendedDS, X, Y),
  224	    empty_cell(Sheet, X,Y)
  225	).
  226cell_class(Sheet, X,Y, Type) :-
  227	Type == empty, !,
  228	sheet_bb(Sheet, SheetDS),
  229	ds_grow(SheetDS, 1, ExtendedDS),
  230	ds_inside(ExtendedDS, X, Y),
  231	empty_cell(Sheet, X,Y).
  232cell_class(Sheet, X,Y, Type) :-
  233	cell_type(Sheet, X,Y, Type).
  234
  235empty_cell(Sheet, X, Y) :-
  236	cell_type(Sheet, X,Y, Type), !,
  237	(   Type == string
  238	->  cell_value(Sheet, X, Y, '')
  239	;   Type == no_type
  240	).
  241empty_cell(_,_,_).
 sheet_bb(:Sheet, ?DS) is nondet
True if DS is a datasource that describes all cells in Sheet. Fails of the sheet is empty.
  250:- dynamic
  251	sheet_bb_cache/6,
  252	sheet_bb_cached/2.  253
  254sheet_bb(M:Sheet, cell_range(Sheet,SX,SY,EX,EY)) :-
  255	M:sheet(Sheet, _),
  256	(   sheet_bb_cached(M, Sheet)
  257	->  sheet_bb_cache(M, Sheet, SX,SY,EX,EY)
  258	;   sheet_bb(M, Sheet, SX0,SY0,EX0,EY0)
  259	->  assertz(sheet_bb_cached(M, Sheet)),
  260	    assertz(sheet_bb_cache(M, Sheet, SX0,SY0,EX0,EY0)),
  261	    SX=SX0, SY=SY0, EX=EX0,EY=EY0
  262	;   assertz(sheet_bb_cached(M, Sheet)), % empty sheet
  263	    fail
  264	).
  265
  266sheet_bb(M, Sheet, SX,SY,EX,EY) :-
  267	M:sheet(Sheet, _),
  268	findall(X-Y, cell_exists(M:Sheet, X,Y), Pairs),
  269	maplist(arg(1), Pairs, AtCol),
  270	min_list(AtCol, SX),
  271	max_list(AtCol, EX),
  272	maplist(arg(2), Pairs, AtRow),
  273	min_list(AtRow, SY),
  274	max_list(AtRow, EY).
  275
  276cell_exists(M:Sheet,X,Y) :-
  277	cell(M:Sheet, X,Y, _,_,_,_,_),
  278	\+ empty_cell(M:Sheet, X, Y).
 ds_join(+DSList, -GroupedDSList) is det
Create larger datasources by grouping adjacent ones.
  284%ds_join(List, List) :-
  285%	tbd.