~ubuntu-branches/ubuntu/lucid/erlang/lucid-proposed

« back to all changes in this revision

Viewing changes to lib/stdlib/src/regexp.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
112
112
reg3p([$?|S], L) -> reg3p(S, {optional,L});
113
113
reg3p(S, L) -> {L,S}.
114
114
 
 
115
-define(HEX(C), C >= $0 andalso C =< $9 orelse 
 
116
                C >= $A andalso C =< $F orelse 
 
117
                C >= $a andalso C =< $f).
 
118
 
115
119
reg4([$(|S0]) ->
116
120
    case reg(S0) of
117
121
        {R,[$)|S1]} -> {R,S1};
120
124
reg4([$\\,O1,O2,O3|S]) when
121
125
  O1 >= $0, O1 =< $7, O2 >= $0, O2 =< $7, O3 >= $0, O3 =< $7 ->
122
126
    {(O1*8 + O2)*8 + O3 - 73*$0,S};
 
127
reg4([$\\,$x,H1,H2|S]) when ?HEX(H1), ?HEX(H2) ->
 
128
    {erlang:list_to_integer([H1,H2], 16),S};
 
129
reg4([$\\,$x,${|S]) ->
 
130
    hex(S, []);
 
131
reg4([$\\,$x|_]) ->
 
132
    throw({error,{illegal,[$x]}});
123
133
reg4([$\\,C|S]) -> {escape_char(C),S};
124
134
reg4([$\\]) -> throw({error,{unterminated,"\\"}});
125
135
reg4([$^|S]) -> {bos,S};
144
154
reg4([C|_S]) -> throw({error,{illegal,[C]}});
145
155
reg4([]) -> {epsilon,[]}.
146
156
 
 
157
hex([C|Cs], L) when ?HEX(C) ->
 
158
    hex(Cs, [C|L]);
 
159
hex([$}|S], L) ->
 
160
    case catch erlang:list_to_integer(lists:reverse(L), 16) of
 
161
        V when V =< 16#FF ->
 
162
            {V,S};
 
163
        _ ->
 
164
            throw({error,{illegal,[$}]}})
 
165
    end;
 
166
hex(_S, _) ->
 
167
    throw({error,{unterminated,"\\x{"}}).
 
168
 
147
169
escape_char($n) -> $\n;                         %\n = LF
148
170
escape_char($r) -> $\r;                         %\r = CR
149
171
escape_char($t) -> $\t;                         %\t = TAB
161
183
char($\\, [O1,O2,O3|S]) when
162
184
  O1 >= $0, O1 =< $7, O2 >= $0, O2 =< $7, O3 >= $0, O3 =< $7 ->
163
185
    {(O1*8 + O2)*8 + O3 - 73*$0,S};
 
186
char($\\, [$x,H1,H2|S]) when ?HEX(H1), ?HEX(H2) ->
 
187
    {erlang:list_to_integer([H1,H2], 16),S};
 
188
char($\\,[$x,${|S]) ->
 
189
    hex(S, []);
 
190
char($\\,[$x|_]) ->
 
191
    throw({error,{illegal,[$x]}});
164
192
char($\\, [C|S]) -> {escape_char(C),S};
165
193
char(C, S) -> {C,S}.
166
194