Skip to content

Conversation

alainfrisch
Copy link
Contributor

See https://caml.inria.fr/mantis/view.php?id=7005

Deprecation warnings in a signature are usually intended for clients of the library, not for internal references. Typically, when a type declaration is marked as deprecated in an .mli file, it is a bit silly to report references to that declaration in the same .mli file.

The current PR changes the handling of deprecation attributes on type declarations. For now, this is for discussion only, and if this semantics is adopted, it should be generalized to other kinds of declarations that support the deprecated attribute.

The idea is to make deprecation attributes visible only outside the current signature/structure, not for type-checking the rest of the signature/structure. This is achieved by removing the attribute before type-checking and adding them back to the type-checked declarations that will end up in the synthesized internal module type. In particular, the type-checking environments used for the rest of the signature/structure and for the declaration itself (for recursive definitions) will not see the attribute.

This gives the following behavior:

module A : sig
  type t = X of t [@@ocaml.deprecated] (* => no warning *)
  val x: t  (* => no warning *)
  module B: sig
    type s = t (* => no warning *)
    val x: t (* => no warning *)

    type u [@@ocaml.deprecated]
  end

  val y: B.u (* => WARNING! *)
end

I wanted to get people's opinion on this new interpretation of deprecation warnings.

Note: I guess that those warnings are mostly used on value declarations in signatures, and this change would not impact this case.

@jberdine
Copy link
Contributor

FWIW, I think this interpretation is a definite improvement.

@Drup
Copy link
Contributor

Drup commented Jul 12, 2017

I'm actually not very fond of this. If a type is deprecated, why should the library use it in its API? I understand there are use-cases but that's not the behavior I would prefer by default.

Maybe the behavior could be toggled ? [@@ocaml.deprecated ignore_local] (syntax to be improved).

@alainfrisch
Copy link
Contributor Author

The library could expose operations related to the deprecated type. They would themselves likely be marked as deprecated, but we don't want them to trigger the warning themselves. One could also decide that declarations marked with the deprecation flag themselves don't trigger the deprecation warning if they refer to deprecated components.

@Drup
Copy link
Contributor

Drup commented Jul 12, 2017

One could also decide that declarations marked with the deprecation flag themselves don't trigger the deprecation warning if they refer to deprecated components.

I like that version a lot more.

@aantron
Copy link
Contributor

aantron commented Jul 12, 2017

I don't think this should be solved this way.

The Mantis issue seems more narrow, and an actual bug, i.e. I only agree with the type t = X t line having no warning above. For the rest, can't we easily suppress deprecation warnings manually using ocaml.warning "-3" annotations?

I would prefer to explicitly have to mark "my" library's use of its own deprecated items inside the same .mli file with warning suppression annotations, rather than have some non-obvious machinery decide to suppress them for me. It encourages me to think harder about how the respective items are declared and implemented, and whether there is a non-deprecated way to declare them.

This is especially useful when deprecating something in large .mli files, where you might otherwise overlook a remote use of a deprecated item. That is even more useful when contributors without an encyclopedic knowledge of the library API are working on deprecation.

Basically, the deprecation warnings are a useful refactoring tool, and such a broad change will make them less useful, while I don't see what the benefit is. The author who is doing the deprecation is able to modify the same .mli to insert ocaml.warning "-3".

EDIT: replace .mli by signatures in general.

@alainfrisch
Copy link
Contributor Author

@aantron The problem is that disabling warning 3 has a global effect: you won't see when if one of your dependencies marks some of its components as deprecated.

What do you think of my alternative proposal (a component marked as deprecated can itself refer to other deprecated components without triggering the warning)?

@aantron
Copy link
Contributor

aantron commented Jul 12, 2017

I agree with the excessive effect of disabling warning 3. The alternative proposal is definitely preferable to the original. Ideally for me, one could have a way of disabling warning 3 that is attached to specific type expressions (is it possible now?), or some other such more-precise solution. If not that, the alternative proposal is probably the best thing so far in this PR, but I would still prefer to avoid hidden or complex behaviors around this, if possible.

@paurkedal
Copy link

I am in favour of the alternative which silences the deprecation warning only when the referring definition itself is deprecated. My reasoning is that the referring definition would become invalid and would have to be removed at the same time as the referred definition, so it should be deprecated at the same time or earlier. Conversely, keeping a reference to a deprecated feature seems harmless, as long as the referring definition can be removed at the same time as the referred one. So, the deprecation-suppressed warnings should be safe if the project has a strict schedule for removing deprecated part of the API and definitions are not modified after being deprecated. To see the issue with modifying a deprecated definition consider:

type a = A [@@deprecated "will be removed in 2 months"]
type b = B [@@deprecated "will be removed in 1 months"]
type c = C of a [@@deprecated "will be removed in 2 months"]

Modifying c to use b instead of a would block the removal of b according to schedule.

Maybe the behavior could be toggled ? [@@ocaml.deprecated ignore_local] (syntax to be improved).

Or maybe instead of removing [@@ocaml.deprecated] while processing the module, replace it with a new directive [@@ocaml.deprecated.same_module] or such and use a separate warning number? I think this would normally be a project-wide choice, so a compiler option should do, which avoids noise in the source code.

@aantron
Copy link
Contributor

aantron commented Jul 13, 2017

I don't think the referring item has to become invalid at the same time. Here is an entirely contrived example:

module type A =
sig
  type t
    [@@ocaml.deprecated]

  val initial : t
  val to_string : t -> string
end

module A_m : A =
struct
  type t = unit

  let initial = ()
  let to_string _ = "foo"
end

let () =
  print_endline (A_m.to_string (A_m.initial))

The code at the bottom does not, and should not, trigger deprecation warnings on uses of A_m.initial or A_m.to_string. I should still be able to deprecate the type intelligently. I may want to discourage the naming and/or use of a type, without preventing the use of operations on that type, because I intend to substitute the type definition somehow.

Deprecation is introduced at a definition, and used at other definitions. I think it is wrong to conflate the use at those other definitions with whether those other definitions introduce additional separate deprecations or not. It makes deprecation complex and difficult to understand. I would not want to be unduly encouraged to use this mechanism, and I would not want this mechanism to be operating "behind the scenes" anyway, if on some occasion I do deprecate a definition and a using definitions at the same time – I would now be worried about the quality of refactoring.

Instead, ideally we could both control exactly what is deprecated (introduction), and exactly which uses should not trigger warnings. This is easy to understand, and, instead of us trying to predict, during this PR, the deprecation strategies projects may want to use, we provide a straightforward mechanism so that projects can create their own deprecation strategies as they see fit. I have a particular interest in this, because we use deprecation a lot in Lwt, and we want to be able to come up with more creative strategies in the future. I think merging this PR, including with the alternative proposal, will hinder me, and, more importantly, it will hinder contributors or my future replacement(s).

I haven't looked into it yet because I am traveling, but if it's not yet possible to annotate type expressions with [@ocaml.warning "-3"], perhaps I can prepare a PR next week. Not sure if there would be any difficulties with that. That seems like the right way to solve the wider problem. I think this PR should be narrowed to the problem described in the Mantis issue. In particular, IM(strongly-held)O it should only suppress warnings from recursive use in the same type.

I'm not sure, but my first instinct is that it should not suppress warnings even on use in another mutually-recursive type definition (i.e. and).

@paurkedal
Copy link

I don't think the referring item has to become invalid at the same time. Here is an entirely contrived example:

That is true, at least if different deprecation times are needed within a project or due to editing, but I don't follow your example:

From the point of view of the interface user, since A.t is abstract, the only non-esoteric backwards incompatible change would be to remove the type component or rename it. If it is to be renamed, it seems better to introduce it right away under it's future name, say u, and add a deprecated type t = u alias. If it is to be substituted and the new type is known, then the substitution can be done right away, again adding a deprecated type t = ... alias. Finally one might argue there is a case where the substitute is yet to be decided, but in that case the deprecation of t is premature, since it leaves users with no way to name the type which exposed in the interface though the methods.

From the interface implementors point of view, these deprecations are not so useful anyway. One would instead need another kind of annotation which marks the module component not yet exported but to be added later, with warnings triggered for not implementing it.

I disagree in that I think this is a simple and transparent mechanism. It rests on the assumption that deprecation follows real code dependencies, which is a simplification, but based on the intuition that if something is deprecated everything using it must either be rewritten or itself deprecated. It is rather conservative in being restricted to a single module interface. Extending the rule outside a project would be harmful due to different release schedules. Extending within a project will probably work for some projects, but could also elevate the issue of different deprecation schedules where that is important.

A way to extend the rule outside a single module interface, would be to label and possibly version deprecations. That would also work with explicit suppression annotations, which now would be specific enough to be applied to larger blocks of code than a [@ocaml.warning "-3"]. This seems out of scope for this PR, though.

@aantron
Copy link
Contributor

aantron commented Jul 15, 2017

I disagree in that I think this is a simple and transparent mechanism.

And I disagree, and believe that [ocaml.warning "-3"] in type expressions is much simpler and much more transparent. It covers all use cases I can think of for this hidden mechanism. It forces explicit consideration of every use of a deprecated type, which is what I want. I don't want uses silently shadowed by other deprecation. I want it documented when we choose to use a deprecated type, easily followable to a commit in blame with a nice message, etc. The proposed hidden conditional suppression is most definitely more opaque than explicitly stating that you know something is deprecated, and want to use it anyway, and being uniformly forced to make a decision about that by the compiler.

Sometimes a using value (or type) is deprecated, and simultaneously needs its definition adjusted because of a new type name that is available, that should be used instead. This mechanism can hide the need to adjust the type signature.

Some other cases to think of:

  • A polymorphic variant type that an author decided is no longer best defined explicitly for some reason. We may actually want to refer to that variant type instead of pasting the variands in; perhaps we plan to remove some of the variands later, and paste the remainder in only after the set is trimmed. On the other hand, if we are deprecating the using value, we might want to actually be immediately reminded to paste in the variands instead. For the former, we want to annotate the type expression. For the latter, we don't want a hidden suppression, and we want to be forced to choose between annotating the type expression or modifying the declaration, and choose the latter.
  • A type that was both defined and asserted to be equal to another, i.e. type t = foo = ..., being deprecated. Same situation.
  • Or just a type alias being deprecated, or something being deprecated at the same time as becoming an alias.

The abstract type in my example above was basically a red herring. I just didn't have any definition to give it, as it was not relevant to that example.

In the meantime, I got the idea that we don't want to be making predictions about the deprecation in, for example, some complex combinator code that is using some phantom types mainly internally. There is no reason those should be coupled in any way at all to deprecation of the combinators. An example would be TyXML. A much less involved example would be Markup.ml. This can affect libraries that do complex type-level computation.

Also, a using declaration can become deprecated before a type for entirely unrelated reasons. When the type is deprecated later, I would like developers to be forced to consider that previously-deprecated declaration. I also want that consideration reflected in diffs and blame.

Having [@ocaml.warning "-3"] annotations on type expressions is also exactly analogous to [@ocaml.warning "-3"] on expressions. That's a mechanism one often has to use anyway, so why complicate signatures with a different mechanism, that is at the same time more opaque and less precise? The mechanism proposed in this PR is already more difficult to teach a beginner on its own. Its coexistence with [@ocaml.warning "-3"] makes that even worse – we could instead have only the latter to teach.

EDIT: And when I say beginner, I am talking about someone who already knows OCaml, but wants to start out contributing to some complex project that uses deprecation extensively.

In summary, I think the mechanism in this PR makes too strong assumptions about how OCaml users use deprecation, that are not necessary at all to make. I strongly prefer that we not make them. As long as [@ocaml.warning "-3"] on type expressions is possible, we have a strictly better mechanism available.

@paurkedal
Copy link

paurkedal commented Jul 16, 2017

And I disagree, and believe that [ocaml.warning "-3"] in type expressions is much simpler and much more transparent. It covers all use cases I can think of for this hidden mechanism. It forces explicit consideration of every use of a deprecated type, which is what I want. I don't want uses silently shadowed by other deprecation. I want it documented when we choose to use a deprecated type, easily followable to a commit in blame with a nice message, etc. The proposed hidden conditional suppression is most definitely more opaque than explicitly stating that you know something is deprecated, and want to use it anyway, and being uniformly forced to make a decision about that by the compiler.

I have no argument against explicit annotations being more transparent, just that this proposal shouldn't fall on being considered opaque or complex. One way to see why it's simpler than and as transparent as type checking itself, is to consider it like a tiny subtyping system of two types non_deprecated < deprecated where the inferred deprecation-type of a definition is the supremum over its references. Deprecation annotations would then be the analogue of type annotations. (OT: This can be generalised to sets of "taints", such that s1 < s2 iff s1 ⊂ s2, where taints might be "deprecated", "unsafe", "expansive", etc.)

Sometimes a using value (or type) is deprecated, and simultaneously needs its definition adjusted because of a new type name that is available, that should be used instead. This mechanism can hide the need to adjust the type signature.

Some other cases to think of:

  • A polymorphic variant type that an author decided is no longer best defined explicitly for some reason. We may actually want to refer to that variant type instead of pasting the variands in; perhaps we plan to remove some of the variands later, and paste the remainder in only after the set is trimmed. On the other hand, if we are deprecating the using value, we might want to actually be immediately reminded to paste in the variands instead. For the former, we want to annotate the type expression. For the latter, we don't want a hidden suppression, and we want to be forced to choose between annotating the type expression or modifying the declaration, and choose the latter.
  • A type that was both defined and asserted to be equal to another, i.e. type t = foo = ..., being deprecated. Same situation.

So, the type is deprecated, but still used in non-deprecated parts of the interface. The type can be named in a non-deprecated manner, except that name is unknown, since the cases have not yet been decided. Now, consider a user of the library who defines a function which acquires the deprecated type and want's to declare it in an interface. What type should he use?

  • Or just a type alias being deprecated, or something being deprecated at the same time as becoming an alias.

The above objection aside, I see these as instances of the general wish to keep some deprecated definition up to date while others are being introduced. We may have different experiences of how many unrelated deprecations are floating around within same module. I also see deprecations most of all as a cross-project communication tool, to allow combinations of versions to compile for a transition period. I do appreciate being reminded within the project itself, but in the worst case longer-term deprecations can be updated as deprecated features are removed.

The abstract type in my example above was basically a red herring. I just didn't have any definition to give it, as it was not relevant to that example.

And when it is not abstract, it can be substituted, so the deprecated definition becomes unused.

In the meantime, I got the idea that we don't want to be making predictions about the deprecation in, for example, some complex combinator code that is using some phantom types mainly internally. There is no reason those should be coupled in any way at all to deprecation of the combinators. An example would be TyXML. A much less involved example would be Markup.ml. This can affect libraries that do complex type-level computation.

I think this is mostly another special case, but it did suggest to me an impact on user code: I'm familiar with TyXML where the phantom types are polymorphic variants. Since the constructors can't be individually deprecated, I assume we're talking about deprecating a full type alias. There is now a deprecated combinator in the same module using it, which was not updated since the warning was suppressed. The harm of that is that on the next release a user will be hit by two deprecations instead of one, since the value carries with it a deprecated type alias as a phantom type. This is not specific to phantom types, though, and I don't think there is any specific gotcha with complex type-level computation in this regard.

Also, a using declaration can become deprecated before a type for entirely unrelated reasons. When the type is deprecated later, I would like developers to be forced to consider that previously-deprecated declaration. I also want that consideration reflected in diffs and blame.

Yes. I'd might consider them all gone next major version, or those fixed which really needs to stay. You have a higher standard than me on the maintenance of deprecated features. I would worry if using a deprecated feature has real impact on functionality, though if it's bad enough it may be worth doing a breaking change instead of deprecating.

In either case, explicit annotations are needed. I'm sufficiently convinced that deprecation-dependent warning suppression should be (command-line-)optional if implemented, and whether it's worth adding the extra logic to the compiler depends on whether others would be serviced by it, which I don't know.

A way of making warning suppression optional is, as suggested above, to split up the warnings for the two cases. That would also make explicit annotations more precise in the following sense: You have a deprecated type and a deprecated user suppressing the warning. The user get's resurrected, and when removing the deprecation annotation we really want the warning to trigger again, since it's exposing a deprecated type.

@aantron
Copy link
Contributor

aantron commented Jul 16, 2017

I do agree that the implicit mechanism proposed in this PR is likely to handle the vast majority of cases correctly. I just don't agree with it being implicit, or with not handling the remaining cases.

On specific points:

Now, consider a user of the library who defines a function which acquires the deprecated type and want's to declare it in an interface. What type should he use?

I'm not following. The type is deprecated because the library author does not want it used in the declaration of an interface. At the same time, the library author might find it convenient to keep using it for some time. This isn't a likely scenario, but it's a possible scenario.

Consider also that some APIs might be designed exclusively for interactive use in a REPL, on a value-only basis (i.e. types never, or almost never, written).

I also see deprecations most of all as a cross-project communication tool, to allow combinations of versions to compile for a transition period. I do appreciate being reminded within the project itself, but in the worst case longer-term deprecations can be updated as deprecated features are removed.

Of course the cross-project usage of deprecations is the most important, indeed it is one of the few ways to reach users that do not participate in discussions and don't subscribe to announcements. However, I also see deprecation as an intra-project communication tool, including between contributors that do not have the same knowledge/view of the project. Basically, in the specific case of Lwt, it is large enough, and work on one module spread out in time enough, that I would like the strictest deprecation warnings inside the project possible, including within a single module. It is also beneficial to avoid any implicit or hidden behavior, for getting starting contributors up to speed (as I've mentioned before).

There is also yet another teaching benefit to explicit suppression on type expressions: having uniform behavior cross- and intra-project (and cross- and intra-module), in addition to the aforementioned uniform behavior between type and value expressions.

@paurkedal
Copy link

paurkedal commented Jul 16, 2017

Now, consider a user of the library who defines a function which acquires the deprecated type and want's to declare it in an interface. What type should he use?

I'm not following. The type is deprecated because the library author does not want it used in the declaration of an interface. At the same time, the library author might find it convenient to keep using it for some time. This isn't a likely scenario, but it's a possible scenario.

And it is okay to use values of the type as long as long as the only occur in locally? First, note that there will be no warning if the interface of the module is inferred, so this cannot be fully enforced. More to the point, I think it's a good feature of the OCaml module system that it is always possible to name types exposed by a module. Further, deprecation is an intetion to remove, which will break the API, so there should be a plan for replacing it. If that plan is not sufficiently clear yet, then the deprecation is in my opinion premature.

Consider also that some APIs might be designed exclusively for interactive use in a REPL, on a value-only basis (i.e. types never, or almost never, written).

I don't like non-nameable types here either. Practically it may be okay, but it breaks the principal signature of the non-deprecated projection of a module, and I don't see a compelling argument that this will help us evolve interfaces more smoothly.

However, I also see deprecation as an intra-project communication tool, [...]

Yes, I see your reasoning here.

@yminsky
Copy link

yminsky commented Jul 16, 2017

FWIW, I find Alain's proposal compelling, and don't really understand aantron's objection. aantron, perhaps it would be useful to have a non-contrived example which gives an example where Alain's semantics would be problematic, and the tighter control allowed by your semantics would be better? The idea of only ignoring deprecated clauses seems principled to me, and I'm having trouble imagining a sensible counterexample, i.e., an example where Alain's heuristic does the wrong thing.

@aantron
Copy link
Contributor

aantron commented Jul 16, 2017

Sure, but I am repeating myself.

  1. val a : b is deprecated first. type b is deprecated later. I don't want silent suppression at a to hide the use of b from me or from fellow contributors.
  2. I am teaching contributors about the ways of working on a hypothetical big library that uses deprecation a lot. I can teach (1) deprecation suppression annotations in expressions, and (2) a separate heuristic that only exists intra-project for types in signatures. Or I can teach a single mechanism that applies to both type expressions and expressions, is uniform between and within projects, doesn't arbitrarily stop at a signature boundary, is syntactic and requires no inference, and completely subsumes (2). Why should I want (2) to complicate things?

Before continuing further along the path of examples, is there any reason to prefer a heuristic to actual control?

@aantron
Copy link
Contributor

aantron commented Jul 16, 2017

Also, how would this heuristic interact with signature inclusion? Let's say I factor out the using deprecated declaration into its own signature, and then include it. The type would likely be factored out into a separate signature. Does the warning suppression by this heuristic still apply, or does the code have to be modified along the way to use an explicit suppression? I think the latter, at least when compiling the signatures before inclusion, but please correct me if I'm wrong.

Also, regardless of the answer to that question, I think the fact that it's something for people to wonder about and learn should further indicate that the heuristic is more difficult to teach. By comparison, I think it's obvious to people that an explicit suppression is preserved. Conversely, without the heuristic, factoring an included signature in obviously won't introduce any suppression, while with the heuristic, one has to worry at least once, or worse, every time, about how deprecated items will interact.

Basically, without the heuristic, processing of deprecation is orthogonal to signature structure. With the heuristic, they are conflated.

@yminsky
Copy link

yminsky commented Jul 17, 2017

Alain's rule seems pretty natural to me, and not especially hard to explain. That said, the point about it being different within one signature and between signatures is reasonable, and does cut against the naturality argument.

@paurkedal
Copy link

A solution to the scope limitation, would be to pass the scope of deprecation annotations on the command line. The build system could by default use the library name or the name of the opam package it's building. But note that there is another issue at play before this would work. The following does not trigger a warning:

module M : sig
  type t
end = struct
  type t = unit [@@deprecated]
end

So, it seems we should consider deprecation as an auxiliary type (cf my big post yesterday) while doing signature matching. Here the deprecated t does not match the non-deprecated declaration, since deprecated ≰ non_deprecated. I can open a separate issue on this if it's worth looking into, possibly with another solution.

A way to handle a mix of short-term and long-term deprecations would be to accept a serial number in the annotation indicating the code is now scheduled for removal at a predictable point in time, e.g. by encoding the target version or month as an integer. The deprecation warning would trigger if the user has a larger or no serial number in it's own annotation.

@alainfrisch
Copy link
Contributor Author

The following does not trigger a warning

It does in trunk, since #1138 (this will be part of 4.06).

@aantron
Copy link
Contributor

aantron commented Jul 17, 2017

@paurkedal Can you please directly answer why these mechanisms, which look increasingly complicated to me, are preferable to being able to annotate type expressions to suppress warnings?

Among other things, explicit suppressions don't need any interaction with a build system.

A fundamental problem of this PR is this:

Deprecation warnings in a signature are usually intended for clients of the library, not for internal references. Typically, when a type declaration is marked as deprecated in an .mli file, it is a bit silly to report references to that declaration in the same .mli file.

This is highly dependent on the development model. In particular, this does not apply to current Lwt. Perhaps it works for relatively small projects, or relatively tight-knit teams.

I do not want this mechanism extended beyond .mli files into the rest of Lwt. That will do even more damage as we will have to start pedantically checking all deprecations everywhere in the project for unexpected interactions. I definitely don't want it interacting in any way with OPAM or the build system. Build systems are already complicated enough, and you cannot assume OPAM at all – what if we want to package a project in an entirely different way, say for NPM?

Instead of all this complexity for a solution that can't cover everything anyway, I'd like for contributors that already learned the skill of suppressing deprecation warnings when using other projects, to trivially apply the same skill working within Lwt. This is by no means the only advantage of explicit suppression, I just don't want to repeat the text written above.

So, please say what the disadvantage of explicit suppression is. Please also @alainfrisch and other participants address this. Given that alternative, I don't see why we should be so determined to pursue this heuristic, that it's worth considering interactions with builds and OPAM.

@yminsky Here is a reasonable start of an explanation of the rule:

"If you deprecate a type and use it in a deprecated value, you won't get a deprecation warning. However, this only works inside a single signature (or insert an even more complex clause here if we adopt @paurkedal's proposal in the recent comment). If you want to suppress warnings in another signature in the same project, or in a different project, you will have to use a totally separate mechanism, which you may already know. If you are the author of a project and refactor code so that it moves from one signature to another, you may suddenly gain or lose this automatic suppression, and might therefore have to change which suppression mechanism you are using. The suppression is not syntactic, so you have to watch out for pairs of deprecated definitions that may interact. If you want to continue using a deprecated type on purpose for a while, as it is your prerogative as a maintainer, but still retain a warning to be reminded to remove it later, the warning disappears. You have to use a TODO instead. In some situations, whether you ever see warnings about use of deprecated types depends on the historical order in which you deprecate signature items."

So I propose that if this rule seems natural, it is because of stopping after sentence 1 and not considering the extensive list of consequences.

@alainfrisch
Copy link
Contributor Author

The revised proposal was to arrange so that a declaration marked as deprecated automatically doesn't raise the deprecation warning itself when it is processed. As far as I can tell, this does not have the bad consequences on refactoring that you mention. The criterion is local and seems easy to explain.

Now, I fully agree that one should support [@ocaml.warning "-3"] on type expressions. My concern is that it could become a bit heavy to write. But perhaps one could start with that and see if it's enough.
My preference would then not to do anything will recursive types. A self-reference is a reference, and there is no reason that the warning should be suppressed automatically in that case. Do you agree?

@aantron
Copy link
Contributor

aantron commented Jul 17, 2017

The revised proposal was to arrange so that a declaration marked as deprecated automatically doesn't raise the deprecation warning itself when it is processed. As far as I can tell, this does not have the bad consequences on refactoring that you mention. The criterion is local and seems easy to explain.

I think it does, because if I move either declaration to another signature, I lose the automatic suppression. I haven't fully understood #1138 yet (thanks for linking it), so maybe this won't be an issue with inclusion anymore, but there might still be a breaking change involving deprecated declarations (and perhaps it's especially likely). With the explicit annotation, it's a matter of copy-and-paste, as it is uniform. With the implicit mechanism, one has to switch to explicit annotation. Moving things into one signature instead may seem to be less of a problem, since new warnings shouldn't be generated, but I'd rather have accurate annotations and not worry about hidden type computation being introduced here either – I don't want removing an explicit annotation after factoring in, to misleading raise no warning, as if the annotated type wasn't still deprecated.

The criterion is local and seems easy to explain.

It is local to some extent, but not as local as explicit annotation. I may have actually two deprecated types in one module, and another declaration that uses both of them. Perhaps for some reason, I want one suppressed, and another not, for the time being. This is also especially worrisome once one starts thinking about the possible historical orders in which the three declarations might become deprecated, which I haven't done yet, and hope not to have to do :) It's all much clearer and more local with explicit annotation – the historical order is not an issue at all.

My concern is that it could become a bit heavy to write.

I agree with this, but I believe it's the right way. What I don't like the most about that is that the warning number is opaque, but that is, I believe, a separate issue – the actual underlying approach is, I believe, sound, and of course everyone is now I aware I strongly prefer it to the present proposal :)

My preference would then not to do anything will recursive types. A self-reference is a reference, and there is no reason that the warning should be suppressed automatically in that case. Do you agree?

I can see a case being made for automatic suppression in recursive types, but I can also see the argument for a fully uniform approach to suppression, annoying as it may be. The biggest concern here would be some giant recursive type that mentions itself a lot. I guess that's also what implicit suppression might solve. But since I already think we need a better approach than proposed here, to suppression in a wider scope, whatever approach we develop for that might also provide intelligent suppression of self-reference in a large recursive type. So, I'm okay with leaving it in the state you propose for now, with the reasoning you are proposing.

There are some other benefits to explicit suppression, like being able to find it all with grep instead of needing a static analysis, and more explicit documentation for readers of the .mli. There are more, but I keep thinking of them and forgetting them, because of the great number (IMO of course).

Also, for the record, I did consider this alternative implicit approach a pretty good one at first, but eventually I thought that the number of corner cases is just way too large for it to be a good choice :)

@alainfrisch
Copy link
Contributor Author

I think it does, because if I move either declaration to another signature, I lose the automatic suppression.

I don't see why. The revised proposal has nothing to do with where the declaration is. Or do you consider the situation where a module declaration itself is marked as deprecated?

The biggest concern here would be some giant recursive type that mentions itself a lot.

How is that different from a giant recursive type that need to refer to a deprecated type defined earlier?

@paurkedal
Copy link

The following does not trigger a warning

It does in trunk, since #1138 (this will be part of 4.06).

@alainfrisch Nice!

@paurkedal Can you please directly answer why these mechanisms, which look increasingly complicated to me, are preferable to being able to annotate type expressions to suppress warnings?

@aantron Yeah, I guess nobody has given the explicit reason before your post, but

  • What seemed obvious to me was that it avoids clutter and modification of code which will be removed anyway. The assumption to make this point is that the rule adopted is effective; for if one ends up annotating more than half of the cases anyway, we might as well annotate all.
  • The automatic suppression rule is arguably safer in the sense that it only lets a definition depend on a deprecated definition if it is itself deprecated. With an explicit suppression, if we change our minds about a deprecation, we won't get the warning back unless we remember to also remove the warning suppression. The assumption to make this point is that there is no mix of short-term and long-term deprecations and that harmful suppression in very unlikely and can be taken care of with a grep.
  • And well, I don't think it's obvious that deprecations warnings should be suppressed with [@ocaml.warning "-3"] annotations, unless one has a good teacher.

@aantron
Copy link
Contributor

aantron commented Jul 17, 2017

I don't see why. The revised proposal has nothing to do with where the declaration is. Or do you consider the situation where a module declaration itself is marked as deprecated?

I was under the impression that the revised proposal applies only within one signature, as the original proposal. Is that not the case? If not, does that mean that if I use a deprecated type in a deprecated declaration in another project, the warning is suppressed?

How is that different from a giant recursive type that need to refer to a deprecated type defined earlier?

Yep, it's not, so I agree we shouldn't special-case the recursive types (but also not solve the general problem as proposed here). Was thinking "out loud" there.

@aantron
Copy link
Contributor

aantron commented Jul 17, 2017

-What seemed obvious to me was that it avoids clutter and modification of code which will be removed anyway. The assumption to make this point is that the rule adopted is effective; for if one ends up annotating more than half of the cases anyway, we might as well annotate all.

It is indeed more verbose and I can see how that can be annoying, but, indeed, that's what I would like :) Deprecation and removal should be annoying. I want myself, more importantly contributors, to be forced to think about each and every single use, and for this to be triggered independent of historical order.

I would prefer that code be modified for suppression, because

  1. That ends up in visible in blame, and I want to be able to trace it.
  2. The two deprecations might be historically unrelated.
  3. I want it further documented to readers that the type is indeed deprecated.
  4. I want it documented that we made an explicit decision here.
  • The automatic suppression rule is arguably safer in the sense that it only lets a definition depend on a deprecated definition if it is itself deprecated. With an explicit suppression, if we change our minds about a deprecation, we won't get the warning back unless we remember to also remove the warning suppression. The assumption to make this point is that there is no mix of short-term and long-term deprecations and that harmful suppression in very unlikely and can be taken care of with a grep.

I'm not sure how harmful this would be, but doing a grep sounds like a good thing to do anyway when un-deprecating something within a project. We presumably would have explicit suppressions anyway because (1) some using values might not be deprecated for some reason, (2) there may be non-deprecated using values in another project, so this is a skill that will have to be practiced by everyone.

  • And well, I don't think it's obvious that deprecations warnings should be suppressed with [@ocaml.warning "-3"] annotations, unless one has a good teacher.

This I agree with 100%. I'm not pro-that syntax, just pro-the mechanism. Obviously, I think the current lack of a good syntax for this shouldn't be cause to merge an entirely different mechanism that I believe is quite flawed.

@aantron
Copy link
Contributor

aantron commented Jul 17, 2017

I also want to note that deprecated code isn't always scheduled for removal in any practical term (i.e. it could be years). This is sometimes/often the case in Lwt, for instance. In such situations, it is much more valuable to have traceable blame for whoever is working on the project years from now, or reading .mlis, than to avoid a bit of an extra diff. And I mean a bit: for the automatic suppression, it seems like you have to add one annotation to the using definition anyway. It doesn't seem difficult to locally add a few more, in cases where you are deprecating a type at the same time (often NOT the case in Lwt).

I can see the attraction of reducing verbosity by coupling uses of a deprecated declaration to introduction of additional deprecation at that declaration, but it just has too many corner cases, and those corner cases reflect an underlying conflation of two introductions of unrelated instances of a construct, where actually introductions should interact only with eliminations of the same instance of that construct. So you can generate tons of counterexamples by thinking about this conflation. All those corner cases will lead to people wondering about what happens in them, and that is the source of the difficulty in teaching.

Of course for most cases, when this mechanism does the right thing and only makes your signatures less verbose, it looks like the right thing to do, and is easy to teach – but when it doesn't, and does too much thinking for you, then it turns into an indefensible nightmare. Ok, the "nightmare" terminology is too strong :) I am just trying to show what I am focusing on, that is the source of my resistance :)

We should find something else for making signatures less verbose. I'm not against that, I just don't think it should be done as proposed here.

@aantron
Copy link
Contributor

aantron commented Jul 17, 2017

What I propose we do, and I believe I am seconding and agreeing with @alainfrisch, though I am being explicit in case I misunderstood anything:

  • Don't merge the code here.
  • Support [@ocaml.warning "-3"] on type expressions in a separate PR.
  • Change the syntax of [@ocaml.warning "-3"] to be less opaque in a separate PR. Perhaps this can be done by changing to named warnings, which would probably be a long-term discussion. Another way is to have a special annotation with the same meaning.
  • See if that's good enough.
  • If needed, develop some mechanism for suppressing warnings on all uses of specific deprecated types within a scope. This is likely to be challenging in the presence of open, etc. But I think this mechanism will have to be focused on references, not whether the using declaration is itself deprecated.

@gasche
Copy link
Member

gasche commented Jul 17, 2017

Change the syntax of [@ocaml.warning "-3"] to be less opaque in a separate PR. Perhaps this can be done by changing to named warnings, which would probably be a long-term discussion. Another way is to have a special annotation with the same meaning.

I haven't been able to follow the discussion in this PR, apologies, but this rings a bell. I do want to work on moving to named warning at some point, one of the reason making the local-silencing code more readable in the future. But I wouldn't write that off as an easy thing to do: when I brought the idea up to other maintainers, I was told (rightly, I think), that this is a snake nest that will require quite some work to converge to a consensus.

@alainfrisch
Copy link
Contributor Author

I've started working on a branch to support the ocaml.warning/warnerror in many more places, including within type expression (but also on most structure/signature items). Cf https://github.com/ocaml/ocaml/tree/warning_attribute_on_type_exprs

@alainfrisch
Copy link
Contributor Author

@aantron I promise to close this PR if you review #1248 😄

@aantron
Copy link
Contributor

aantron commented Jul 18, 2017

@alainfrisch I started reviewing #1248 yesterday, but it is the first time I have looked into the compiler code (as opposed to stdlib or other code in this repo), so I had a hard time leaving any useful comment. It's more of a learning process for me at this point :)

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment

Projects

None yet

Development

Successfully merging this pull request may close these issues.

7 participants