documentation improvemeents
This commit is contained in:
@@ -1,23 +1,4 @@
|
||||
|
||||
/** @defgroup LineUtilities Line Manipulation Utilities
|
||||
@ingroup YAPLibrary
|
||||
@{
|
||||
|
||||
This package provides a set of useful predicates to manipulate
|
||||
sequences of characters codes, usually first read in as a line. It is
|
||||
available by loading the library `library(lineutils)`.
|
||||
|
||||
|
||||
|
||||
@pred search_for(+ _Char_,+ _Line_)
|
||||
|
||||
|
||||
|
||||
Search for a character _Char_ in the list of codes _Line_.
|
||||
|
||||
|
||||
*/
|
||||
|
||||
:- module(line_utils,
|
||||
[search_for/2,
|
||||
search_for/3,
|
||||
@@ -35,6 +16,17 @@ Search for a character _Char_ in the list of codes _Line_.
|
||||
process/2
|
||||
]).
|
||||
|
||||
/** @defgroup LineUtilities Line Manipulation Utilities
|
||||
@ingroup YAPLibrary
|
||||
@{
|
||||
|
||||
This package provides a set of useful predicates to manipulate
|
||||
sequences of characters codes, usually first read in as a line. It is
|
||||
available by loading the library `library(lineutils)`.
|
||||
|
||||
|
||||
*/
|
||||
|
||||
:- meta_predicate
|
||||
filter(+,+,2),
|
||||
file_filter(+,+,2),
|
||||
@@ -48,6 +40,10 @@ Search for a character _Char_ in the list of codes _Line_.
|
||||
:- use_module(library(readutil),
|
||||
[read_line_to_codes/2]).
|
||||
|
||||
/**
|
||||
@pred search_for(+ _Char_,+ _Line_)
|
||||
Search for a character _Char_ in the list of codes _Line_.
|
||||
*/
|
||||
search_for(C,L) :-
|
||||
search_for(C, L, []).
|
||||
|
||||
@@ -55,6 +51,12 @@ search_for(C) --> [C], !.
|
||||
search_for(C) --> [_],
|
||||
search_for(C).
|
||||
|
||||
/** @pred scan_integer(? _Int_,+ _Line_,+ _RestOfLine_)
|
||||
|
||||
Scan the list of codes _Line_ for an integer _Nat_, either a
|
||||
positive, zero, or negative integer, and unify _RestOfLine_ with
|
||||
the remainder of the line.
|
||||
*/
|
||||
scan_integer(N) -->
|
||||
"-", !,
|
||||
scan_natural(0, N0),
|
||||
@@ -62,6 +64,12 @@ scan_integer(N) -->
|
||||
scan_integer(N) -->
|
||||
scan_natural(0, N).
|
||||
|
||||
/** @pred scan_natural(? _Nat_,+ _Line_,+ _RestOfLine_)
|
||||
|
||||
Scan the list of codes _Line_ for a natural number _Nat_, zero
|
||||
or a positive integer, and unify _RestOfLine_ with the remainder
|
||||
of the line.
|
||||
*/
|
||||
scan_natural(N) -->
|
||||
scan_natural(0, N).
|
||||
|
||||
@@ -72,9 +80,31 @@ scan_natural(N0,N) -->
|
||||
get_natural(N1,N).
|
||||
scan_natural(N,N) --> [].
|
||||
|
||||
/** @pred split(+ _Line_,- _Split_)
|
||||
|
||||
Unify _Words_ with a set of strings obtained from _Line_ by
|
||||
using the blank characters as separators.
|
||||
*/
|
||||
split(String, Strings) :-
|
||||
split_at_blank(" ", Strings, String, []).
|
||||
|
||||
/** @pred split(+ _Line_,+ _Separators_,- _Split_)
|
||||
|
||||
|
||||
|
||||
Unify _Words_ with a set of strings obtained from _Line_ by
|
||||
using the character codes in _Separators_ as separators. As an
|
||||
example, consider:
|
||||
|
||||
~~~~~{.prolog}
|
||||
?- split("Hello * I am free"," *",S).
|
||||
|
||||
S = ["Hello","I","am","free"] ?
|
||||
|
||||
no
|
||||
~~~~~
|
||||
|
||||
*/
|
||||
split(String, SplitCodes, Strings) :-
|
||||
split_at_blank(SplitCodes, Strings, String, []).
|
||||
|
||||
@@ -96,9 +126,28 @@ split(SplitCodes, [C|New], Set) -->
|
||||
split(SplitCodes, New, Set).
|
||||
split(_, [], []) --> [].
|
||||
|
||||
/** @pred fields(+ _Line_,- _Split_)
|
||||
|
||||
Unify _Words_ with a set of strings obtained from _Line_ by
|
||||
using the blank characters as field separators.
|
||||
|
||||
*/
|
||||
fields(String, Strings) :-
|
||||
fields(" ", Strings, String, []).
|
||||
|
||||
/** @pred fields(+ _Line_,+ _Separators_,- _Split_)
|
||||
|
||||
Unify _Words_ with a set of strings obtained from _Line_ by
|
||||
using the character codes in _Separators_ as separators for
|
||||
fields. If two separators occur in a row, the field is considered
|
||||
empty. As an example, consider:
|
||||
|
||||
~~~~~{.prolog}
|
||||
?- fields("Hello I am free"," *",S).
|
||||
|
||||
S = ["Hello","","I","am","","free"] ?
|
||||
~~~~~
|
||||
*/
|
||||
fields(String, FieldsCodes, Strings) :-
|
||||
dofields(FieldsCodes, First, More, String, []),
|
||||
(
|
||||
@@ -118,16 +167,32 @@ dofields(FieldsCodes, [C|New], Set) -->
|
||||
dofields(FieldsCodes, New, Set).
|
||||
dofields(_, [], []) --> [].
|
||||
|
||||
/** @pred glue(+ _Words_,+ _Separator_,- _Line_)
|
||||
|
||||
Unify _Line_ with string obtained by glueing _Words_ with
|
||||
the character code _Separator_.
|
||||
*/
|
||||
glue([], _, []).
|
||||
glue([A], _, A) :- !.
|
||||
glue([H|T], [B|_], Merged) :-
|
||||
append(H, [B|Rest], Merged),
|
||||
glue(T, [B], Rest).
|
||||
|
||||
/** @pred copy_line(+ _StreamInput_,+ _StreamOutput_)
|
||||
|
||||
Copy a line from _StreamInput_ to _StreamOutput_.
|
||||
*/
|
||||
copy_line(StreamInp, StreamOut) :-
|
||||
read_line_to_codes(StreamInp, Line),
|
||||
format(StreamOut, '~s~n', [Line]).
|
||||
|
||||
|
||||
/** @pred filter(+ _StreamInp_, + _StreamOut_, + _Goal_)
|
||||
|
||||
For every line _LineIn_ in stream _StreamInp_, execute
|
||||
`call(Goal,LineIn,LineOut)`, and output _LineOut_ to
|
||||
stream _StreamOut_.
|
||||
*/
|
||||
filter(StreamInp, StreamOut, Command) :-
|
||||
repeat,
|
||||
read_line_to_codes(StreamInp, Line),
|
||||
@@ -141,7 +206,11 @@ filter(StreamInp, StreamOut, Command) :-
|
||||
fail
|
||||
).
|
||||
|
||||
/** @pred process(+ _StreamInp_, + _Goal_)
|
||||
|
||||
For every line _LineIn_ in stream _StreamInp_, call
|
||||
`call(Goal,LineIn)`.
|
||||
*/
|
||||
process(StreamInp, Command) :-
|
||||
repeat,
|
||||
read_line_to_codes(StreamInp, Line),
|
||||
@@ -155,6 +224,12 @@ process(StreamInp, Command) :-
|
||||
).
|
||||
|
||||
|
||||
/** @pred file_filter(+ _FileIn_, + _FileOut_, + _Goal_)
|
||||
|
||||
For every line _LineIn_ in file _FileIn_, execute
|
||||
`call(Goal,LineIn,LineOut)`, and output _LineOut_ to file
|
||||
_FileOut_.
|
||||
*/
|
||||
file_filter(Inp, Out, Command) :-
|
||||
open(Inp, read, StreamInp),
|
||||
open(Out, write, StreamOut),
|
||||
@@ -162,6 +237,12 @@ file_filter(Inp, Out, Command) :-
|
||||
close(StreamInp),
|
||||
close(StreamOut).
|
||||
|
||||
/** @pred file_filter_with_initialization(+ _FileIn_, + _FileOut_, + _Goal_, + _FormatCommand_, + _Arguments_)
|
||||
|
||||
Same as file_filter/3, but before starting the filter execute
|
||||
`format/3` on the output stream, using _FormatCommand_ and
|
||||
_Arguments_.
|
||||
*/
|
||||
file_filter_with_initialization(Inp, Out, Command, FormatString, Parameters) :-
|
||||
open(Inp, read, StreamInp),
|
||||
open(Out, write, StreamOut),
|
||||
@@ -169,5 +250,6 @@ file_filter_with_initialization(Inp, Out, Command, FormatString, Parameters) :-
|
||||
filter(StreamInp, StreamOut, Command),
|
||||
close(StreamInp),
|
||||
close(StreamOut).
|
||||
|
||||
|
||||
/**
|
||||
@}
|
||||
*/
|
||||
|
Reference in New Issue
Block a user