aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/string.erl
diff options
context:
space:
mode:
authorHans Bolinder <[email protected]>2011-05-06 15:11:15 +0200
committerHans Bolinder <[email protected]>2011-05-12 15:18:41 +0200
commit76ca320fd37cecdcf225ddcc094bc72a607b0453 (patch)
tree15c6c9cac782836be6deed2316b04f2cea74e7b3 /lib/stdlib/src/string.erl
parent68fe6a14539b82250373ef114d6576e74e1b8f2e (diff)
downloadotp-76ca320fd37cecdcf225ddcc094bc72a607b0453.tar.gz
otp-76ca320fd37cecdcf225ddcc094bc72a607b0453.tar.bz2
otp-76ca320fd37cecdcf225ddcc094bc72a607b0453.zip
Types and specifications have been modified and added
Diffstat (limited to 'lib/stdlib/src/string.erl')
-rw-r--r--lib/stdlib/src/string.erl175
1 files changed, 137 insertions, 38 deletions
diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl
index 264348180f..30eac4f07d 100644
--- a/lib/stdlib/src/string.erl
+++ b/lib/stdlib/src/string.erl
@@ -29,23 +29,23 @@
%%---------------------------------------------------------------------------
--type direction() :: 'left' | 'right' | 'both'.
-
-%%---------------------------------------------------------------------------
-
%% Robert's bit
%% len(String)
%% Return the length of a string.
--spec len(string()) -> non_neg_integer().
+-spec len(String) -> Length when
+ String :: string(),
+ Length :: non_neg_integer().
len(S) -> length(S).
%% equal(String1, String2)
%% Test if 2 strings are equal.
--spec equal(string(), string()) -> boolean().
+-spec equal(String1, String2) -> boolean() when
+ String1 :: string(),
+ String2 :: string().
equal(S, S) -> true;
equal(_, _) -> false.
@@ -53,7 +53,10 @@ equal(_, _) -> false.
%% concat(String1, String2)
%% Concatenate 2 strings.
--spec concat(string(), string()) -> string().
+-spec concat(String1, String2) -> String3 when
+ String1 :: string(),
+ String2 :: string(),
+ String3 :: string().
concat(S1, S2) -> S1 ++ S2.
@@ -61,7 +64,10 @@ concat(S1, S2) -> S1 ++ S2.
%% rchr(String, Char)
%% Return the first/last index of the character in a string.
--spec chr(string(), char()) -> non_neg_integer().
+-spec chr(String, Character) -> Index when
+ String :: string(),
+ Character :: char(),
+ Index :: non_neg_integer().
chr(S, C) when is_integer(C) -> chr(S, C, 1).
@@ -69,7 +75,10 @@ chr([C|_Cs], C, I) -> I;
chr([_|Cs], C, I) -> chr(Cs, C, I+1);
chr([], _C, _I) -> 0.
--spec rchr(string(), char()) -> non_neg_integer().
+-spec rchr(String, Character) -> Index when
+ String :: string(),
+ Character :: char(),
+ Index :: non_neg_integer().
rchr(S, C) when is_integer(C) -> rchr(S, C, 1, 0).
@@ -85,7 +94,10 @@ rchr([], _C, _I, L) -> L.
%% Return the first/last index of the sub-string in a string.
%% index/2 is kept for backwards compatibility.
--spec str(string(), string()) -> non_neg_integer().
+-spec str(String, SubString) -> Index when
+ String :: string(),
+ SubString :: string(),
+ Index :: non_neg_integer().
str(S, Sub) when is_list(Sub) -> str(S, Sub, 1).
@@ -97,7 +109,10 @@ str([C|S], [C|Sub], I) ->
str([_|S], Sub, I) -> str(S, Sub, I+1);
str([], _Sub, _I) -> 0.
--spec rstr(string(), string()) -> non_neg_integer().
+-spec rstr(String, SubString) -> Index when
+ String :: string(),
+ SubString :: string(),
+ Index :: non_neg_integer().
rstr(S, Sub) when is_list(Sub) -> rstr(S, Sub, 1, 0).
@@ -116,7 +131,10 @@ prefix(Pre, String) when is_list(Pre), is_list(String) -> false.
%% span(String, Chars) -> Length.
%% cspan(String, Chars) -> Length.
--spec span(string(), string()) -> non_neg_integer().
+-spec span(String, Chars) -> Length when
+ String :: string(),
+ Chars :: string(),
+ Length :: non_neg_integer().
span(S, Cs) when is_list(Cs) -> span(S, Cs, 0).
@@ -127,7 +145,10 @@ span([C|S], Cs, I) ->
end;
span([], _Cs, I) -> I.
--spec cspan(string(), string()) -> non_neg_integer().
+-spec cspan(String, Chars) -> Length when
+ String :: string(),
+ Chars :: string(),
+ Length :: non_neg_integer().
cspan(S, Cs) when is_list(Cs) -> cspan(S, Cs, 0).
@@ -142,14 +163,21 @@ cspan([], _Cs, I) -> I.
%% substr(String, Start, Length)
%% Extract a sub-string from String.
--spec substr(string(), pos_integer()) -> string().
+-spec substr(String, Start) -> SubString when
+ String :: string(),
+ SubString :: string(),
+ Start :: pos_integer().
substr(String, 1) when is_list(String) ->
String;
substr(String, S) when is_integer(S), S > 1 ->
substr2(String, S).
--spec substr(string(), pos_integer(), non_neg_integer()) -> string().
+-spec substr(String, Start, Length) -> SubString when
+ String :: string(),
+ SubString :: string(),
+ Start :: pos_integer(),
+ Length :: non_neg_integer().
substr(String, S, L) when is_integer(S), S >= 1, is_integer(L), L >= 0 ->
substr1(substr2(String, S), L).
@@ -163,7 +191,10 @@ substr2([_|String], S) -> substr2(String, S-1).
%% tokens(String, Seperators).
%% Return a list of tokens seperated by characters in Seperators.
--spec tokens(string(), string()) -> [[char(),...]].
+-spec tokens(String, SeparatorList) -> Tokens when
+ String :: string(),
+ SeparatorList :: string(),
+ Tokens :: [Token :: nonempty_string()].
tokens(S, Seps) ->
tokens1(S, Seps, []).
@@ -184,11 +215,18 @@ tokens2([C|S], Seps, Toks, Cs) ->
tokens2([], _Seps, Toks, Cs) ->
reverse([reverse(Cs)|Toks]).
--spec chars(char(), non_neg_integer()) -> string().
+-spec chars(Character, Number) -> String when
+ Character :: char(),
+ Number :: non_neg_integer(),
+ String :: string().
chars(C, N) -> chars(C, N, []).
--spec chars(char(), non_neg_integer(), string()) -> string().
+-spec chars(Character, Number, Tail) -> String when
+ Character :: char(),
+ Number :: non_neg_integer(),
+ Tail :: string(),
+ String :: string().
chars(C, N, Tail) when N > 0 ->
chars(C, N-1, [C|Tail]);
@@ -199,7 +237,10 @@ chars(C, 0, Tail) when is_integer(C) ->
%%% COPIES %%%
--spec copies(string(), non_neg_integer()) -> string().
+-spec copies(String, Number) -> Copies when
+ String :: string(),
+ Copies :: string(),
+ Number :: non_neg_integer().
copies(CharList, Num) when is_list(CharList), is_integer(Num), Num >= 0 ->
copies(CharList, Num, []).
@@ -211,11 +252,16 @@ copies(CharList, Num, R) ->
%%% WORDS %%%
--spec words(string()) -> pos_integer().
+-spec words(String) -> Count when
+ String :: string(),
+ Count :: pos_integer().
words(String) -> words(String, $\s).
--spec words(string(), char()) -> pos_integer().
+-spec words(String, Character) -> Count when
+ String :: string(),
+ Character :: char(),
+ Count :: pos_integer().
words(String, Char) when is_integer(Char) ->
w_count(strip(String, both, Char), Char, 0).
@@ -226,11 +272,18 @@ w_count([_H|T], Char, Num) -> w_count(T, Char, Num).
%%% SUB_WORDS %%%
--spec sub_word(string(), integer()) -> string().
+-spec sub_word(String, Number) -> Word when
+ String :: string(),
+ Word :: string(),
+ Number :: integer().
sub_word(String, Index) -> sub_word(String, Index, $\s).
--spec sub_word(string(), integer(), char()) -> string().
+-spec sub_word(String, Number, Character) -> Word when
+ String :: string(),
+ Word :: string(),
+ Number :: integer(),
+ Character :: char().
sub_word(String, Index, Char) when is_integer(Index), is_integer(Char) ->
case words(String, Char) of
@@ -254,14 +307,21 @@ s_word([_|T],Stop,Char,Index,Res) when Index < Stop ->
strip(String) -> strip(String, both).
--spec strip(string(), direction()) -> string().
+-spec strip(String, Direction) -> Stripped when
+ String :: string(),
+ Stripped :: string(),
+ Direction :: left | right | both.
strip(String, left) -> strip_left(String, $\s);
strip(String, right) -> strip_right(String, $\s);
strip(String, both) ->
strip_right(strip_left(String, $\s), $\s).
--spec strip(string(), direction(), char()) -> string().
+-spec strip(String, Direction, Character) -> Stripped when
+ String :: string(),
+ Stripped :: string(),
+ Direction :: left | right | both,
+ Character :: char().
strip(String, right, Char) -> strip_right(String, Char);
strip(String, left, Char) -> strip_left(String, Char);
@@ -285,11 +345,18 @@ strip_right([], Sc) when is_integer(Sc) ->
%%% LEFT %%%
--spec left(string(), non_neg_integer()) -> string().
+-spec left(String, Number) -> Left when
+ String :: string(),
+ Left :: string(),
+ Number :: non_neg_integer().
left(String, Len) when is_integer(Len) -> left(String, Len, $\s).
--spec left(string(), non_neg_integer(), char()) -> string().
+-spec left(String, Number, Character) -> Left when
+ String :: string(),
+ Left :: string(),
+ Number :: non_neg_integer(),
+ Character :: char().
left(String, Len, Char) when is_integer(Char) ->
Slen = length(String),
@@ -303,11 +370,18 @@ l_pad(String, Num, Char) -> String ++ chars(Char, Num).
%%% RIGHT %%%
--spec right(string(), non_neg_integer()) -> string().
+-spec right(String, Number) -> Right when
+ String :: string(),
+ Right :: string(),
+ Number :: non_neg_integer().
right(String, Len) when is_integer(Len) -> right(String, Len, $\s).
--spec right(string(), non_neg_integer(), char()) -> string().
+-spec right(String, Number, Character) -> Right when
+ String :: string(),
+ Right :: string(),
+ Number :: non_neg_integer(),
+ Character :: char().
right(String, Len, Char) when is_integer(Char) ->
Slen = length(String),
@@ -321,11 +395,18 @@ r_pad(String, Num, Char) -> chars(Char, Num, String).
%%% CENTRE %%%
--spec centre(string(), non_neg_integer()) -> string().
+-spec centre(String, Number) -> Centered when
+ String :: string(),
+ Centered :: string(),
+ Number :: non_neg_integer().
centre(String, Len) when is_integer(Len) -> centre(String, Len, $\s).
--spec centre(string(), non_neg_integer(), char()) -> string().
+-spec centre(String, Number, Character) -> Centered when
+ String :: string(),
+ Centered :: string(),
+ Number :: non_neg_integer(),
+ Character :: char().
centre(String, 0, Char) when is_list(String), is_integer(Char) ->
[]; % Strange cases to centre string
@@ -341,11 +422,18 @@ centre(String, Len, Char) when is_integer(Char) ->
%%% SUB_STRING %%%
--spec sub_string(string(), pos_integer()) -> string().
+-spec sub_string(String, Start) -> SubString when
+ String :: string(),
+ SubString :: string(),
+ Start :: pos_integer().
sub_string(String, Start) -> substr(String, Start).
--spec sub_string(string(), pos_integer(), pos_integer()) -> string().
+-spec sub_string(String, Start, Stop) -> SubString when
+ String :: string(),
+ SubString :: string(),
+ Start :: pos_integer(),
+ Stop :: pos_integer().
sub_string(String, Start, Stop) -> substr(String, Start, Stop - Start + 1).
@@ -370,23 +458,34 @@ to_upper_char(C) when is_integer(C), 16#F8 =< C, C =< 16#FE ->
to_upper_char(C) ->
C.
--spec to_lower(string()) -> string()
- ; (char()) -> char().
+-spec to_lower(String) -> Result when
+ String :: string(),
+ Result :: string()
+ ; (Char) -> CharResult when
+ Char :: char(),
+ CharResult :: char().
to_lower(S) when is_list(S) ->
[to_lower_char(C) || C <- S];
to_lower(C) when is_integer(C) ->
to_lower_char(C).
--spec to_upper(string()) -> string()
- ; (char()) -> char().
+-spec to_upper(String) -> Result when
+ String :: string(),
+ Result :: string()
+ ; (Char) -> CharResult when
+ Char :: char(),
+ CharResult :: char().
to_upper(S) when is_list(S) ->
[to_upper_char(C) || C <- S];
to_upper(C) when is_integer(C) ->
to_upper_char(C).
--spec join([string()], string()) -> string().
+-spec join(StringList, Separator) -> String when
+ StringList :: [string()],
+ Separator :: string(),
+ String :: string().
join([], Sep) when is_list(Sep) ->
[];