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_data,
   35	  [ assert_table/1,		% +Table
   36	    assert_block/1,		% +Block
   37	    retract_block/1,		% +BlockId
   38
   39	    sheet_object/3,		% ?Sheet, ?Type, ?Object
   40	    object_union/2,		% ?Object, ?Union
   41	    object_id/2,		% ?Object, ?Id
   42	    object_data_type/2,		% ?Object, ?Type
   43
   44	    assert_object_property/2,	% :ObjId, +Property
   45
   46	    assert_cell_property/4,	% :Sheet, +X, +Y, ?Property
   47	    cell_property/4,		% :Sheet, ?X, ?Y, ?Property
   48
   49	    assert_label/2,		% :Label, +Count
   50
   51	    clean_data/0
   52	  ]).   53:- use_module(library(error)).   54:- use_module(datasource).   55:- use_module(sheet).   56
   57:- meta_predicate
   58	assert_table(:),
   59	assert_block(:),
   60	retract_block(:),
   61	sheet_object(:, ?, ?),
   62	assert_object_property(:, +),
   63	assert_cell_property(:, +, +, +),
   64	cell_property(:,?,?,?),
   65	assert_label(:,+).   66
   67:- module_transparent
   68	clean_data/0.

Data store module

Defined relations:

*/

   81data(object_property/2).
   82data(cell_property/3).
   83data(table/5).
   84data(block/3).
   85data(label/2).
   86
   87clean_data :-
   88	context_module(M),
   89	forall(ods_data:data(Name/Arity),
   90	       ( functor(Head, Name, Arity),
   91		 retractall(M:Head)
   92	       )).
   93
   94
   95		 /*******************************
   96		 *	       TABLES		*
   97		 *******************************/
 assert_table(:Table) is det
Arguments:
Table- is table(TableId, _Type, _MainDS, _HdrDS, Union)
  103assert_table(M:T) :-
  104	assertz(M:T),
  105	T = table(TabId, _Type, _MainDS, _HdrDS, Union),
  106	ds_sheet(Union, Sheet),
  107	forall(ds_inside(Union, X, Y),
  108	       assert_cell_property(M:Sheet, X, Y, table(TabId))).
 assert_block(:Block) is det
Arguments:
Block- is block(BlockId, Type, DS)
  114assert_block(M:T) :-
  115	assertz(M:T),
  116	T = block(BlockId, _Type, DS),
  117	ds_sheet(DS, Sheet),
  118	forall(ds_inside(DS, X, Y),
  119	       assert_cell_property(M:Sheet, X, Y, block(BlockId))).
 retract_block(:BlockId) is det
  123retract_block(M:BlockId) :-
  124	must_be(atom, BlockId),
  125	retract(M:block(BlockId, _, _)), !.
  126retract_block(M:BlockId) :-
  127	existence_error(block, M:BlockId).
 sheet_object(:Sheet, ?Type, ?Object)
True when Sheet contains Object. Object is a table or block
table(TabId, Type, DataDS, HeaderDSList, UnionDS)
  137sheet_object(M:Sheet, table, table(TabId, Type, DataDS, HdrDS, Union)) :-
  138	ds_sheet(DataDS, Sheet),
  139	M:table(TabId, Type, DataDS, HdrDS, Union).
  140sheet_object(M:Sheet, block, block(BlockId, Type, DataDS)) :-
  141	ds_sheet(DataDS, Sheet),
  142	M:block(BlockId, Type, DataDS).
 object_union(+Object, -Union) is det
True if Union is the UnionDS of Object.
  148object_union(table(_TableId, _Type, _DataDS, _HdrDS, Union), Union).
  149object_union(block(_BlockId, _Type, DataDS), DataDS).
 object_id(+Object, -Id) is det
  153object_id(table(TableId, _Type, _DataDS, _HdrDS, _Union), TableId).
  154object_id(block(BlockId, _Type, _DataDS), BlockId).
 object_data_type(+Object, -Type) is det
  158object_data_type(table(_TableId, Type, _DataDS, _HdrDS, _Union), Type).
  159object_data_type(block(_BlockId, Type, _DataDS), Type).
 assert_object_property(:ObjId, +Property)
  163assert_object_property(M:ObjId, Property) :-
  164	(   M:object_property(ObjId, Property)
  165	->  true
  166	;   assertz(M:object_property(ObjId, Property))
  167	).
  168
  169
  170		 /*******************************
  171		 *	       CELLS		*
  172		 *******************************/
 assert_cell_property(:Sheet, +X, +Y, +Property) is det
Add a property to a cell. Does nothing if the property is already defined.
  179assert_cell_property(M:Sheet, X, Y, Property) :-
  180	cell_id(X,Y,CellId),
  181	assertz(M:cell_property(Sheet,CellId,Property)).
 cell_property(:Sheet, ?X, ?Y, ?Property)
Query (inferred) properties of the cell Sheet.XY.
  188cell_property(M:Sheet, X, Y, Property) :-
  189	(   nonvar(X), nonvar(Y)
  190	->  cell_id(X,Y,Id),
  191	    M:cell_property(Sheet,Id,Property)
  192	;   M:cell_property(Sheet,Id,Property),
  193	    cell_id(X,Y,Id)
  194	).
  195
  196
  197		 /*******************************
  198		 *	       LABELS		*
  199		 *******************************/
 assert_label(:Label, +Count) is det
Assert to label/2
  205assert_label(M:Label, Count) :-
  206	assertz(M:label(Label, Count))