34
35:- module(readln,
36 [ readln/1, 37 readln/2, 38 readln/5 39 ]). 40:- autoload(library(lists),[append/3,member/2]).
131readln(Read) :- 132 string_codes("_0123456789", Arg2),
133 rl_readln(Line, LastCh, [10], Arg2, uppercase),
134 ( LastCh == end_of_file
135 -> append(Line,[end_of_file], Read)
136 ; Read = Line
137 ).
138
139readln(Read, LastCh):-
140 string_codes("_0123456789", Arg2),
141 rl_readln(Read, LastCh, [10], Arg2, uppercase).
142
143readln(P, EOF, StopChars, WordChars, Case) :-
144 ( var(StopChars)
145 -> Arg1 = [10]
146 ; Arg1 = StopChars
147 ),
148 ( var(WordChars)
149 -> string_codes("01234567890_", Arg2)
150 ; Arg2 = WordChars
151 ),
152 ( var(Case)
153 -> Arg3 = lowercase
154 ; Arg3 = Case
155 ),
156 rl_readln(P, EOF, Arg1, Arg2, Arg3).
157
158rl_readln(P, EOF, StopChars, WordChars, Case) :-
159 rl_initread(L, EOF, StopChars),
160 rl_blanks(L, LL),
161 !,
162 rl_words(P, LL,[], options(WordChars, Case)),
163 !.
164
165rl_initread(S, EOF, StopChars) :-
166 get_code(K),
167 rl_readrest(K, S, EOF, StopChars).
168
169rl_readrest(-1, [], end_of_file, _) :- !.
170rl_readrest(0'\\, [K1|R], EOF, StopChars) :-
171 get_code(K1), 172 get_code(K2),
173 rl_readrest(K2, R, EOF, StopChars).
174rl_readrest(K, [K], K, StopChars) :- 175 member(K, StopChars),
176 !.
177rl_readrest(K, [K|R], EOF, StopChars) :- 178 get_code(K1),
179 rl_readrest(K1, R, EOF, StopChars).
180
181rl_words([W|Ws], S1, S4, Options) :-
182 rl_word(W, S1, S2, Options),
183 !,
184 rl_blanks(S2, S3),
185 rl_words(Ws, S3, S4, Options).
186rl_words([], S1, S2, _) :-
187 rl_blanks(S1, S2),
188 !.
189rl_words([], S, S, _).
190
191rl_word(N, [46|S1], S3, _) :- 192 rl_basic_num(N1, S1, S2), 193 !,
194 rl_basic_nums(Rest, S2, S3, dot), 195 name(N,[48, 46, N1|Rest]). 196rl_word(N, S0, S2, _) :-
197 rl_basic_num(N1, S0, S1),
198 !,
199 rl_basic_nums(Rest, S1, S2, _),
200 name(N,[N1|Rest]).
201rl_word(W, S0, S2, Options) :-
202 rl_basic_char(C1, S0, S1, Options),
203 !,
204 rl_basic_chars(Rest, S1, S2, Options),
205 name(W, [C1|Rest]).
206rl_word(P,[C|R], R, _) :-
207 name(P, [C]),
208 !.
209
210rl_basic_chars([A|As], S0, S2, Options) :-
211 rl_basic_char(A, S0, S1, Options),
212 !,
213 rl_basic_chars(As, S1, S2, Options).
214rl_basic_chars([], S, S, _).
215
216rl_basic_nums([46,N|As], [46|S1], S3, Dot) :- 217 var(Dot), 218 rl_basic_num(N, S1, S2),
219 !,
220 rl_basic_nums(As, S2, S3, dot).
221rl_basic_nums([A|As], S0, S2, Dot) :-
222 rl_basic_num(A, S0, S1),
223 !,
224 rl_basic_nums(As, S1, S2, Dot).
225rl_basic_nums([], S, S, _).
226
227rl_blanks([C|S0], S1) :-
228 rl_blank(C),
229 !,
230 rl_blanks(S0, S1).
231rl_blanks(S, S).
232
234
235rl_basic_char(A, [C|S], S, options(WordChars, Case)) :-
236 rl_lc(C, A, WordChars, Case).
237
238rl_basic_num(N, [N|R], R) :-
239 code_type(N, digit).
240
241rl_blank(X) :-
242 code_type(X, space).
243
244rl_lc(X, X1, _, Case) :-
245 code_type(X, upper),
246 !,
247 rl_fix_case(Case, X, X1).
248rl_lc(X, X, _, _) :-
249 code_type(X, lower).
250rl_lc(X, X, WordChars, _) :-
251 memberchk(X, WordChars).
252
253rl_fix_case(lowercase, U, L) :-
254 !,
255 code_type(L, lower(U)).
256rl_fix_case(_, C, C)
Read line as list of tokens
Read a sentence from the current input stream and convert it into a list of atoms and numbers:
The reader is flexible, you can define yourself:
character(s)
that make up a word (execpt the characters A-Z, a-z that always make up words!! and (real)-numbers that always are grouped together!!)readln/1 The default setting for readln/1 is
underscore('_')
and numbers 0-9 as part of wordscharacter(s)
: instantiate argument 3 with the list of ASCII code's of the desired stop characters (Note: you can also say: ".!?", what is equivalent to [46,33,63]).character(s)
: instantiate argument 4 with the list of ASCII code's of the desired word-part characters (Note: wou can also say: "", what is equivalent to [] ; i.e. no extra characters).Main predicates provided:
read_sentence(P,Case)
:-readln(P,_,".!?","_0123456789",Case)
.read_in(P)
:- % with numbers as separatereadln(P,Eof,_,"", _)
. % entities.read_atom(A)
:- % stop on newline,readln(A,_,_," ",_)
. % space is part of word