This commit is contained in:
Vitor Santos Costa
2016-08-01 21:45:42 -05:00
72 changed files with 8053 additions and 54 deletions

358
regression/dados/csv2pl_v3 Normal file
View File

@@ -0,0 +1,358 @@
% ICD: it does not take into account missing values
%
% utility to translate from CSV style files to Prolog facts.
%
% assumes key is first argument.
%
% call as yap csv2pl -- prefix < Inp.csv > Out
%
% ICD: yap -l csv2pl_v3 -- --modes in.csv out
% alternatively you can call yap and invoke: main(['--modes','in.csv',out]).
% this will generate three files: out.facts, out.modes and out.txt
% out.facts contains all prolog facts for the csv table
% out.modes contains all modes to run with aleph (change as appropriate)
% out.txt contains basic data description (counters)
:- source.
:- style_check(all).
:- yap_flag(unknown, error).
:- yap_flag(write_strings, on).
:- use_module(library(readutil),
[read_line_to_codes/2]).
:- use_module(library(lineutils),
[split/3]).
:- use_module(library(system),
[mktime/2]).
:- ensure_loaded(order_by). % order predicate values
:- ensure_loaded(daynumber).
:- initialization(main).
:- dynamic output_modes/0.
main :-
unix(argv(Args)),
% write(Args),
main(Args).
main(['--modes'|R]) :- !,
assert(output_modes),
main(R).
%ICD: changed here to write in two different files
% also added counters
main([F,O]) :-
open(F, read, S),
atom_concat(O,'.modes',W1),
atom_concat(O,'.facts',W2),
open(W1, write, WModes),
open(W2, write, WFacts),
do(S, WModes, WFacts),
close(WModes), close(WFacts),
close(S),
write('WILL START COUNTING'), nl,
count(O).
/*
main([F]) :-
unix(argv([F])), !,
open(F, read, S),
W = user_output,
do(S, W),
close(S).
main([]) :-
S = user_input,
W = user_output,
do(S, W).
*/
do(S, WModes, WFacts) :-
get_titles(S, WModes, Titles),
get_lines(S, WFacts, Titles).
get_titles(S, W, Titles) :-
read_line_to_codes(S,Line),
split(Line, ",", OTitles),
list_of_titles(OTitles, Titles),
% format('~q~n~q~n',[OTitles,Titles]),
output_modes(Titles, W).
%ICD: changed here to use the Key name
%output_modes(_Key.Titles, W) :-
output_modes([Key|Titles], W) :-
format('~q~n',[[Key|Titles]]),
output_modes, !,
send_determinations(Titles, W),
% format(W, ':- modeh(*,upgrade(+key)).~n',[]),
format(W, ':- modeh(*,upgrade(+~q)).~n',[Key]),
% send_modes(Titles, W).
send_modes(Titles, Key, W).
send_determinations([], W) :-
nl(W).
send_determinations([T|Titles], W) :-
format(W, ':- determination(upgrade/1,~q/2).~n',[T]),
send_determinations(Titles, W).
%ICD: changed to use the key name
send_modes([], _, W) :-
nl(W).
send_modes([T|Titles], Key, W) :-
format(W, ':- modeb(*,~q(+~q,-~q)).~n',[T,Key,T]),
format(W, ':- modeb(*,~q(+~q,#~q)).~n',[T,Key,T]),
send_modes(Titles, Key, W).
list_of_titles([],[]).
list_of_titles([S|Ss], [A|As]) :-
% atom(A, S), % ICD: convert first letter to lowercase, remove plics
S = [H|T], char_type(LowH,to_lower(H)), atom_codes(A,[LowH|T]),
list_of_titles(Ss, As).
continue_list(Titles) -->
",", !,
list_of_titles(Titles).
continue_list([]) --> [].
get_lines(S, W, Titles) :-
read_line_to_codes(S, Line),
write(Line), nl, % ICD
add_line(Line, S, W, Titles).
add_line(end_of_file, _, _, _) :- !.
add_line(Line, S, W, Titles) :-
get_data(Titles, W, Line, []), !,
% write('Parsed correctly'), nl,
get_lines(S, W, Titles).
get_data([_|Titles], W, S1, S) :-
get_field(N, S1,S2),
% write(S1), nl, write(N), nl, write(S2), nl,
get_more_data(Titles, W, N, S2, S).
get_more_data([Field|L], W, Key, L, L) :- !,
add_as_empty([Field|L], W, Key).
get_more_data([Field|L], W, Key) -->
% {write([Field|L]), nl},
",", !,
get_field(N),
% { write(N), write('--'), nl },
{ output_field(W, Field, Key, N) },
get_more_data(L, W, Key).
get_more_data([], _, _) --> [].
get_field(N) -->
"\"", time(N), "\"", !.
get_field(N) -->
time(N), !.
get_field(N) -->
timeHours(N), !.
get_field(N) -->
atom(N), !.
get_field(N) -->
number(N), !.
get_field(?) -->
empty, !.
get_field(A) -->
any(S),
{atom_codes(A, S) }.
any([], [0',|L], [0',|L]) :- !.
any([], [], []) :- !.
any([C|Cs]) --> [C], any(Cs).
time(N) -->
natural(Year),
"-",
% "/",
month(Month),
"-",
% "/",
natural(Day),
{ %writeln(Day:Month:Year),
cvt_to_n(Day, Month, Year, N) }.
timeHours(H:M:S) -->
natural(H),
{format('~q~n',[H])},
":",
natural(M),
":",
natural(S).
cvt_to_n(D, M, Y0, N) :-
Y0 =< 10,
!,
Y is 2000+Y0,
days(Y,M,D,N).
cvt_to_n(D, M, Y0, N) :-
Y0 > 10,
Y0 < 100,
!,
Y is 1900+Y0,
days(Y,M,D,N).
cvt_to_n(D, M, Y, N) :-
days(Y,M,D,N).
number(N) -->
"-", !,
pos_number(N1),
{ N is -N1 }.
number(N) -->
"+", !,
pos_number(N1),
{ N is -N1 }.
number(N) -->
pos_number(N).
pos_number(N) -->
natural(L, L0),
do_float(L0),
{ number_codes(N,L) }.
do_float([0'e|L0]) -->
"e", !,
integer(L0, []).
do_float([0'E|L0]) -->
"E", !,
integer(L0, []).
do_float([0'.|L0]) -->
".", !,
natural(L0, []).
do_float([]) -->
[].
natural(N) -->
natural(L, []),
{ number_codes(N, L) }.
natural([C|L], L0) -->
[C],
{ C >= 0'0, C =< 0'9 }, !,
more_naturals(L, L0).
more_naturals([C|L], L0) -->
[C],
{ C >= 0'0, C =< 0'9 }, !,
more_naturals(L, L0).
more_naturals(L0, L0) --> [].
integer(L,L0) -->
"+", !,
natural(L, L0).
integer([0'-|L],L0) -->
"-", !,
natural(L, L0).
integer(L,L0) -->
natural(L, L0).
atom(T) -->
"\"",
quoted(Name),
{ atom_codes(T, Name) }.
quoted([0'"|Name]) --> "\"\"", !, %"
quoted(Name).
quoted([]) --> "\"", !.
quoted([C|Name]) --> [C],
quoted(Name).
empty([0',|L], [0',|L]).
empty([], []).
month(1) --> "Jan", !.
month(2) --> "Feb", !.
month(3) --> "Mar", !.
month(4) --> "Apr", !.
month(5) --> "May", !.
month(6) --> "Jun", !.
month(7) --> "Jul", !.
month(8) --> "Aug", !.
month(9) --> "Sep", !.
month(10) --> "Oct", !.
month(11) --> "Nov", !.
month(12) --> "Dec", !.
month(I) --> natural(I).
add_as_empty([], _, _).
add_as_empty([Field|L], W, Key) :-
output_field(W, Field, Key, ?),
add_as_empty(L, W, Key).
% ICD: changed
%output_field(_W, _Field, _Key, ?) :- !.
% format(W,'~q(~q,~q).~n',[Field,Key,N]).
%output_field(W, Field, Key, N) :-
% format(W,'~q(~q,~q).~n',[Field,Key,N]).
% ICD: included counters for Field/Value
output_field(W, Field, Key, ?) :- !,
format(W,'~q(~q,~q).~n',[Field,Key,?]),
counting(Field,missing).
/*
output_field(W, Field, Key, N) :-
not atom(N), !,
format(W,'~q(~q,~q).~n',[Field,Key,N]),
counting(Field,N).
output_field(W, Field, Key, N) :-
% convert first letter of predicate value N to lower case if it is uppercase
atom_chars(N,[Char|Chars]),
char_type(Char,upper),
atom_codes(Char,Code),
char_type(LowChar,to_lower(Code)), atom_chars(A,[LowChar|Chars]),
format(W,'~q(~q,~q).~n',[Field,Key,A]),
counting(Field,A), !.
*/
output_field(W, Field, Key, N) :-
format(W,'~q(~q,~q).~n',[Field,Key,N]),
counting(Field,N).
% ICD: include counters
counting(Field,Value) :-
retract(counter(Field,Value,C)),
C1 is C + 1,
assertz(counter(Field,Value,C1)), !.
counting(Field,Value) :-
assertz(counter(Field,Value,1)).
% when it ends
count(FileDescription) :-
write('WILL START COUNTING'), nl,
atom_concat(FileDescription,'.txt',File),
tell(File),
% listing(counter),
counter(Field,_Value,_C),
once(counter(Field,_Value,_C)),
% format('**** WILL WRITE ALL VALUES FOR FIELD: ~q~n',[Field]),
mydisplay(Field),
% format('**** WROTE ALL VALUES FOR FIELD: ~q~n',[Field]),
fail.
count(_) :- told.
/*
mydisplay(Field) :-
write(Field), nl,
counter(Field,Value,C),
tab(4),
format('~q: ~q~n',[Value,C]),
fail.
mydisplay(Field) :-
% format('**** REMOVING ALL FIELD: ~q~n',[Field]),
retractall(counter(Field,_,_)).
*/
% other solution
mydisplay(Field) :-
write(Field), nl,
order_by(counter/3, 2),
forall(counter(Field,Value,C),
(tab(4), format('~q: ~q~n',[Value,C]))
),
retractall(counter(Field,_,_)). %,
% format('REMOVED ALL FIELD: ~q~n',[Field]). %,
% listing(counter).

View File

@@ -0,0 +1,32 @@
ID,Date,Time,Value_Carbs,Value_Glucose,Value_Insulin
1,2016-04-23,15:25:47,50,125,5
2,2016-04-23,21:28:10,100,69,10
3,2016-04-23,23:19:04,21,260,21
4,2016-04-24,09:31:40,18,256,6.5
5,2016-04-25,09:32:20,19,72,6.5
6,2016-04-25,16:11:11,20,136,1
7,2016-04-25,20:55:59,50,274,5.5
8,2016-04-26,08:04:07,18,264,7
9,2016-04-26,10:24:41,40,52,9
10,2016-04-26,15:01:50,100,256,10.5
11,2016-04-26,21:33:31,46,168,8
12,2016-04-27,07:32:04,18,99,4
13,2016-04-27,10:02:53,16,103,1.5
14,2016-04-27,15:51:03,115,222,14
15,2016-04-27,20:27:01,50,191,7.5
16,2016-04-28,07:33:27,20,99,5
17,2016-04-28,10:30:33,18,143,2
18,2016-04-28,14:09:37,85,203,10.5
19,2016-04-28,20:45:52,55,134,7.5
20,2016-04-29,07:33:31,20,89,3
21,2016-04-29,10:36:58,16,112,1
22,2016-04-29,15:17:26,111,266,13.5
23,2016-04-29,20:16:38,65,108,10
24,2016-04-30,10:11:31,20,89,2.5
25,2016-04-30,14:31:12,60,258,6
26,2016-04-30,17:44:53,20,57,7
27,2016-04-30,21:26:38,95,227,8
28,2016-05-01,09:51:14,50,129,9.5
29,2016-05-02,09:23:07,20,200,2.5
30,2016-05-02,14:14:50,150,207,17
31,2016-05-02,20:35:16,45,182,6.5
1 ID Date Time Value_Carbs Value_Glucose Value_Insulin
2 1 2016-04-23 15:25:47 50 125 5
3 2 2016-04-23 21:28:10 100 69 10
4 3 2016-04-23 23:19:04 21 260 21
5 4 2016-04-24 09:31:40 18 256 6.5
6 5 2016-04-25 09:32:20 19 72 6.5
7 6 2016-04-25 16:11:11 20 136 1
8 7 2016-04-25 20:55:59 50 274 5.5
9 8 2016-04-26 08:04:07 18 264 7
10 9 2016-04-26 10:24:41 40 52 9
11 10 2016-04-26 15:01:50 100 256 10.5
12 11 2016-04-26 21:33:31 46 168 8
13 12 2016-04-27 07:32:04 18 99 4
14 13 2016-04-27 10:02:53 16 103 1.5
15 14 2016-04-27 15:51:03 115 222 14
16 15 2016-04-27 20:27:01 50 191 7.5
17 16 2016-04-28 07:33:27 20 99 5
18 17 2016-04-28 10:30:33 18 143 2
19 18 2016-04-28 14:09:37 85 203 10.5
20 19 2016-04-28 20:45:52 55 134 7.5
21 20 2016-04-29 07:33:31 20 89 3
22 21 2016-04-29 10:36:58 16 112 1
23 22 2016-04-29 15:17:26 111 266 13.5
24 23 2016-04-29 20:16:38 65 108 10
25 24 2016-04-30 10:11:31 20 89 2.5
26 25 2016-04-30 14:31:12 60 258 6
27 26 2016-04-30 17:44:53 20 57 7
28 27 2016-04-30 21:26:38 95 227 8
29 28 2016-05-01 09:51:14 50 129 9.5
30 29 2016-05-02 09:23:07 20 200 2.5
31 30 2016-05-02 14:14:50 150 207 17
32 31 2016-05-02 20:35:16 45 182 6.5

View File

@@ -0,0 +1 @@
?-

View File

@@ -0,0 +1,155 @@
date(1,42481).
time(1,15:25:47).
value_Carbs(1,50).
value_Glucose(1,125).
value_Insulin(1,5).
date(2,42481).
time(2,21:28:10).
value_Carbs(2,100).
value_Glucose(2,69).
value_Insulin(2,10).
date(3,42481).
time(3,23:19:4).
value_Carbs(3,21).
value_Glucose(3,260).
value_Insulin(3,21).
date(4,42482).
time(4,9:31:40).
value_Carbs(4,18).
value_Glucose(4,256).
value_Insulin(4, 6.500000).
date(5,42483).
time(5,9:32:20).
value_Carbs(5,19).
value_Glucose(5,72).
value_Insulin(5, 6.500000).
date(6,42483).
time(6,16:11:11).
value_Carbs(6,20).
value_Glucose(6,136).
value_Insulin(6,1).
date(7,42483).
time(7,20:55:59).
value_Carbs(7,50).
value_Glucose(7,274).
value_Insulin(7, 5.500000).
date(8,42484).
time(8,8:4:7).
value_Carbs(8,18).
value_Glucose(8,264).
value_Insulin(8,7).
date(9,42484).
time(9,10:24:41).
value_Carbs(9,40).
value_Glucose(9,52).
value_Insulin(9,9).
date(10,42484).
time(10,15:1:50).
value_Carbs(10,100).
value_Glucose(10,256).
value_Insulin(10, 10.500000).
date(11,42484).
time(11,21:33:31).
value_Carbs(11,46).
value_Glucose(11,168).
value_Insulin(11,8).
date(12,42485).
time(12,7:32:4).
value_Carbs(12,18).
value_Glucose(12,99).
value_Insulin(12,4).
date(13,42485).
time(13,10:2:53).
value_Carbs(13,16).
value_Glucose(13,103).
value_Insulin(13, 1.500000).
date(14,42485).
time(14,15:51:3).
value_Carbs(14,115).
value_Glucose(14,222).
value_Insulin(14,14).
date(15,42485).
time(15,20:27:1).
value_Carbs(15,50).
value_Glucose(15,191).
value_Insulin(15, 7.500000).
date(16,42486).
time(16,7:33:27).
value_Carbs(16,20).
value_Glucose(16,99).
value_Insulin(16,5).
date(17,42486).
time(17,10:30:33).
value_Carbs(17,18).
value_Glucose(17,143).
value_Insulin(17,2).
date(18,42486).
time(18,14:9:37).
value_Carbs(18,85).
value_Glucose(18,203).
value_Insulin(18, 10.500000).
date(19,42486).
time(19,20:45:52).
value_Carbs(19,55).
value_Glucose(19,134).
value_Insulin(19, 7.500000).
date(20,42487).
time(20,7:33:31).
value_Carbs(20,20).
value_Glucose(20,89).
value_Insulin(20,3).
date(21,42487).
time(21,10:36:58).
value_Carbs(21,16).
value_Glucose(21,112).
value_Insulin(21,1).
date(22,42487).
time(22,15:17:26).
value_Carbs(22,111).
value_Glucose(22,266).
value_Insulin(22, 13.500000).
date(23,42487).
time(23,20:16:38).
value_Carbs(23,65).
value_Glucose(23,108).
value_Insulin(23,10).
date(24,42488).
time(24,10:11:31).
value_Carbs(24,20).
value_Glucose(24,89).
value_Insulin(24, 2.500000).
date(25,42488).
time(25,14:31:12).
value_Carbs(25,60).
value_Glucose(25,258).
value_Insulin(25,6).
date(26,42488).
time(26,17:44:53).
value_Carbs(26,20).
value_Glucose(26,57).
value_Insulin(26,7).
date(27,42488).
time(27,21:26:38).
value_Carbs(27,95).
value_Glucose(27,227).
value_Insulin(27,8).
date(28,42489).
time(28,9:51:14).
value_Carbs(28,50).
value_Glucose(28,129).
value_Insulin(28, 9.500000).
date(29,42490).
time(29,9:23:7).
value_Carbs(29,20).
value_Glucose(29,200).
value_Insulin(29, 2.500000).
date(30,42490).
time(30,14:14:50).
value_Carbs(30,150).
value_Glucose(30,207).
value_Insulin(30,17).
date(31,42490).
time(31,20:35:16).
value_Carbs(31,45).
value_Glucose(31,182).
value_Insulin(31, 6.500000).

View File

@@ -0,0 +1,18 @@
:- determination(upgrade/1,date/2).
:- determination(upgrade/1,time/2).
:- determination(upgrade/1,value_Carbs/2).
:- determination(upgrade/1,value_Glucose/2).
:- determination(upgrade/1,value_Insulin/2).
:- modeh(*,upgrade(+iD)).
:- modeb(*,date(+iD,-date)).
:- modeb(*,date(+iD,#date)).
:- modeb(*,time(+iD,-time)).
:- modeb(*,time(+iD,#time)).
:- modeb(*,value_Carbs(+iD,-value_Carbs)).
:- modeb(*,value_Carbs(+iD,#value_Carbs)).
:- modeb(*,value_Glucose(+iD,-value_Glucose)).
:- modeb(*,value_Glucose(+iD,#value_Glucose)).
:- modeb(*,value_Insulin(+iD,-value_Insulin)).
:- modeb(*,value_Insulin(+iD,#value_Insulin)).

View File

@@ -0,0 +1,113 @@
time
7:32:4: 1
7:33:27: 1
7:33:31: 1
8:4:7: 1
9:23:7: 1
9:31:40: 1
9:32:20: 1
9:51:14: 1
10:2:53: 1
10:11:31: 1
10:24:41: 1
10:30:33: 1
10:36:58: 1
14:9:37: 1
14:14:50: 1
14:31:12: 1
15:1:50: 1
15:17:26: 1
15:25:47: 1
15:51:3: 1
16:11:11: 1
17:44:53: 1
20:16:38: 1
20:27:1: 1
20:35:16: 1
20:45:52: 1
20:55:59: 1
21:26:38: 1
21:28:10: 1
21:33:31: 1
23:19:4: 1
value_Glucose
52: 1
57: 1
69: 1
72: 1
89: 2
99: 2
103: 1
108: 1
112: 1
125: 1
129: 1
134: 1
136: 1
143: 1
168: 1
182: 1
191: 1
200: 1
203: 1
207: 1
222: 1
227: 1
256: 2
258: 1
260: 1
264: 1
266: 1
274: 1
date
42481: 3
42482: 1
42483: 3
42484: 4
42485: 4
42486: 4
42487: 4
42488: 4
42489: 1
42490: 3
value_Carbs
16: 2
18: 4
19: 1
20: 6
21: 1
40: 1
45: 1
46: 1
50: 4
55: 1
60: 1
65: 1
85: 1
95: 1
100: 2
111: 1
115: 1
150: 1
value_Insulin
1.500000: 1
2.500000: 2
5.500000: 1
6.500000: 3
7.500000: 2
9.500000: 1
10.500000: 2
13.500000: 1
1: 2
2: 1
3: 1
4: 1
5: 2
6: 1
7: 2
8: 2
9: 1
10: 2
14: 1
17: 1
21: 1

View File

@@ -0,0 +1,197 @@
days(Y,M,D,Total) :-
years_to_days(Y, D1),
months_to_day(M, Y, D2),
Total is D1+D2+D-1.
years_to_days(Y0, DY) :-
Y1 is Y0-1900,
DY is Y1*365+((Y1+3)//4).
months_to_day(1,_,0).
months_to_day(2,_,31).
months_to_day(3,Y,DM) :-
extra_day(Y,ED),
DM is 31+28+ED.
months_to_day(4,Y,DM) :-
extra_day(Y,ED),
DM is 31+28+31+ED.
months_to_day(5,Y,DM) :-
extra_day(Y,ED),
DM is 31+28+31+30+ED.
months_to_day(6,Y,DM) :-
extra_day(Y,ED),
DM is 31+28+31+30+31+ED.
months_to_day(7,Y,DM) :-
extra_day(Y,ED),
DM is 31+28+31+30+31+30+ED.
months_to_day(8,Y,DM) :-
extra_day(Y,ED),
DM is 31+28+31+30+31+30+31+ED.
months_to_day(9,Y,DM) :-
extra_day(Y,ED),
DM is 31+28+31+30+31+30+31+31+ED.
months_to_day(10,Y,DM) :-
extra_day(Y,ED),
DM is 31+28+31+30+31+30+31+31+30+ED.
months_to_day(11,Y,DM) :-
extra_day(Y,ED),
DM is 31+28+31+30+31+30+31+31+30+31+ED.
months_to_day(12,Y,DM) :-
extra_day(Y,ED),
DM is 31+28+31+30+31+30+31+31+30+31+30+ED.
months_to_day(13,Y,DM) :- % should never succeed...
extra_day(Y,ED),
DM is 31+28+31+30+31+30+31+31+30+31+30+31+ED.
extra_day(Y,1) :- Y mod 4 == 0, !.
extra_day(_,0).
date(Total, Y, M, D) :-
get_years(Total, Y, DaysLeft),
get_months(DaysLeft, Y, M, D0),
D is D0+1.
get_years(Total, Y, DaysLeft) :-
daysperyear(Y,D0),
D0 =< Total,
Y1 is Y+1,
daysperyear(Y1,D1),
D1 > Total, !,
DaysLeft is Total-D0.
get_months(Total, Y, Month, Days) :-
months_to_day(Month, Y, DM),
DM =< Total,
Month1 is Month+1,
months_to_day(Month1, Y, DM1),
DM1 > Total, !,
Days is Total-DM.
gendays(120,_) :- !.
gendays(I0,D0) :- !,
J is I0+1900,
format('days(~d,~d).~n',[J,D0]),
( I0 mod 4 =:= 0 -> D is D0+366 ; D is D0+365 ),
I is I0+1,
gendays(I, D).
daysperyear(1900,0).
daysperyear(1901,366).
daysperyear(1902,731).
daysperyear(1903,1096).
daysperyear(1904,1461).
daysperyear(1905,1827).
daysperyear(1906,2192).
daysperyear(1907,2557).
daysperyear(1908,2922).
daysperyear(1909,3288).
daysperyear(1910,3653).
daysperyear(1911,4018).
daysperyear(1912,4383).
daysperyear(1913,4749).
daysperyear(1914,5114).
daysperyear(1915,5479).
daysperyear(1916,5844).
daysperyear(1917,6210).
daysperyear(1918,6575).
daysperyear(1919,6940).
daysperyear(1920,7305).
daysperyear(1921,7671).
daysperyear(1922,8036).
daysperyear(1923,8401).
daysperyear(1924,8766).
daysperyear(1925,9132).
daysperyear(1926,9497).
daysperyear(1927,9862).
daysperyear(1928,10227).
daysperyear(1929,10593).
daysperyear(1930,10958).
daysperyear(1931,11323).
daysperyear(1932,11688).
daysperyear(1933,12054).
daysperyear(1934,12419).
daysperyear(1935,12784).
daysperyear(1936,13149).
daysperyear(1937,13515).
daysperyear(1938,13880).
daysperyear(1939,14245).
daysperyear(1940,14610).
daysperyear(1941,14976).
daysperyear(1942,15341).
daysperyear(1943,15706).
daysperyear(1944,16071).
daysperyear(1945,16437).
daysperyear(1946,16802).
daysperyear(1947,17167).
daysperyear(1948,17532).
daysperyear(1949,17898).
daysperyear(1950,18263).
daysperyear(1951,18628).
daysperyear(1952,18993).
daysperyear(1953,19359).
daysperyear(1954,19724).
daysperyear(1955,20089).
daysperyear(1956,20454).
daysperyear(1957,20820).
daysperyear(1958,21185).
daysperyear(1959,21550).
daysperyear(1960,21915).
daysperyear(1961,22281).
daysperyear(1962,22646).
daysperyear(1963,23011).
daysperyear(1964,23376).
daysperyear(1965,23742).
daysperyear(1966,24107).
daysperyear(1967,24472).
daysperyear(1968,24837).
daysperyear(1969,25203).
daysperyear(1970,25568).
daysperyear(1971,25933).
daysperyear(1972,26298).
daysperyear(1973,26664).
daysperyear(1974,27029).
daysperyear(1975,27394).
daysperyear(1976,27759).
daysperyear(1977,28125).
daysperyear(1978,28490).
daysperyear(1979,28855).
daysperyear(1980,29220).
daysperyear(1981,29586).
daysperyear(1982,29951).
daysperyear(1983,30316).
daysperyear(1984,30681).
daysperyear(1985,31047).
daysperyear(1986,31412).
daysperyear(1987,31777).
daysperyear(1988,32142).
daysperyear(1989,32508).
daysperyear(1990,32873).
daysperyear(1991,33238).
daysperyear(1992,33603).
daysperyear(1993,33969).
daysperyear(1994,34334).
daysperyear(1995,34699).
daysperyear(1996,35064).
daysperyear(1997,35430).
daysperyear(1998,35795).
daysperyear(1999,36160).
daysperyear(2000,36525).
daysperyear(2001,36891).
daysperyear(2002,37256).
daysperyear(2003,37621).
daysperyear(2004,37986).
daysperyear(2005,38352).
daysperyear(2006,38717).
daysperyear(2007,39082).
daysperyear(2008,39447).
daysperyear(2009,39813).
daysperyear(2010,40178).
daysperyear(2011,40543).
daysperyear(2012,40908).
daysperyear(2013,41274).
daysperyear(2014,41639).
daysperyear(2015,42004).
daysperyear(2016,42369).
daysperyear(2017,42735).
daysperyear(2018,43100).
daysperyear(2019,43465).

View File

@@ -0,0 +1,32 @@
% taken from http://stackoverflow.com/questions/12272888/default-prolog-predicate-sort
/* File: order_by.pl
Author: Carlo,,,
Created: Sep 5 2012
Purpose: sort fact
*/
:- module(order_by,
[order_by/2
]).
:- use_module(library(apply_macros)).
order_by(PredicateIndicator, Argument) :-
( PredicateIndicator = Module:Functor/Arity
; PredicateIndicator = Functor/Arity, Module = user
),
length(EmptyArgs, Arity),
P =.. [Functor|EmptyArgs],
findall(P, retract(Module:P), L),
predsort(by_arg(Argument), L, S),
maplist(assert_in_module(Module), S).
assert_in_module(Module, P) :-
assertz(Module:P).
by_arg(Argument, Delta, E1, E2) :-
arg(Argument, E1, A1),
arg(Argument, E2, A2),
( A1 @< A2
-> Delta = <
; Delta = >
).

1
regression/dados/run Executable file
View File

@@ -0,0 +1 @@
yap -l csv2pl_v3 -- --modes dados.csv > dados.yap

10
regression/plsimple.pl Normal file
View File

@@ -0,0 +1,10 @@
:- use_module(library(plunit)).
:- begin_tests(lists).
:- use_module(library(lists)).
test(reverse) :-
reverse([a,b], [b,a]).
:- end_tests(lists).