Replies: 11 comments 6 replies
-
Without actually running the code my guess would be that the Try this instead.
After further looking at the rest of the predicates, most of the others also need cuts, |
Beta Was this translation helpful? Give feedback.
-
Try instead: string([X|Xs]) --> [X], {once((char_type(X, alpha); memberchk(X, "_")))}, !, string(Xs).
string([]) --> [].
num([X|Xs]) --> [X], {char_type(X, numeric)}, !, num(Xs).
num([]) --> []. I.e. do eager parsing instead of lazy parsing for those two non-terminals. |
Beta Was this translation helpful? Give feedback.
-
Paulo gave more of what needs changing. Also this needs some cuts
most likely
|
Beta Was this translation helpful? Give feedback.
-
Thanks for the suggestions, it is much faster now! This is what I have currently: :- use_module(library(dcgs)).
:- use_module(library(lists)).
:- use_module(library(charsio)).
:- use_module(library(pio)).
ws --> [W], { char_type(W, whitespace) }, ws.
ws --> [].
string([X|Xs]) --> [X], { once((char_type(X, alpha) ; memberchk(X, "_"))) }, !, string(Xs).
string([]) --> [].
num([X|Xs]) --> [X], {char_type(X, numeric)}, !, num(Xs).
num([]) --> [].
decimal(N) --> num(A), ".", num(B), { append(A, ".", A0), append(A0, B, N) }.
unit(ms) --> "ms", !.
unit(ns) --> "ns", !.
unit(us) --> "us", !.
unit(s) --> "s", !.
unit(m) --> "m".
result(result(N, unit(U))) --> decimal(N), !, " ", unit(U), !.
benchmark_header(Tag, Type) --> string(Tag), " - ", string(Type).
benchmark_body(Name, Mean, Std_dev) -->
string(Name), !, ws, !, num(_Samples), !, ws, !, num(_Iterations), !, ws, !, result(_),
!, ws, !, result(Mean), !, ws, !, result(_LowMean), !, ws, !, result(_HighMean),
!, ws, !, result(Std_dev), !, ws, !, result(_LowStd_dev), !, ws, !, result(_HighStd_dev), !, ws, !.
benches([body(N, M , S)]) --> benchmark_body(N, M, S), ws.
benches([body(N, M , S)|Bs]) --> benchmark_body(N, M, S), ws, benches(Bs).
benchmark(header(Tag, Type), Bs) -->
"-------------------------------------------------------------------------------\n",
benchmark_header(Tag, Type), !, ws, !,
"-------------------------------------------------------------------------------\n",
string(_File), ".cpp:", num(_Line), !, ws, !,
"...............................................................................\n\n",
"benchmark name samples iterations estimated", !, ws,
" mean low mean high mean", !, ws,
" std dev low std dev high std dev", !, ws,
"-------------------------------------------------------------------------------\n", !,
benches(Bs). I am not sure if all my cuts are in sensible places, so any comments would be appreciated, but I think I understand the idea of adding the cuts!. |
Beta Was this translation helpful? Give feedback.
-
For the units, you can also do a look-ahead to benefit from first-argument indexing: result(result(N, unit(U))) --> decimal(N), " ", [C], unit(C, U).
unit(n, ns) --> "s".
unit(u, us) --> "s".
unit(s, s) --> [].
unit(m, ms) --> "s", !.
unit(m, m) --> []. |
Beta Was this translation helpful? Give feedback.
-
As I noted I work with SWI-Prolog.
Can you list the similar results for Scryer. I am curious what it shows. (Sorry I don't have Scryer currently installed). |
Beta Was this translation helpful? Give feedback.
-
I think by far the most significant performance improvement you can make to this code is to test earlier whether a described character is of the desired type. In particular, if you change the two rules: string([X|Xs]) --> [X], string(Xs), { char_type(X, alpha); memberchk(X, "_") }. num([X|Xs]) --> [X], num(Xs), {char_type(X, numeric)}. to, respectively: string([X|Xs]) --> [X], { char_type(X, alpha); memberchk(X, "_") }, string(Xs). num([X|Xs]) --> [X], {char_type(X, numeric)}, num(Xs). then the time for parsing the file decreases dramatically. Note that adding |
Beta Was this translation helpful? Give feedback.
-
As a follow up to what Markus is saying, see: https://stackoverflow.com/a/12942551/1243762 |
Beta Was this translation helpful? Give feedback.
-
In your larger example input there is a problem
Based on the DCG given would have expected something like
which is a tag and type separated by Should the DCG be modified or should the input be changed? |
Beta Was this translation helpful? Give feedback.
-
Here is a much more complete example done using SWI-Prolog. Since this a project for your course you can learn from it and use it for your talk. Take from it what you like and pass on what you don't. I know the expected comments will be
:- module(example,
[
check/1
]).
% -----------------------------------------------------------------------------
:- set_prolog_flag(double_quotes, codes).
:- set_prolog_flag(back_quotes, string).
% ----------------------------------------------------------------------------
:- nb_setval(line_count,0).
inc(line_count) :-
nb_getval(line_count,Line_count0),
Line_count is Line_count0 + 1,
nb_setval(line_count,Line_count).
ws --> ws(_).
'ws+' --> 'ws+'(_).
'ws*' --> 'ws*'(_).
'ws+'([H|T]) -->
ws(H),
'ws*'(T).
'ws*'([H|T]) -->
ws(H), !,
'ws*'(T).
'ws*'([]) --> [].
ws(0x20) --> " ".
ws(0x0A) -->
"\n",
{ inc(line_count) }.
ws(0x0D) --> "\r".
ws(0x09) --> "\t".
eol --> eol(_).
eol(eol(0x0D,0x0A)) -->
"\r\n",
!,
{ inc(line_count) }.
eol(eol(0x0D)) --> "\r", !.
eol(eol(0x0A)) -->
"\n",
{ inc(line_count) }.
string --> string(_).
string(string(String)) -->
'string_char+'(Codes),
{ string_codes(String,Codes) }.
'string_char+'([H|T]) -->
string_char(H),
'string_char*'(T).
'string_char*'([H|T]) -->
string_char(H), !,
'string_char*'(T).
'string_char*'([]) --> [].
string_char(C) -->
[C],
{ char_type(C,alpha) }, !.
string_char(0'_) --> "_".
num --> num(_).
num(num(Number)) -->
'digit+'(Digits),
{ number_codes(Number,Digits) }.
decimal(decimal(Decimal)) -->
'digit+'(T0,T1),
period(T1,T2),
'digit+'(T2,T),
{
T = [],
number_codes(Decimal,T0)
}.
% closed list variation
'digit+'([H|T]) -->
digit(H),
'digit*'(T).
% closed list variation
'digit*'([H|T]) -->
digit(H), !,
'digit*'(T).
'digit*'([]) --> [].
% open list variation
'digit+'(T0,T) -->
digit(T0,T1),
'digit*'(T1,T).
% open list variation
'digit*'(T0,T) -->
digit(T0,T1), !,
'digit*'(T1,T).
'digit*'(T,T) --> [].
% open list variation
digit(T0,T) -->
digit(C),
{ T0 = [C|T] }.
digit(C) -->
[C],
{ between(0'0,0'9,C) }, !.
% open list variation
period(T0,T) -->
period(C),
{ T0 = [C|T] }.
period(0'.) -->
".".
unit(0'n, unit(ns)) --> "s".
unit(0'u, unit(us)) --> "s".
unit(0's, unit(s)) --> [].
unit(0'm, unit(ms)) --> "s", !.
unit(0'm, unit(m)) --> [].
result --> result(_).
result(result(N, U)) -->
decimal(decimal(N)),
" ",
[C], unit(C, unit(U)).
benchmark_detail(benchmark_detail(Name, mean(Mean_value,Mean_unit), std_dev(Std_dev_value,Std_dev_unit))) -->
string(string(Name)), 'ws+', num, 'ws+', num, 'ws+', result, eol,
'ws+', result(result(Mean_value,Mean_unit)), 'ws+', result, 'ws+', result, eol,
'ws+', result(result(Std_dev_value,Std_dev_unit)), 'ws+', result, 'ws+', result, eol, !.
'benchmark_detail+'([H|T]) -->
'ws*',
benchmark_detail(H),
'benchmark_detail*'(T).
'benchmark_detail*'([H|T]) -->
'ws*',
benchmark_detail(H), !,
'benchmark_detail*'(T).
'benchmark_detail*'([]) -->
'ws*'.
benchmark_header(benchmark_header(Tag, Type)) -->
string(string(Tag)),
" - ",
string(string(Type)).
benchmark_detail_header(benchmark_detail_header(Tag,Type)) -->
"-------------------------------------------------------------------------------",eol,
benchmark_header(benchmark_header(Tag, Type)),eol,
"-------------------------------------------------------------------------------",eol,
string, ".cpp:", num, eol,
"...............................................................................",eol,
eol,
"benchmark name samples iterations estimated",eol,
" mean low mean high mean",eol,
" std dev low std dev high std dev",eol,
"-------------------------------------------------------------------------------",eol.
% closed list variation
'benchmark+'([H|T]) -->
'ws*',
benchmark(H),
'benchmark*'(T).
% closed list variation
'benchmark*'([H|T]) -->
'ws*',
benchmark(H), !,
'benchmark*'(T).
'benchmark*'([]) --> [].
benchmark(benchmark(Tag, Type, Details)) -->
benchmark_detail_header(benchmark_detail_header(Tag,Type)),
'benchmark_detail+'(Details).
benchmarks(Benchmarks) -->
% { gtrace },
'benchmark+'(Benchmarks),
'ws*',
(
"===============================================================================", !
;
[]
),
'ws*'.
lookahead(C1,C2,C3),[C1,C2,C3] --> [C1],[C2],[C3].
peek -->
lookahead(C1,C2,C3),
{
format('~d,~d,~d~n',[C1,C2,C3]),
char_code(Ch_1,C1),
char_code(Ch_2,C2),
char_code(Ch_3,C3),
format('~p,~p,~p~n',[Ch_1,Ch_2,Ch_3])
}.
input_file('benchmarks.txt').
check(1) :-
input_file(Input_file),
DCG = benchmarks(Benchmarks),
phrase_from_file(DCG, Input_file),
print_term(Benchmarks,[]).
check(2) :-
setup_call_cleanup(
(
input_file(Input_file),
open(Input_file,read,Input_stream)
),
(
read_stream_to_codes(Input_stream, Codes),
DCG = benchmarks(Benchmarks),
phrase(DCG,Codes,Rest)
),
(
assertion( Rest == [] ),
close(Input_stream)
)
),
print_term(Benchmarks,[]). Example run. Only demonstrates first two because it fails on
Hope you or others can learn something from it. Ask questions if you have any but I don't plan to do another complete example for any more questions. :) |
Beta Was this translation helpful? Give feedback.
-
@euanlacy : Could you post your current version? There could be some further improvements. |
Beta Was this translation helpful? Give feedback.
-
Hi, I've written a prolog script to read in output from a cpp benchmarking library, but it takes 10s of seconds to parse, which seems excessive. I was wondering if I've done anything obviously wrong which is affecting performance?
Which parses output like this:
Beta Was this translation helpful? Give feedback.
All reactions