aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/binary.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/binary.erl')
-rw-r--r--lib/stdlib/src/binary.erl77
1 files changed, 8 insertions, 69 deletions
diff --git a/lib/stdlib/src/binary.erl b/lib/stdlib/src/binary.erl
index af00410572..fb0c395d70 100644
--- a/lib/stdlib/src/binary.erl
+++ b/lib/stdlib/src/binary.erl
@@ -20,7 +20,7 @@
-module(binary).
%%
%% Implemented in this module:
--export([split/2,split/3,replace/3,replace/4]).
+-export([replace/3,replace/4]).
-export_type([cp/0]).
@@ -34,7 +34,8 @@
decode_unsigned/2, encode_unsigned/1, encode_unsigned/2,
first/1, last/1, list_to_bin/1, longest_common_prefix/1,
longest_common_suffix/1, match/2, match/3, matches/2,
- matches/3, part/2, part/3, referenced_byte_size/1]).
+ matches/3, part/2, part/3, referenced_byte_size/1,
+ split/2, split/3]).
-spec at(Subject, Pos) -> byte() when
Subject :: binary(),
@@ -198,19 +199,13 @@ part(_, _, _) ->
referenced_byte_size(_) ->
erlang:nif_error(undef).
-%%% End of BIFs.
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% split
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-
-spec split(Subject, Pattern) -> Parts when
Subject :: binary(),
Pattern :: binary() | [binary()] | cp(),
Parts :: [binary()].
-split(H,N) ->
- split(H,N,[]).
+split(_, _) ->
+ erlang:nif_error(undef).
-spec split(Subject, Pattern, Options) -> Parts when
Subject :: binary(),
@@ -219,53 +214,10 @@ split(H,N) ->
Option :: {scope, part()} | trim | global | trim_all,
Parts :: [binary()].
-split(Haystack,Needles,Options) ->
- try
- {Part,Global,Trim,TrimAll} =
- get_opts_split(Options,{no,false,false,false}),
- Moptlist = case Part of
- no ->
- [];
- {A,B} ->
- [{scope,{A,B}}]
- end,
- MList = if
- Global ->
- binary:matches(Haystack,Needles,Moptlist);
- true ->
- case binary:match(Haystack,Needles,Moptlist) of
- nomatch -> [];
- Match -> [Match]
- end
- end,
- do_split(Haystack,MList,0,Trim,TrimAll)
- catch
- _:_ ->
- erlang:error(badarg)
- end.
-
-do_split(H,[],N,true,_) when N >= byte_size(H) ->
- [];
-do_split(H,[],N,_,true) when N >= byte_size(H) ->
- [];
-do_split(H,[],N,_,_) ->
- [binary:part(H,{N,byte_size(H)-N})];
-do_split(H,[{A,B}|T],N,Trim,TrimAll) ->
- case binary:part(H,{N,A-N}) of
- <<>> when TrimAll == true ->
- do_split(H,T,A+B,Trim,TrimAll);
- <<>> ->
- Rest = do_split(H,T,A+B,Trim,TrimAll),
- case {Trim, Rest} of
- {true,[]} ->
- [];
- _ ->
- [<<>> | Rest]
- end;
- Oth ->
- [Oth | do_split(H,T,A+B,Trim,TrimAll)]
- end.
+split(_, _, _) ->
+ erlang:nif_error(undef).
+%%% End of BIFs.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% replace
@@ -352,19 +304,6 @@ splitat(H,N,[I|T]) ->
%% Simple helper functions
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-get_opts_split([],{Part,Global,Trim,TrimAll}) ->
- {Part,Global,Trim,TrimAll};
-get_opts_split([{scope,{A,B}} | T],{_Part,Global,Trim,TrimAll}) ->
- get_opts_split(T,{{A,B},Global,Trim,TrimAll});
-get_opts_split([global | T],{Part,_Global,Trim,TrimAll}) ->
- get_opts_split(T,{Part,true,Trim,TrimAll});
-get_opts_split([trim | T],{Part,Global,_Trim,TrimAll}) ->
- get_opts_split(T,{Part,Global,true,TrimAll});
-get_opts_split([trim_all | T],{Part,Global,Trim,_TrimAll}) ->
- get_opts_split(T,{Part,Global,Trim,true});
-get_opts_split(_,_) ->
- throw(badopt).
-
get_opts_replace([],{Part,Global,Insert}) ->
{Part,Global,Insert};
get_opts_replace([{scope,{A,B}} | T],{_Part,Global,Insert}) ->