Skip to content

Conversation

trefis
Copy link
Contributor

@trefis trefis commented Nov 13, 2018

This is a refresh of #1506 which includes the restrictions that were discussed during the last developer meeting and since then on github (cf. #1506 (comment)).

More precisely:

  • open in signatures is changed to accept extended module paths
  • open in structures, as well as let open in expressions, are extended to accept any module expression
  • let open in classes and class types is unchanged: before extending it we would need to add support for let module, which is complicated. Cf. the discussion on MPR#6271
  • the short syntaxes for local module opens (e.g. M.(expr), M.(pat), M.[expr], etc.) are still restricted to module paths.

Things to note:

  • I had to update Rec_check, but I didn't spend to much time on it, and it is untested. So it's likely to be wrong. It'd be nice if @gasche or @yallop could have a look.
  • I imported the tests from Extending open to accept arbitrary module expression #1506 as they were, and updated the output in a separate commit, so it's easier to spot the differences between the two PRs
  • the manual still needs to be updated

@yallop
Copy link
Member

yallop commented Nov 13, 2018

Thanks, @trefis. I plan to take a look at this soon (but not before next week).

Copy link
Contributor

@lpw25 lpw25 left a comment

Choose a reason for hiding this comment

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

I've looked over the translation parts so far. Looks good but there are a couple of bugs and some places where we could avoid allocating in the open struct ... end case.

@trefis trefis force-pushed the extended-open branch 2 times, most recently from 268ae41 to 3d4f72a Compare November 16, 2018 11:29
Copy link
Contributor

@lpw25 lpw25 left a comment

Choose a reason for hiding this comment

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

There are a couple of bugs, and a couple of bits that should be tidied up. Once they're fixed this should be good to go.

@Octachron
Copy link
Member

On the documentation front, I have a subpr here that adds some basic explanations and examples for the new features, if people wish to discuss the documentation separately.

@trefis
Copy link
Contributor Author

trefis commented Nov 23, 2018

I have rebased, answered all of @lpw25's comments, and included @Octachron's changes to the manual.

@trefis
Copy link
Contributor Author

trefis commented Nov 23, 2018

I pushed one last commit which updates the manual as discussed.
I think this is now ready to go.

@yallop
Copy link
Member

yallop commented Nov 23, 2018

I had to update Rec_check, but I didn't spend to much time on it, and it is untested. So it's likely to be wrong. It'd be nice if @gasche or @yallop could have a look.

Is the following intentional?

# let rec x = let module M = struct let y = lazy x end in ();;
val x : unit = ()
# let rec x = let module M = struct include struct let y = lazy x end end in ();;
val x : unit = ()
# let rec x = let module M = struct module M = struct let y = lazy x end end in ();;
val x : unit = ()
# let rec x = let module M = struct open struct let y = lazy x end end in ();;
Line 1, characters 12-74:
1 | let rec x = let module M = struct open struct let y = lazy x end end in ();;
                ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: This kind of expression is not allowed as right-hand side of `let rec'

@trefis
Copy link
Contributor Author

trefis commented Nov 23, 2018

I guess it is:

# let rec x = let module M = struct include (struct let y = lazy x end : sig end) end in ();;                                                                       
Line 1, characters 12-89:
1 | let rec x = let module M = struct include (struct let y = lazy x end : sig end) end in ();;
                ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: This kind of expression is not allowed as right-hand side of `let rec'

I guess you might want to make modexp a bit cleverer when looking at Tmod_constraint.

@lpw25
Copy link
Contributor

lpw25 commented Nov 24, 2018

From the CI, it looks like ocamlnat needs updating.

else
type_args [] [] ty (instance ty) ty sargs []
let ty = funct.exp_type in
if ignore_labels then
Copy link
Contributor

Choose a reason for hiding this comment

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

just curious, do we have an official code style for ocaml compiler source code now? are we using ocamlformat?

Copy link
Contributor Author

Choose a reason for hiding this comment

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

No.

| Texp_extension_constructor _ ->
()
| Texp_open (_od, e) ->
iter_expression e
Copy link
Contributor

Choose a reason for hiding this comment

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

should we iter _od here? also we should iter Tstr_open?

Copy link
Contributor Author

Choose a reason for hiding this comment

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

I updated this and Tstr_open to do the same thing as with includes.

Texp_unreachable
| Texp_extension_constructor _ as e ->
e
| Texp_open (od, exp) -> Texp_open (od, map_expression exp)
Copy link
Contributor

Choose a reason for hiding this comment

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

should we map over module expression of od here? Also Tstr_open

Copy link
Contributor Author

Choose a reason for hiding this comment

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

Updated.

match m.mod_desc with
Tmod_ident _ -> Alias
| Tmod_constraint (m,_,_,_) -> pure_module m
| _ -> Strict
Copy link
Contributor

Choose a reason for hiding this comment

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

can we list out all other cases here explicitly?

Copy link
Contributor Author

Choose a reason for hiding this comment

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

I just moved this code from Translmod to Translcore. I didn't actually write it. So I'd rather not update it.

(** Extracts the list of "value" identifiers bound by a signature.
"Value" identifiers are identifiers for signature components that
correspond to a run-time value: values, extensions, modules, classes.
Note: manifest primitives do not correspond to a run-time value! *)
Copy link
Contributor

Choose a reason for hiding this comment

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

I know this is copied over from another file, but I'd like to know what "manifest primitives" means. Thanks.

Copy link
Contributor Author

Choose a reason for hiding this comment

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

I think reading this as "externals" is acceptable.

\begin{caml_example}{verbatim}
module M = struct
open struct type 'a t = 'a option = None | Some of 'a end
let x : int t = Some 1
Copy link
Contributor

Choose a reason for hiding this comment

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

add one whitespace before let

Copy link
Contributor Author

Choose a reason for hiding this comment

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

Done.

Copy link
Contributor

@lpw25 lpw25 left a comment

Choose a reason for hiding this comment

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

Good to merge once CI passes.

@trefis trefis merged commit 4e4c0a3 into ocaml:trunk Nov 26, 2018
@yallop
Copy link
Member

yallop commented Nov 27, 2018

Thanks, @trefis!

@objmagic
Copy link
Contributor

Thank you for the work @trefis!

@lpw25
Copy link
Contributor

lpw25 commented Nov 27, 2018

There's a bug in this PR. is_nonexpansive in typecore.ml needs to be extended to handle Texp_open. We should also add a test for this case to the testsuite, and maybe not use a fragile match for that function.

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