Skip to content

Conversation

@fpottier
Copy link
Collaborator

@fpottier fpottier commented Jun 6, 2018

dune.opam:
Add a constraint that Menhir (if present) must be >= 20180523.
src/jbuild.{ml,mli}:
Change the type of the flags in a (menhir ... stanza)
from [Ordered_set_lang.Unexpanded.t] to [string list].
This makes it possible for the build rules to depend
on the presence of certain flags (such as --only-tokens).
src/menhir.ml:
Update the build rules to take advantage of the commands
[--infer-write-query] and [--infer-read-reply] offered by Menhir.

Copy link
Member

@rgrinberg rgrinberg left a comment

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Thanks Francois, this looks good. A few points to get the PR rolling:

  • Make sure to sign off your commit with -s. We require a DCO for all contributions to dune: https://github.com/ocaml/dune/blob/master/CONTRIBUTING.md

  • You can run the tests with $ make test. If you're happy with the changes to expect tests, you can accept them with $ make accept-corrections and commit the result.

  • If it's not too much trouble, could you run your code through ocp-indent? I have nothing against your formatting, but I'm afraid it will be hard to keep it up without any kind of formatting tool.

src/menhir.ml Outdated
| "--infer"
| "--infer-write-query"
| "--infer-read-reply" ->
Loc.fail stanza.loc
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Slightly nicer would be to use a more precise location for the flags. For example, here's what you can do attach a loc to every flag:

diff --git a/src/jbuild.ml b/src/jbuild.ml
index c1717d63..dd9e3a3d 100644
--- a/src/jbuild.ml
+++ b/src/jbuild.ml
@@ -1077,7 +1077,7 @@ end
 module Menhir = struct
   type t =
     { merge_into : string option
-    ; flags      : string list
+    ; flags      : (Loc.t * string) list
     ; modules    : string list
     ; mode       : Rule.Mode.t
     ; loc        :  Loc.t
@@ -1086,7 +1086,7 @@ module Menhir = struct
   let v1 =
     record
       (field_o "merge_into" string >>= fun merge_into ->
-       field "flags" (list string) ~default:[] >>= fun flags ->
+       field "flags" (list (located string)) ~default:[] >>= fun flags ->
        field "modules" (list string) >>= fun modules ->
        Rule.Mode.field >>= fun mode ->
        return
diff --git a/src/jbuild.mli b/src/jbuild.mli
index 609ccece..a0a60e98 100644
--- a/src/jbuild.mli
+++ b/src/jbuild.mli
@@ -298,7 +298,7 @@ end
 module Menhir : sig
   type t =
     { merge_into : string option
-    ; flags      : string list
+    ; flags      : (Loc.t * string) list
     ; modules    : string list
     ; mode       : Rule.Mode.t
     ; loc        : Loc.t

And if that is a bit fine grained, we can consider Loc.t * (string list). But it's really nice to have precise error messages for your editor to jump to.

Copy link
Collaborator Author

@fpottier fpottier Jun 8, 2018

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Regarding make test: (updated comment) after I installed all required packages, this command succeeds with just a couple warnings (warning 40) in upstream/master.

I will make sure that my PR does not cause new failures to appear.

src/menhir.ml Outdated
List.mem "--only-tokens" ~set:stanza.flags
in
rule (menhir args)
if ocaml_type_inference_disabled then
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

It's a bit sad to lose the ability to use Ordered_set_lang.t because of this. Would it make sense for this option to be toggled with a separate field in the stanza if there's no workaround?

The reason why it's nice to have Ordered_set_lang.t btw is that it lets you change the set of flags in a future proof way. Eventually, we'll have the ability to change what :standard will mean for a project and it would be nice if such changes propagated.

Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I could revert to Ordered_set_lang.t if you wish.
Then, how would I implement your other suggestion of giving a precise error location when a reserved flag is given by the user? It seems that Super_context.expand_and_eval_set returns an action of type (unit, string list) Build.t which does not give me access to the location of each individual flag.

Copy link

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I suggest the following: we add a function in Ordered_set_lang.Unexpanded.t to scan the the static strings. Then in menhir we do the following:

  • scan the flags for a plain --only-tokens flag and select the behaviour accordingly
  • if --only-tokens wasn't present, scan the flags after they are fully evaluated and error out if --only-tokens is present

Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

That sounds good. It should still allow catching the cases where people pass incorrect static flags, and would still allow using your expansion mechanism inside flags.

Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Okay, this behavior seems good to me. Supporting Ordered_ste_lang is now even more important as it's going to be a mechanism for controlling bulk builds in conjunction with (env ..)

Copy link

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

master now has Ordered_set_lang.Unexpanded.fold_strings and String_with_vars.text_only which should allow implementing this.

@rgrinberg
Copy link
Member

Oh and 1 more thing, this PR will also require update CHANGES and the manual. But that doesn't have to come right away.

I'm also thinking that we should give the menhir support its own page in the manual page. Our manual is written in a markdown like markup called rst and you can preview the manual locally by installing sphinx. The manual is updated on every commit and is available here: http://dune.readthedocs.io/. Don't worry about the formatting too much if you're unfamiliar with rst, we can fix that up.

@rgrinberg
Copy link
Member

@fpottier okay now if you rebase this on master, you will have menhir.rst where you can update the docs.

@Niols
Copy link
Contributor

Niols commented Jun 22, 2018

Hey there. I would love to see that happening as the current state of Dune prevents me from using it in many of my projects that require Menhir!

@trefis
Copy link
Collaborator

trefis commented Jun 28, 2018

Note: for merlin we use the --cmly flag, which generates an extra file.
It would be nice to add proper support for this, i.e. to register the extra target when the flag is passed.

I'd be happy to make a PR for that once this one gets merged, but as I suspect it's just a few more lines of code it could probably be directly added to this PR.

@rgrinberg
Copy link
Member

@fpottier would you mind signing your commit here? I'd like to push some of the improvements we discussed to this branch, but that would make signing the commit for you later harder.

@fpottier
Copy link
Collaborator Author

fpottier commented Aug 2, 2018

Sorry, what exactly should I do?
I have lost track of the various commits/branches and their state
and am on vacation, so don't have a lot of time to look into this.

@rgrinberg
Copy link
Member

According to https://github.com/ocaml/dune/blob/master/CONTRIBUTING.md, every dev must sign their commits for them to be considered for inclusion. This is done by creating the commit with -s. You can also sign an existing commit with $ git commit --amend -s. After that just force push the commit to this branch.

Enjoy your vacation!

@fpottier
Copy link
Collaborator Author

fpottier commented Aug 3, 2018

OK, I have signed my commit (I think).

I haven't changed the code to use Ordered_set_lang.t again.
Perhaps you could do it? Or I'll do it later on.

There are more small improvements that I could make in the future.
Is there a place in the repository where I could store a TODO file specific to Menhir support in Dune?

@rgrinberg
Copy link
Member

OK, I have signed my commit (I think).

Thanks, it is signed.

I haven't changed the code to use Ordered_set_lang.t again.
Perhaps you could do it? Or I'll do it later on.

I will take care of it.

Is there a place in the repository where I could store a TODO file specific to Menhir support in Dune?

You might as well just create a TODO.org (or .md, or whatever else you prefer) in the root of the repository. Just section the menhir section somehow so that others can use the file as well. You should also consider making full blown issues on the bug tracker if you have time to describe the features in more detail, or would like to solicit some feedback from maintainers/users.

@ghost
Copy link

ghost commented Aug 6, 2018

Is there a place in the repository where I could store a TODO file specific to Menhir support in Dune?

You might as well just create a TODO.org (or .md, or whatever else you prefer) in the root of the repository. Just section the menhir section somehow so that others can use the file as well. You should also consider making full blown issues on the bug tracker if you have time to describe the features in more detail, or would like to solicit some feedback from maintainers/users.

I would put this in a comment in src/menhir.ml directly. The closer it is to the actual source code, the more likely it is to stay in sync.

@rgrinberg
Copy link
Member

@fpottier I've made the adjustment to use the ordered set language. We might still want to consider using an explicit field to control this however. Inferring user intent from flags isn't the most reliable thing and it's now how we want to handle things with opaque for example. I don't have such a strong opinion about this however

@rgrinberg
Copy link
Member

@trefis I added the cmly support as it was really trivial.

@diml mind giving this another read? this PR is quite old and had a long discussion so I'm sure missing some things.

@rgrinberg
Copy link
Member

I can't reproduce the syntax error in 4.06.1, but I can reproduce it in 4.05.0. Here's the offending line:

  and _menhir_goto_reference_tag : _menhir_env -> 'ttv_tail -> _menhir_state -> (_[< DocOckPaths.Reference.kind
          > `Class `ClassType `Constructor `Exception `Extension `Field
            `InstanceVariable `Label `Method `Module `ModuleType `Type `Value ]
        DocOckPaths.Reference.tag) -> 'ttv_return =

The _[< on the first line is the offending bit.

@rgrinberg
Copy link
Member

For reference, this is what menhir generates for 4.06.1:

  and _menhir_goto_reference_tag : _menhir_env -> 'ttv_tail -> _menhir_state -> ([< DocOckPaths.Reference.kind
         > `Class `ClassType `Constructor `Exception `Extension `Field
           `InstanceVariable `Label `Method `Module `ModuleType `Type `Value ]
        DocOckPaths.Reference.tag) -> 'ttv_return =

and this is indeed valid.

@fpottier
Copy link
Collaborator Author

@rgrinberg: regarding the syntax error in your last two messages, how is it produced? These two messages look as though they belong in some other thread (which I would be interested to read, if it concerns a bug in Menhir).

@rgrinberg
Copy link
Member

@fpottier yeah, it certainly doesn't look like it's related to this PR. You can reproduce the bug if you have opam2 to install the deps:

$ git clone https://github.com/ocaml-doc/doc-ock-xml -b v1.2.1
$ cd doc-ock-xml
$ opam install --deps-only .
$ dune build --profile release # will fail on 4.05 but pass on 4.06

@ghost
Copy link

ghost commented Aug 21, 2018

@rgrinberg isn't the error introduced by this PR? The compilation of doc-ock-xml in travis seems to work fine with master.

@rgrinberg
Copy link
Member

Well the new rules are a bit different now. We're now using --infer-write-query and --infer-read-reply by default. I assume that these shouldn't introduce any regressions in the parsers they generate.

@ghost
Copy link

ghost commented Aug 21, 2018

We are also reading the output of ocamlc -i, which is not always valid OCaml

@ghost
Copy link

ghost commented Aug 21, 2018

I mean menhir is reading it. I don't know what menhir is doing with it though

@ghost
Copy link

ghost commented Aug 21, 2018

@fpottier does menhir parses the output of ocamlc -i or is it possible that it is transported as it to the output file? That would explain the error

@fpottier
Copy link
Collaborator Author

Menhir reads the output of ocamlc -i using a very basic lexer (src/lexmli.mll) and copies the types produced by ocamlc -i verbatim to its own output files. So, if ocamlc -i produces types that OCaml won't accept as an input, then we are in trouble. Is that the case here?

@ghost
Copy link

ghost commented Aug 21, 2018

I haven't checked, but that would explain the issue. @rgrinberg could you check the contents of the inferred mli file generated by the menhir rules with OCaml 4.05?

@fpottier fpottier requested a review from emillon as a code owner September 1, 2018 10:22
@rgrinberg
Copy link
Member

Here's the output (_build/default/src/docOckXmlParser__mock.mli.inferred):

module Make :
  functor (Root : sig type t end) ->
    sig
      type token =
          WITH
        | VIRTUAL
        | VERSION
        | VERBATIM
        | VARIANT
        | VAR
        | VALUE
        | URL
        | UNKNOWN
        | UNIT
        | Title of int
        | Target of string option
        | TYPE_SUBST
        | TYPEOF
        | TYPE
        | TUPLE
        | TEXT
        | TAG
        | SUPERSCRIPT
        | SUBST_ALIAS
        | SUBST
        | SUBSCRIPT
        | STOP
        | SPECIAL
        | SOURCE
        | SINCE
        | SIGNATURE
        | SEE
        | ROOT
        | RIGHT
        | RETURN
        | RESULT
        | RESOLVED
        | REFERENCE
        | RECORD
        | RAISE
        | PRIVATE
        | PRIMITIVE
        | PRECODE
        | POSITION
        | POS
        | POLY_VARIANT
        | POLY
        | PATH
        | PARAM
        | PAGE
        | PACKAGE
        | PACK
        | OPTIONAL
        | OPEN
        | OFFSET
        | OBJECT
        | NEWLINE
        | NEG
        | NAME
        | MUTABLE
        | MODULE_TYPE
        | MODULE_SUBST
        | MODULES
        | MODULE
        | METHOD
        | LOCATION
        | LIST
        | LINK
        | LINE
        | LEFT
        | LABEL
        | ITEM
        | ITALIC
        | INTERFACE
        | INSTANCE_VARIABLE
        | INLINE
        | INHERIT
        | INDEX
        | INCLUDE
        | IMPORT
        | IDENTIFIER
        | HIDDEN
        | FUNCTOR
        | FORWARD
        | FIXED
        | FILENAME
        | FILE
        | FIELD
        | EXTERNAL
        | EXTENSION
        | EXTENSIBLE
        | EXPANSION
        | EXCEPTION
        | ERROR
        | EOF
        | ENUM
        | EMPHASIZE
        | ELEMENT
        | Data of string
        | DTD
        | DOT
        | DOC
        | DIR
        | DIGEST
        | DEPRECATED
        | Custom of string
        | CONSTRUCTOR
        | CONSTRAINT
        | CONSTANT
        | COMMENT
        | COLUMN
        | CODE
        | CLOSED
        | CLOSE
        | CLASS_TYPE
        | CLASS
        | CENTER
        | CANONICAL
        | Base of Root.t
        | BOLD
        | BEFORE
        | Argument of int option
        | AUTHOR
        | ARROW
        | ARGUMENTS
        | APPLY
        | ANY
        | ALREADY_A_SIG
        | ALIAS
      val relax_class_path :
        ('a, DocOckPaths.Kind.identifier_class) DocOckPaths.Path.Resolved.t ->
        ('a, [< DocOckPaths.Path.kind > `Class ]) DocOckPaths.Path.Resolved.t
      val relax_class_type_path :
        'a DocOck.Paths.Path.Resolved.class_type ->
        ('a, [< DocOckPaths.Path.kind > `Class `ClassType ])
        DocOckPaths.Path.Resolved.t
      val relax_class_reference :
        'a DocOck.Paths.Reference.Resolved.class_ ->
        ('a, [< DocOckPaths.Reference.kind > `Class ])
        DocOckPaths.Reference.Resolved.t
      val menhir_begin_marker : int
      val xv_variance : DocOckTypes.TypeDecl.variance
      val xv_value_identifier :
        (Root.t, DocOckPaths.Kind.identifier_value) DocOckPaths.Identifier.t
      val xv_unit_import : Root.t DocOckTypes.Unit.Import.t
      val xv_unit_file : Root.t DocOckTypes.Unit.t
      val xv_unit_content : Root.t DocOckTypes.Unit.content
      val xv_unit : Root.t DocOckTypes.Unit.t
      val xv_type_resolved_path :
        (Root.t, DocOckPaths.Kind.path_type) DocOckPaths.Path.Resolved.t
      val xv_type_resolved_fragment :
        (Root.t, DocOckPaths.Kind.fragment_type, [ `Branch ])
        DocOckPaths.Fragment.Resolved.raw
      val xv_type_representation :
        Root.t DocOckTypes.TypeDecl.Representation.t
      val xv_type_path :
        (Root.t, DocOckPaths.Kind.path_type) DocOckPaths.Path.t
      val xv_type_parameter : DocOckTypes.TypeDecl.param
      val xv_type_identifier : Root.t DocOckPaths.Identifier.type_
      val xv_type_fragment :
        (Root.t, DocOckPaths.Kind.fragment_type, [ `Branch ])
        DocOckPaths.Fragment.raw
      val xv_type_expr : Root.t DocOckTypes.TypeExpr.t
      val xv_type_equation : Root.t DocOckTypes.TypeDecl.Equation.t
      val xv_type_constraint :
        Root.t DocOckTypes.TypeExpr.t * Root.t DocOckTypes.TypeExpr.t
      val xv_text_entry : Root.t DocOck.Types.Documentation.text
      val xv_text_element : Root.t DocOckTypes.Documentation.text_element
      val xv_text : Root.t DocOck.Types.Documentation.text
      val xv_tags : Root.t DocOckTypes.Documentation.tag list
      val xv_tag : Root.t DocOckTypes.Documentation.tag
      val xv_substitution : Root.t DocOckTypes.ModuleType.substitution
      val xv_string : string
      val xv_special : Root.t DocOckTypes.Documentation.special
      val xv_source_file : string
      val xv_source_build_dir : string
      val xv_source : Root.t DocOckTypes.Unit.Source.t
      val xv_signature_resolved_reference :
        Root.t DocOck.Paths.Reference.Resolved.signature
      val xv_signature_resolved_fragment :
        Root.t DocOck.Paths.Fragment.Resolved.signature
      val xv_signature_reference :
        (Root.t, DocOckPaths.Kind.signature) DocOckPaths.Reference.t
      val xv_signature_item : Root.t DocOckTypes.Signature.item
      val xv_signature_identifier : Root.t DocOck.Paths.Identifier.signature
      val xv_signature_fragment : Root.t DocOck.Paths.Fragment.signature
      val xv_see : DocOckTypes.Documentation.see
      val xv_reference_tag :
        _[< DocOckPaths.Reference.kind
          > `Class `ClassType `Constructor `Exception `Extension `Field
            `InstanceVariable `Label `Method `Module `ModuleType `Type `Value ]
        DocOckPaths.Reference.tag
      val xv_reference : Root.t DocOckTypes.Documentation.reference
      val xv_position : DocOckTypes.Documentation.Error.Position.t
      val xv_poly_variant_kind : DocOckTypes.TypeExpr.Variant.kind
      val xv_poly_variant_element :
        Root.t DocOckTypes.TypeExpr.Variant.element
      val xv_poly_variant : Root.t DocOckTypes.TypeExpr.Variant.t
      val xv_parent_resolved_reference :
        Root.t DocOck.Paths.Reference.Resolved.parent
      val xv_parent_reference : Root.t DocOck.Paths.Reference.parent
      val xv_parent_identifier : Root.t DocOck.Paths.Identifier.parent
      val xv_page_identifier :
        (Root.t, DocOckPaths.Kind.identifier_page) DocOckPaths.Identifier.t
      val xv_page_file : Root.t DocOckTypes.Page.t
      val xv_page : Root.t DocOckTypes.Page.t
      val xv_packed_item : Root.t DocOckTypes.Unit.Packed.item
      val xv_package_substitution :
        Root.t DocOckTypes.TypeExpr.Package.substitution
      val xv_package : Root.t DocOckTypes.TypeExpr.Package.t
      val xv_opttext : Root.t DocOck.Types.Documentation.text option
      val xv_option_variance_ : DocOckTypes.TypeDecl.variance option
      val xv_option_type_representation_ :
        Root.t DocOckTypes.TypeDecl.Representation.t option
      val xv_option_type_expr_ : Root.t DocOckTypes.TypeExpr.t option
      val xv_option_source_ : Root.t DocOckTypes.Unit.Source.t option
      val xv_option_module_type_expr_ :
        Root.t DocOckTypes.ModuleType.expr option
      val xv_option_module_decl_ : Root.t DocOckTypes.Module.decl option
      val xv_option_location_ :
        DocOckTypes.Documentation.Error.Location.t option
      val xv_option_label_identifier_ :
        Root.t DocOckPaths.Identifier.label option
      val xv_option_digest_ : string option
      val xv_option_argument_label_ : DocOckTypes.TypeExpr.label option
      val xv_offset : DocOckTypes.Documentation.Error.Offset.t
      val xv_object_method : Root.t DocOckTypes.TypeExpr.Object.method_
      val xv_object_field : Root.t DocOckTypes.TypeExpr.Object.field
      val xv_object_ : Root.t DocOckTypes.TypeExpr.Object.t
      val xv_nonempty_list_type_expr_ : Root.t DocOckTypes.TypeExpr.t list
      val xv_nonempty_list_text_element_ :
        Root.t DocOck.Types.Documentation.text
      val xv_nonempty_list_substitution_ :
        Root.t DocOckTypes.ModuleType.substitution list
      val xv_nonempty_list_name_ : string list
      val xv_nonempty_list_module_argument_ :
        Root.t DocOckTypes.FunctorArgument.t option list
      val xv_nonempty_list_item_ :
        Root.t DocOck.Types.Documentation.text list
      val xv_nonempty_list_field_ : Root.t DocOckTypes.TypeDecl.Field.t list
      val xv_nonempty_list_external_primitive_ : string list
      val xv_nonempty_list_extension_constructor_ :
        Root.t DocOckTypes.Extension.Constructor.t list
      val xv_nonempty_list_constructor_ :
        Root.t DocOckTypes.TypeDecl.Constructor.t list
      val xv_name : string
      val xv_module_type_resolved_reference :
        Root.t DocOck.Paths.Reference.Resolved.module_type
      val xv_module_type_resolved_path :
        Root.t DocOckPaths.Path.Resolved.module_type
      val xv_module_type_path : Root.t DocOckPaths.Path.module_type
      val xv_module_type_identifier :
        Root.t DocOckPaths.Identifier.module_type
      val xv_module_type_expr : Root.t DocOckTypes.ModuleType.expr
      val xv_module_resolved_reference :
        Root.t DocOck.Paths.Reference.Resolved.module_
      val xv_module_resolved_path : Root.t DocOck.Paths.Path.Resolved.module_
      val xv_module_resolved_fragment :
        Root.t DocOck.Paths.Fragment.Resolved.module_
      val xv_module_reference : Root.t DocOckPaths.Reference.module_
      val xv_module_path : Root.t DocOck.Paths.Path.module_
      val xv_module_identifier : Root.t DocOckPaths.Identifier.module_
      val xv_module_fragment : Root.t DocOckPaths.Fragment.module_
      val xv_module_expansion_opt :
        Root.t DocOckTypes.Module.expansion option
      val xv_module_decl : Root.t DocOckTypes.Module.decl
      val xv_module_argument : Root.t DocOckTypes.FunctorArgument.t option
      val xv_method_identifier :
        (Root.t, DocOckPaths.Kind.identifier_method) DocOckPaths.Identifier.t
      val xv_location : DocOckTypes.Documentation.Error.Location.t
      val xv_list_unit_import_ : Root.t DocOckTypes.Unit.Import.t list
      val xv_list_type_parameter_ : DocOckTypes.TypeDecl.param list
      val xv_list_type_expr_ : Root.t DocOckTypes.TypeExpr.t list
      val xv_list_type_constraint_ :
        (Root.t DocOckTypes.TypeExpr.t * Root.t DocOckTypes.TypeExpr.t) list
      val xv_list_text_element_ : Root.t DocOck.Types.Documentation.text
      val xv_list_tag_ : Root.t DocOckTypes.Documentation.tag list
      val xv_list_signature_item_ : Root.t DocOckTypes.Signature.t
      val xv_list_poly_variant_element_ :
        Root.t DocOckTypes.TypeExpr.Variant.element list
      val xv_list_packed_item_ : Root.t DocOck.Types.Unit.Packed.t
      val xv_list_package_substitution_ :
        Root.t DocOckTypes.TypeExpr.Package.substitution list
      val xv_list_object_field_ :
        Root.t DocOckTypes.TypeExpr.Object.field list
      val xv_list_name_ : string list
      val xv_list_module_argument_ :
        Root.t DocOckTypes.FunctorArgument.t option list
      val xv_list_documented_module_ :
        (Root.t DocOckPaths.Reference.module_ *
         Root.t DocOck.Types.Documentation.text)
        list
      val xv_list_class_signature_item_ :
        Root.t DocOckTypes.ClassSignature.item list
      val xv_line : int
      val xv_label_parent_resolved_reference :
        (Root.t, DocOckPaths.Kind.label_parent)
        DocOckPaths.Reference.Resolved.t
      val xv_label_parent_reference :
        (Root.t, DocOckPaths.Kind.label_parent) DocOckPaths.Reference.t
      val xv_label_parent_identifier :
        Root.t DocOck.Paths.Identifier.label_parent
      val xv_label_identifier : Root.t DocOckPaths.Identifier.label
      val xv_item : Root.t DocOck.Types.Documentation.text
      val xv_int : int
      val xv_instance_variable_identifier :
        (Root.t, DocOckPaths.Kind.identifier_instance_variable)
        DocOckPaths.Identifier.t
      val xv_include_expansion : Root.t DocOckTypes.Include.expansion
      val xv_flag_VIRTUAL_ : bool
      val xv_flag_RESOLVED_ : bool
      val xv_flag_PRIVATE_ : bool
      val xv_flag_OPEN_ : bool
      val xv_flag_MUTABLE_ : bool
      val xv_flag_INTERFACE_ : bool
      val xv_flag_HIDDEN_ : bool
      val xv_flag_CONSTANT_ : bool
      val xv_filename : string
      val xv_field_identifier :
        (Root.t, DocOckPaths.Kind.identifier_field) DocOckPaths.Identifier.t
      val xv_field : Root.t DocOckTypes.TypeDecl.Field.t
      val xv_external_primitive : string
      val xv_extension_identifier :
        (Root.t, DocOckPaths.Kind.identifier_extension)
        DocOckPaths.Identifier.t
      val xv_extension_constructor :
        Root.t DocOckTypes.Extension.Constructor.t
      val xv_expansion_opt : Root.t DocOckTypes.Signature.t option
      val xv_exception_identifier : Root.t DocOckPaths.Identifier.exception_
      val xv_element_resolved_reference :
        (Root.t, DocOckPaths.Reference.kind) DocOckPaths.Reference.Resolved.t
      val xv_element_reference : Root.t DocOckPaths.Reference.any
      val xv_element_identifier : Root.t DocOck.Paths.Identifier.any
      val xv_documented_module :
        Root.t DocOckPaths.Reference.module_ *
        Root.t DocOck.Types.Documentation.text
      val xv_doc_error : Root.t DocOckTypes.Documentation.Error.t
      val xv_doc : Root.t DocOckTypes.Documentation.t
      val xv_digest : string
      val xv_datatype_resolved_reference :
        Root.t DocOck.Paths.Reference.Resolved.datatype
      val xv_datatype_reference : Root.t DocOck.Paths.Reference.datatype
      val xv_constructor_result : Root.t DocOckTypes.TypeExpr.t option
      val xv_constructor_identifier :
        (Root.t, DocOckPaths.Kind.identifier_constructor)
        DocOckPaths.Identifier.t
      val xv_constructor_arguments :
        Root.t DocOckTypes.TypeDecl.Constructor.argument
      val xv_constructor : Root.t DocOckTypes.TypeDecl.Constructor.t
      val xv_comment : Root.t DocOckTypes.Documentation.comment
      val xv_column : int
      val xv_class_type_signature : Root.t DocOckTypes.ClassSignature.t
      val xv_class_type_resolved_reference :
        Root.t DocOck.Paths.Reference.Resolved.class_signature
      val xv_class_type_resolved_path :
        Root.t DocOck.Paths.Path.Resolved.class_type
      val xv_class_type_path : Root.t DocOckPaths.Path.class_type
      val xv_class_type_identifier : Root.t DocOckPaths.Identifier.class_type
      val xv_class_type_expr : Root.t DocOckTypes.ClassType.expr
      val xv_class_type_expansion_opt :
        Root.t DocOckTypes.ClassSignature.t option
      val xv_class_signature_reference :
        Root.t DocOck.Paths.Reference.class_signature
      val xv_class_signature_item : Root.t DocOckTypes.ClassSignature.item
      val xv_class_signature_identifier :
        Root.t DocOck.Paths.Identifier.class_signature
      val xv_class_resolved_reference :
        Root.t DocOck.Paths.Reference.Resolved.class_
      val xv_class_resolved_path :
        (Root.t, DocOckPaths.Kind.identifier_class)
        DocOckPaths.Path.Resolved.t
      val xv_class_identifier : Root.t DocOckPaths.Identifier.class_
      val xv_class_decl : Root.t DocOckTypes.Class.decl
      val xv_canonical :
        (Root.t DocOckPaths.Path.module_ *
         Root.t DocOckPaths.Reference.module_)
        option
      val xv_argument_label : DocOckTypes.TypeExpr.label
      val menhir_end_marker : int
    end

@rgrinberg
Copy link
Member

And here's the diff in the file above between 4.05 and 4.06. Clearly shows the incorrect source produced by 4.05:

189,191c189,191
<         [< DocOckPaths.Reference.kind
<          > `Class `ClassType `Constructor `Exception `Extension `Field
<            `InstanceVariable `Label `Method `Module `ModuleType `Type `Value ]
---
>         _[< DocOckPaths.Reference.kind
>           > `Class `ClassType `Constructor `Exception `Extension `Field
>             `InstanceVariable `Label `Method `Module `ModuleType `Type `Value ]

@ghost
Copy link

ghost commented Sep 3, 2018

I suggest that we simply disable the infer mode when OCaml <= 4.05.

@fpottier
Copy link
Collaborator Author

fpottier commented Sep 3, 2018

@diml: this seems safe, but perhaps a bit drastic? Some features of Menhir, such as the inspection API, require type inference to be turned on. (That said, it is still possible to provide every type by hand using %type declarations.)

Another approach would be to add an option inside a menhir stanza that allows disabling infer mode. But then, the build instructions for old versions of the doc-ock-xml package would have to be updated (a pain, too, I suppose).

@ghost
Copy link

ghost commented Oct 2, 2018

No problem

fpottier and others added 12 commits October 2, 2018 10:44
dune.opam:
  Add a constraint that Menhir (if present) must be >= 20180523.
src/jbuild.{ml,mli}:
  Change the type of the flags in a (menhir ... stanza)
  from [Ordered_set_lang.Unexpanded.t] to [string list].
  This makes it possible for the build rules to depend
  on the presence of certain flags (such as --only-tokens).
src/menhir.ml:
  Update the build rules to take advantage of the commands
  [--infer-write-query] and [--infer-read-reply] offered by Menhir.

Signed-off-by: François Pottier <[email protected]>
latest releasd versions of menhir and reason aren't compatible

Signed-off-by: Rudi Grinberg <[email protected]>
New directories will test other features

Signed-off-by: Rudi Grinberg <[email protected]>
Signed-off-by: Rudi Grinberg <[email protected]>
Signed-off-by: Rudi Grinberg <[email protected]>
Rename Loc.fail to Errors.fail

Signed-off-by: Rudi Grinberg <[email protected]>
Signed-off-by: Rudi Grinberg <[email protected]>
Signed-off-by: Rudi Grinberg <[email protected]>
Infer is disabled by default and can be re-enabled only in syntax (2, 0) of
menhir

Signed-off-by: Rudi Grinberg <[email protected]>
Signed-off-by: Rudi Grinberg <[email protected]>
@rgrinberg rgrinberg dismissed their stale review October 2, 2018 15:03

I addressed all these comments

@fpottier
Copy link
Collaborator Author

fpottier commented Oct 2, 2018

I don't quite follow what is going on, but I think true should be the default value of the infer field. It provides more functionality out of the box (better type error messages, access to Menhir's incremental API, etc.).

@ghost
Copy link

ghost commented Oct 2, 2018

@fpottier agreed. Changing the default of the infer field to true is a breaking change so we need to bump the major version of the menhir extension from 1 to 2. This way existing projects are not affected. New projects always use the latest versions. In conclusion:

  • existing projects will have to manually change the version of the menhir extension in their dune-project to 2.0 to be able to use the infer mode
  • new projects will use the infer mode by default

In both cases, users will be able to add (infer false) to individual menhir stanzas or change their code when they hit a printing bug.

@rgrinberg
Copy link
Member

Okay. infer is now the default. I've updated the CHANGES and manual as well. The manual could use a little more work, but I'll let @fpottier look it over whenever he has some time.

Signed-off-by: Rudi Grinberg <[email protected]>
Signed-off-by: Rudi Grinberg <[email protected]>
Signed-off-by: Rudi Grinberg <[email protected]>
@rgrinberg rgrinberg merged commit 0c9a1e7 into ocaml:master Oct 2, 2018
rgrinberg added a commit to rgrinberg/opam-repository that referenced this pull request Oct 4, 2018
CHANGES:

- Do not fail if the output of `ocamlc -config` doesn't include
  `standard_runtime` (ocaml/dune#1326, @diml)

- Let `Configurator.V1.C_define.import` handle negative integers
  (ocaml/dune#1334, @Chris00)

- Re-execute actions when a target is modified by the user inside
  `_build` (ocaml/dune#1343, fix ocaml/dune#1342, @diml)

- Pass `--set-switch` to opam (ocaml/dune#1341, fix ocaml/dune#1337, @diml)

- Fix bad interaction between multi-directory libraries the `menhir`
  stanza (ocaml/dune#1373, fix ocaml/dune#1372, @diml)

- Integration with automatic formatters (ocaml/dune#1252, fix ocaml/dune#1201, @emillon)

- Better error message when using `(self_build_stubs_archive ...)` and
  `(c_names ...)` or `(cxx_names ...)` simultaneously.
  (ocaml/dune#1375, fix ocaml/dune#1306, @nojb)

- Improve name detection for packages when the prefix isn't an actual package
  (ocaml/dune#1361, fix ocaml/dune#1360, @rgrinberg)

- Support for new menhir rules (ocaml/dune#863, fix ocaml/dune#305, @fpottier, @rgrinberg)

- Do not remove flags when compiling compatibility modules for wrapped mode
  (ocaml/dune#1382, fix ocaml/dune#1364, @rgrinberg)

- Fix reason support when using `staged_pps` (ocaml/dune#1384, @charlesetc)

- Add support for `enabled_if` in `rule`, `menhir`, `ocamllex`,
  `ocamlyacc` (ocaml/dune#1387, @diml)

- Exit gracefully when a signal is received (ocaml/dune#1366, @diml)

- Load all defined libraries recursively into utop (ocaml/dune#1384, fix ocaml/dune#1344,
  @rgrinberg)

- Allow to use libraries `bytes`, `result` and `uchar` without `findlib`
  installed (ocaml/dune#1391, @nojb)
rgrinberg added a commit to rgrinberg/opam-repository that referenced this pull request Oct 10, 2018
CHANGES:

- Do not fail if the output of `ocamlc -config` doesn't include
  `standard_runtime` (ocaml/dune#1326, @diml)

- Let `Configurator.V1.C_define.import` handle negative integers
  (ocaml/dune#1334, @Chris00)

- Re-execute actions when a target is modified by the user inside
  `_build` (ocaml/dune#1343, fix ocaml/dune#1342, @diml)

- Pass `--set-switch` to opam (ocaml/dune#1341, fix ocaml/dune#1337, @diml)

- Fix bad interaction between multi-directory libraries the `menhir`
  stanza (ocaml/dune#1373, fix ocaml/dune#1372, @diml)

- Integration with automatic formatters (ocaml/dune#1252, fix ocaml/dune#1201, @emillon)

- Better error message when using `(self_build_stubs_archive ...)` and
  `(c_names ...)` or `(cxx_names ...)` simultaneously.
  (ocaml/dune#1375, fix ocaml/dune#1306, @nojb)

- Improve name detection for packages when the prefix isn't an actual package
  (ocaml/dune#1361, fix ocaml/dune#1360, @rgrinberg)

- Support for new menhir rules (ocaml/dune#863, fix ocaml/dune#305, @fpottier, @rgrinberg)

- Do not remove flags when compiling compatibility modules for wrapped mode
  (ocaml/dune#1382, fix ocaml/dune#1364, @rgrinberg)

- Fix reason support when using `staged_pps` (ocaml/dune#1384, @charlesetc)

- Add support for `enabled_if` in `rule`, `menhir`, `ocamllex`,
  `ocamlyacc` (ocaml/dune#1387, @diml)

- Exit gracefully when a signal is received (ocaml/dune#1366, @diml)

- Load all defined libraries recursively into utop (ocaml/dune#1384, fix ocaml/dune#1344,
  @rgrinberg)

- Allow to use libraries `bytes`, `result` and `uchar` without `findlib`
  installed (ocaml/dune#1391, @nojb)

- Take argument to self_build_stubs_archive into account. (ocaml/dune#1395, @nojb)

- Fix bad interaction between `env` customization and vendored
  projects: when a vendored project didn't have its own `env` stanza,
  the `env` stanza from the enclosing project was in effect (ocaml/dune#1408,
  @diml)

- Fix stop early bug when scanning for watermarks (ocaml/dune#1423, @diml)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment

Labels

None yet

Projects

None yet

Development

Successfully merging this pull request may close these issues.

5 participants