aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/erl_parse.yrl
AgeCommit message (Collapse)Author
2018-12-28Fix erl_parse:af_constraint()Péter Gömöri
Add missing list wrapper.
2018-12-28Fix erl_parse:af_fun_type()Péter Gömöri
`af_function_type()` already contains the `{'type', anno(), 'fun', ...}` tuple so it does not have to be wrapped again.
2018-12-27Add literal character to erl_parse:abstract_type/0 typePéter Gömöri
This is allowed since 19.3 (commit 6d238032) and documented since commit 744fb920.
2018-06-28Fix typo in erl_parse type unary_op()Péter Gömöri
2018-06-18Update copyright yearHenrik Nord
2018-03-26Compile external fun expressions to literalsMichał Muskała
The expressions fun M:F/A, when all elements are literals are also treated as a literal. Since they have consistent representation and don't depend on the code currently loaded in the VM, this is safe. This can provide significant performance improvements in code using such functions extensively - a full function call to erlang:make_fun/3 is replaced by a single move instruction and no register shuffling or saving registers to stack is necessary. Additionally, compound data types that contain such external functions as elements can be treated as literals too. The commit also changes the representation of external funs to be a valid Erlang syntax and adds support for literal external funs to core Erlang.
2017-11-30Add syntax in try/catch to retrieve the stacktrace directlyBjörn Gustavsson
This commit adds a new syntax for retrieving the stacktrace without calling erlang:get_stacktrace/0. That allow us to deprecate erlang:get_stacktrace/0 and ultimately remove it. The problem with erlang:get_stacktrace/0 is that it can keep huge terms in a process for an indefinite time after an exception. The stacktrace can be huge after a 'function_clause' exception or a failed call to a BIF or operator, because the arguments for the call will be included in the stacktrace. For example: 1> catch abs(lists:seq(1, 1000)). {'EXIT',{badarg,[{erlang,abs, [[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20|...]], []}, {erl_eval,do_apply,6,[{file,"erl_eval.erl"},{line,674}]}, {erl_eval,expr,5,[{file,"erl_eval.erl"},{line,431}]}, {shell,exprs,7,[{file,"shell.erl"},{line,687}]}, {shell,eval_exprs,7,[{file,"shell.erl"},{line,642}]}, {shell,eval_loop,3,[{file,"shell.erl"},{line,627}]}]}} 2> erlang:get_stacktrace(). [{erlang,abs, [[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22, 23,24|...]], []}, {erl_eval,do_apply,6,[{file,"erl_eval.erl"},{line,674}]}, {erl_eval,expr,5,[{file,"erl_eval.erl"},{line,431}]}, {shell,exprs,7,[{file,"shell.erl"},{line,687}]}, {shell,eval_exprs,7,[{file,"shell.erl"},{line,642}]}, {shell,eval_loop,3,[{file,"shell.erl"},{line,627}]}] 3> We can extend the syntax for clauses in try/catch to optionally bind the stacktrace to a variable. Here is an example using the current syntax: try Expr catch C:E -> Stk = erlang:get_stacktrace(), . . . In the new syntax, it would look like: try Expr catch C:E:Stk -> . . . Only a variable (not a pattern) is allowed in the stacktrace position, to discourage matching of the stacktrace. (Matching would also be expensive, because the raw format of the stacktrace would have to be converted to the cooked form before matching.) Note that: try Expr catch E -> . . . is a shorthand for: try Expr catch throw:E -> . . . If the stacktrace is to be retrieved for a throw, the 'throw:' prefix must be explicitly included: try Expr catch throw:E:Stk -> . . .
2017-11-30erl_parse: Use a new pat_expr rule for pattern expressionsBjörn Gustavsson
In the grammar file for the Erlang language, patterns are parsed as expressions. erl_lint will then weed out expressions that are not legal patterns. The rule sharing causes problems if we were to introduce new syntax, for example a pattern followed by a ':'. There would be a shift/reduce conflict, and a pattern followed by a ':' would be parsed as a remote call. Introduce a new pat_expr rule to express exactly the subset of expressions that is allowed in pattern. Note: For the moment, we must allow full expressions in case clauses to keep 'merl' working.
2017-06-09stdlib: Improve Unicode handling of the Erlang parserHans Bolinder
2017-05-22stdlib: Warn for bad type variables of parameterized typesHans Bolinder
The linter emits warnings about using '_' as type variable in parameterized types.
2017-03-08stdlib: Extend functions in erl_parse to handle form_info()Hans Bolinder
For convenience, for instance in parse transforms, the different functions handling erl_anno:anno() can handle {eof, Location}, and are documented to handle all form_info().
2017-03-08stdlib: Add debug tests to the erl_parse moduleHans Bolinder
2017-01-13Merge branch 'hasse/stdlib/check_type_constraints/OTP-14070/PR-1214'Hans Bolinder
* hasse/stdlib/check_type_constraints/OTP-14070/PR-1214: stdilb: Check for bad type constraints in function types
2017-01-12Merge branch 'maint'Hans Bolinder
* maint: stdlib: Correct signatures of functions in erl_parse
2017-01-10stdlib: Correct signatures of functions in erl_parseHans Bolinder
The signatures of erl_parse:anno_to_term/1 and erl_parse:anno_from_term/1 are corrected. Using these function no longer results in false Dialyzer warnings.
2017-01-10Merge branch 'maint'Hans Bolinder
* maint: stdlib: Allow characters in types and constant patterns
2016-12-21stdlib: Allow characters in types and constant patternsHans Bolinder
Characters ($char) can be used in constant pattern expressions. They can also be used in types and contracts.
2016-12-01stdilb: Check for bad type constraints in function typesHans Bolinder
The parser recognizes the 'is_subtype(V, T)' syntax for constraints, and of course the new 'V :: T' syntax, but other variants result in an error message. Up to now, the parser and linter have let badly formed constraints through, and relied upon Dialyzer to emit warnings. is_subtype/2 cannot easily be taken out from the parser. Not only would we need find a way to emit a (linter) warning, but there also needs to be an option for suppressing the linter warning as compilation with +warnings_as_errors has to work. (Notice that the abstract format representation for 'V :: T' is the same as for 'is_subtype(V, T)'.) This correction was triggered by an email from Robert, and Kostis created pull request 1214 to provide a fix. However, Kostis' fix disallowed is_subtype() altogether, which breaks backward compatibility. As of Erlang/OTP 19.0 (ticket OTP-11879), the 'is_subtype(V, T)' is no longer documented.
2016-11-23Make use of the Header feature in yeccRichard Carlsson
2016-11-23Merge branch 'maint'Hans Bolinder
* maint: stdlib: Correct types of the abstract format
2016-11-22stdlib: Correct types of the abstract formatHans Bolinder
The types in erl_parse.yrl are more in harmony with the description in The Abstract Format (in ERTS User's Guide).
2016-09-01Remove sys_pre_expandBjörn Gustavsson
The previous commits have made sys_pre_expand superfluous. Since sys_pre_expand is undocumented and unsupported it can be removed in a major release without prior deprecation. Also remove code in erl_parse that handles abstract code that has passed through sys_pre_expand. We considered deprecating sys_pre_expand just in case, but decided against it for the following reasons: - Anyone brave and knowledgeable enough to use sys_pre_expand should be able to cope with sys_pre_expand being removed. - If we kept it, but didn't test it anywhere in OTP, it could potentially stop working. So we would probably have to add some test cases.
2016-06-10Merge branch 'hasse/dialyzer/improve_from_form/OTP-13547'Hans Bolinder
* hasse/dialyzer/improve_from_form/OTP-13547: Update primary bootstrap stdlib: Correct types and specs dialyzer: Minor adjustments dialyzer: Suppress unmatched_return for send/2 dialyzer: Improve the translation of forms to types dialyzer: Use a cache when translating forms to types dialyzer: Prepare erl_types:t_from_form() for a cache dialyzer: Optimize erl_types:t_form_form() dialyzer: Correct types syntax_tools: Correct types erts: Correct character repr in doc of the abstract format stdlib: Correct types and specs
2016-06-09Remove support for '...' in Maps typesHans Bolinder
It is possible that '...' is added later (OTP 20.0), but for now we are not sure of all details.
2016-06-09stdlib: Correct types and specsHans Bolinder
2016-06-09stdlib: Correct types and specsHans Bolinder
2016-04-28stdlib: Correct association typesHans Bolinder
'...' is allowed at the end of of association types.
2016-04-28erl_parse: Add parsing for new map type syntaxMagnus Lång
erl_types typesets mandatory keys with :=, and uses "..." as a shorthand for "any() => any()". Add these to erl_parse so that all representable types can be written in type-specs.
2016-03-01Generalize bit string comprehensionsBjörn Gustavsson
The expression in a bit string comprehension is limited to a literal bit string expression. That is, the following code is legal: << <<X>> || X <- List >> but not this code: << foo(X) || X <- List >> The limitation is annoying. For one thing, tools that transform the abstract format must be careful not to produce code such as: << begin %% Some instrumentation code. <<X>> end || X <- List >> One reason for the limitation could be that we'll get reduce/reduce conflicts if we try to allow an arbitrary expression in a bit string comprehension: binary_comprehension -> '<<' expr '||' lc_exprs '>>' : {bc,?anno('$1'),'$2','$4'}. Unfortunately, there does not seem to be an easy way to work around that problem. The best we can do is to allow 'expr_max' expressions (as in the binary syntax): binary_comprehension -> '<<' expr_max '||' lc_exprs '>>' : {bc,?anno('$1'),'$2','$4'}. That will work, but functions calls must be enclosed in parentheses: << (foo(X)) || X <- List >>
2016-01-20stdlib: Update erl_parse(3)Hans Bolinder
Calls to map_anno(), fold_anno(), and mapfold_anno() with lists of erl_parse trees have been replaced. Those functions accept lists of erl_parse trees, but it was not the intention when the functions were introduced, and it is not documented.
2016-01-20stdlib: Refine the types of the abstract formatHans Bolinder
2015-12-15stdlib: Remove undocumented function specification syntaxHans Bolinder
The syntax -spec/callback F/A :: FunctionType; has been removed. No deprecation was deemed necessary.
2015-10-08Take out automatic insertion of 'undefined' from typed record fieldsKostis Sagonas
Background ----------- In record fields with a type declaration but without an initializer, the Erlang parser inserted automatically the singleton type 'undefined' to the list of declared types, if that value was not present there. I.e. the record declaration: -record(rec, {f1 :: float(), f2 = 42 :: integer(), f3 :: some_mod:some_typ()}). was translated by the parser to: -record(rec, {f1 :: float() | 'undefined', f2 = 42 :: integer(), f3 :: some_mod:some_typ() | 'undefined'}). The rationale for this was that creation of a "dummy" #rec{} record should not result in a warning from dialyzer that e.g. the implicit initialization of the #rec.f1 field violates its type declaration. Problems --------- This seemingly innocent action has some unforeseen consequences. For starters, there is no way for programmers to declare that e.g. only floats make sense for the f1 field of #rec{} records when there is no `obvious' default initializer for this field. (This also affects tools like PropEr that use these declarations produced by the Erlang parser to generate random instances of records for testing purposes.) It also means that dialyzer does not warn if e.g. an is_atom/1 test or something more exotic like an atom_to_list/1 call is performed on the value of the f1 field. Similarly, there is no way to extend dialyzer to warn if it finds record constructions where f1 is not initialized to some float. Last but not least, it is semantically problematic when the type of the field is an opaque type: creating a union of an opaque and a structured type is very problematic for analysis because it fundamentally breaks the opacity of the term at that point. Change ------- To solve these problems the parser will not automatically insert the 'undefined' value anymore; instead the user has the option to choose the places where this value makes sense (for the field) and where it does not and insert the | 'undefined' there manually. Consequences of this change ---------------------------- This change means that dialyzer will issue a warning for all places where records with uninitialized fields are created and those fields have a declared type that is incompatible with 'undefined' (e.g. float()). This warning can be suppressed easily by adding | 'undefined' to the type of this field. This also adds documentation that the user really intends to create records where this field is uninitialized.
2015-09-15stdlib: Remove deprecated functions in erl_parse and erl_scanHans Bolinder
The recently added module erl_anno can no longer handle negative line numbers.
2015-06-18Change license text to APLv2Bruce Yinhe
2015-06-12stdlib: Introduce precedence for operators in typesHans Bolinder
Add new functions erl_parse:type_inop_prec() and erl_parse:type_preop_prec(). Get rid of paren_type used for parentheses in types.
2015-04-30stdlib: Use module erl_annoHans Bolinder
2015-04-30stdlib: Add module erl_annoHans Bolinder
Introduce erl_anno, an abstraction of the second element of tokens and tuples in the abstract format. The convention that negative line numbers can be used for silencing compiler warnings will no longer work in OTP 19; instead the annotation 'generated' is to be used.
2014-11-20stdlib: remove the last traces of Mnemosyne RulesHans Bolinder
Robert has OK'ed the removal of the token ':-'.
2014-10-01Merge branch 'maint'Björn-Egil Dahlberg
2014-09-30stdlib: erl_parse abstract MapsBjörn-Egil Dahlberg
2014-09-30stdlib: Refactor Maps farity attributesBjörn-Egil Dahlberg
2014-08-04Allow Name/Arity syntax in maps inside attributesAndrey Tsirulev
Currently Name/Arity syntax is supported in list and tuple terms. This change makes it possible to use this syntax in map terms for consistency and convenience. Example: -custom(#{test1 => init/2, test2 => [val/1, val/2]}).
2014-05-14Merge branch 'maint'Marcus Arendt
2014-05-14Merge branch 'fenollp/remove-erl_parse-legacy-map' into maintMarcus Arendt
* fenollp/remove-erl_parse-legacy-map: Replace local mapl/2 (Erlang < 5.0) unique call by a LC
2014-04-29Modify representation of the map typeHans Bolinder
Types are represented by quadruples {type, LINE, Name, Args}, but maps were represented by five-tuples {type, LINE, map_field_assoc, Dom, Range}. Note: this is *not* about the quadruples used for representing expressions, {map_field_assoc,L,K,V}.
2014-04-29Disallow '_' as type variableHans Bolinder
"... when _ :: ..." used to compile, but Dialyzer crashed.
2014-04-29Allow more type namesHans Bolinder
product/_, union/_, range/2 as well as tuple/N (N > 0), map/N (N > 0), atom/1, integer/1, binary/2, record/_, and 'fun'/_ can now be used as type names.
2014-03-25stdlib: Generalize erl_parse:abstract/2Hans Bolinder
The 'encoding' option of erl_parse:abstract/2 has been extended to include 'none' and a callback function (a predicate). The rationale is that a more general means of determining what integer lists are to be represented as strings may help readability when generating Erlang code given input in some other encoding than Latin-1 or UTF-8.
2014-03-11Replace local mapl/2 (Erlang < 5.0) unique call by a LCPierre Fenoll