. (utf8) 2:- module( 3 string_ext, 4 [ 5 max_string_length/2, % +Strings, -Max 6 message_lines/3, % +Message, +MaxLength, -Lines 7 read_string/2, % +In, -String 8 split_string/3, % +String, +SepChars, -SubStrings 9 string_code/2, % ?String, ?Code 10 string_ellipsis/3, % +Original, ?MaxLength, ?Ellipsed 11 string_list_concat/2, % +Strings, ?String 12 string_list_concat/3, % ?Strings, ?Separator, ?String 13 string_postfix/2, % +Original, ?Postfix 14 string_postfix/3, % +Original, ?Length, ?Postfix 15 string_prefix/2, % +Original, ?Prefix 16 string_prefix/3, % +Original, ?Length, ?Prefix 17 string_strip/2, % +Original, ?Stripped 18 string_strip/3, % +Original, +Strip, ?Stripped 19 string_truncate/3, % +Original, +MaxLength, ?Truncated 20 words_lines/3, % +Words, +MaxLength, -Lines 21 words_lines/4 % +Words, +MaxLength, +Separator, -Lines 22 ] 23).
31:- use_module(library(apply)). 32:- use_module(library(clpfd)). 33:- use_module(library(error)). 34:- use_module(library(lists)).
40max_string_length([], 0) :- !. 41max_string_length(Strings, Len) :- 42 aggregate_all( 43 max(Len0), 44 ( 45 member(String, Strings), 46 string_length(String, Len0) 47 ), 48 Len 49 ).
57message_lines(Message, Max, Lines) :-
58 string_list_concat(Words, ' ', Message),
59 words_lines(Words, Max, Lines).
68read_string(In, String) :-
69 read_string(In, _, String).
76split_string(String, SepChars, SubStrings) :-
77 split_string(String, SepChars, "", SubStrings).
85string_code(String, Code) :- 86 ground(String), !, 87 atom_string(Char, String), 88 char_code(Char, Code). 89string_code(String, Code) :- 90 ground(Code), !, 91 char_code(Char, Code), 92 atom_string(Char, String). 93string_code(String, Code) :- 94 instantiation_error([String,Code]).
?- string_ellipsis("monkey", Length, Ellipsed). Length = 2, Ellipsed = "mâ¦" ; Length = 3, Ellipsed = "moâ¦" ; Length = 4, Ellipsed = "monâ¦" ; Length = 5, Ellipsed = "monkâ¦" ; Length = 6, Ellipsed = "monkey".
122string_ellipsis(String, MaxLength, String) :- 123 MaxLength == inf, !. 124string_ellipsis(Original, MaxLength, Ellipsed) :- 125 string_length(Original, Length), 126 ( between(2, Length, MaxLength) 127 *-> ( MaxLength =:= Length 128 -> Ellipsed = Original 129 ; PrefixLength is MaxLength - 1, 130 string_prefix(Original, PrefixLength, Prefix), 131 string_concat(Prefix, "â¦", Ellipsed) 132 ) 133 ; must_be(between(2,inf), MaxLength), 134 Ellipsed = Original 135 ). 136 137:- begin_tests(string_ellipsis). 138 139test('string_ellipsis(+,+,+)', [forall(string_ellipsis_test(Original,MaxLength,Ellipsed))]) :- 140 string_ellipsis(Original, MaxLength, Ellipsed). 141test('string_ellipsis(+,+,-)', [forall(string_ellipsis_test(Original,MaxLength,Ellipsed))]) :- 142 string_ellipsis(Original, MaxLength, Ellipsed0), 143 assertion(Ellipsed == Ellipsed0). 144test('string_ellipsis(+,+,-) err_1', [error(type_error(between(2,inf),MaxLength))]) :- 145 member(MaxLength, [-1,0,1,'0']), 146 string_ellipsis("monkey", MaxLength, ""). 147test('string_ellipsis(+,-,-)', [forall(string_ellipsis_test(Original,MaxLength,Ellipsed))]) :- 148 string_ellipsis(Original, MaxLength, Ellipsed). 149 150string_ellipsis_test("monkey", 2, "mâ¦"). 151string_ellipsis_test("monkey", 3, "moâ¦"). 152string_ellipsis_test("monkey", 4, "monâ¦"). 153string_ellipsis_test("monkey", 5, "monkâ¦"). 154string_ellipsis_test("monkey", 6, "monkey"). 155string_ellipsis_test("monkey", 7, "monkey"). 156string_ellipsis_test("monkey", inf, "monkey"). 157 158:- end_tests(string_ellipsis).
170string_list_concat(Strings, String) :- 171 atomics_to_string(Strings, String). 172 173 174string_list_concat(Strings, Separator, String):- 175 ( ground(Strings-Separator) 176 -> atomics_to_string(Strings, Separator, String) 177 ; maplist(atom_string, [Separator0,String0], [Separator,String]), 178 atomic_list_concat(Strings0, Separator0, String0), 179 maplist(atom_string, Strings0, Strings) 180 ). 181 182:- begin_tests(string_list_concat). 183 184test(ambiguïty) :- 185 string_list_concat([], "a", ""). 186test('string_list_concat(+,+,+)', [forall(test_string_list_concat(Strings,Separator,String))]) :- 187 string_list_concat(Strings, Separator, String). 188test('string_list_concat(+,+,-)', [forall(test_string_list_concat(Strings,Separator,String))]) :- 189 string_list_concat(Strings, Separator, String0), 190 assertion(String == String0). 191test('string_list_concat(-,+,+)', [forall(test_string_list_concat(Strings,Separator,String))]) :- 192 string_list_concat(Strings0, Separator, String), 193 assertion(Strings == Strings0). 194 195test_string_list_concat([""], "a", ""). 196test_string_list_concat(["","","",""], "a", "aaa"). 197 198:- end_tests(string_list_concat).
218string_postfix(Original, Postfix) :- 219 string_postfix(Original, _, Postfix). 220 221 222string_postfix(Original, Length, Postfix) :- 223 sub_string(Original, _, Length, 0, Postfix). 224 225:- begin_tests(string_postfix). 226 227test('string_postfix(+,+,+)', [forall(test_string_postfix(Original,Length,Postfix))]) :- 228 string_postfix(Original, Length, Postfix). 229test('string_postfix(+,+,-)', [forall(test_string_postfix(Original,Length,Postfix))]) :- 230 string_postfix(Original, Length, Postfix0), 231 assertion(Postfix == Postfix0). 232test('string_postfix(+,-,+)', [forall(test_string_postfix(Original,Length,Postfix))]) :- 233 string_postfix(Original, Length0, Postfix), 234 assertion(Length == Length0). 235test('string_postfix(+,-,-)', [all(Length-Postfix == [4-"abcd",3-"bcd",2-"cd",1-"d",0-""])]) :- 236 string_postfix("abcd", Length, Postfix). 237 238test_string_postfix("abcd", 4, "abcd"). 239test_string_postfix("abcd", 3, "bcd"). 240test_string_postfix("abcd", 2, "cd"). 241test_string_postfix("abcd", 1, "d"). 242test_string_postfix("abcd", 0, ""). 243 244:- end_tests(string_postfix).
Fails in case Length exceeds the Original string length.
267string_prefix(Original, Prefix) :- 268 string_prefix(Original, _, Prefix). 269 270 271string_prefix(Original, Length, Prefix) :- 272 sub_string(Original, 0, Length, _, Prefix). 273 274:- begin_tests(string_prefix). 275 276test('string_prefix(+,+,+)', [forall(test_string_prefix(Original,Length,Prefix))]) :- 277 string_prefix(Original, Length, Prefix). 278test('string_prefix(+,+,-)', [forall(test_string_prefix(Original,Length,Prefix))]) :- 279 string_prefix(Original, Length, Prefix0), 280 assertion(Prefix == Prefix0). 281test('string_prefix(+,-,+)', [forall(test_string_prefix(Original,Length,Prefix))]) :- 282 string_prefix(Original, Length0, Prefix), 283 assertion(Length == Length0). 284test('string_prefix(+,-,-)', [all(Length-Prefix == [0-"",1-"a",2-"ab",3-"abc",4-"abcd"])]) :- 285 string_prefix("abcd", Length, Prefix). 286 287test_string_prefix("abcd", 0, ""). 288test_string_prefix("abcd", 1, "a"). 289test_string_prefix("abcd", 2, "ab"). 290test_string_prefix("abcd", 3, "abc"). 291test_string_prefix("abcd", 4, "abcd"). 292 293:- end_tests(string_prefix).
Notice that the order in which the characters in Strip are specified is significant.
The default Strip characters are space, newline and horizontal tab.
316string_strip(Original, Stripped) :- 317 string_strip(Original, ['\t','\n',' ','\u00a0'], Stripped). 318 319 320string_strip(Original, Strip0, Stripped) :- 321 string_chars(Strip, Strip0), 322 split_string(Original, "", Strip, [Stripped]). 323 324:- begin_tests(string_strip). 325 326test('string_strip(+,+,+)', [forall(test_string_strip(Original,Strip,Stripped))]) :- 327 string_strip(Original, Strip, Stripped). 328test('string_strip(+,+,-)', [forall(test_string_strip(Original,Strip,Stripped))]) :- 329 string_strip(Original, Strip, Stripped0), 330 assertion(Stripped == Stripped0). 331 332test_string_strip(" a ", [' '], "a"). 333test_string_strip(" a ", [' ',a], ""). 334test_string_strip("", [' '], ""). 335test_string_strip(" ", [], " "). 336 337:- end_tests(string_strip).
349string_truncate(Original, MaxLength, Truncated) :- 350 string_length(Original, Length), 351 ( Length > MaxLength 352 -> string_prefix(Original, MaxLength, Truncated) 353 ; Truncated = Original 354 ). 355 356:- begin_tests(string_truncate). 357 358test('string_truncate(+,+,+)', [forall(string_truncate_test(Original,MaxLength,Truncated))]) :- 359 string_truncate(Original, MaxLength, Truncated). 360test('string_truncate(+,+,-)', [forall(string_truncate_test(Original,MaxLength,Truncated))]) :- 361 string_truncate(Original, MaxLength, Truncated0), 362 assertion(Truncated == Truncated0). 363test('string_truncate(+,-,-)', [error(instantiation_error,_Context)]) :- 364 string_truncate("abcd", _MaxLength, "abcd"). 365 366string_truncate_test("monkey", 3, "mon"). 367string_truncate_test("monkey", 1 000, "monkey"). 368 369:- end_tests(string_truncate).
384words_lines(Words, Max, Lines) :- 385 words_lines(Words, Max, ' ', Lines). 386 387 388words_lines(Words, Max, Sep, Lines) :- 389 string_length(Sep, SepLen), 390 words_lines_(Words, SepLen, Max, Wordss), 391 maplist( 392 {Sep}/[Strings0,String0]>>string_list_concat(Strings0, Sep, String0), 393 Wordss, 394 Lines 395 ). 396 397words_lines_([], _, _, []) :- !. 398words_lines_(Words1, SepLen, Max, [Line|Lines]) :- 399 words_line_(Words1, SepLen, Max, Max, Line, Words2), 400 words_lines_(Words2, SepLen, Max, Lines). 401 402words_line_([Word|Words], _, _, Max, _, [Word], Words) :- 403 string_length(Word, Length), 404 Length >= Max, !. 405words_line_([Word|Words], SepLen, Remaining1, Max, [Word|Line], WordsSol) :- 406 string_length(Word, Length), 407 Length =< Remaining1, !, 408 Remaining2 #= Remaining1 - Length - SepLen, 409 words_line_(Words, SepLen, Remaining2, Max, Line, WordsSol). 410words_line_(Words, _, _, _, [], Words)
Extended support for strings
Extends the string support in the SWI-Prolog standard library.
*/