Commit Graph

175 Commits (64f6f83f447e02d49e998f4c7ae39db4057301fe)

Author SHA1 Message Date
Gabriel Scherer 82b29828d2
Allow `[@tailcall true]` and `[@tailcall false]` (#9754)
* remove the unused is_native_tail_call_heuristic forward reference

This forward-reference from Lambda to Asmcomp was used to generate
machine-specific tailcall information in -annot output; this only use
was removed in 57d329e07b, so we can now
remove it to simplify the codebase.

The logic was non-trivial and might be useful again in the future.

* [minor] testsuite: convert warnings/w51.ml to an expect-test

* [minor] translattribute: refactor attribute payload deconstruction

* [@tailcall false]: warn if the call *is* a tailcall

(+ constructor renaming suggested by Nicolás during review)

* Changes

* testsuite: add an example with the 'invalid payload' exception

(suggested by Nicolás during review)
2020-10-10 13:41:39 +02:00
Leo White fdbb4e201e Fix PR#7538 2020-09-18 09:38:08 +01:00
hhugo 49aa87c316
Introduce warning 68 to warn about hidden allocation due to pattern match of mutable field in curried functions (#9751)
Introduce new warning 68
2020-08-17 09:47:36 +01:00
Fourchaux 44e6cf4e0f
typos (#9806) 2020-07-28 12:22:03 +01:00
Nicolás Ojeda Bär 5789d6c6df Rename Expect_tailcall => Tailcall_expected 2020-07-20 08:31:18 +02:00
Gabriel Scherer fdf86ad403 matching: a first-order representation for match-failure handling 2020-07-08 22:38:47 +02:00
Gabriel Scherer 6aeed1c84d pass a proper location to Matching.for_trywith
Actually *using* the location in the failure handler would be
incorrect, as it adds noise to backtraces involving partial exception
handlers. This is now properly documented.

We still take the caller location (which is currently ignored) for
consistency with other toplevel Matching functions, and because that
may become useful if we want to add more error-reporting or warnings
in compile_matching.
2020-07-08 22:38:10 +02:00
Gabriel Scherer 50806ced7f
Merge pull request #9216 from gasche/lambda-duplicate
extend Lambda.subst on bound variables, add Lambda.duplicate
2020-07-02 22:55:49 +02:00
Jacques Garrigue 95a8fbfd5b change API for Env.open_signature to clarify errors 2020-06-23 16:36:55 +02:00
Nicolás Ojeda Bär 33416d11db
Merge pull request #9469 from lpw25/fix-lazy-backtraces
Better backtraces for lazy values
2020-06-14 11:34:04 +02:00
Leo White a02707c610 Better backtraces for lazy values 2020-06-14 07:57:35 +01:00
Gabriel Scherer b7509ca82f
Merge pull request #9442 from gasche/tailcall-attribute-refactoring
[minor] refactoring the datatype for the [@tailcall] attribute
2020-06-10 10:18:12 +02:00
Gabriel Scherer cc7d557b55 extend Lambda.subst on bound variables, add Lambda.duplicate
It is invalid to reuse a Lambda.t term twice, because bound variables
may be used non-uniquely. If we want to perform a code transformation
may duplicate subterms in some cases, we have to refresh all bound
variables of the copied subterm.

The present PR implements a function

    Lambda.duplicate : lambda -> lambda

that does exactly this. It is implemented by making Lambda.subst
parametrized over a transformation on bound variables.
2020-06-09 09:38:26 +02:00
Gabriel Scherer d260a79416 [refactoring] gives tailcall attributes a more standard structure
We want to start allowing more information in the payload of
[@tailcall] attributes (currently no payload is supported), for
example we could consider using [@tailcall false] to ask the code
generator to disable a tail call.

A first required step in this direction is to use a custom datatype to
represent the tail-call attribute, instead of a boolean. This is
consistent with the other application-site
attributes (inline_attribute, specialise_attribute, local_attribute),
so it makes the code more regular -- but the change itself is
boilerplate-y.
2020-06-08 15:39:50 +02:00
Gabriel Scherer 792deb120f [minor] printlambda: print the 'tailcall' attribute in the same style as others 2020-06-08 15:39:20 +02:00
Gabriel Scherer 68a3c8eef9 matching: [minor] refactor the local control flow of the Unused exception 2020-06-07 16:27:16 +02:00
Thomas Refis ddf93aa22c matching: try => match with exception
This makes it clearer where the exception comes from.
2020-06-06 18:46:34 +02:00
Thomas Refis e17f81511c matching: flatten_simple_pattern does not raise 2020-06-06 18:46:34 +02:00
Thomas Refis f491929b3b matching: push simple types to flatten_pattern
Unfortunately since the function is exposed and used in translcore we
need to keep the generic one, and introduce a flatten_simple_pattern.
2020-06-06 18:46:34 +02:00
Thomas Refis 2f57af2c40 matching: argo => arg_id 2020-06-05 23:07:16 +02:00
Xavier Leroy 4aa90e9784
Limit the number of parameters for an uncurried or untupled function (#9620)
This commit introduces a quantity Lambda.max_arity that is the maximal
number of parameters that a Lambda function can have.

Uncurrying is throttled so that, for example, assuming the limit is 10,
a 15-argument curried function fun x1 ... x15 -> e
becomes a 10-argument function (x1...x10) that returns a 5-argument
function (x11...x15).

Concerning untupling, a function that takes a N-tuple of arguments,
where N is above the limit, remains a function that takes a single
argument that is a tuple.

Currently, max_arity is set to 126 in native-code, to match the new
representation of closures implemented by #9619.  A signed 8-bit field
is used to store the arity.  126 instead of 127 to account for the
extra "environment" argument.

In bytecode the limit is infinity (max_int) because there are no needs
yet for a limit on the number of parameters.
2020-06-05 18:45:38 +02:00
Stephen Dolan 0d44a6cfe6 Remove Const_pointer from Lambda and Clambda (#9585)
Lambda and Clambda distinguish Const_int from Const_pointer only so
that they can pass the information to Cmm. But now that that
Const_pointer is gone from Cmm (#9578), there's no need for the
distinction in Lambda either.

This PR requires a bootstrap, because the .cmo format changes:
Lambda.structured_constant has one fewer constructor.  The bootstrap
is in the following commit.
2020-06-02 11:19:20 +02:00
Gabriel Scherer bf95a24739 Matching: propagate constructor descriptions in complete_pats_constrs
This simplifies this particular interface boundary between Matching
and Parmatch.

(Suggested by Florian Angeletti)
2020-05-26 15:47:41 +02:00
Gabriel Scherer d333ac83ec matching: use constructor descriptions instead of tags as matching keys
This loses no information (descriptions contain the tag), but it will
make it easier to obtain the descriptions inside `combine_constructor`
without doing a dynamic check on the patterns. This will in turn help
simplify the interaction with `Parmatch.complete_constrs`.

Note: after this patch we use `Types.equal_tag` instead of `( = )` to
compare tags during pattern-matching compilation. This is better code,
and we believe that it does not change the behavior: `Types.equal_tag`
is mostly similar to a type-specialized version of `( = )`, except
that it calls `Ident.same` that just compares the stamps and ignore
the names, which (assuming well-formedness of idents) is equivalent
and slightly faster.
2020-05-25 17:06:31 +02:00
Gabriel Scherer 1ee6ee4194 fixup! matching: use pattern views in Parmatch as well 2020-05-21 09:51:30 +02:00
Gabriel Scherer 68dc87c9e9 matching: use pattern views in Parmatch as well 2020-05-14 10:27:50 +02:00
Gabriel Scherer e19a3afcb4 matching: move {general,simple,half_simple}_view to Patterns 2020-05-14 10:27:15 +02:00
Gabriel Scherer 4d6267d3ba matching: move (Non_empty_row, views, General) to patterns.ml 2020-05-14 10:26:01 +02:00
Gabriel Scherer 0e979b7ea9 patterns: reuse ('a Typedtree.pattern_) to define Patterns.Head.t 2020-05-14 10:26:01 +02:00
Gabriel Scherer f5f4ba67a9 matching: separate types for rows and clauses
"rows" are common abstraction of both pattern analysis and
compilation, but clauses carrying a Lambda.t term are
compilation-specific. Separating rows will thus enable moving more
logic to typing/patterns for use in both settings.
2020-05-14 10:16:34 +02:00
Gabriel Scherer 54b79d3b27 [minor] matching: rename Non_empty_clause.{map_head => map_first} 2020-05-14 10:13:02 +02:00
Gabriel Scherer ffb6caef8b patterns: move Parmatch.Pattern_head into Patterns.Head
The aim is to also move the Simple/Half_simple/General stuff from
matching, but we need to split in those modules the part that are
purely structural (they go in Patterns) and the parts that are
actually compilation logic (Half_simple.of_clause), those stay in
Matching.
2020-05-14 10:11:36 +02:00
Gabriel Scherer b3434751e2
Merge pull request #9520 from trefis/rematch-make_matching-cleanup
pattern-matching refactoring: refactor the `make_<foo>_matching` functions
2020-05-14 09:21:07 +02:00
Nicolás Ojeda Bär 4e33dcf35f Add %loc_FUNCTION primitive 2020-05-13 20:49:01 +02:00
Gabriel Scherer 065139617f matching: factorize the make_*_matching functions
Before, each head construction had a `make_<foo>_matching` construct that
was responsible for three things:
- consuming the argument from the argument list
  (the "argument" is a piece of lambda code to access
   the value of the current scrutinee)
- building arguments for the subpatterns of the scrutinee
  and pushing them to the argument list
- building a `cell` structure out of this, representing a head group
  during compilation

Only the second point is really specific to each construction.

This refactoring turns this second point into a construct-specific
`get_expr_args_<foo>` function (similarly to `get_pat_args_<foo>`),
and moves the first and third point to a generic `make_matching`
function.

Note: this commit contains a minor improvement to the location used to
force (lazy ..) arguments.
2020-05-13 17:18:08 +02:00
Gabriel Scherer 3527653363 matching: add a comment suggested by Florian Angeletti's review 2020-05-01 21:58:28 +02:00
Gabriel Scherer 50fdc06fcd [minor] matching.ml: tune ~scopes handling 2020-05-01 21:56:27 +02:00
Gabriel Scherer ac1243cbd1 matching: use heads in the make_*_matching specialization calls 2020-05-01 21:56:27 +02:00
Gabriel Scherer a26e509c57 matching: finally, merge matcher and Context.ctx_matcher 2020-05-01 21:56:15 +02:00
Gabriel Scherer 387955e189 matching: refine the types in Context.ctx_matcher 2020-05-01 21:56:15 +02:00
Gabriel Scherer 0f5a1c4d1e matching: consolidate all matcher_ functions in a single matcher_head
This commit is delicate and needs a careful review.

The `matcher_of_pattern` function is a temporary measure to reduce the
invasiveness of the patch, and make it easier to review.

(Note for reviewers: in the previous version the Record case had
a funny handling of Any, but it is in fact equivalent to just adding
omegas as we now do in all cases.)

There are two obvious directions for improvement:

- Get rid of matcher_of_pattern and pass a head directly to the
  various make_matching_* functions.

- Try to factorize this code with ctx_matcher which, it is now
  obvious, does essentially the same thing.

Another, less immediate area of attack would be to consider
a presentation of Pattern_head.t where the Any case can be statically
ruled out -- maybe the description could have two levels, one
isomorphic to option (Any or not?) and one for non-any heads.
2020-05-01 21:56:15 +02:00
Gabriel Scherer 97caf289b5 matching: specialize_matrix uses non-empty rows 2020-05-01 21:56:15 +02:00
Gabriel Scherer 67c56e6ec8 matching: matcher_* take Simple.pattern arguments 2020-05-01 21:56:15 +02:00
Stephen Dolan 2986beaa78 Replace Location.t with Lambda.scoped_location in Lambda code
This commit threads scopes through translation from Typedtree to
Lambda, extending the scopes when entering functions, modules,
classes and methods.
2020-04-27 12:58:53 +01:00
Stephen Dolan a5292808d2 Introduce the Lambda.scoped_location type 2020-04-27 12:51:46 +01:00
Gabriel Scherer 4943a373f3
Merge pull request #9464 from gasche/rematch-exceptionless-matcher
pattern-matching refactoring: simplify `Default_env.specialize_matrix` by avoiding exceptions
2020-04-23 12:18:13 +02:00
Thomas Refis 9f49a71e90
Add forgotten substitution when compiling anonymous modules (#9477)
Fixes #9375
2020-04-23 10:55:40 +02:00
Gabriel Scherer 6e153b1e71 matching: remove the OrPat exception by handling Tpat_or on the caller side
(This commit is more tricky than the previous ones in the patchset
and requires a careful review.)

This refactoring clarifies and simplifies the specialize_matrix logic
by getting rid of the OrPat exception used in a higher-order
way (or sometimes not used in certain matchers, when it is possible to
"push" the or-pattern down in the pattern). Instead it uses an
arity-based criterion to implement the or-pattern-related logic once
in the specializer, instead of having to implement it in each
matcher. As a result, the compiler improves a bit as it will push
or-patterns down during specialization in valid situations that were
not implemented before -- probably because they are not terribly
important in practice: all constant and arity-1 constructs benefit
from optimized or-pattern handling, in particular the following are
new:
- lazy patterns
- non-constant polymorphic variants
- size-one records and arrays
2020-04-22 21:32:38 +02:00
Gabriel Scherer a2e6746f64 matching: refactor recursive specialization functions for clarity
Several functions in the pattern-matching compiler do recursive
"specialization" through a filter_rec helper written in tail-call
style with a 'rem' parameter containing the matrix rows yet to be
processed as input. Typical returns of the function are

  foo :: filter_rec rem

to add a new output, and

  filter_rec (foo :: rem)

to add a new input to be processed (usually by partial decomposition
of the current input row).

Some places would contain the declaration (let rem = filter_rec rem)
to factorize outputs of the first kind, but this gives a programming
style that is very confusing as `rem` may now represent either an
input or an output of the filter.

Using better types (as will be done farther away in the
pattern-matching refactoring) avoids this problem completely:
specialization then has different input and output types (typically,
from general to half-simple patterns), so incorrectly mixing inputs
and outputs is impossible. Yay typing.
2020-04-22 09:58:04 +02:00
Gabriel Scherer 537e395cc0 matching: pass explicit arity to Default_environment.specialize 2020-04-18 11:08:12 +02:00