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(datasource,
   35	  [ ds_sheet/2,			% +DS, -Sheet
   36	    ds_size/3,			% +DS, -Columns, -Rows
   37	    ds_cell_count/2,		% +DS, -Cells
   38	    ds_empty/1,			% +DS
   39	    ds_side/3,			% ?Side, ?DS, ?RowCol
   40	    ds_id/2,			% ?DS, ?Id
   41	    ds_id/3,			% ?DS, ?Id, ?Type
   42
   43	    ds_inside/3,		% +DS, ?X, ?Y
   44	    ds_adjacent/3,		% +DS1, ?Rel, +DS2
   45
   46	    ds_intersection/3,		% +DS1, +DS2, -DS
   47	    ds_union/3,			% +DS1, +DS2, -DS
   48	    ds_union/2,			% +DSList, -DS
   49	    ds_intersections/2,		% +DSList, -Pairs
   50	    ds_subtract/3,		% +Subtract, +From, -DSList
   51	    ds_row_slice/3,		% +DS1, ?Offset, ?Slice
   52	    ds_row_slice/4,		% +DS1, ?Offset, ?Height, ?Slice
   53	    ds_unbounded_row_slice/3,	% +DS1, +Offset, ?Slice
   54	    ds_column_slice/3,		% +DS1, ?Offset, ?Slice
   55	    ds_column_slice/4,		% +DS1, ?Offset, ?Width, ?Slice
   56	    ds_unbounded_column_slice/3,% +DS1, +Offset, ?Slice
   57	    ds_grow/3			% +DS0, +Offset, -DS
   58	  ]).   59:- use_module(sheet).   60:- use_module(library(apply)).

Represent and reason about sheet areas

This module represents rectangular areas in a sheet and can reason about such regions. */

   69		 /*******************************
   70		 *	 SIMPLE PROPERTIES	*
   71		 *******************************/
 ds_sheet(+DS, -Sheet) is det
True when DS is on Sheet.
   77ds_sheet(cell_range(Sheet, _,_, _,_), Sheet).
 ds_size(+DS, -Columns, -Rows) is det
True when Columns and Rows represent the size of a datasource
   83ds_size(cell_range(_Sheet, SX,SY, EX,EY), Columns, Rows) :-
   84	Columns is EX-SX+1,
   85	Rows is EY-SY+1.
 ds_cell_count(+DS, -Count) is det
True when Count is the number of cells in DS.
   91ds_cell_count(cell_range(_Sheet, SX,SY, EX,EY), Cells) :-
   92	Columns is EX-SX+1,
   93	Rows is EY-SY+1,
   94	Cells is Rows*Columns.
 ds_side(?Which, ?DS, ?Value)
True when Value is the row/column of the indicated side of the datasource. Which is one of left, right, top or bottom.
  101ds_side(left,   cell_range(_Sheet, SX,_SY, _EX,_EY), SX).
  102ds_side(right,  cell_range(_Sheet, _SX,_SY, EX,_EY), EX).
  103ds_side(top,    cell_range(_Sheet, _SX,SY, _EX,_EY), SY).
  104ds_side(bottom, cell_range(_Sheet, _SX,_SY, _EX,EY), EY).
 ds_empty(+DS) is semidet
True if DS is empty (contains no cells)
  110ds_empty(cell_range(_Sheet, SX,SY, EX,EY)) :-
  111	(   EX < SX
  112	->  true
  113	;   EY < SY
  114	).
 ds_id(+DS, -ID) is det
ds_id(-DS, +ID) is det
True when ID is an identifier for DS
  121ds_id(DS, Id) :-
  122	ds_id(DS, Id, _).
  123
  124ds_id(DS, Id, Type) :-
  125	ground(DS), !,
  126	DS = cell_range(Sheet, SX,SY, EX,EY),
  127	column_name(SX, SC),
  128	column_name(EX, EC),
  129	(   var(Type)
  130	->  Prefix = ''
  131	;   type_prefix(Type, Prefix)
  132	),
  133	(   sheet_name_need_quotes(Sheet)
  134	->  format(atom(Id), '~w[\'~w\'.~w~w:~w~w]', [Prefix,Sheet,SC,SY,EC,EY])
  135	;   format(atom(Id), '~w[~w.~w~w:~w~w]', [Prefix,Sheet,SC,SY,EC,EY])
  136	).
  137ds_id(DS, Id, Type) :-
  138	type_prefix(Prefix, Type),
  139	sub_atom(Id, 0, 1, _, Prefix),
  140	sub_atom(Id, 1, 1, _, '['),
  141	sub_atom(Id, 1, _, 0, DSID),
  142	atom_codes(DSID, Codes),
  143	phrase(ods_reference(DS, ''), Codes).
  144
  145type_prefix(block, 'B').
  146type_prefix(table, 'T').
  147
  148
  149		 /*******************************
  150		 *	    COORDINATES		*
  151		 *******************************/
 ds_inside(+DS, ?X, ?Y) is nondet
True when X,Y is inside the datasource
  157ds_inside(cell_range(_Sheet, SX,SY, EX,EY), X, Y) :-
  158	between(SY, EY, Y),
  159	between(SX, EX, X).
  160
  161
  162		 /*******************************
  163		 *	 SPATIAL RELATIONS	*
  164		 *******************************/
 ds_adjacent(+DS1, -Rel, +DS2) is semidet
True if DS1 is above, below left_of or right_of DS2.
  170ds_adjacent(cell_range(Sheet, SX1,SY1, EX1,EY1),
  171	    Rel,
  172	    cell_range(Sheet, SX2,SY2, EX2,EY2)) :-
  173	(   range_intersect(SY1,EY1, SY2,EY2, _,_)
  174	->  (   EX1+1 =:= SX2
  175	    ->  Rel = left_of
  176	    ;	EX2+1 =:= SX1
  177	    ->	Rel = right_of
  178	    )
  179	;   range_intersect(SX1,EX1, SX2,EX2, _,_)
  180	->  (   EY1+1 =:= SY2
  181	    ->  Rel = above
  182	    ;	EY2+1 =:= SY1
  183	    ->	Rel = below
  184	    )
  185	).
  186
  187
  188
  189		 /*******************************
  190		 *	     SET LOGIC		*
  191		 *******************************/
 ds_intersection(+DS1, +DS2, -DS) is semidet
True when the intersection of DS1 and DS2 is DS. Fails if the two do not intersect.
  198ds_intersection(cell_range(Sheet, SX1,SY1, EX1,EY1),
  199		cell_range(Sheet, SX2,SY2, EX2,EY2),
  200		cell_range(Sheet, SX,SY, EX,EY)) :-
  201	range_intersect(SX1,EX1, SX2,EX2, SX,EX),
  202	range_intersect(SY1,EY1, SY2,EY2, SY,EY).
  203
  204range_intersect(S1,E1, S2,E2, S,E) :-
  205	S is max(S1,S2),
  206	E is min(E1,E2),
  207	S =< E.
 ds_union(+DS1, +DS2, -DS) is det
True when the union of DS1 and DS2 is DS.
  214ds_union(cell_range(Sheet, SX1,SY1, EX1,EY1),
  215	 cell_range(Sheet, SX2,SY2, EX2,EY2),
  216	 cell_range(Sheet, SX,SY, EX,EY)) :-
  217	range_union(SX1,EX1, SX2,EX2, SX,EX),
  218	range_union(SY1,EY1, SY2,EY2, SY,EY).
  219
  220range_union(S1,E1, S2,E2, S,E) :-
  221	S is min(S1,S2),
  222	E is max(E1,E2).
 ds_union(+DSList, -DS) is det
True when DS is the union of all datasources
  229ds_union([], cell_range(_, 0,0,0,0)).
  230ds_union([H|T], Union) :-
  231	ds_union_list(T, H, Union).
  232
  233ds_union_list([], DS, DS).
  234ds_union_list([H|T], DS0, DS) :-
  235	ds_union(H, DS0, DS1),
  236	ds_union_list(T, DS1, DS).
 ds_intersections(+ListOfDS, -Pairs) is semidet
True when Pairs is a non-empty list of pairs of datasources with a non-empty intersection.
To be done
- Can be more efficient
  246ds_intersections(ListOfDS, Pairs) :-
  247	findall(A-B,
  248		( member(A,ListOfDS),
  249		  member(B,ListOfDS),
  250		  A@>B,
  251		  ds_intersection(A,B,_)
  252		),
  253		Pairs),
  254	Pairs \== [].
 ds_subtract(+Subtract, +From, -Remainder:list(pair(where-datasource))) is det
Remainder is a list of pairs of the form <location>-datasource that describes the area of From that is not covered by Subtract. Defined locations are:
all
From is unaffected
top and bottom
Subtract removes a set of rows
left and right
Subtract removes a set of columns $ top/left, top/middle, top/right, middle/left, middle/right, bottom/left, bottom/middle and bottom/right : Subtract is enclosed in From

Empty datasources are removed from the result set. E.g., if Subtract removes the top N rows of From, Remainder is a list holding only bottom - DSRem.

  278ds_subtract(Subtract, From, Remainder) :-
  279	ds_intersection(Subtract, From, I), !,
  280	ds_subtract_i(From, I, Remainder).
  281ds_subtract(_, From, [all-From]).	% no intersection: From is unaffected
  282
  283ds_subtract_i(DS, DS, Remainder) :- !,
  284	Remainder = [].			% DS1 is entirely enclosed by DS2
  285ds_subtract_i(cell_range(Sheet, SX,SY, EX,EY),
  286	      cell_range(Sheet, SX,Sy, EX,Ey),
  287	      Remainder) :- !,
  288	Sy1 is Sy-1,
  289	Ey1 is Ey+1,
  290	Rem0 = [ top    - cell_range(Sheet, SX, SY,  EX, Sy1),  % top
  291		 bottom - cell_range(Sheet, SX, Ey1, EX, EY)    % bottom
  292	       ],
  293	exclude(empty_value, Rem0, Remainder).
  294ds_subtract_i(cell_range(Sheet, SX,SY, EX,EY),
  295	      cell_range(Sheet, Sx,SY, Ex,EY),
  296	      Remainder) :- !,
  297	Sx1 is Sx-1,
  298	Ex1 is Ex+1,
  299	Rem0 = [ left  - cell_range(Sheet, SX,  SY, Sx1, EY),  % left
  300		 right - cell_range(Sheet, Ex1, SY, EX, EY)    % right
  301	       ],
  302	exclude(empty_value, Rem0, Remainder).
  303ds_subtract_i(cell_range(Sheet, SX,SY, EX,EY),
  304	      cell_range(Sheet, Sx,Sy, Ex,Ey),
  305	      Remainder) :-
  306	Sx1 is Sx-1, Sy1 is Sy-1,
  307	Ex1 is Ex+1, Ey1 is Ey+1,
  308	Rem0 = [ top/left      - cell_range(Sheet, SX,   SY, Sx1, Sy1),
  309		 top/middle    - cell_range(Sheet, Sx,   SY,  Ex, Sy1),
  310		 top/right     - cell_range(Sheet, Ex1,  SY,  EX, Sy1),
  311		 middle/left   - cell_range(Sheet, SX,   Sy, Sx1,  Ey),
  312		 middle/right  - cell_range(Sheet, Ex1,  Sy,  EX,  Ey),
  313		 bottom/left   - cell_range(Sheet, SX,  Ey1, Sx1,  EY),
  314		 bottom/middle - cell_range(Sheet, Sx,  Ey1,  Ex,  EY),
  315		 bottom/right  - cell_range(Sheet, Ex1, Ey1,  EX,  EY)
  316	       ],
  317	exclude(empty_value, Rem0, Remainder).
  318
  319empty_value(_-DS) :-
  320	ds_empty(DS).
  321
  322
  323		 /*******************************
  324		 *	      SLICING		*
  325		 *******************************/
 ds_row_slice(+DS, ?Offset, ?Slice) is det
True when Slice is a row from DS at offset Offset. Offsets are 0-based.
  332ds_row_slice(cell_range(Sheet, SX,SY, EX,EY), Offset,
  333	     cell_range(Sheet, SX,RY, EX,RY)) :-
  334	H is EY-SY,
  335	between(0,H,Offset),
  336	RY is SY+Offset.
 ds_unbounded_row_slice(+DS, +Offset, -Slice) is det
True when Slice is a row from DS at offset Offset. Offsets are 0-based. It is allowed for Slice to be outside the range of the datasouce.
  345ds_unbounded_row_slice(cell_range(Sheet, SX,SY, EX,_), Offset,
  346	     cell_range(Sheet, SX,RY, EX,RY)) :-
  347	RY is SY+Offset.
 ds_column_slice(+DS, ?Offset, ?Slice) is det
True when Slice is a column from DS at offset Offset. Offsets are 0-based.
  354ds_column_slice(cell_range(Sheet, SX,SY, EX,EY), Offset,
  355		cell_range(Sheet, CX,SY, CX,EY)) :-
  356	W is EX-SX,
  357	between(0,W,Offset),
  358	CX is SX+Offset.
 ds_row_slice(+DS, +Offset, +Height, -Slice) is det
True when Slice is a horizontal slice from DS, starting at Offset (0-based, relative to DS) and being rows high.
  365ds_row_slice(cell_range(Sheet, SX,SY, EX,EY), Offset, Height,
  366	     cell_range(Sheet, SX,CY, EX,ZY)) :-
  367	Height >= 0,
  368	H is EY-SY,
  369	between(0,H,Offset),
  370	CY is SY+Offset,
  371	ZY is CY+Height-1,
  372	ZY =< EY.
 ds_column_slice(+DS, +Offset, +Width, -Slice) is det
True when Slice is a vertical slice from DS, starting at Offset (0-based, relative to DS) and being Columns wide.
  379ds_column_slice(cell_range(Sheet, SX,SY, EX,EY), Offset, Width,
  380		cell_range(Sheet, CX,SY, ZX,EY)) :-
  381	Width >= 0,
  382	W is EX-SX,
  383	between(0,W,Offset),
  384	CX is SX+Offset,
  385	ZX is CX+Width-1,
  386	ZX =< EX.
 ds_unbounded_column_slice(+DS, +Offset, -Slice) is det
True when Slice is a column from DS at offset Offset. Offsets are 0-based. It is allowed for Slice to be outside the range of the datasouce.
  394ds_unbounded_column_slice(cell_range(Sheet, SX,SY,  _,EY), Offset,
  395			  cell_range(Sheet, CX,SY, CX,EY)) :-
  396	CX is SX+Offset.
 ds_grow(+DS0, +Amount, -DS)
  400ds_grow(cell_range(Sheet, SX0,SY0, EX0,EY0),
  401	Offset,
  402	cell_range(Sheet, SX,SY, EX,EY)) :-
  403	SX is SX0-Offset,
  404	SY is SY0-Offset,
  405	EX is EX0+Offset,
  406	EY is EY0+Offset