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

« back to all changes in this revision

Viewing changes to lib/common_test/src/rx.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%%<copyright>
2
 
%% <year>2003-2008</year>
3
 
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
 
%%</copyright>
5
 
%%<legalnotice>
6
 
%% ``The contents of this file are subject to the Erlang Public License,
7
 
%% Version 1.1, (the "License"); you may not use this file except in
8
 
%% compliance with the License. You should have received a copy of the
9
 
%% Erlang Public License along with this software. If not, it can be
10
 
%% retrieved online at http://www.erlang.org/.
11
 
%%
12
 
%% Software distributed under the License is distributed on an "AS IS"
13
 
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
 
%% the License for the specific language governing rights and limitations
15
 
%% under the License.
16
 
%%
17
 
%% The Initial Developer of the Original Code is Ericsson AB.
18
 
%%</legalnotice>
19
 
%%
20
 
 
21
 
-module(rx).
22
 
-export([match/2, lmatch/2, match_pos/2]).
23
 
-export([t/0]).
24
 
 
25
 
-import(lists, [reverse/1]).
26
 
 
27
 
-include("ct_util.hrl").
28
 
 
29
 
%% @spec t() -> ok
30
 
%% @doc For debugging only.
31
 
t() ->
32
 
    tmatch("glurf", "glarf"),
33
 
    tmatch("kalle sover", "([^ ]*) so").
34
 
 
35
 
tmatch(Str, Pattern) ->
36
 
    io:format("~s =~~ /~s/", [Str,Pattern]),
37
 
    io:format("=> ~p\n", [match(Str, Pattern)]).
38
 
 
39
 
init() ->
40
 
    DriverPath = code:priv_dir(common_test) ++ "/lib",
41
 
    erl_ddll:load_driver(DriverPath, "erl_rx_driver"),
42
 
    P = open_port({spawn,erl_rx_driver}, []),
43
 
    register(erl_rx_driver, P),
44
 
    P.
45
 
 
46
 
port_call(Data) ->
47
 
    case whereis(erl_rx_driver) of
48
 
        undefined ->
49
 
            init(); % a raise condition might be possible 
50
 
        _P ->
51
 
            true
52
 
    end,
53
 
    port_control(erl_rx_driver, 0, Data).
54
 
            
55
 
 
56
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
57
 
%%
58
 
%% @spec match(Str, RegExp) -> nomatch | [string()]
59
 
%% Str = string() | [string|binary] | binary
60
 
%% RegExp = string() | binary
61
 
%% 
62
 
%% @doc This function tries to match the Posix regular expression
63
 
%% <code>RegExp</code> with the contents of <code>Str</code>. It returns
64
 
%% a list of matched strings if a match was found and
65
 
%% <code>nomatch</code> otherwise. The list of matched strings looks
66
 
%% like this: <code>[FullMatch, SubMatch1, SubMatch2, ...]</code>
67
 
%% where <code>FullMatch</code> is the string matched by the whole
68
 
%% regular expression and <code>SubMatchN</code> is the string that
69
 
%% matched subexpression no N. Subexpressions are denoted with '(' ')'
70
 
%% in the regular expression
71
 
%%
72
 
%% <p>Example:
73
 
%% <pre>
74
 
%% match("abc01xyz02rst23", "abc[0-9][0-9]"),
75
 
%% returns  ["abc01"]
76
 
%%
77
 
%% match("abc01xyz02rst23", "([a-z]+[0-9]+)([a-z]+[0-9]+)([a-z]+[0-9]+)"),
78
 
%% returns ["abc01xyz02rst23","abc01","xyz02","rst23"]
79
 
%% </pre></p>
80
 
%%
81
 
%% @end
82
 
 
83
 
match(Str, RegExp) ->
84
 
    match(Str, RegExp, strings).
85
 
 
86
 
 
87
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
88
 
%%
89
 
%% @spec match_pos(Str, RegExp) -> nomatch | [{Start,End}]
90
 
%% Start = integer()
91
 
%% End = integer()
92
 
%% 
93
 
%% @doc This function is equivalent to <code>match/2</code>, but it
94
 
%% returns a list of positions instead for a list of strings.
95
 
match_pos(Str, RegExp) ->
96
 
    match(Str, RegExp, pos).
97
 
 
98
 
    
99
 
 
100
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
101
 
%%
102
 
%% @spec lmatch(Lines, RegExp) -> nomatch | {[string()],Rest}
103
 
%% Lines = [Str]
104
 
%% Rest = [Str]
105
 
%% Str = string() | [string|binary] | binary
106
 
%% RegExp = string() | binary
107
 
%% 
108
 
%% @doc Performs match/2 on each string in <code>Lines</code>. The
109
 
%% first match found is returned along with the rest of the
110
 
%% <code>Lines</code>. If no match is found, <code>nomatch</code> is
111
 
%% returned.
112
 
%%
113
 
%% @see match/2
114
 
%%
115
 
%% @end
116
 
lmatch([Str|RestLines], RegExp) ->
117
 
    case match(Str, RegExp) of
118
 
        nomatch ->
119
 
            lmatch(RestLines, RegExp);
120
 
        Match ->
121
 
            {Match,RestLines}
122
 
    end;
123
 
lmatch([], _) ->
124
 
    nomatch.
125
 
 
126
 
 
127
 
 
128
 
%%%-----------------------------------------------------------------
129
 
%%% Internal Functions
130
 
match(Str, RegExp, ReturnType) when is_binary(RegExp) ->
131
 
    Data = [<<(size(RegExp)):32/native,RegExp/binary>>|Str],
132
 
    return(ReturnType, list_to_binary(Str),port_call(Data));
133
 
match(Str, RegExp, ReturnType) when is_list(RegExp) ->
134
 
    match(Str, list_to_binary(RegExp), ReturnType).
135
 
 
136
 
 
137
 
return(_Type,_,[]) -> nomatch;
138
 
return(Type, Str, Bin) ->
139
 
    return_1(Type, Str, Bin, []).
140
 
 
141
 
return_1(Type, Str, <<S:32/native,E:32/native,T/binary>>, Acc) ->
142
 
    Result = return_2(Type,Str,E,S),
143
 
    return_1(Type, Str, T, [Result|Acc]);
144
 
return_1(_, _, <<>>, Acc) -> reverse(Acc).
145
 
 
146
 
 
147
 
return_2(strings, Str, E, S) ->
148
 
    ResLen = E - S,
149
 
    <<_:S/binary,Result:ResLen/binary,_/binary>> = Str,
150
 
    binary_to_list(Result);
151
 
return_2(pos, _Str, E, S) ->
152
 
    {S+1,E}.