~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/stdlib/src/erl_parse.yrl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% -*- erlang -*-
1
2
%% ``The contents of this file are subject to the Erlang Public License,
2
3
%% Version 1.1, (the "License"); you may not use this file except in
3
4
%% compliance with the License. You should have received a copy of the
569
570
        {error,E} -> {error,E}
570
571
    end.
571
572
 
572
 
-type(attributes() :: 'export' | 'file' | 'import' | 'module'
573
 
                    | 'record' | 'spec' | 'type').
 
573
-type attributes() :: 'export' | 'file' | 'import' | 'module'
 
574
                    | 'record' | 'spec' | 'type'.
574
575
 
575
576
build_typed_attribute({atom,La,record}, 
576
577
                      {typed_record, {atom,_Ln,RecordName}, RecTuple}) ->
704
705
    end;
705
706
build_attribute({atom,La,Attr}, Val) ->
706
707
    case Val of
707
 
        [Expr] ->
 
708
        [Expr0] ->
 
709
            Expr = attribute_farity(Expr0),
708
710
            {attribute,La,Attr,term(Expr)};
709
711
        _Other -> return_error(La, "bad attribute")
710
712
    end.
715
717
var_list(Other) ->
716
718
    return_error(?line(Other), "bad variable list").
717
719
 
718
 
-spec(error_bad_decl/2 :: (integer(), attributes()) -> no_return()).
 
720
attribute_farity({cons,L,H,T}) ->
 
721
    {cons,L,attribute_farity(H),attribute_farity(T)};
 
722
attribute_farity({tuple,L,Args0}) ->
 
723
    Args = attribute_farity_list(Args0),
 
724
    {tuple,L,Args};
 
725
attribute_farity({op,L,'/',{atom,_,_}=Name,{integer,_,_}=Arity}) ->
 
726
    {tuple,L,[Name,Arity]};
 
727
attribute_farity(Other) -> Other.
 
728
 
 
729
attribute_farity_list(Args) ->
 
730
    [attribute_farity(A) || A <- Args].
 
731
    
 
732
-spec error_bad_decl(integer(), attributes()) -> no_return().
719
733
 
720
734
error_bad_decl(L, S) ->
721
735
    return_error(L, io_lib:format("bad ~w declaration", [S])).
853
867
abstract(T) when is_atom(T) -> {atom,0,T};
854
868
abstract([]) -> {nil,0};
855
869
abstract(B) when is_bitstring(B) ->
856
 
    {bin, 0, lists:map(fun(Byte) when is_integer(Byte) ->
857
 
                               {bin_element, 0,
858
 
                                {integer, 0, Byte}, default, default};
859
 
                          (Bits) ->
860
 
                               Sz = bit_size(Bits),
861
 
                               <<Val:Sz>> = Bits,
862
 
                               {bin_element, 0,
863
 
                                {integer, 0, Val}, {integer, 0, Sz}, default}
864
 
                       end,
865
 
                       bitstring_to_list(B))};
 
870
    {bin, 0, [abstract_byte(Byte, 0) || Byte <- bitstring_to_list(B)]};
866
871
abstract([C|T]) when is_integer(C), 0 =< C, C < 256 ->
867
872
    abstract_string(T, [C]);
868
873
abstract([H|T]) ->
887
892
abstract_list([]) ->
888
893
    [].
889
894
 
 
895
abstract_byte(Byte, Line) when is_integer(Byte) ->
 
896
    {bin_element, Line, {integer, Line, Byte}, default, default};
 
897
abstract_byte(Bits, Line) ->
 
898
    Sz = bit_size(Bits),
 
899
    <<Val:Sz>> = Bits,
 
900
    {bin_element, Line, {integer, Line, Val}, {integer, Line, Sz}, default}.
 
901
 
890
902
%%% abstract/2 keeps the line number
891
903
abstract(T, Line) when is_integer(T) -> {integer,Line,T};
892
904
abstract(T, Line) when is_float(T) -> {float,Line,T};
893
905
abstract(T, Line) when is_atom(T) -> {atom,Line,T};
894
906
abstract([], Line) -> {nil,Line};
895
907
abstract(B, Line) when is_bitstring(B) ->
896
 
    {bin, Line, lists:map(fun(Byte) when is_integer(Byte) ->
897
 
                               {bin_element, Line,
898
 
                                {integer, Line, Byte}, default, default};
899
 
                          (Bits) ->
900
 
                               Sz = bit_size(Bits),
901
 
                               <<Val:Sz>> = Bits,
902
 
                               {bin_element, Line,
903
 
                                {integer, Line, Val},
904
 
                                {integer, Line, Sz},
905
 
                                default}
906
 
                       end,
907
 
                       bitstring_to_list(B))};
 
908
    {bin, Line, [abstract_byte(Byte, Line) || Byte <- bitstring_to_list(B)]};
908
909
abstract([C|T], Line) when is_integer(C), 0 =< C, C < 256 ->
909
910
    abstract_string(T, [C], Line);
910
911
abstract([H|T], Line) ->