~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/xmerl/src/xmerl_regexp.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
257
257
%% match(String, RegExp) -> {match,Start,Length} | nomatch | {error,E}.
258
258
%%  Find the longest match of RegExp in String.
259
259
 
260
 
match(S, RegExp) when list(RegExp) ->
 
260
match(S, RegExp) when is_list(RegExp) ->
261
261
    case parse(RegExp) of
262
262
        {ok,RE} -> match(S, RE);
263
263
        {error,E} -> {error,E}
323
323
%% first_match(String, RegExp) -> {match,Start,Length} | nomatch | {error,E}.
324
324
%%  Find the first match of RegExp in String.
325
325
 
326
 
first_match(S, RegExp) when list(RegExp) ->
 
326
first_match(S, RegExp) when is_list(RegExp) ->
327
327
    case parse(RegExp) of
328
328
        {ok,RE} -> first_match(S, RE);
329
329
        {error,E} -> {error,E}
357
357
%% matches(String, RegExp) -> {match,[{Start,Length}]} | {error,E}.
358
358
%%  Return the all the non-overlapping matches of RegExp in String.
359
359
 
360
 
matches(S, RegExp) when list(RegExp) ->
 
360
matches(S, RegExp) when is_list(RegExp) ->
361
361
    case parse(RegExp) of
362
362
        {ok,RE} -> matches(S, RE);
363
363
        {error,E} -> {error,E}
391
391
%%  the string Replace in String. Accept pre-parsed regular
392
392
%%  expressions.
393
393
 
394
 
sub(String, RegExp, Rep) when list(RegExp) ->
 
394
sub(String, RegExp, Rep) when is_list(RegExp) ->
395
395
    case parse(RegExp) of
396
396
        {ok,RE} -> sub(String, RE, Rep);
397
397
        {error,E} -> {error,E}
445
445
%%  Substitute every match of the regular expression RegExp with the
446
446
%%  string New in String. Accept pre-parsed regular expressions.
447
447
 
448
 
gsub(String, RegExp, Rep) when list(RegExp) ->
 
448
gsub(String, RegExp, Rep) when is_list(RegExp) ->
449
449
    case parse(RegExp) of
450
450
        {ok,RE} -> gsub(String, RE, Rep);
451
451
        {error,E} -> {error,E}
515
515
        [[]|Ss] -> {ok,Ss};
516
516
        Ss -> {ok,Ss}
517
517
    end;
518
 
split(String, RegExp) when list(RegExp) ->
 
518
split(String, RegExp) when is_list(RegExp) ->
519
519
    case parse(RegExp) of
520
520
        {ok,{regexp,RE}} -> {ok,split_apply_re(String, RE, false)};
521
521
        {error,E} -> {error,E}
556
556
%%      {match,Start,Length,SubExprs} | nomatch | {error,E}.
557
557
%%  Find the longest match of RegExp in String.
558
558
 
559
 
sub_match(S, RegExp) when list(RegExp) ->
 
559
sub_match(S, RegExp) when is_list(RegExp) ->
560
560
    case parse(RegExp) of
561
561
        {ok,RE} -> sub_match(S, RE);
562
562
        {error,E} -> {error,E}
897
897
        true -> nomatch;
898
898
        false -> re_apply_more(More, S, P+1, Subs)
899
899
    end;
900
 
re_apply(C, More, [C|S], P, Subs) when integer(C) ->
 
900
re_apply(C, More, [C|S], P, Subs) when is_integer(C) ->
901
901
    re_apply_more(More, S, P+1, Subs);
902
902
re_apply(_RE, _More, _S, _P, _Subs) ->
903
903
    %% io:format("~p : ~p\n", [_RE,_S]),
1115
1115
build_nfa(eos, N, S, NFA) ->
1116
1116
    {[#nfa_state{no=S,edges=[{[eos],N}]}|NFA],N+1,N};
1117
1117
%%{[#nfa_state{no=S,edges=[{[eos],N}]}|NFA],N+1,N};
1118
 
build_nfa(C, N, S, NFA) when integer(C) ->
 
1118
build_nfa(C, N, S, NFA) when is_integer(C) ->
1119
1119
    {[#nfa_state{no=S,edges=[{[{C,C}],N}]}|NFA],N+1,N}.
1120
1120
 
1121
1121
nfa_char_class(Cc) ->
1187
1187
    %% List of all transition sets.
1188
1188
    Crs0 = [Cr || S <- Set,
1189
1189
                  {Crs,_St} <- (element(S, NFA))#nfa_state.edges,
1190
 
                  list(Crs),
 
1190
                 is_list(Crs),
1191
1191
                  Cr <- Crs ],
1192
1192
    Crs1 = lists:usort(Crs0),                   %Must remove duplicates!
1193
1193
    %% Build list of disjoint test ranges.
1261
1261
move(Sts, Cr, NFA) ->
1262
1262
    [ St || N <- Sts,
1263
1263
            {Crs,St} <- (element(N, NFA))#nfa_state.edges,
1264
 
            list(Crs),
 
1264
           is_list(Crs),
1265
1265
%%          begin
1266
1266
%%              io:fwrite("move1: ~p\n", [{Sts,Cr,Crs,in_crs(Cr,Crs)}]),
1267
1267
%%              true