~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/megaco/src/text/megaco_text_gen_v1.hrl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%%<copyright>
2
 
%% <year>2000-2008</year>
3
 
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
 
%%</copyright>
5
 
%%<legalnotice>
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2000-2009. 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
%% 
 
17
%% %CopyrightEnd%
16
18
%%
17
 
%% The Initial Developer of the Original Code is Ericsson AB.
18
 
%%</legalnotice>
 
19
 
19
20
%%
20
21
%%----------------------------------------------------------------------
21
22
%% Purpose: Encode Megaco/H.248 text messages from internal form
1916
1917
        synchISDN -> ?SynchISDNToken
1917
1918
    end.
1918
1919
 
1919
 
enc_DigitMapDescriptor(Val, State)
1920
 
  when is_record(Val, 'DigitMapDescriptor') ->
 
1920
enc_DigitMapDescriptor(#'DigitMapDescriptor'{digitMapName  = asn1_NOVALUE,
 
1921
                                             digitMapValue = Value} = Val, 
 
1922
                       State) 
 
1923
  when (Value =/= asn1_NOVALUE) ->
 
1924
    case is_empty_DigitMapValue(Value) of
 
1925
        true ->
 
1926
            error({invalid_DigitMapDescriptor, Val});
 
1927
        false ->
 
1928
            [
 
1929
             ?DigitMapToken,
 
1930
             ?EQUAL,
 
1931
             ?LBRKT_INDENT(State),
 
1932
             enc_DigitMapValue(Value, ?INC_INDENT(State)),
 
1933
             ?RBRKT_INDENT(State)
 
1934
            ]
 
1935
    end;
 
1936
enc_DigitMapDescriptor(#'DigitMapDescriptor'{digitMapName  = Name, 
 
1937
                                             digitMapValue = asn1_NOVALUE}, 
 
1938
                       State) 
 
1939
  when (Name =/= asn1_NOVALUE) ->
1921
1940
    [
1922
1941
     ?DigitMapToken,
1923
1942
     ?EQUAL,
1924
 
     enc_DigitMapName(Val#'DigitMapDescriptor'.digitMapName, State),
1925
 
     ?LBRKT_INDENT(State),
1926
 
     enc_DigitMapValue(Val#'DigitMapDescriptor'.digitMapValue,
1927
 
                       ?INC_INDENT(State)),
1928
 
     ?RBRKT_INDENT(State)
1929
 
    ].
 
1943
     enc_DigitMapName(Name, State)
 
1944
    ];
 
1945
enc_DigitMapDescriptor(#'DigitMapDescriptor'{digitMapName  = Name,
 
1946
                                             digitMapValue = Value}, 
 
1947
                       State) 
 
1948
  when (Name =/= asn1_NOVALUE) andalso (Value =/= asn1_NOVALUE) ->
 
1949
    case is_empty_DigitMapValue(Value) of
 
1950
        true ->
 
1951
            [
 
1952
             ?DigitMapToken,
 
1953
             ?EQUAL,
 
1954
             enc_DigitMapName(Name, State)
 
1955
            ];
 
1956
        false ->
 
1957
            [
 
1958
             ?DigitMapToken,
 
1959
             ?EQUAL,
 
1960
             enc_DigitMapName(Name, State),
 
1961
             ?LBRKT_INDENT(State),
 
1962
             enc_DigitMapValue(Value, ?INC_INDENT(State)),
 
1963
             ?RBRKT_INDENT(State)
 
1964
            ]
 
1965
    end;
 
1966
enc_DigitMapDescriptor(BadVal, _State) ->
 
1967
    error({invalid_DigitMapDescriptor, BadVal}).
1930
1968
 
1931
1969
enc_DigitMapName({'DigitMapName',Val}, State) ->
1932
1970
    enc_DigitMapName(Val, State);
1933
1971
enc_DigitMapName(Val, State) ->
1934
1972
    enc_Name(Val, State).
1935
1973
 
 
1974
is_empty_DigitMapValue(#'DigitMapValue'{startTimer   = asn1_NOVALUE,
 
1975
                                        shortTimer   = asn1_NOVALUE,
 
1976
                                        longTimer    = asn1_NOVALUE,
 
1977
                                        digitMapBody = []}) ->
 
1978
    true;
 
1979
is_empty_DigitMapValue(#'DigitMapValue'{}) ->
 
1980
    false.
 
1981
    
1936
1982
enc_DigitMapValue(Val, State)
1937
1983
  when is_record(Val, 'DigitMapValue') ->
1938
1984
    [
2139
2185
enc_Value({'Value',Val}, State) ->
2140
2186
    enc_Value(Val, State);
2141
2187
enc_Value(String, _State) ->
2142
 
    case quoted_string_count(String, 0, true) of
2143
 
        {_, 0} ->
2144
 
            [?DQUOTE, String, ?DQUOTE];
2145
 
        {false, _} ->
2146
 
            [?DQUOTE, String, ?DQUOTE];
2147
 
        {true, _} ->
 
2188
    case quoted_string_count(String, 0, true, false) of
 
2189
        {_, 0, _} ->
 
2190
            [?DQUOTE, String, ?DQUOTE];
 
2191
        {false, _, _} ->
 
2192
            [?DQUOTE, String, ?DQUOTE];
 
2193
        {true, _, _} ->
2148
2194
            [String]
2149
2195
    end.
2150
2196
 
2151
 
quoted_string_count([H | T], Count, IsSafe) ->
 
2197
quoted_string_count([?DoubleQuoteToken | T], 0 = Count, _IsSafe, _MaybeQuoted) ->
 
2198
    %% Already a quoted string. Make sure it ends
 
2199
    quoted_string_count(T, Count + 1, true, true);
 
2200
quoted_string_count([?DoubleQuoteToken], Count, IsSafe, true = MaybeQuoted) ->
 
2201
    %% An explicitly quoted string
 
2202
    {IsSafe, Count, MaybeQuoted};
 
2203
quoted_string_count([H | T], Count, IsSafe, MaybeQuoted) ->
2152
2204
    case ?classify_char(H) of
2153
 
        safe_char_upper -> quoted_string_count(T, Count + 1, IsSafe);
2154
 
        safe_char       -> quoted_string_count(T, Count + 1, IsSafe);
2155
 
        rest_char       -> quoted_string_count(T, Count + 1, false);
2156
 
        white_space     -> quoted_string_count(T, Count + 1, false);
 
2205
        safe_char_upper -> quoted_string_count(T, Count + 1, IsSafe, MaybeQuoted);
 
2206
        safe_char       -> quoted_string_count(T, Count + 1, IsSafe, MaybeQuoted);
 
2207
        rest_char       -> quoted_string_count(T, Count + 1, false, MaybeQuoted);
 
2208
        white_space     -> quoted_string_count(T, Count + 1, false, MaybeQuoted);
2157
2209
        _               -> error({illegal_char, H})
2158
2210
    end;
2159
 
quoted_string_count([], Count, IsSafe) ->
2160
 
    {IsSafe, Count}.
 
2211
quoted_string_count([], _Count, _IsSafe, true = _MaybeQuoted) ->
 
2212
    error({illegal_char, ?DoubleQuoteToken});
 
2213
quoted_string_count([], Count, IsSafe, MaybeQuoted) ->
 
2214
    {IsSafe, Count, MaybeQuoted}.
2161
2215
 
2162
2216
enc_DigitString(String, _State) when is_list(String) ->
2163
2217
    [?DQUOTE, String, ?DQUOTE].
2181
2235
    [].
2182
2236
 
2183
2237
enc_QUOTED_STRING(String, _State) when is_list(String) ->
2184
 
    {_IsSafe, Count} = quoted_string_count(String, 0, true),
2185
 
    verify_count(Count, 1, infinity),
2186
 
    [?DQUOTE, String, ?DQUOTE].
 
2238
    case quoted_string_count(String, 0, true, false) of
 
2239
        {_IsSafe, Count, false = _QuotedString} ->
 
2240
            verify_count(Count, 1, infinity),
 
2241
            [?DQUOTE, String, ?DQUOTE];
 
2242
        {_IsSafe, Count, true = _QuotedString} ->
 
2243
            verify_count(Count, 3, infinity), % quotes not included in the count
 
2244
            [String]
 
2245
    end.
 
2246
 
2187
2247
 
2188
2248
%% The internal format of hex digits is a list of octets
2189
2249
%% Min and Max means #hexDigits