more fixes to messages
improve lineutils git-svn-id: https://yap.svn.sf.net/svnroot/yap/trunk@2117 b08c6af1-5177-4d33-ba66-4b1c6b8b522a
This commit is contained in:
parent
6a7e26eab1
commit
a3f3d62b1b
@ -2,11 +2,21 @@
|
|||||||
[search_for/3,
|
[search_for/3,
|
||||||
scan_natural/3,
|
scan_natural/3,
|
||||||
scan_integer/3,
|
scan_integer/3,
|
||||||
split/3
|
split/3,
|
||||||
|
glue/3,
|
||||||
|
filter/3,
|
||||||
|
copy_line/2,
|
||||||
|
file_filter/3
|
||||||
]).
|
]).
|
||||||
|
|
||||||
|
:- meta_predicate filter(+,+,:).
|
||||||
|
|
||||||
:- use_module(library(lists),
|
:- use_module(library(lists),
|
||||||
[member/2]).
|
[member/2,
|
||||||
|
append/3]).
|
||||||
|
|
||||||
|
:- use_module(library(readutil),
|
||||||
|
[read_line_to_codes/2]).
|
||||||
|
|
||||||
|
|
||||||
search_for(C) --> [C], !.
|
search_for(C) --> [C], !.
|
||||||
@ -27,15 +37,55 @@ scan_natural(N0,N) -->
|
|||||||
get_natural(N1,N).
|
get_natural(N1,N).
|
||||||
scan_natural(N,N) --> [].
|
scan_natural(N,N) --> [].
|
||||||
|
|
||||||
split(String, SplitCodes, [S|Strings]) :-
|
split(String, SplitCodes, Strings) :-
|
||||||
split(SplitCodes, S, Strings, String, []).
|
split_at_blank(SplitCodes, Strings, String, []).
|
||||||
|
|
||||||
split(SplitCodes, [], [New|Set]) -->
|
split_at_blank(SplitCodes, More) -->
|
||||||
[C],
|
[C],
|
||||||
{ member(C, SplitCodes) }, !,
|
{ member(C, SplitCodes) }, !,
|
||||||
split(SplitCodes, New, Set).
|
split_at_blank(SplitCodes, More).
|
||||||
|
split_at_blank(SplitCodes, [[C|New]| More]) -->
|
||||||
|
[C], !,
|
||||||
|
split(SplitCodes, New, More).
|
||||||
|
split_at_blank(_, []) --> [].
|
||||||
|
|
||||||
|
split(SplitCodes, [], More) -->
|
||||||
|
[C],
|
||||||
|
{ member(C, SplitCodes) }, !,
|
||||||
|
split_at_blank(SplitCodes, More).
|
||||||
split(SplitCodes, [C|New], Set) -->
|
split(SplitCodes, [C|New], Set) -->
|
||||||
[C], !,
|
[C], !,
|
||||||
split(SplitCodes, New, Set).
|
split(SplitCodes, New, Set).
|
||||||
split(_, [], []) --> [].
|
split(_, [], []) --> [].
|
||||||
|
|
||||||
|
glue([], _, []).
|
||||||
|
glue([H|T], [B|_], Merged) :-
|
||||||
|
append(H, [B|Rest], Merged),
|
||||||
|
glue(T, [B], Rest).
|
||||||
|
|
||||||
|
copy_line(StreamInp, StreamOut) :-
|
||||||
|
read_line_to_codes(StreamInp, Line),
|
||||||
|
format(StreamOut, '~s~n', [Line]).
|
||||||
|
|
||||||
|
filter(StreamInp, StreamOut, Command) :-
|
||||||
|
repeat,
|
||||||
|
read_line_to_codes(StreamInp, Line),
|
||||||
|
(
|
||||||
|
Line == end_of_file
|
||||||
|
->
|
||||||
|
true
|
||||||
|
;
|
||||||
|
call(Command, Line, NewLine),
|
||||||
|
format(StreamOut, '~s~n', [NewLine]),
|
||||||
|
fail
|
||||||
|
).
|
||||||
|
|
||||||
|
|
||||||
|
file_filter(Inp, Out, Command) :-
|
||||||
|
open(Inp, read, StreamInp),
|
||||||
|
open(Out, write, StreamOut),
|
||||||
|
filter(StreamInp, StreamOut, Command),
|
||||||
|
close(StreamInp),
|
||||||
|
close(StreamOut).
|
||||||
|
|
||||||
|
|
||||||
|
@ -11,7 +11,7 @@
|
|||||||
* File: utilities for displaying messages in YAP. *
|
* File: utilities for displaying messages in YAP. *
|
||||||
* comments: error messages for YAP *
|
* comments: error messages for YAP *
|
||||||
* *
|
* *
|
||||||
* Last rev: $Date: 2008-02-23 01:32:31 $,$Author: vsc $ *
|
* Last rev: $Date: 2008-02-25 10:15:31 $,$Author: vsc $ *
|
||||||
* *
|
* *
|
||||||
* *
|
* *
|
||||||
*************************************************************************/
|
*************************************************************************/
|
||||||
@ -58,7 +58,7 @@ generate_message(prompt(BreakLevel,TraceDebug)) --> !,
|
|||||||
)
|
)
|
||||||
;
|
;
|
||||||
(
|
(
|
||||||
var(TraceDebug) ->
|
{ var(TraceDebug) } ->
|
||||||
[ '~d' - [BreakLevel] ]
|
[ '~d' - [BreakLevel] ]
|
||||||
;
|
;
|
||||||
[ '~d ~a' - [BreakLevel, TraceDebug] ]
|
[ '~d ~a' - [BreakLevel, TraceDebug] ]
|
||||||
@ -252,7 +252,7 @@ system_message(error(system_error(Message), Where)) -->
|
|||||||
system_message(error(type_error(T,_,Err,M), _Where)) -->
|
system_message(error(type_error(T,_,Err,M), _Where)) -->
|
||||||
[ 'TYPE ERROR- ~w: expected ~w, got ~w' - [T,Err,M] ].
|
[ 'TYPE ERROR- ~w: expected ~w, got ~w' - [T,Err,M] ].
|
||||||
system_message(error(type_error(TE,W), Where)) -->
|
system_message(error(type_error(TE,W), Where)) -->
|
||||||
{ type_error(TE, M) }, !,
|
{ object_name(TE, M) }, !,
|
||||||
[ 'TYPE ERROR- ~w: expected ~a, got ~w' - [Where,M,W] ].
|
[ 'TYPE ERROR- ~w: expected ~a, got ~w' - [Where,M,W] ].
|
||||||
system_message(error(type_error(TE,W), Where)) -->
|
system_message(error(type_error(TE,W), Where)) -->
|
||||||
[ 'TYPE ERROR- ~w: expected ~q, got ~w' - [Where,TE,W] ].
|
[ 'TYPE ERROR- ~w: expected ~q, got ~w' - [Where,TE,W] ].
|
||||||
@ -302,7 +302,7 @@ domain_error(predicate_spec, Opt) --> !,
|
|||||||
[ '~w invalid predicate specifier' - [Opt] ].
|
[ '~w invalid predicate specifier' - [Opt] ].
|
||||||
domain_error(radix, Opt) --> !,
|
domain_error(radix, Opt) --> !,
|
||||||
[ 'invalid radix ~w' - [Opt] ].
|
[ 'invalid radix ~w' - [Opt] ].
|
||||||
domain_error(read_option, Opt) --> !,
|
vdomain_error(read_option, Opt) --> !,
|
||||||
[ '~w invalid option to read_term' - [Opt] ].
|
[ '~w invalid option to read_term' - [Opt] ].
|
||||||
domain_error(semantics_indicatior, Opt) --> !,
|
domain_error(semantics_indicatior, Opt) --> !,
|
||||||
[ '~w expected predicate indicator, got ~w' - [Opt] ].
|
[ '~w expected predicate indicator, got ~w' - [Opt] ].
|
||||||
|
Reference in New Issue
Block a user