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

« back to all changes in this revision

Viewing changes to lib/stdlib/test/binref.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
-module(binref).
 
2
 
 
3
-export([compile_pattern/1,match/2,match/3,matches/2,matches/3,
 
4
         split/2,split/3,replace/3,replace/4,first/1,last/1,at/2,
 
5
         part/2,part/3,copy/1,copy/2,encode_unsigned/1,encode_unsigned/2,
 
6
         decode_unsigned/1,decode_unsigned/2,referenced_byte_size/1,
 
7
         longest_common_prefix/1,longest_common_suffix/1,bin_to_list/1,
 
8
         bin_to_list/2,bin_to_list/3,list_to_bin/1]).
 
9
 
 
10
 
 
11
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
12
%% compile_pattern, a dummy
 
13
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
14
compile_pattern(Pattern) when is_binary(Pattern) ->
 
15
    {[Pattern]};
 
16
compile_pattern(Pattern) ->
 
17
    try
 
18
        [ true = is_binary(P) || P <- Pattern ],
 
19
        {Pattern}
 
20
    catch
 
21
        _:_ ->
 
22
            erlang:error(badarg)
 
23
    end.
 
24
 
 
25
 
 
26
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
27
%% match and matches
 
28
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
29
match(H,N) ->
 
30
    match(H,N,[]).
 
31
match(Haystack,Needle,Options) when is_binary(Needle) ->
 
32
    match(Haystack,[Needle],Options);
 
33
match(Haystack,{Needles},Options) ->
 
34
    match(Haystack,Needles,Options);
 
35
match(Haystack,Needles,Options) ->
 
36
    try
 
37
        true = is_binary(Haystack) and is_list(Needles), % badarg, not function_clause
 
38
        case get_opts_match(Options,nomatch) of
 
39
            nomatch ->
 
40
                mloop(Haystack,Needles);
 
41
            {A,B} when B > 0 ->
 
42
                <<_:A/binary,SubStack:B/binary,_/binary>> = Haystack,
 
43
                mloop(SubStack,Needles,A,B+A);
 
44
            {A,B} when B < 0 ->
 
45
                Start = A + B,
 
46
                Len = -B,
 
47
                <<_:Start/binary,SubStack:Len/binary,_/binary>> = Haystack,
 
48
                mloop(SubStack,Needles,Start,Len+Start);
 
49
            _ ->
 
50
                nomatch
 
51
        end
 
52
    catch
 
53
        _:_ ->
 
54
            erlang:error(badarg)
 
55
    end.
 
56
matches(H,N) ->
 
57
    matches(H,N,[]).
 
58
matches(Haystack,Needle,Options) when is_binary(Needle) ->
 
59
    matches(Haystack,[Needle],Options);
 
60
matches(Haystack,{Needles},Options) ->
 
61
    matches(Haystack,Needles,Options);
 
62
matches(Haystack,Needles,Options) ->
 
63
    try
 
64
        true = is_binary(Haystack) and is_list(Needles), % badarg, not function_clause
 
65
        case get_opts_match(Options,nomatch) of
 
66
            nomatch ->
 
67
                msloop(Haystack,Needles);
 
68
            {A,B} when B > 0 ->
 
69
                <<_:A/binary,SubStack:B/binary,_/binary>> = Haystack,
 
70
                msloop(SubStack,Needles,A,B+A);
 
71
            {A,B} when B < 0 ->
 
72
                Start = A + B,
 
73
                Len = -B,
 
74
                <<_:Start/binary,SubStack:Len/binary,_/binary>> = Haystack,
 
75
                msloop(SubStack,Needles,Start,Len+Start);
 
76
            _ ->
 
77
                []
 
78
        end
 
79
    catch
 
80
        _:_ ->
 
81
            erlang:error(badarg)
 
82
    end.
 
83
 
 
84
mloop(Haystack,Needles) ->
 
85
    mloop(Haystack,Needles,0,byte_size(Haystack)).
 
86
 
 
87
mloop(_Haystack,_Needles,N,M) when N >= M ->
 
88
    nomatch;
 
89
mloop(Haystack,Needles,N,M) ->
 
90
    case mloop2(Haystack,Needles,N,nomatch) of
 
91
        nomatch ->
 
92
            % Not found
 
93
            <<_:8,NewStack/binary>> = Haystack,
 
94
            mloop(NewStack,Needles,N+1,M);
 
95
        {N,Len} ->
 
96
            {N,Len}
 
97
    end.
 
98
 
 
99
msloop(Haystack,Needles) ->
 
100
    msloop(Haystack,Needles,0,byte_size(Haystack)).
 
101
 
 
102
msloop(_Haystack,_Needles,N,M) when N >= M ->
 
103
    [];
 
104
msloop(Haystack,Needles,N,M) ->
 
105
    case mloop2(Haystack,Needles,N,nomatch) of
 
106
        nomatch ->
 
107
            % Not found
 
108
            <<_:8,NewStack/binary>> = Haystack,
 
109
            msloop(NewStack,Needles,N+1,M);
 
110
        {N,Len} ->
 
111
            NewN = N+Len,
 
112
            if
 
113
                NewN >= M ->
 
114
                    [{N,Len}];
 
115
                true ->
 
116
                    <<_:Len/binary,NewStack/binary>> = Haystack,
 
117
                    [{N,Len} | msloop(NewStack,Needles,NewN,M)]
 
118
            end
 
119
    end.
 
120
 
 
121
mloop2(_Haystack,[],_N,Res) ->
 
122
    Res;
 
123
mloop2(Haystack,[Needle|Tail],N,Candidate) ->
 
124
    NS = byte_size(Needle),
 
125
    case Haystack of
 
126
        <<Needle:NS/binary,_/binary>> ->
 
127
            NewCandidate = case Candidate of
 
128
                               nomatch ->
 
129
                                   {N,NS};
 
130
                               {N,ONS} when ONS < NS ->
 
131
                                   {N,NS};
 
132
                               Better ->
 
133
                                   Better
 
134
                           end,
 
135
            mloop2(Haystack,Tail,N,NewCandidate);
 
136
        _ ->
 
137
            mloop2(Haystack,Tail,N,Candidate)
 
138
    end.
 
139
 
 
140
 
 
141
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
142
%% split
 
143
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
144
split(H,N) ->
 
145
    split(H,N,[]).
 
146
split(Haystack,{Needles},Options) ->
 
147
    split(Haystack, Needles, Options);
 
148
split(Haystack,Needles0,Options) ->
 
149
    try
 
150
        Needles = if
 
151
                      is_list(Needles0) ->
 
152
                          Needles0;
 
153
                      is_binary(Needles0) ->
 
154
                          [Needles0];
 
155
                      true ->
 
156
                          exit(badtype)
 
157
                  end,
 
158
        {Part,Global,Trim} = get_opts_split(Options,{nomatch,false,false}),
 
159
        {Start,End,NewStack} =
 
160
            case Part of
 
161
                nomatch ->
 
162
                    {0,byte_size(Haystack),Haystack};
 
163
                {A,B} when B >= 0 ->
 
164
                    <<_:A/binary,SubStack:B/binary,_/binary>> = Haystack,
 
165
                    {A,A+B,SubStack};
 
166
                {A,B} when B < 0 ->
 
167
                    S = A + B,
 
168
                    L = -B,
 
169
                    <<_:S/binary,SubStack:L/binary,_/binary>> = Haystack,
 
170
                    {S,S+L,SubStack}
 
171
            end,
 
172
        MList = if
 
173
                    Global ->
 
174
                        msloop(NewStack,Needles,Start,End);
 
175
                    true ->
 
176
                        case mloop(NewStack,Needles,Start,End) of
 
177
                            nomatch ->
 
178
                                [];
 
179
                            X ->
 
180
                                [X]
 
181
                        end
 
182
                end,
 
183
        do_split(Haystack,MList,0,Trim)
 
184
    catch
 
185
        _:_ ->
 
186
            erlang:error(badarg)
 
187
    end.
 
188
 
 
189
do_split(H,[],N,true) when N >= byte_size(H) ->
 
190
    [];
 
191
do_split(H,[],N,_) ->
 
192
    [part(H,{N,byte_size(H)-N})];
 
193
do_split(H,[{A,B}|T],N,Trim) ->
 
194
    case part(H,{N,A-N}) of
 
195
        <<>> ->
 
196
            Rest =  do_split(H,T,A+B,Trim),
 
197
            case {Trim, Rest} of
 
198
                {true,[]} ->
 
199
                    [];
 
200
                _ ->
 
201
                    [<<>> | Rest]
 
202
            end;
 
203
        Oth ->
 
204
            [Oth | do_split(H,T,A+B,Trim)]
 
205
    end.
 
206
 
 
207
 
 
208
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
209
%% replace
 
210
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
211
replace(H,N,R) ->
 
212
    replace(H,N,R,[]).
 
213
replace(Haystack,{Needles},Replacement,Options) ->
 
214
    replace(Haystack,Needles,Replacement,Options);
 
215
 
 
216
replace(Haystack,Needles0,Replacement,Options) ->
 
217
    try
 
218
        Needles = if
 
219
                      is_list(Needles0) ->
 
220
                          Needles0;
 
221
                      is_binary(Needles0) ->
 
222
                          [Needles0];
 
223
                      true ->
 
224
                          exit(badtype)
 
225
                  end,
 
226
        true = is_binary(Replacement), % Make badarg instead of function clause
 
227
        {Part,Global,Insert} = get_opts_replace(Options,{nomatch,false,[]}),
 
228
        {Start,End,NewStack} =
 
229
            case Part of
 
230
                nomatch ->
 
231
                    {0,byte_size(Haystack),Haystack};
 
232
                {A,B} when B >= 0 ->
 
233
                    <<_:A/binary,SubStack:B/binary,_/binary>> = Haystack,
 
234
                    {A,A+B,SubStack};
 
235
                {A,B} when B < 0 ->
 
236
                    S = A + B,
 
237
                    L = -B,
 
238
                    <<_:S/binary,SubStack:L/binary,_/binary>> = Haystack,
 
239
                    {S,S+L,SubStack}
 
240
            end,
 
241
        MList = if
 
242
                    Global ->
 
243
                        msloop(NewStack,Needles,Start,End);
 
244
                    true ->
 
245
                        case mloop(NewStack,Needles,Start,End) of
 
246
                            nomatch ->
 
247
                                [];
 
248
                            X ->
 
249
                                [X]
 
250
                        end
 
251
                end,
 
252
        ReplList = case Insert of
 
253
                       [] ->
 
254
                           Replacement;
 
255
                       Y when is_integer(Y) ->
 
256
                           splitat(Replacement,0,[Y]);
 
257
                       Li when is_list(Li) ->
 
258
                           splitat(Replacement,0,lists:sort(Li))
 
259
                   end,
 
260
        erlang:iolist_to_binary(do_replace(Haystack,MList,ReplList,0))
 
261
   catch
 
262
       _:_ ->
 
263
            erlang:error(badarg)
 
264
   end.
 
265
 
 
266
 
 
267
do_replace(H,[],_,N) ->
 
268
    [part(H,{N,byte_size(H)-N})];
 
269
do_replace(H,[{A,B}|T],Replacement,N) ->
 
270
    [part(H,{N,A-N}),
 
271
     if
 
272
         is_list(Replacement) ->
 
273
             do_insert(Replacement, part(H,{A,B}));
 
274
         true ->
 
275
             Replacement
 
276
     end
 
277
     | do_replace(H,T,Replacement,A+B)].
 
278
 
 
279
do_insert([X],_) ->
 
280
    [X];
 
281
do_insert([H|T],R) ->
 
282
    [H,R|do_insert(T,R)].
 
283
 
 
284
splitat(H,N,[]) ->
 
285
    [part(H,{N,byte_size(H)-N})];
 
286
splitat(H,N,[I|T]) ->
 
287
    [part(H,{N,I-N})|splitat(H,I,T)].
 
288
 
 
289
 
 
290
 
 
291
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
292
%% first, last and at
 
293
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
294
first(Subject) ->
 
295
    try
 
296
        <<A:8,_/binary>> = Subject,
 
297
        A
 
298
    catch
 
299
        _:_ ->
 
300
            erlang:error(badarg)
 
301
    end.
 
302
 
 
303
last(Subject) ->
 
304
    try
 
305
        N = byte_size(Subject) - 1,
 
306
        <<_:N/binary,A:8>> = Subject,
 
307
        A
 
308
    catch
 
309
        _:_ ->
 
310
            erlang:error(badarg)
 
311
    end.
 
312
 
 
313
at(Subject,X) ->
 
314
    try
 
315
        <<_:X/binary,A:8,_/binary>> = Subject,
 
316
        A
 
317
    catch
 
318
        _:_ ->
 
319
            erlang:error(badarg)
 
320
    end.
 
321
 
 
322
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
323
% bin_to_list
 
324
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
325
bin_to_list(Subject) ->
 
326
    try
 
327
        binary_to_list(Subject)
 
328
    catch
 
329
        _:_ ->
 
330
            erlang:error(badarg)
 
331
    end.
 
332
 
 
333
bin_to_list(Subject,T) ->
 
334
    try
 
335
        {A0,B0} = T,
 
336
        {A,B} = if
 
337
                    B0 < 0 ->
 
338
                        {A0+B0,-B0};
 
339
                    true ->
 
340
                        {A0,B0}
 
341
                end,
 
342
        binary_to_list(Subject,A+1,A+B)
 
343
    catch
 
344
        _:_ ->
 
345
            erlang:error(badarg)
 
346
    end.
 
347
 
 
348
bin_to_list(Subject,A,B) ->
 
349
    try
 
350
        bin_to_list(Subject,{A,B})
 
351
    catch
 
352
        _:_ ->
 
353
            erlang:error(badarg)
 
354
    end.
 
355
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
356
% list_to_bin
 
357
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
358
list_to_bin(List) ->
 
359
    try
 
360
        erlang:list_to_binary(List)
 
361
    catch
 
362
        _:_ ->
 
363
            erlang:error(badarg)
 
364
    end.
 
365
 
 
366
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
367
%% longest_common_prefix
 
368
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
369
longest_common_prefix(LB) ->
 
370
    try
 
371
        true = is_list(LB) and (length(LB) > 0), % Make badarg instead of function clause
 
372
        do_longest_common_prefix(LB,0)
 
373
    catch
 
374
        _:_ ->
 
375
            erlang:error(badarg)
 
376
    end.
 
377
 
 
378
do_longest_common_prefix(LB,X) ->
 
379
    case do_lcp(LB,X,no) of
 
380
        true ->
 
381
            do_longest_common_prefix(LB,X+1);
 
382
        false ->
 
383
            X
 
384
    end.
 
385
do_lcp([],_,_) ->
 
386
    true;
 
387
do_lcp([Bin|_],X,_) when byte_size(Bin) =< X ->
 
388
    false;
 
389
do_lcp([Bin|T],X,no) ->
 
390
    Ch = at(Bin,X),
 
391
    do_lcp(T,X,Ch);
 
392
do_lcp([Bin|T],X,Ch) ->
 
393
    Ch2 = at(Bin,X),
 
394
    if
 
395
        Ch =:= Ch2 ->
 
396
            do_lcp(T,X,Ch);
 
397
        true ->
 
398
            false
 
399
    end.
 
400
 
 
401
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
402
%% longest_common_suffix
 
403
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
404
longest_common_suffix(LB) ->
 
405
    try
 
406
        true = is_list(LB) and (length(LB) > 0), % Make badarg instead of function clause
 
407
        do_longest_common_suffix(LB,0)
 
408
    catch
 
409
        _:_ ->
 
410
            erlang:error(badarg)
 
411
    end.
 
412
 
 
413
do_longest_common_suffix(LB,X) ->
 
414
    case do_lcs(LB,X,no) of
 
415
        true ->
 
416
            do_longest_common_suffix(LB,X+1);
 
417
        false ->
 
418
            X
 
419
    end.
 
420
do_lcs([],_,_) ->
 
421
    true;
 
422
do_lcs([Bin|_],X,_) when byte_size(Bin) =< X ->
 
423
    false;
 
424
do_lcs([Bin|T],X,no) ->
 
425
    Ch = at(Bin,byte_size(Bin) - 1 - X),
 
426
    do_lcs(T,X,Ch);
 
427
do_lcs([Bin|T],X,Ch) ->
 
428
    Ch2 = at(Bin,byte_size(Bin) - 1 - X),
 
429
    if
 
430
        Ch =:= Ch2 ->
 
431
            do_lcs(T,X,Ch);
 
432
        true ->
 
433
            false
 
434
    end.
 
435
 
 
436
 
 
437
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
438
%% part
 
439
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
440
part(Subject,Part) ->
 
441
    try
 
442
        do_part(Subject,Part)
 
443
    catch
 
444
        _:_ ->
 
445
            erlang:error(badarg)
 
446
    end.
 
447
 
 
448
part(Subject,Pos,Len) ->
 
449
    part(Subject,{Pos,Len}).
 
450
 
 
451
do_part(Bin,{A,B}) when B >= 0 ->
 
452
    <<_:A/binary,Sub:B/binary,_/binary>> = Bin,
 
453
    Sub;
 
454
do_part(Bin,{A,B}) when B < 0 ->
 
455
    S = A + B,
 
456
    L = -B,
 
457
    <<_:S/binary,Sub:L/binary,_/binary>> = Bin,
 
458
    Sub.
 
459
 
 
460
 
 
461
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
462
%% copy
 
463
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
464
copy(Subject) ->
 
465
    copy(Subject,1).
 
466
copy(Subject,N) ->
 
467
    try
 
468
        true = is_integer(N) and (N >= 0) and is_binary(Subject), % Badarg, not function clause
 
469
        erlang:list_to_binary(lists:duplicate(N,Subject))
 
470
    catch
 
471
        _:_ ->
 
472
            erlang:error(badarg)
 
473
    end.
 
474
 
 
475
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
476
%% encode_unsigned
 
477
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
478
encode_unsigned(Unsigned) ->
 
479
    encode_unsigned(Unsigned,big).
 
480
encode_unsigned(Unsigned,Endian) ->
 
481
    try
 
482
        true = is_integer(Unsigned) and (Unsigned >= 0),
 
483
        if
 
484
            Unsigned =:= 0 ->
 
485
                <<0>>;
 
486
            true ->
 
487
                case Endian of
 
488
                    big ->
 
489
                        list_to_binary(do_encode(Unsigned,[]));
 
490
                    little ->
 
491
                        list_to_binary(do_encode_r(Unsigned))
 
492
                end
 
493
        end
 
494
    catch
 
495
        _:_ ->
 
496
            erlang:error(badarg)
 
497
    end.
 
498
 
 
499
do_encode(0,L) ->
 
500
    L;
 
501
do_encode(N,L) ->
 
502
    Byte = N band 255,
 
503
    NewN = N bsr 8,
 
504
    do_encode(NewN,[Byte|L]).
 
505
 
 
506
do_encode_r(0) ->
 
507
    [];
 
508
do_encode_r(N) ->
 
509
    Byte = N band 255,
 
510
    NewN = N bsr 8,
 
511
    [Byte|do_encode_r(NewN)].
 
512
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
513
%% decode_unsigned
 
514
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
515
decode_unsigned(Subject) ->
 
516
    decode_unsigned(Subject,big).
 
517
 
 
518
decode_unsigned(Subject,Endian) ->
 
519
    try
 
520
        true = is_binary(Subject),
 
521
        case Endian of
 
522
            big ->
 
523
                do_decode(Subject,0);
 
524
            little ->
 
525
                do_decode_r(Subject,0)
 
526
        end
 
527
    catch
 
528
        _:_ ->
 
529
            erlang:error(badarg)
 
530
    end.
 
531
 
 
532
do_decode(<<>>,N) ->
 
533
    N;
 
534
do_decode(<<X:8,Bin/binary>>,N) ->
 
535
    do_decode(Bin,(N bsl 8) bor X).
 
536
 
 
537
do_decode_r(<<>>,N) ->
 
538
    N;
 
539
do_decode_r(Bin,N) ->
 
540
    Sz = byte_size(Bin) - 1,
 
541
    <<NewBin:Sz/binary,X>> = Bin,
 
542
    do_decode_r(NewBin, (N bsl 8) bor X).
 
543
 
 
544
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
545
%% referenced_byte_size cannot
 
546
%% be implemented in pure
 
547
%% erlang
 
548
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
549
referenced_byte_size(Bin) when is_binary(Bin) ->
 
550
    erlang:error(not_implemented);
 
551
referenced_byte_size(_) ->
 
552
    erlang:error(badarg).
 
553
 
 
554
 
 
555
 
 
556
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
557
%% Simple helper functions
 
558
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
559
 
 
560
%% Option "parsing"
 
561
get_opts_match([],Part) ->
 
562
    Part;
 
563
get_opts_match([{scope,{A,B}} | T],_Part) ->
 
564
    get_opts_match(T,{A,B});
 
565
get_opts_match(_,_) ->
 
566
    throw(badopt).
 
567
 
 
568
get_opts_split([],{Part,Global,Trim}) ->
 
569
    {Part,Global,Trim};
 
570
get_opts_split([{scope,{A,B}} | T],{_Part,Global,Trim}) ->
 
571
    get_opts_split(T,{{A,B},Global,Trim});
 
572
get_opts_split([global | T],{Part,_Global,Trim}) ->
 
573
    get_opts_split(T,{Part,true,Trim});
 
574
get_opts_split([trim | T],{Part,Global,_Trim}) ->
 
575
    get_opts_split(T,{Part,Global,true});
 
576
get_opts_split(_,_) ->
 
577
    throw(badopt).
 
578
 
 
579
get_opts_replace([],{Part,Global,Insert}) ->
 
580
    {Part,Global,Insert};
 
581
get_opts_replace([{scope,{A,B}} | T],{_Part,Global,Insert}) ->
 
582
    get_opts_replace(T,{{A,B},Global,Insert});
 
583
get_opts_replace([global | T],{Part,_Global,Insert}) ->
 
584
    get_opts_replace(T,{Part,true,Insert});
 
585
get_opts_replace([{insert_replaced,N} | T],{Part,Global,_Insert}) ->
 
586
    get_opts_replace(T,{Part,Global,N});
 
587
get_opts_replace(_,_) ->
 
588
    throw(badopt).