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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

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-2010. 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);
217
206
    try
218
207
    {NewOpt,Convert,Unicode} =
219
208
        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)
230
 
                end
231
 
        end,
232
 
    case do_replace(FlatSubject,Subject,RE,Replacement,NewOpt) of
 
209
    FlatSubject = to_binary(Subject, Unicode),
 
210
    FlatReplacement = to_binary(Replacement, Unicode),
 
211
    case do_replace(FlatSubject,Subject,RE,FlatReplacement,NewOpt) of
233
212
        {error,_Err} ->
234
213
            throw(badre);
235
214
        IoList ->
237
216
                iodata ->
238
217
                    IoList;
239
218
                binary ->
240
 
                    iolist_to_binary(IoList);
 
219
                    case Unicode of
 
220
                        false ->
 
221
                            iolist_to_binary(IoList);
 
222
                        true ->
 
223
                            unicode:characters_to_binary(IoList,unicode)
 
224
                    end;
241
225
                list ->
242
226
                    case Unicode of
243
227
                        false ->
324
308
    {[H|NT],NC,NU,NL,NS,NG}.
325
309
 
326
310
apply_mlist(Subject,Replacement,Mlist) ->
327
 
    do_mlist(Subject,Subject,0,precomp_repl(iolist_to_binary(Replacement)),
328
 
             Mlist).
 
311
    do_mlist(Subject,Subject,0,precomp_repl(Replacement), Mlist).
329
312
 
330
313
 
331
314
precomp_repl(<<>>) ->
545
528
 
546
529
ucompile(RE,Options) ->
547
530
    try
548
 
        re:compile(unicode:characters_to_binary(RE,unicode))
 
531
        re:compile(unicode:characters_to_binary(RE,unicode),Options)
549
532
    catch
550
533
        error:AnyError ->
551
534
            {'EXIT',{new_stacktrace,[{Mod,_,L}|Rest]}} = 
618
601
 
619
602
grun2(Subject,RE,{Options,NeedClean}) ->
620
603
    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,
 
604
    FlatSubject = to_binary(Subject, Unicode),
633
605
    do_grun(FlatSubject,Subject,Unicode,RE,{Options,NeedClean}).
634
606
 
635
607
do_grun(FlatSubject,Subject,Unicode,RE,{Options0,NeedClean}) ->
749
721
    true;
750
722
runopt(_) ->
751
723
    false.
 
724
 
 
725
to_binary(Bin, _IsUnicode) when is_binary(Bin) ->
 
726
    Bin;
 
727
to_binary(Data, true) ->
 
728
    unicode:characters_to_binary(Data,unicode);
 
729
to_binary(Data, false) ->
 
730
    iolist_to_binary(Data).