diff options
| author | Hans Bolinder <[email protected]> | 2014-10-24 10:15:25 +0200 | 
|---|---|---|
| committer | Hans Bolinder <[email protected]> | 2014-11-20 08:57:25 +0100 | 
| commit | eaa4be863f11eb905e3fa379aabe303abf1cb786 (patch) | |
| tree | aeb6bfd2a6a6062818686647caf5cae86f862403 /lib/stdlib/src | |
| parent | 71ec59a0d9c89a2dedcdca29844d037c01623fb9 (diff) | |
| download | otp-eaa4be863f11eb905e3fa379aabe303abf1cb786.tar.gz otp-eaa4be863f11eb905e3fa379aabe303abf1cb786.tar.bz2 otp-eaa4be863f11eb905e3fa379aabe303abf1cb786.zip | |
stdlib: remove the last traces of Mnemosyne Rules
Robert has OK'ed the removal of the token ':-'.
Diffstat (limited to 'lib/stdlib/src')
| -rw-r--r-- | lib/stdlib/src/erl_lint.erl | 6 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_parse.yrl | 22 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_pp.erl | 23 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_scan.erl | 5 | 
4 files changed, 4 insertions, 52 deletions
| diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 39f8a26fe1..26d8454731 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -389,9 +389,7 @@ format_error({underspecified_opaque, {TypeName, Arity}}) ->                    [TypeName, gen_type_paren(Arity)]);  %% --- obsolete? unused? ---  format_error({format_error, {Fmt, Args}}) -> -    io_lib:format(Fmt, Args); -format_error({mnemosyne, What}) -> -    "mnemosyne " ++ What ++ ", missing transformation". +    io_lib:format(Fmt, Args).  gen_type_paren(Arity) when is_integer(Arity), Arity >= 0 ->      gen_type_paren_1(Arity, ")"). @@ -759,8 +757,6 @@ function_state({attribute,La,Attr,_Val}, St) ->      add_error(La, {attribute,Attr}, St);  function_state({function,L,N,A,Cs}, St) ->      function(L, N, A, Cs, St); -function_state({rule,L,_N,_A,_Cs}, St) -> -    add_error(L, {mnemosyne,"rule"}, St);  function_state({eof,L}, St) -> eof(L, St).  %% eof(LastLine, State) -> diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 767b620871..3502a50eaa 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -42,7 +42,6 @@ function_call argument_list  exprs guard  atomic strings  prefix_op mult_op add_op list_op comp_op -rule rule_clauses rule_clause rule_body  binary bin_elements bin_element bit_expr  opt_bit_size_expr bit_size_expr opt_bit_type_list bit_type_list bit_type  top_type top_type_100 top_types type typed_expr typed_attr_val @@ -54,7 +53,7 @@ bin_base_type bin_unit_type type_200 type_300 type_400 type_500.  Terminals  char integer float atom string var -'(' ')' ',' '->' ':-' '{' '}' '[' ']' '|' '||' '<-' ';' ':' '#' '.' +'(' ')' ',' '->' '{' '}' '[' ']' '|' '||' '<-' ';' ':' '#' '.'  'after' 'begin' 'case' 'try' 'catch' 'end' 'fun' 'if' 'of' 'receive' 'when'  'andalso' 'orelse'  'bnot' 'not' @@ -73,7 +72,6 @@ Rootsymbol form.  form -> attribute dot : '$1'.  form -> function dot : '$1'. -form -> rule dot : '$1'.  attribute -> '-' atom attr_val               : build_attribute('$2', '$3').  attribute -> '-' atom typed_attr_val         : build_typed_attribute('$2','$3'). @@ -520,17 +518,6 @@ comp_op -> '>' : '$1'.  comp_op -> '=:=' : '$1'.  comp_op -> '=/=' : '$1'. -rule -> rule_clauses : build_rule('$1'). - -rule_clauses -> rule_clause : ['$1']. -rule_clauses -> rule_clause ';' rule_clauses : ['$1'|'$3']. - -rule_clause -> atom clause_args clause_guard rule_body : -	{clause,?line('$1'),element(3, '$1'),'$2','$3','$4'}. - -rule_body -> ':-' lc_exprs: '$2'. - -  Erlang code.  -export([parse_form/1,parse_exprs/1,parse_term/1]). @@ -846,13 +833,6 @@ build_function(Cs) ->      Arity = length(element(4, hd(Cs))),      {function,?line(hd(Cs)),Name,Arity,check_clauses(Cs, Name, Arity)}. -%% build_rule([Clause]) -> {rule,Line,Name,Arity,[Clause]'} - -build_rule(Cs) -> -    Name = element(3, hd(Cs)), -    Arity = length(element(4, hd(Cs))), -    {rule,?line(hd(Cs)),Name,Arity,check_clauses(Cs, Name, Arity)}. -  %% build_fun(Line, [Clause]) -> {'fun',Line,{clauses,[Clause]}}.  build_fun(Line, Cs) -> diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl index 17a758ff58..469ce544c7 100644 --- a/lib/stdlib/src/erl_pp.erl +++ b/lib/stdlib/src/erl_pp.erl @@ -22,7 +22,7 @@  %%% the parser. It does not always produce pretty code.  -export([form/1,form/2, -         attribute/1,attribute/2,function/1,function/2,rule/1,rule/2, +         attribute/1,attribute/2,function/1,function/2,           guard/1,guard/2,exprs/1,exprs/2,exprs/3,expr/1,expr/2,expr/3,expr/4]).  -import(lists, [append/1,foldr/3,mapfoldl/3,reverse/1,reverse/2]). @@ -91,12 +91,6 @@ function(F) ->  function(F, Options) ->      frmt(lfunction(F, options(Options)), state(Options)). -rule(R) -> -    rule(R, none). - -rule(R, Options) -> -    frmt(lrule(R, options(Options)), state(Options)). -  -spec(guard(Guard) -> io_lib:chars() when        Guard :: [erl_parse:abstract_expr()]). @@ -199,8 +193,6 @@ lform({attribute,Line,Name,Arg}, Opts, State) ->      lattribute({attribute,Line,Name,Arg}, Opts, State);  lform({function,Line,Name,Arity,Clauses}, Opts, _State) ->      lfunction({function,Line,Name,Arity,Clauses}, Opts); -lform({rule,Line,Name,Arity,Clauses}, Opts, _State) -> -    lrule({rule,Line,Name,Arity,Clauses}, Opts);  %% These are specials to make it easier for the compiler.  lform({error,E}, _Opts, _State) ->      leaf(format("~p\n", [{error,E}])); @@ -418,19 +410,6 @@ func_clause(Name, {clause,Line,Head,Guard,Body}, Opts) ->      Bl = body(Body, Opts),      {step,Gl,Bl}. -lrule({rule,_Line,Name,_Arity,Cs}, Opts) -> -    Cll = nl_clauses(fun (C, H) -> rule_clause(Name, C, H) end, $;, Opts, Cs), -    [Cll,leaf(".\n")]. - -rule_clause(Name, {clause,Line,Head,Guard,Body}, Opts) -> -    Hl = call({atom,Line,Name}, Head, 0, Opts), -    Gl = guard_when(Hl, Guard, Opts, leaf(" :-")), -    Bl = rule_body(Body, Opts), -    {step,Gl,Bl}. - -rule_body(Es, Opts) -> -    lc_quals(Es, Opts). -  guard_when(Before, Guard, Opts) ->      guard_when(Before, Guard, Opts, ' ->'). diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl index 6fd6bb888b..4960a86760 100644 --- a/lib/stdlib/src/erl_scan.erl +++ b/lib/stdlib/src/erl_scan.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-2014. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -599,9 +599,6 @@ scan1("|"=Cs, _St, Line, Col, Toks) ->  %% :=  scan1(":="++Cs, St, Line, Col, Toks) ->      tok2(Cs, St, Line, Col, Toks, ":=", ':=', 2); -%% :- -scan1(":-"++Cs, St, Line, Col, Toks) -> -    tok2(Cs, St, Line, Col, Toks, ":-", ':-', 2);  %% :: for typed records  scan1("::"++Cs, St, Line, Col, Toks) ->      tok2(Cs, St, Line, Col, Toks, "::", '::', 2); | 
