diff options
Diffstat (limited to 'lib/stdlib/src')
| -rw-r--r-- | lib/stdlib/src/erl_expand_records.erl | 5 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_lint.erl | 8 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_parse.yrl | 39 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_pp.erl | 24 | ||||
| -rw-r--r-- | lib/stdlib/src/lib.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/src/ms_transform.erl | 7 | ||||
| -rw-r--r-- | lib/stdlib/src/proplists.erl | 5 | ||||
| -rw-r--r-- | lib/stdlib/src/qlc.erl | 7 | ||||
| -rw-r--r-- | lib/stdlib/src/qlc_pt.erl | 18 | ||||
| -rw-r--r-- | lib/stdlib/src/sofs.erl | 3 | 
10 files changed, 58 insertions, 60 deletions
| diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl index 9c0a7fb7d5..ebcbc54ab1 100644 --- a/lib/stdlib/src/erl_expand_records.erl +++ b/lib/stdlib/src/erl_expand_records.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 2005-2015. All Rights Reserved. +%% Copyright Ericsson AB 2005-2016. All Rights Reserved.  %%  %% Licensed under the Apache License, Version 2.0 (the "License");  %% you may not use this file except in compliance with the License. @@ -37,8 +37,9 @@                   checked_ra=[]        % successfully accessed records                  }). --spec(module(AbsForms, CompileOptions) -> AbsForms when +-spec(module(AbsForms, CompileOptions) -> AbsForms2 when        AbsForms :: [erl_parse:abstract_form()], +      AbsForms2 :: [erl_parse:abstract_form()],        CompileOptions :: [compile:option()]).  %% Is is assumed that Fs is a valid list of forms. It should pass diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 2508f96b91..e9332ce069 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -99,7 +99,7 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->                 module='',                       %Module                 behaviour=[],                    %Behaviour                 exports=gb_sets:empty()	:: gb_sets:set(fa()),%Exports -               imports=[] :: [fa()],            %Imports, an orddict() +               imports=[] :: orddict:orddict(fa(), module()),%Imports                 compile=[],                      %Compile flags                 records=dict:new()               %Record definitions                     :: dict:dict(atom(), {line(),Fields :: term()}), @@ -467,7 +467,7 @@ used_vars(Exprs, BindingsList) ->  %%  really all ordsets!  -spec(module(AbsForms) -> {ok, Warnings} | {error, Errors, Warnings} when -      AbsForms :: [erl_parse:abstract_form()], +      AbsForms :: [erl_parse:abstract_form() | erl_parse:form_info()],        Warnings :: [{file:filename(),[ErrorInfo]}],        Errors :: [{FileName2 :: file:filename(),[ErrorInfo]}],        ErrorInfo :: error_info()). @@ -479,7 +479,7 @@ module(Forms) ->  -spec(module(AbsForms, FileName) ->               {ok, Warnings} | {error, Errors, Warnings} when -      AbsForms :: [erl_parse:abstract_form()], +      AbsForms :: [erl_parse:abstract_form() | erl_parse:form_info()],        FileName :: atom() | string(),        Warnings :: [{file:filename(),[ErrorInfo]}],        Errors :: [{FileName2 :: file:filename(),[ErrorInfo]}], @@ -492,7 +492,7 @@ module(Forms, FileName) ->  -spec(module(AbsForms, FileName, CompileOptions) ->               {ok, Warnings} | {error, Errors, Warnings} when -      AbsForms :: [erl_parse:abstract_form()], +      AbsForms :: [erl_parse:abstract_form() | erl_parse:form_info()],        FileName :: atom() | string(),        CompileOptions :: [compile:option()],        Warnings :: [{file:filename(),[ErrorInfo]}], diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index a896de4f1c..85b2816451 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -170,9 +170,6 @@ fun_type -> '(' top_types ')' '->' top_type                                     : {type, ?anno('$1'), 'fun',                                        [{type, ?anno('$1'), product, '$2'},'$5']}. -map_pair_types  -> '...'           : [{type, ?anno('$1'), map_field_assoc, -                                       [{type, ?anno('$1'), any, []}, -                                        {type, ?anno('$1'), any, []}]}].  map_pair_types -> map_pair_type                    : ['$1'].  map_pair_types -> map_pair_type ',' map_pair_types : ['$1'|'$3']. @@ -534,7 +531,7 @@ Erlang code.  -compile([{hipe,[{regalloc,linear_scan}]}]).  -export_type([abstract_clause/0, abstract_expr/0, abstract_form/0, -              abstract_type/0, error_info/0]). +              abstract_type/0, form_info/0, error_info/0]).  %% Start of Abstract Format @@ -546,7 +543,6 @@ Erlang code.                         | af_export()                         | af_import()                         | af_export_type() -                       | af_optional_callbacks()                         | af_compile()                         | af_file()                         | af_record_decl() @@ -573,9 +569,6 @@ Erlang code.  -type af_ta_list() :: [{type_name(), arity()}]. --type af_optional_callbacks() :: -        {'attribute', anno(), 'optional_callbacks', af_fa_list()}. -  -type af_compile() :: {'attribute', anno(), 'compile', any()}.  -type af_file() :: {'attribute', anno(), 'file', {string(), anno()}}. @@ -867,16 +860,22 @@ Erlang code.                                     | af_unary_op(af_singleton_integer_type())                                     | af_binary_op(af_singleton_integer_type()). --type af_literal() :: af_atom() | af_integer() | af_float() | af_string(). +-type af_literal() :: af_atom() +                    | af_character() +                    | af_float() +                    | af_integer() +                    | af_string().  -type af_atom() :: af_lit_atom(atom()).  -type af_lit_atom(A) :: {'atom', anno(), A}. --type af_integer() :: {'integer', anno(), non_neg_integer()}. +-type af_character() :: {'char', anno(), char()}.  -type af_float() :: {'float', anno(), float()}. +-type af_integer() :: {'integer', anno(), non_neg_integer()}. +  -type af_string() :: {'string', anno(), string()}.  -type af_match(T) :: {'match', anno(), af_pattern(), T}. @@ -944,6 +943,10 @@ Erlang code.  -type type_name() :: atom(). +-type form_info() :: {'eof', erl_anno:line()} +                   | {'error', erl_scan:error_info() | error_info()} +                   | {'warning', erl_scan:error_info() | error_info()}. +  %% End of Abstract Format  %% XXX. To be refined. @@ -1503,8 +1506,9 @@ type_preop_prec('#') -> {700,800}.                          | abstract_type().  -spec map_anno(Fun, Abstr) -> NewAbstr when -      Fun :: fun((Anno) -> Anno), +      Fun :: fun((Anno) -> NewAnno),        Anno :: erl_anno:anno(), +      NewAnno :: erl_anno:anno(),        Abstr :: erl_parse_tree(),        NewAbstr :: erl_parse_tree(). @@ -1513,14 +1517,14 @@ map_anno(F0, Abstr) ->      {NewAbstr, []} = modify_anno1(Abstr, [], F),      NewAbstr. --spec fold_anno(Fun, Acc0, Abstr) -> NewAbstr when +-spec fold_anno(Fun, Acc0, Abstr) -> Acc1 when        Fun :: fun((Anno, AccIn) -> AccOut),        Anno :: erl_anno:anno(),        Acc0 :: term(), +      Acc1 :: term(),        AccIn :: term(),        AccOut :: term(), -      Abstr :: erl_parse_tree(), -      NewAbstr :: erl_parse_tree(). +      Abstr :: erl_parse_tree().  fold_anno(F0, Acc0, Abstr) ->      F = fun(A, Acc) -> {A, F0(A, Acc)} end, @@ -1528,8 +1532,9 @@ fold_anno(F0, Acc0, Abstr) ->      NewAcc.  -spec mapfold_anno(Fun, Acc0, Abstr) -> {NewAbstr, Acc1} when -      Fun :: fun((Anno, AccIn) -> {Anno, AccOut}), +      Fun :: fun((Anno, AccIn) -> {NewAnno, AccOut}),        Anno :: erl_anno:anno(), +      NewAnno :: erl_anno:anno(),        Acc0 :: term(),        Acc1 :: term(),        AccIn :: term(), @@ -1545,7 +1550,9 @@ mapfold_anno(F, Acc0, Abstr) ->        Abstr :: erl_parse_tree().  new_anno(Term) -> -    map_anno(fun erl_anno:new/1, Term). +    F = fun(L, Acc) -> {erl_anno:new(L), Acc} end, +    {NewAbstr, []} = modify_anno1(Term, [], F), +    NewAbstr.  -spec anno_to_term(Abstr) -> term() when        Abstr :: erl_parse_tree(). diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl index ca764675fc..016962f538 100644 --- a/lib/stdlib/src/erl_pp.erl +++ b/lib/stdlib/src/erl_pp.erl @@ -70,13 +70,13 @@  %%%  -spec(form(Form) -> io_lib:chars() when -      Form :: erl_parse:abstract_form()). +      Form :: erl_parse:abstract_form() | erl_parse:form_info()).  form(Thing) ->      form(Thing, none).  -spec(form(Form, Options) -> io_lib:chars() when -      Form :: erl_parse:abstract_form(), +      Form :: erl_parse:abstract_form() | erl_parse:form_info(),        Options :: options()).  form(Thing, Options) -> @@ -344,27 +344,9 @@ binary_type(I1, I2) ->  map_type(Fs) ->      {first,[$#],map_pair_types(Fs)}. -map_pair_types(Fs0) -> -    Fs = replace_any_map(Fs0), +map_pair_types(Fs) ->      tuple_type(Fs, fun map_pair_type/2). -replace_any_map([{type,Line,map_field_assoc,[KType,VType]}]=Fs) -> -    IsAny = fun({type,_,any,[]}) -> true; -    %%         ({var,_,'_'}) -> true; -               (_) -> false -            end, -    case IsAny(KType) andalso IsAny(VType) of -        true -> -            [{type,Line,map_field_assoc,any}]; -        false -> -            Fs -    end; -replace_any_map([F|Fs]) -> -    [F|replace_any_map(Fs)]; -replace_any_map([]) -> []. - -map_pair_type({type,_Line,map_field_assoc,any}, _Prec) -> -    leaf("...");  map_pair_type({type,_Line,map_field_assoc,[KType,VType]}, Prec) ->      {list,[{cstep,[ltype(KType, Prec),leaf(" =>")],ltype(VType, Prec)}]};  map_pair_type({type,_Line,map_field_exact,[KType,VType]}, Prec) -> diff --git a/lib/stdlib/src/lib.erl b/lib/stdlib/src/lib.erl index 6fba63a895..56654097d9 100644 --- a/lib/stdlib/src/lib.erl +++ b/lib/stdlib/src/lib.erl @@ -73,7 +73,7 @@ nonl([H|T]) -> [H|nonl(T)].  send(To, Msg) -> To ! Msg. --spec sendw(To, Msg) -> Msg when +-spec sendw(To, Msg) -> term() when        To :: pid() | atom() | {atom(), node()},        Msg :: term(). diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl index 24b5fde1db..c0eea652e7 100644 --- a/lib/stdlib/src/ms_transform.erl +++ b/lib/stdlib/src/ms_transform.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 2002-2015. All Rights Reserved. +%% Copyright Ericsson AB 2002-2016. All Rights Reserved.  %%   %% Licensed under the Apache License, Version 2.0 (the "License");  %% you may not use this file except in compliance with the License. @@ -224,8 +224,9 @@ transform_from_shell(Dialect, Clauses, BoundEnvironment) ->  %% Called when translating during compiling  %% --spec parse_transform(Forms, Options) -> Forms when -      Forms :: [erl_parse:abstract_form()], +-spec parse_transform(Forms, Options) -> Forms2 when +      Forms :: [erl_parse:abstract_form() | erl_parse:form_info()], +      Forms2 :: [erl_parse:abstract_form() | erl_parse:form_info()],        Options :: term().  parse_transform(Forms, _Options) -> diff --git a/lib/stdlib/src/proplists.erl b/lib/stdlib/src/proplists.erl index 8e99ec0ed9..5356467b19 100644 --- a/lib/stdlib/src/proplists.erl +++ b/lib/stdlib/src/proplists.erl @@ -438,8 +438,9 @@ substitute_aliases_1([], P) ->  %% @see normalize/2  -spec substitute_negations(Negations, ListIn) -> ListOut when -      Negations :: [{Key, Key}], -      Key :: term(), +      Negations :: [{Key1, Key2}], +      Key1 :: term(), +      Key2 :: term(),        ListIn :: [term()],        ListOut :: [term()]. diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl index b396ba7057..f3665824f2 100644 --- a/lib/stdlib/src/qlc.erl +++ b/lib/stdlib/src/qlc.erl @@ -734,10 +734,11 @@ table(TraverseFun, Options) when is_function(TraverseFun) ->  table(T1, T2) ->      erlang:error(badarg, [T1, T2]). --spec(transform_from_evaluator(LC, Bs) -> Expr when +-spec(transform_from_evaluator(LC, Bs) -> Return when        LC :: abstract_expr(), -      Expr :: abstract_expr(), -      Bs :: erl_eval:binding_struct()). +      Bs :: erl_eval:binding_struct(), +      Return :: {ok, abstract_expr()} +              | {not_ok, {error, module(), Reason :: term()}}).  transform_from_evaluator(LC, Bs0) ->      qlc_pt:transform_from_evaluator(LC, Bs0). diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl index e4b9768b12..0db63b81f4 100644 --- a/lib/stdlib/src/qlc_pt.erl +++ b/lib/stdlib/src/qlc_pt.erl @@ -67,8 +67,8 @@  %%%  -spec(parse_transform(Forms, Options) -> Forms2 when -      Forms :: [erl_parse:abstract_form()], -      Forms2 :: [erl_parse:abstract_form()], +      Forms :: [erl_parse:abstract_form() | erl_parse:form_info()], +      Forms2 :: [erl_parse:abstract_form() | erl_parse:form_info()],        Options :: [Option],        Option :: type_checker | compile:option()). @@ -117,19 +117,21 @@ parse_transform(Forms0, Options) ->          true = ets:delete(NodeInfo)      end. --spec(transform_from_evaluator(LC, Bs) -> Expr when +-spec(transform_from_evaluator(LC, Bs) -> Return when        LC :: erl_parse:abstract_expr(), -      Expr :: erl_parse:abstract_expr(), -      Bs :: erl_eval:binding_struct()). +      Bs :: erl_eval:binding_struct(), +      Return :: {ok, erl_parse:abstract_expr()} +              | {not_ok, {error, module(), Reason :: term()}}).  transform_from_evaluator(LC, Bindings) ->      ?DEBUG("qlc Parse Transform (Evaluator Version)~n", []),      transform_expression(LC, Bindings, false). --spec(transform_expression(LC, Bs) -> Expr when +-spec(transform_expression(LC, Bs) -> Return when        LC :: erl_parse:abstract_expr(), -      Expr :: erl_parse:abstract_expr(), -      Bs :: erl_eval:binding_struct()). +      Bs :: erl_eval:binding_struct(), +      Return :: {ok, erl_parse:abstract_expr()} +              | {not_ok, [{error, Reason :: term()}]}).  transform_expression(LC, Bindings) ->      transform_expression(LC, Bindings, true). diff --git a/lib/stdlib/src/sofs.erl b/lib/stdlib/src/sofs.erl index b18df2ad09..c244e06ca4 100644 --- a/lib/stdlib/src/sofs.erl +++ b/lib/stdlib/src/sofs.erl @@ -621,6 +621,9 @@ canonical_relation(Sets) when ?IS_SET(Sets) ->  %%% Functions on binary relations only.  %%% +-spec(rel2fam(BinRel) -> Family when +      Family :: family(), +      BinRel :: binary_relation()).  rel2fam(R) ->      relation_to_family(R). | 
