
:- dynamic triple/3.
:- index(triple(1,1,0)).

go(Name) :-
	retractall(three(_,_,_)),
	good(relation(Name,Attrs,Scores,Data)),
	wme0(Attrs,W0),
	rows(Data,Scores,1,W0,W).

good(relation(Name,Attrs,Scores,Data)) :-
	relation(Name,Attrs,Scorse,Data),
	(ground(relation(Name,Attrs,Scores,Data)) 
     -> true
     ;  error(not(ground(relation)))
    ),
	(\+ nth(N,Data,Datum),  
	    bad(Scores,Attrs,Datum,Because), 
        warning(row(N,Because))
    ).

bad(Scores,Attrs,Datum,bad(Klass)) :- 
	last(Datum,Klass), 
	\+ number(Klass), 
	\+ member(Klass= _,Scores).
bad(Scores,Attrs,Datum, wrong(size(N1,N2))) :- 
	length(Datum,N1),
	length(Attrs,N2),
	\+ N2 is N1 + 1
	
wme0(L0,L) :- maplst(wme0a,L0,L).
wme0a(X,X=[]).

% for rows in relation do
rows([]        ,_     ,_,W, W).
rows([Row|Rows],Scores,N,W0,W) :- 
	append(Inputs,[Klass],Row),
	row(Inputs,Klass,1,N,W0,W1), 
	N1 is N + 1, 
	rows(Rows,Scores,N1,W1,W).

% for cells in row do
row([],_,_,_,[],[]) :-
row([Input0|Inputs],Klass,Col,Row,[Attr=Details0|W0],[Attr=About|W]) :-
	cell(Input,Attr,Klass,Col,Row,About0,About),
	Col1 is Col + 1,
	row(Inputs,Klass,Col1,Row,W0,W).

% for one cell do
cell(Value,_,_,_,_A,A) :- dunno(Value).
cell(Value,Attr,Klass,Col,Row,N,W0,W) :- 
	(dependent(Attr) -> assert(triple(Col,Row,Value); true).
	@(Value,Old,[Klass=Row|Old],[],W0,W).		

dunno(?).
dependent(+ X).
independent(X) :- \+ dependent(X).
	

reads1(end_of_file,L, L).
reads1(X, L0, L) :-
	once(read1(X, L0, L1)),
	read(Y), 
	reads1(Y, L1,L).

read1(attr=L)     --> attr(L).
read1(scores=L)   --> @(scores,L).
read1(data=L) 	  --> row(L).
read1(relation=R) --> @(relation,R).
read1(X)          --> {error(X)}.

report([cols=L]) :- printPairs(L).

attr(L0) --> {maplist(attr1,L0,L)}, @(cols,L).
attr1(X,X=[]).

row(L) --> 
	{last(L,Klass)}, 
	@(cols,Cols0,Cols,[]),
	{bad(L,Cols0) -> Cols0=Cols ; cells(L,Cols0,Klass,Cols) }.

bad(L,Cols) :- once(bad1(L,Cols,Err)),error(Err).
 
bad1(L,Cols,[want(N), got(N1),L]) :-
	length(L,N),
	length(Cols,N1),
	not( N1 = N).
bad1(L,_,not(ground(L))) :- not(ground(L)).
bad1(_,Cols,not(ground(Cols))) :- not(ground(Cols)).

cells([],_,_,[]).
cells([Val|Vals],[X=Col0|Col0s],Klass,[X=Col|Cols]) :-
	cell(Val,Klass,Col0,Col),
	cells(Vals,Col0s,Klass,Cols).

cell( ?      ,_) --> !.
cell( Val,Klass) --> cell1(Val,Klass), total(Val).

cell1(Val,Klass) --> @(Klass,Old,New,[]), {+(Val,Old,New)}.
total(Val)       --> {all(All)}, cell1(Val,All),cell1(All,All).

all($all).

+(X,L0,L) :- @(X,Old,New,0,L0,L),New is Old+1.

@(Key,Old)   --> @(Key,Old,Old,Old).
@(Key,Old,New,_,      L0,[Key=New|L]) :- less1(Key=Old,L0,L),!.
@(Key,Old,New,Default,L0,L) :- @(Key,Old,New,Default,[Key=Default|L0],L).

less1(Old, [Old|T ], T ).
less1(Old, [H  |T0], [H  |T1]) :- less1(Old,T0,T1).

error(X) :- warning(X),fail.
warning(X) :-
	source_location(File, Line)
    -> file_base_name(File,Base),
	   format('% ?? ~w, line ~w: ~w\n',[Base,Line,X])
    ;  format('% ??  ~w\n',[X]).

printPairs(L) :- nl,printPairs(L,'|    ',[]),nl.

printPairs(X,Pad,Padding) :- 
	once(printPairs1(X,Pad,Padding)).

printPairs1(X,_,_) :- 
	var(X),
	write('?').
printPairs1(X=Y,Pad,Padding) :- 
	nl,
	forall(member(P,Padding),print(P)),
	write(X), write(' = '),
	printPairs(Y,Pad,[Pad|Padding]).
printPairs1([],_,_). 
printPairs1([H|T],Pad,Padding) :- 
	printPairs(H,Pad,Padding), 
	printPairs(T,Pad,Padding).
printPairs1(X,_,_) :- write(X).

%score(L,Scores,W,S) :- 
%	@(scores,Scores,W), 
%	score(L,0,S).

%score([],X,X).
%score([H|T]) --> score1(H),score(T).

:- op(700,yfx,of).

in(X=Y ,L,L) :- in(X=Y,L).
in(X=Y   ,L) :- member(X=Y,L).
in(X of Y,L) :- member(Y=Temp,L),in(X,Temp).

baseline(Klass,All,Scores,S) -->
	{all(All)},
	in(All=Counts of Klass of cols),
	{baseline1(All,Counts,Scores,0,S)}.

baseline1([]   ,_  ,_     ,S, S).
baseline1([H|T],All,Scores,S0,S) :-
	baseline2(H,All,Scores,S0,S1),
	baseline1(T,All,Scores,S1,S).
	
baseline2(All,All,_,S, S) :- !.
baseline2(One,_  ,Scores,S0,S) :-
	member(One/S1,Scores),
	S is S0 + S1.	

baseline(Wme,S) :-
	all(All),	
	member(cols=Col,Wme),
	member(scores=Scores,Wme),
	last(Col,_=AllCounts),
	member(All=Counts,AllCounts),
	append(Before,[All=Total|After],Counts),
	weightedSum(Before,Scores,S0),
	weightedSum(After,Scores,S1),
	S is (S0+S1)/Total.

weightedSum([],_,0).
weightedSum([H=N1|T],Scores,(N1*N2)+S) :-
	member(H=N2,Scores),
	weightedSum(T,Scores,S).
	
demo(read3) :- 
	reads('data/contact.csv',L),
	baseline(L,S),
	print(S),nl.
demo(read2) :- reads('data/waveform.csv',L),printPairs(L).
demo(read1) :- reads('data/contact.csv',L),printPairs(L).
demo(read0) :- reads('data/data1.csv',L),printPairs(L).
