Skip to content

Commit

Permalink
Work on showing sheets
Browse files Browse the repository at this point in the history
  • Loading branch information
Jan Wielemaker authored and Jan Wielemaker committed Nov 8, 2012
1 parent 47b6aeb commit fe84368
Show file tree
Hide file tree
Showing 7 changed files with 125 additions and 34 deletions.
3 changes: 3 additions & 0 deletions bisect.pl
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,9 @@
bisect(Test, From, To, Last) :-
bsect(Test, From, To, Last).

:- meta_predicate
bsect(1, +, +, -).

bsect(Test, From, To, Last) :-
Mid is (From+To)//2,
( call(Test, Mid)
Expand Down
2 changes: 2 additions & 0 deletions ods_table.pl
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,8 @@
column_name/2, % ?Index, ?Name
ods_DOM/3, % :Source, -DOM, +Options

cell_id/3, % ?X, ?Y, ?Id

sheet_name_need_quotes/1, % +SheetName
ods_reference//2 % -Expr, +Table
]).
Expand Down
33 changes: 14 additions & 19 deletions recognise.pl
Original file line number Diff line number Diff line change
Expand Up @@ -12,9 +12,10 @@
cell_class/1, % ?Class
cell_class/4, % :Sheet, ?SX, ?SY, ?Class

sheet_bb/5 % :Sheet, SX,SY, EX,SY
sheet_bb/2 % :Sheet, -DataSource
]).
:- use_module(ods_table).
:- use_module(datasource).
:- use_module(library(apply)).
:- use_module(library(lists)).

Expand Down Expand Up @@ -141,31 +142,29 @@
( cell_type(Sheet, X,Y, Type0)
-> Type = Type0
; Type = empty
-> sheet_bb(Sheet, MinX,MinY,MaxX,MaxY),
between(MinX, MaxX, X),
between(MinY, MaxY, Y),
-> sheet_bb(Sheet, SheetDS),
ds_inside(SheetDS, X, Y),
\+ cell_type(Sheet, X,Y, _)
).
cell_class(Sheet, X,Y, Type) :-
Type == empty, !,
sheet_bb(Sheet, MinX,MinY,MaxX,MaxY),
between(MinX, MaxX, X),
between(MinY, MaxY, Y),
sheet_bb(Sheet, SheetDS),
ds_inside(SheetDS, X, Y),
\+ cell_type(Sheet, X,Y, _).
cell_class(Sheet, X,Y, Type) :-
cell_type(Sheet, X,Y, Type).


%% sheet_bb(:Sheet, ?SX,?SY, ?EX,?EY) is nondet.
%% sheet_bb(:Sheet, ?DS) is nondet.
%
% True if Sheet is covered by the given bounding box. Note that
% SX and SY may be 0. Fails of the sheet is empty.
% True if DS is a datasource that describes all cells in Sheet.
% Fails of the sheet is empty.

:- dynamic
sheet_bb_cache/6,
sheet_bb_cached/2.

sheet_bb(M:Sheet, SX,SY,EX,EY) :-
sheet_bb(M:Sheet, cell_range(Sheet,SX,SY,EX,EY)) :-
M:sheet(Sheet, _),
( sheet_bb_cached(M, Sheet)
-> sheet_bb_cache(M, Sheet, SX,SY,EX,EY)
Expand All @@ -181,15 +180,11 @@
M:sheet(Sheet, _),
findall(X-Y, cell_exists(M:Sheet, X,Y), Pairs),
maplist(arg(1), Pairs, AtCol),
min_list(AtCol, MinX),
max_list(AtCol, MaxX),
min_list(AtCol, SX),
max_list(AtCol, EX),
maplist(arg(2), Pairs, AtRow),
min_list(AtRow, MinY),
max_list(AtRow, MaxY),
SX is MinX - 1,
SY is MinY - 1,
EX is MaxX + 1,
EY is MaxY + 1.
min_list(AtRow, SY),
max_list(AtRow, EY).

cell_exists(M:Sheet,X,Y) :-
cell(M:Sheet, X,Y, _,_,_,_,_).
Expand Down
39 changes: 33 additions & 6 deletions table.pl
Original file line number Diff line number Diff line change
Expand Up @@ -2,25 +2,53 @@
[ assert_tables/2, % ?Sheet, ?Type
tables/3, % ?Sheet, +Type, -Tables
table/2, % +Data, -Support
cell_property/4, % :Sheet, ?X, ?Y, ?Property
cells_outside_tables/3 % +Sheet, +Table, -Cells
]).
:- use_module(recognise).
:- use_module(datasource).
:- use_module(ods_table).
:- use_module(library(lists)).

:- meta_predicate
tables(:, ?, -),
assert_tables(:, ?).
assert_tables(:, ?),
cell_property(:,?,?,?).

%% assert_tables(:Sheet, ?Type) is det.
%
% Infer and assert identified tables.
% Infer and assert identified tables. Creates the following facts:
%
% * table(TableID, Type, MainDS, HeaderDSList, UnionDS)
% * cell_property(Sheet CellId, table(TableID))

assert_tables(Sheet, Type) :-
Sheet = M:_,
tables(Sheet, Type, Tables),
forall(member(T, Tables),
assertz(M:T)).
assert_table(M:T)).

assert_table(M:T) :-
assertz(M:T),
T = table(TabId, _Type, _MainDS, _HdrDS, Union),
ds_sheet(Union, Sheet),
forall(ds_inside(Union, X, Y),
( cell_id(X,Y,CellId),
assertz(M:cell_property(Sheet,CellId,table(TabId)))
)).

%% cell_property(:Sheet, ?X, ?Y, ?Property)
%
% Query (inferred) properties of the cell Sheet.XY.

cell_property(M:Sheet, X, Y, Property) :-
( nonvar(X), nonvar(Y)
-> cell_id(X,Y,Id),
M:cell_property(Sheet,Id,Property)
; M:cell_property(Sheet,Id,Property),
cell_id(X,Y,Id)
).


%% tables(?Sheet, +Type, -Tables) is det.
%
Expand Down Expand Up @@ -72,9 +100,8 @@

cells_outside_tables(Sheet, Tables, Cells) :-
findall(cell(Sheet,X,Y),
( sheet_bb(Sheet, SX,SY, EX,EY),
between(SX, EX, X),
between(SY, EY, Y),
( sheet_bb(Sheet, SheetDS),
ds_inside(SheetDS, X, Y),
cell_value(Sheet, X, Y, _),
\+ ( member(table(_,_,DS), Tables),
ds_inside(DS,X,Y)
Expand Down
10 changes: 9 additions & 1 deletion test.pl
Original file line number Diff line number Diff line change
Expand Up @@ -7,12 +7,17 @@
:- initialization
start_server.

:- dynamic
server_url/1.

start_server :-
server_url(_), !.
start_server :-
server(Port),
format(atom(URL), 'http://localhost:~d/', [Port]),
assertz(server_url(URL)),
www_open_url(URL).


file('E-Design WindEnergie.ods').
sheet('WindopLand').

Expand All @@ -39,6 +44,9 @@
passed/3,
failed/4.

:- meta_predicate
test(:, ?, ?, 0).

test(Sheet, X,Y, Cont) :-
clean_stats,
State = state(0),
Expand Down
16 changes: 16 additions & 0 deletions webui.css
Original file line number Diff line number Diff line change
@@ -1,3 +1,6 @@
/* See http://www.w3schools.com/css/css_table.asp
*/

table.spreadsheet
{ border-collapse:collapse;
}
Expand All @@ -6,3 +9,16 @@ table.spreadsheet td
{ border: 1px solid black;
}

table.spreadsheet td.intable
{ background-color:#a8ffcc;
}

table.spreadsheet td.float,td.percentage
{ text-align:right;
}

table.spreadsheet td.derived
{ color:blue;
//font-weight:bold;
}

56 changes: 48 additions & 8 deletions webui.pl
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,8 @@
:- use_module(library(http/http_dispatch)).
:- use_module(library(http/html_head)).
:- use_module(library(http/html_write)).
:- use_module(table).
:- use_module(recognise).

:- http_handler(root(.), home, []).
:- http_handler(root('webui.css'), http_reply_file('webui.css', []), []).
Expand All @@ -21,6 +23,7 @@
reply_html_page(title('Spreadsheet analyzer'),
[ \html_requires(root('webui.css')),
h1('Spreadsheet analyzer'),
\error_area,
\log_area([id(log)]),
\form_area([id(form)])
]).
Expand All @@ -38,6 +41,9 @@
html(h4('Showing ~p'-[Data])),
web_portray(Data).

web_portray(Var) -->
{ var(Var) }, !,
html(p('Unbound variable')).
web_portray(cell_range(Sheet, SX,SY, EX,EY)) -->
{ integer(SX), integer(SY), integer(EX), integer(EY) }, !,
html(table(class(spreadsheet),
Expand All @@ -46,6 +52,9 @@
web_portray(cell_range(Sheet, X,Y, X,Y)).
web_portray(table(_Id,_Type,_DS,_Headers,Union)) -->
web_portray(Union).
web_portray(sheet(Sheet)) -->
{ sheet_bb(user:Sheet, DS) }, !,
web_portray(DS).
web_portray(List) -->
{ is_list(List), !,
length(List, Len)
Expand Down Expand Up @@ -78,19 +87,50 @@
table_row(Sheet, Y, X2,EX).
table_row(_, _, _,_) --> [].

%% table_cell(+Sheet, +SX, +SY)//

table_cell(Sheet, SX, SY) -->
{ cell_type(Sheet, SX,SY,percentage),
cell_value(Sheet, SX,SY, Value),
{ ( cell_type(Sheet, SX,SY, Type)
-> true
; Type = empty
),
findall(A, cell_class_attr(Sheet,SX,SY,Type,A), Classes),
( Classes == []
-> Attrs = []
; Attrs = [class(Classes)]
)
},
table_cell(Type, Sheet, SX, SY, Attrs).

cell_class_attr(_, _, _, Type, Type).
cell_class_attr(Sheet, X, Y, _, intable) :-
cell_property(Sheet, X, Y, table(_)).
cell_class_attr(Sheet, X, Y, _, derived) :-
cell_formula(Sheet, X, Y, _).

%% table_cell(+Sheet, +SX, +SY, +Style)//

table_cell(percentage, Sheet, SX, SY, Attrs) -->
{ cell_value(Sheet, SX,SY, Value),
Val is Value*100
}, !,
html(td([Val,'%'])).
table_cell(Sheet, SX, SY) -->
html(td(Attrs, ['~3f%'-[Val]])).
table_cell(float, Sheet, SX, SY, Attrs) -->
{ cell_value(Sheet, SX,SY, Value),
number(Value),
ndigits(Value, 5, V2)
}, !,
html(td(Attrs, [V2])).
table_cell(_, Sheet, SX, SY, Attrs) -->
{ cell_value(Sheet, SX,SY, Value)
}, !,
( { atomic(Value) }
-> html(td(Value))
; html(td('~q'-[Value]))
-> html(td(Attrs, Value))
; html(td(Attrs, '~q'-[Value]))
).
table_cell(_, _, _) -->
html(td(class(empty), [])).
table_cell(_, _, _, _, Attrs) -->
html(td(Attrs, [])).

ndigits(F0, N, F) :-
Times is 10**max(1,N-round(log10(F0))),
F is round(F0*Times)/Times.

0 comments on commit fe84368

Please sign in to comment.