~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2008-2011. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(re).
32
32
    try
33
33
    {NewOpt,Convert,Unicode,Limit,Strip,Group} =
34
34
        process_split_params(Options,iodata,false,-1,false,false),
35
 
    FlatSubject = 
36
 
        case is_binary(Subject) of
37
 
            true ->
38
 
                Subject;
39
 
            false ->
40
 
                case Unicode of
41
 
                    true ->
42
 
                        unicode:characters_to_binary(Subject,unicode);
43
 
                    false ->
44
 
                        iolist_to_binary(Subject)
45
 
                end
46
 
        end,
 
35
    FlatSubject = to_binary(Subject, Unicode),
47
36
    case compile_split(RE,NewOpt) of
48
37
        {error,_Err} ->
49
38
            throw(badre);
50
39
        {PreCompiled, NumSub, RunOpt} ->
51
 
            % OK, lets run
 
40
            %% OK, lets run
52
41
            case re:run(FlatSubject,PreCompiled,RunOpt ++ [global]) of
53
42
                nomatch ->
54
43
                    case Group of
55
44
                        true ->
56
45
                            convert_any_split_result([[FlatSubject]], 
57
 
                                                     Convert, Unicode,true);
 
46
                                                     Convert, Unicode, true);
58
47
                        false ->
59
48
                            convert_any_split_result([FlatSubject], 
60
 
                                                     Convert, Unicode,false)
 
49
                                                     Convert, Unicode, false)
61
50
                    end;
62
51
                {match, Matches} ->
63
52
                    Res = do_split(FlatSubject, 0, Matches, NumSub, 
80
69
            erlang:error(badarg,[Subject,RE,Options])
81
70
    end.
82
71
 
83
 
backstrip_empty(List,false) ->
 
72
backstrip_empty(List, false) ->
84
73
    do_backstrip_empty(List);
85
74
backstrip_empty(List, true) ->
86
75
    do_backstrip_empty_g(List).
207
196
    end;
208
197
compile_split(_,_) ->
209
198
    throw(badre).
210
 
            
211
199
    
212
200
 
213
 
 
214
201
replace(Subject,RE,Replacement) ->
215
202
    replace(Subject,RE,Replacement,[]).
 
203
 
216
204
replace(Subject,RE,Replacement,Options) ->
217
205
    try
218
206
    {NewOpt,Convert,Unicode} =
219
207
        process_repl_params(Options,iodata,false),
220
 
    FlatSubject = 
221
 
        case is_binary(Subject) of
222
 
            true ->
223
 
                Subject;
224
 
            false ->
225
 
                case Unicode of
226
 
                    true ->
227
 
                        unicode:characters_to_binary(Subject,unicode);
228
 
                    false ->
229
 
                        iolist_to_binary(Subject)
 
208
    FlatSubject = to_binary(Subject, Unicode),
 
209
    FlatReplacement = to_binary(Replacement, Unicode),
 
210
    IoList = do_replace(FlatSubject,Subject,RE,FlatReplacement,NewOpt),
 
211
        case Convert of
 
212
            iodata ->
 
213
                IoList;
 
214
            binary ->
 
215
                case Unicode of
 
216
                    false ->
 
217
                        iolist_to_binary(IoList);
 
218
                    true ->
 
219
                        unicode:characters_to_binary(IoList,unicode)
 
220
                end;
 
221
            list ->
 
222
                case Unicode of
 
223
                    false ->
 
224
                        binary_to_list(iolist_to_binary(IoList));
 
225
                    true ->
 
226
                        unicode:characters_to_list(IoList,unicode)
230
227
                end
231
 
        end,
232
 
    case do_replace(FlatSubject,Subject,RE,Replacement,NewOpt) of
233
 
        {error,_Err} ->
234
 
            throw(badre);
235
 
        IoList ->
236
 
            case Convert of
237
 
                iodata ->
238
 
                    IoList;
239
 
                binary ->
240
 
                    iolist_to_binary(IoList);
241
 
                list ->
242
 
                    case Unicode of
243
 
                        false ->
244
 
                            binary_to_list(iolist_to_binary(IoList));
245
 
                        true ->
246
 
                            unicode:characters_to_list(IoList,unicode)
247
 
                    end
248
 
            end
249
 
    end
 
228
        end
250
229
    catch
251
230
        throw:badopt ->
252
231
            erlang:error(badarg,[Subject,RE,Replacement,Options]);
255
234
        error:badarg ->
256
235
            erlang:error(badarg,[Subject,RE,Replacement,Options])
257
236
    end.
258
 
    
 
237
 
259
238
 
260
239
do_replace(FlatSubject,Subject,RE,Replacement,Options) ->
261
240
    case re:run(FlatSubject,RE,Options) of
324
303
    {[H|NT],NC,NU,NL,NS,NG}.
325
304
 
326
305
apply_mlist(Subject,Replacement,Mlist) ->
327
 
    do_mlist(Subject,Subject,0,precomp_repl(iolist_to_binary(Replacement)),
328
 
             Mlist).
 
306
    do_mlist(Subject,Subject,0,precomp_repl(Replacement), Mlist).
329
307
 
330
308
 
331
309
precomp_repl(<<>>) ->
332
310
    [];
333
311
precomp_repl(<<$\\,X,Rest/binary>>) when X < $1 ; X > $9 ->
334
 
    % Escaped character
 
312
    %% Escaped character
335
313
    case precomp_repl(Rest) of
336
314
        [BHead | T0] when is_binary(BHead) ->
337
315
            [<<X,BHead/binary>> | T0];
541
519
    {[H|NL],NType};
542
520
process_uparams([],Type) ->
543
521
    {[],Type}.
544
 
                                                           
 
522
 
545
523
 
546
524
ucompile(RE,Options) ->
547
525
    try
548
 
        re:compile(unicode:characters_to_binary(RE,unicode))
 
526
        re:compile(unicode:characters_to_binary(RE,unicode),Options)
549
527
    catch
550
528
        error:AnyError ->
551
529
            {'EXIT',{new_stacktrace,[{Mod,_,L}|Rest]}} = 
565
543
                                    [Subject,RE,Options])),
566
544
            erlang:raise(error,AnyError,[{Mod,run,L}|Rest])
567
545
    end.
 
546
 
568
547
urun2(Subject0,RE0,Options0) ->
569
548
    {Options,RetType} = case (catch process_uparams(Options0,index)) of
570
549
                            {A,B} ->
590
569
        _ ->
591
570
            Ret
592
571
    end.
593
 
    
594
572
        
595
573
 
596
574
%% Might be called either with two-tuple (if regexp was already compiled)
618
596
 
619
597
grun2(Subject,RE,{Options,NeedClean}) ->
620
598
    Unicode = check_for_unicode(RE,Options),
621
 
    FlatSubject = 
622
 
        case is_binary(Subject) of
623
 
            true ->
624
 
                Subject;
625
 
            false ->
626
 
                case Unicode of
627
 
                    true ->
628
 
                        unicode:characters_to_binary(Subject,unicode);
629
 
                    false ->
630
 
                        iolist_to_binary(Subject)
631
 
                end
632
 
        end,
 
599
    FlatSubject = to_binary(Subject, Unicode),
633
600
    do_grun(FlatSubject,Subject,Unicode,RE,{Options,NeedClean}).
634
601
 
635
602
do_grun(FlatSubject,Subject,Unicode,RE,{Options0,NeedClean}) ->
749
716
    true;
750
717
runopt(_) ->
751
718
    false.
 
719
 
 
720
to_binary(Bin, _IsUnicode) when is_binary(Bin) ->
 
721
    Bin;
 
722
to_binary(Data, true) ->
 
723
    unicode:characters_to_binary(Data,unicode);
 
724
to_binary(Data, false) ->
 
725
    iolist_to_binary(Data).