1 :- module(ltsmin_trace, [csv_to_trace/3]).
2
3 :- use_module(library(lists)).
4 :- use_module(library(fastrw)).
5 :- use_module(probsrc(tools), [split_chars/3, split_complex_sep/3]).
6
7 :- use_module(extension('ltsmin/ltsmin_c_interface'), [read_hex_str/2, free_str/1, loadfr/0,atom_charptr/2]).
8 :- use_module(extension('ltsmin/ltsmin'), [generate_bindings/3]).
9
10
11 read_all_lines(Acc, R) :-
12 read_line(L),
13 (L == end_of_file
14 -> Acc = R
15 ; read_all_lines([L|Acc], R)).
16
17
18 read_trace(Filename, TypeInfo, Lines, ButLastLines) :-
19 open(Filename, read, Stream),
20 see(Stream),
21 read_all_lines([], ReversedLines),
22 seen,
23 ReversedLines = [_LastLine|ButLastLinesRev],
24 reverse(ReversedLines, [TypeInfo|Lines]),
25 reverse(ButLastLinesRev, [TypeInfo|ButLastLines]).
26
27
28 %% HACK: some values are not pretty printed into the #hexcode# representation
29 %% TODO: either fix LTSmin to do so or handle these cases separately (pk, 30.11.2017)
30 fast_buf_hex_to_term("\"D]\"", []) :- !.
31 fast_buf_hex_to_term(HexStr, Term) :-
32 read_hex_str(HexStr, Tmp),
33 fast_buf_read(Term, Tmp),
34 free_str(Tmp).
35
36
37
38 line_to_state(VariableList, Line, State) :-
39 split_chars(Line, ",", Vals),
40 length(VariableList, Len),
41 length(BinState, Len),
42 prefix(Vals, BinState),
43 maplist(fast_buf_hex_to_term, BinState, UnboundState),
44 generate_bindings(UnboundState, VariableList, State).
45
46 butlast(L, BL) :-
47 reverse(L, [_Last|Rev]),
48 reverse(Rev, BL).
49
50 extract_op(Line, Op) :-
51 split_complex_sep(Line, ",,", Vals),
52 reverse(Vals, [QuotedOpCodesFRW|_]),
53 butlast(QuotedOpCodesFRW, [_|OpCodesFRW]),
54 atom_charptr(OpCodesFRW, OpFRW),
55 fast_buf_read(Op, OpFRW),
56 free_str(OpFRW).
57
58 :- meta_predicate take_while(1,*,*).
59 :- meta_predicate take_while1(*,1,*).
60 take_while(Pred, List, Res) :-
61 take_while1(List, Pred, Res).
62 take_while1([], _, []).
63 take_while1([H|T], Pred, R) :-
64 (call(Pred, H)
65 -> R = [H|RT], take_while1(T, Pred, RT)
66 ; R = []).
67
68
69 starts_with(Pre, Str) :-
70 append(Pre, _, Str).
71
72 split_at_colon(S, L, R) :-
73 split_chars(S, ":", [L, R]).
74
75 extract_variable_list(TypeInfoLine, Variables, _Types) :-
76 split_complex_sep(TypeInfoLine, ",,", TypeInfo),
77 take_while(starts_with("DA"), TypeInfo, TypedVariables),
78 maplist(split_at_colon, TypedVariables, DAVariables, _TypesAsStrings),
79 maplist(append("DA"), VariablesStrs, DAVariables),
80 maplist(atom_codes, Variables, VariablesStrs).
81
82 csv_to_trace(FileName, StateList, ['$init_state'|OpList]) :-
83 loadfr,
84 read_trace(FileName, TypeInfo, [DummyState|Lines], [DummyState|ButLastLines]),
85 extract_variable_list(TypeInfo, VariableList, _TypeList),
86 extract_op(DummyState, '$init_state'),
87 maplist(line_to_state(VariableList), Lines, StateList),
88 maplist(extract_op, ButLastLines, OpList).