haskell / core-libraries-committee

95 stars 15 forks source link

Add the `todo` function #260

Closed MangoIV closed 1 month ago

MangoIV commented 6 months ago

Dear Haskell core library committee.

Currently there are multiple ways of describing something as unimplemented

problems of the above solutions

  1. Problems of the functions currently in base:
    • undefined:
    • doesn't give you a warning if it remains in code
    • doesn't read as "this is open, I will definitely implement it soon"
    • a lot to type for "please compiler, be quiet for the second, I will come back to this"
    • error:
    • also doesn't give you a warning if it remains in code
    • may read as "this is open, I will definitely implement it soon" but this is a lot to type
    • even more to type for "please compiler, be quiet for the second, I will come back to this", sometimes even needs paranthesis
  2. external dependencies:
    • just for doing a quick debugging todo, it doesn't seem worth adding an alternative Prelude or even add a dependency just for the sake of this
  3. typed holes
    • they are, by default, errors, not warnings
    • they are very noisy (by default they produce a lot of output)
    • they are slow (by default)

That's why propose a function todo that has the following properties:

implementation of the solution

{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE MagicHash #-}
{-# OPTIONS_GHC -Wall #-}

module Todo (todo) where

import GHC.Base (raise#, TYPE, RuntimeRep)
import GHC.Exception (errorCallWithCallStackException)
import GHC.Stack (HasCallStack)

{- | 'todo' indicates unfinished code. 

It is to be used whenever you want to indicate that you are missing a part of 
the implementation and want to fill that in later. 

The main difference to other alternatives like typed holes and 'undefined' 
or 'error' is, this does not throw an error but only emits a warning. 

Similarly to 'undefined', 'error' and typed holes, this will throw an error if 
it is evaluated at runtime which can only be caught in 'IO'. 

This is intended to *never* stay in code but exists purely for signifying
"work in progress" code. 

To make the emitted warning error instead (e.g. for the use in CI), add 
the @-Werror=x-todo@ flag to your @OPTIONS_GHC@.

==== __Examples__

@
superComplexFunction :: 'Maybe' a -> 'IO' 'Int'
-- we already know how to implement this in the 'Nothing' case
superComplexFunction 'Nothing' = 'pure' 42
-- but the 'Just' case is super complicated, so we leave it as 'todo' for now
superComplexFunction ('Just' a) = 'todo'
@
-}
todo :: forall {r :: RuntimeRep} (a :: TYPE r). (HasCallStack) => a
todo = raise# (errorCallWithCallStackException "Prelude.todo: not yet implemented" ?callStack)
{-# WARNING in "x-todo" todo "todo remains in code" #-}

try it out in a separate module, as such:

module TodoExample where

import Todo

superComplexFunction :: Maybe a -> IO Int
-- we already know how to implement this in the 'Nothing' case
superComplexFunction Nothing = pure 42
-- but the 'Just' case is super complicated, so we leave it as 'todo' for now
superComplexFunction (Just a) = todo

This implementation will work from >= ghc981

impact

on hoogle I currently find 4 functions which this would break, two of which have similar semantics to this one, making it improbable that they will be found in code out there.

Another advantage of this function is that there will be no need of a *-compat package because code that does contain this function is not supposed to live anywhere or compile with more than the compiler than the base version this is going to be shipped with supports.

I will obviously run a proper impact assessment though.

why I think this belongs in Prelude

The main reason I think this belongs into Prelude is because it is not possible to replace this with the same level of simplicity with any other solution

I think this will also have the positive impact of offering a real alternative to dangerous uses of undefined

also look at

rust std's todo! and unimplemented! macros

rendered docs

rendered docs without expanded Examples rendered docs with expanded Examples

some more screenshots

Amendment to this proposal (28 Mar 2024)

After what I consider a very productive and diverse discussion, I think the most prominent conclusion is that this might not make the jump into Prelude all at once. I still want to proceed with this proposal for the following two reasons:

  1. accessibility and visibility as well as usefulness in general (least overhead, least tooling issues, least possibility of divergence, etc.) will be greatest if this is in base
  2. and most importantly: I still want this is Prelude eventually; this seems to be only possible when something has been in base for a long time and one has to start at some point ;)

a new module, Debug.Placeholder Develop.Placeholder

There will be a new module Debug.Placeholder Develop.Placeholder that will contain both the

These implementations include many useful improvements to the function described above, which is really awesome.

The name of the module is justified as follows:

Note: if people think that the proposed namespace is incorrect, I would like to hear convincing arguments and am happy to adjust accordingly.

out of scope for this proposal

While there were some really nice suggestions to make the proposal "more complete", I will consider the following out of scope for this proposal while expressing the strong intention to later add them in a follow-up proposal:

Kleidukos commented 5 months ago

I don't know if it can cure all ailments but I too would love to see a day where I can just put "todo" in my in-progress work without thinking (until GHC makes me.)

ekmett commented 5 months ago

todo feels like a dev tool to me, so if a new top-level name isn't so bad, I could imagine something like Develop.Todo. I could not find any Develop.* modules using serokell's search, but note that there is some prior art for Development e.g. shake, gitrev.

If we're citing the existing Development namespace for a precedent, then I'd really prefer not to fragment it into Develop and Development. Moreover, random abbreviations for abbreviation sake seem like they make things harder to recall.

My main argument for going with Control.Placeholder was to lean in on the hackage namespace guidelines. I sat down, thought about what namespaces we did have official descriptions for, and while this clearly isn't Data one can argue that it very much does have a Control effect (stopping evaluation and telling you where you ran into code you haven't finished), so it met the letter of the law of one of the current two big hierarchies, enough that I didn't feel guilty picking a bikeshed.

avanov commented 5 months ago

@hasufell not sure how you got to the idea that the -Werror faction might complain to warnings originating from undefined, but as one of those who uses -Werror in production code and who complains on not being able to publish packages on Hackage with this flag on, I would highly appreciate the day when undefined finally become errors in my toolchain.

hasufell commented 5 months ago

@avanov I sympathize. But to me it seems making undefined throw a warning is now even more controversial than the existing proposal.

We'd need to demonstrate that all major use cases can be covered in different ways (like Proxy). Or we acknowledge that there can be a warning class that cannot be turned off by changing code, but requires users to silence the warning explicitly. I'm not sure if there's a precedence for that in other languages.

cbrt-x commented 5 months ago

I've skimmed through the discussion and haven't yet seen anyone dicussing or mentioning the function without implementation or signatures without binding GHC issues, which would allow the programmer to omit a binding and recieve a warning.

foo :: a -> b -> c
-- GHC creates a dummy implementation
-- foo = error "blah blah"
-- and omits a warning

If this CLC proposal was to go through and the above was implemented in GHC, there would be two, nearly identical ways of achieving the same thing. I'm personally in favor of this proposal, but this should probably be coordinated with the above issues.

If this proposal is accepted, in my opinion they should either not be implemented at all, or implemented in terms of todo:

foo :: a -> b -> c
-- GHC generated the definition 
-- foo = todo
tbidne commented 5 months ago

todo feels like a dev tool to me, so if a new top-level name isn't so bad, I could imagine something like Develop.Todo. I could not find any Develop.* modules using serokell's search, but note that there is some prior art for Development e.g. shake, gitrev.

If we're citing the existing Development namespace for a precedent, then I'd really prefer not to fragment it into Develop and Development. Moreover, random abbreviations for abbreviation sake seem like they make things harder to recall.

I don't really consider Develop an abbreviation. But fragmentation is a reasonable objection, and I am largely indifferent on Develop vs. Development.

My main argument for going with Control.Placeholder was to lean in on the hackage namespace guidelines. I sat down, thought about what namespaces we did have official descriptions for, and while this clearly isn't Data one can argue that it very much does have a Control effect (stopping evaluation and telling you where you ran into code you haven't finished), so it met the letter of the law of one of the current two big hierarchies, enough that I didn't feel guilty picking a bikeshed.

I share the unease over Control and Data -- thus preferring Develop/Development -- but if you're trying to rationalize your way into one of them, this is probably the best you can do :slightly_smiling_face:.

Kleidukos commented 5 months ago

I would vote in favour of Development.

merijn commented 5 months ago

Both of your proposed alternatives completely miss the point; holes introduce compile errors, while todo removes it, a library is not a match to built-in functionality for "quick and dirty" programming technique. Doing nothing and sticking to error "TODO" is a better alternative than those two (and, IMO, an acceptable one).

I mean, that's why there is a flag to turn typed holes into warnings. The entire point of that is that you can set that flag while developing. And then, when you want to go to production you remove that flag and any untyped holes you missed/forgot to implement turn into errors.

Overall, enabling 1 single flag during development and using typed holes, seems a lot simpler than this proposal. Which seems a lot of work AND a modification for base to get a less robust solution to a problem that's already solved?

sullyj3 commented 5 months ago

If this CLC proposal was to go through and the above was implemented in GHC, there would be two, nearly identical ways of achieving the same thing.

They don't quite cover the same use cases, since todo could be used within a definition to stub out its parts

f :: Int -> List a -> String
f n lst
  | n == 1 = "one"
  | n < 7 = case lst of
    [] -> "list is empty"
    (x : xs) -> todo
  | n > 100 = "huge!"
  | todo = todo

Whereas signatures without binding could only be used at the top level, or in let or where.

I agree that if those were to go through, it would make sense for them to be implemented in terms of todo if that were possible.

Bodigrim commented 4 months ago

I read the amended proposal and I like it. Develop.Placeholder sounds a bit mouthful to me, how about Develop.Todo?

Bodigrim commented 4 months ago

Dear CLC members, any more opinions on preferred module name to expose todo and TODO from?

@tomjaguarpaw @mixphix @angerman @parsonsmatt @hasufell @velveteer

Bodigrim commented 4 months ago

@MangoIV shall we go for a vote? Did you make up your mind about the final module name?

MangoIV commented 4 months ago

I will go for Develop.Placeholder if no further serious objections come up.

I’ll prepare a patch accordingly.

Bodigrim commented 3 months ago

@MangoIV just a gentle reminder to prepare an MR.

MangoIV commented 3 months ago

Oh it’s already been one month, sorry for the delay, it’s still WIP. I’ll try to hurry up…

Bodigrim commented 2 months ago

@MangoIV it would be great if we make some progress with an MR.

MangoIV commented 2 months ago

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12934

This is the (wip) MR. I will obviously also add tests. I have simplified the implementation a bit which should be fine as far as I can tell. If there will be a compatibility package, it will probably have to look a bit more like Edward Kmett's placeholder package.

Bodigrim commented 2 months ago

@MangoIV please ping when you get CI green:

libraries/base/src/Develop/Placeholder.hs:61:9: error: [GHC-25955]
    Illegal symbol ‘forall’ in type
    Suggested fix:
      Use the ‘ExplicitForAll’ extension (implied by ‘RankNTypes’,
                                                     ‘QuantifiedConstraints’, ‘ScopedTypeVariables’,
                                                     ‘LiberalTypeSynonyms’ and ‘ExistentialQuantification’)
      to enable syntax: forall <tvs>. <type>
   |
61 | todo :: forall {r :: RuntimeRep} (a :: TYPE r). (HasCallStack) => a
   |         ^^^^^^
Bodigrim commented 2 months ago

@MangoIV just a gentle reminder. Let's finish up with the MR and vote.

Bodigrim commented 1 month ago

@MangoIV it would be a shame to close the proposal as inactive after so much of discussion. Could you (or anyone else) please prepare a GHC MR which passes CI?

MangoIV commented 1 month ago

Sorry, I have been unable to do this until now and I’m very sorry to have kept you waiting. I will make the PR ready during the weekend.

Please excuse the delay.

MangoIV commented 1 month ago

I have made some progress with the PR, the haddock provided (as a screenshot of the html generated) should be almost in its final form.

I have decided to replace the adhoc exception with callstack exception type copied from error/ undefined with the throw as all of this should be subsumed by the ExceptionWithContext mechanism.

There's currently a problem which makes me consider to drop the TODO pattern for the purpose of this proposal, I haven't found a definite answer to this yet, though.

MangoIV commented 1 month ago

the todo haddock, rendered

MangoIV commented 1 month ago

@Bodigrim as far as I can tell the failed job on the PR are not related to the PR itself, the test it complains about is okay. I think this means this PR is ready for a vote.

I additionally want to disclose a problem I found with the TODO pattern; similarly to orphan instances, pattern completeness is infective, i.e., if I

  1. import Control.Placeholder (it is not relevant, what I import from there, e.g. import Control.Placeholder () is enough
  2. am in a context where I have a HasCallStack constraint in scope e.g as in
    x :: HasCallStack => Maybe () -> () 
    x = \case {}
  3. have -Wincomplete-patterns on
  4. have a case statement with none of the branches filled
  5. the case statement is not complete (e.g. by matching on empty data decls)

in these cases, GHC will sometimes propose (in the warning) to match on TODO instead of the actual data constructors. I don't think this is generally the wrong behaviour, after all it makes things like Seqs patterns possible. Perhaps GHC should not propose matches on patterns where the pattern doesn't have a concrete outermost type, but this is out of scope for this proposal.

If anybody thinks this will be problematic, I will exclude the TODO pattern from the proposal going forward and remove it from the MR.

As for the other changes in the PR (as compared to the original proposal at the top), please refer to my previous messages.

Bodigrim commented 1 month ago

in these cases, GHC will sometimes propose (in the warning) to match on TODO instead of the actual data constructors.

I think this is actually a desired behaviour: it's very nice of GHC to improve discoverability of pattern TODO. There is a warning attached, so it cannot be left in the code accidentally.

Bodigrim commented 1 month ago

Unless there is any further discussion, I'll open the vote soon.

mixphix commented 1 month ago

_

Bodigrim commented 1 month ago

I additionally want to disclose a problem I found with the TODO pattern

@MangoIV is it still relevant? I see that you filed https://gitlab.haskell.org/ghc/ghc/-/issues/25115, which is now resolved; was it the same issue?

MangoIV commented 1 month ago

@Bodigrim yes, this means the issue is at least partially resolved.

The compiler will generally not propose pattern synonyms if a constructor of the type is in scope and it will, in particular, not propose the synonym if it itself is not in scope.

Bodigrim commented 1 month ago

Dear CLC members, let's vote on the proposal to add a new module Develop.Placeholder with two entities todo and pattern TODO + a dedicated exception type TodoException. Here todo is essentially an enhanced version of undefined to use in your code during development and pattern TODO is even more powerful because it can be used to silence incomplete pattern matching warnings. Both entities have {-# WARNING in "x-todo" #-} to prevent you from leaving them in your code unnoticed. The MR is available at https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12934/diffs.

@tomjaguarpaw @hasufell @mixphix @angerman @parsonsmatt @velveteer


+1 from me, I think it strikes right balance.

mixphix commented 1 month ago

-1, typed holes provide more information, only slightly slow down the language server, and are shorter to type.

hasufell commented 1 month ago

I think this is a well put together proposal. And the main reason I find it interesting is pattern TODO, which I don't think can be achieved with current methods. If it wasn't for the pattern, I'd give this a -1 without further thought... after all, you can already write _todo.

And yet, I'm unsure how this fits in the existing realm of typed holes (should it maybe be an implicit typed hole with -fdefer-typed-holes enabled for the given expression? Why can't we have typed pattern holes? Is it just because _ is reserved?). As already pointed out: typed holes carry more information. But todo seems marginally more intuitive/discoverable. Maybe that's an issue of documentation/teaching/etc. Will adding another way improve status quo or make it more messy? I'm not confident to answer.

I also realized both methods suffer from frequent "Ambiguous type variable" errors. Try to use length todo or length _xs. So the ergonomics are still problematic and I'm not sure this is going to be that much fun for beginners anyway.

https://gitlab.haskell.org/ghc/ghc/-/issues/25115#note_577782 suggests that this type of functionality needs ad-hoc logic in GHC too. So I'm wondering whether this should be turned into a language extension instead or just become a part of existing typed holes.

Remember: once we added it to base, it can't really be removed easily.

As such I suggest to give this more iterations, maybe add the current implementation to ghc-experimental and let it sit for a while.


-1 (for now)

MangoIV commented 1 month ago

thank you for your elaboration @hasufell. @BinderDavid has already made a nice suggestion wrt this idea:

So I'm wondering whether this should be turned into a language extension instead or just become a part of existing typed holes.

This is a link to the corresponding comment

As an alternative it might be possible to special case a named typed hole _todo in GHC which would then by default not have these downsides but the semantics you want? Upsides would be that there isn't an additional definition in base and it is almost impossible to break any code since published code usually doesn't contain typed holes.

wrt this:

https://gitlab.haskell.org/ghc/ghc/-/issues/25115#note_577782 suggests that this type of functionality needs ad-hoc logic in GHC too. So I'm wondering whether this should be turned into a language extension instead or just become a part of existing typed holes.

whether adding custom logic is necessary is not too clear to me, see this: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12934#note_578239

tomjaguarpaw commented 1 month ago

-1


I would like to credit @MangoIV for putting together an excellent proposal with a very clear motivation. My personal bar for adding new things base is very high, and this proposal nearly clears the bar. In particular I find the claim that importing a separate feature for this functionality defeats the point: it needs to be easily accessible.

However, the proposal falls down in one major respect: the claim that typed holes are not good enough. @merijn summarizes my thoughts about this precisely:

that's why there is a flag to turn typed holes into warnings. The entire point of that is that you can set that flag while developing. And then, when you want to go to production you remove that flag and any untyped holes you missed/forgot to implement turn into errors.

Overall, enabling 1 single flag during development and using typed holes, seems a lot simpler than this proposal. Which seems a lot of work AND a modification for base to get a less robust solution to a problem that's already solved?

I do not currently see why it's better to use

import Develop.Placeholder (todo)
...
    TODO -> todo

than

{-# OPTIONS_GHC -fdefer-typed-holes -Wwarn=typed-holes #-}
...
    _ -> _

The claim is that "typed holes are slow". I asked in what way they are slow and received no response. Therefore I have no evidence on which to base a judgement that this proposal is better than typed holes. (FWIW, if typed holes really are slow then that seems like something that should be fixed in GHC rather than by adding a library workaround.)

hasufell commented 1 month ago

I do not currently see why it's better to use

Those things aren't really the same.

TODO the pattern is not expressible with typed holes afais.

Compare with

case foo of
    Constr1 -> True
    Constr2 -> False
    TODO -> f == x
    _ -> False

Here the _ is a regular catch-all, but you're not yet sure which cases it should match (or which constructors the type shall have)!

tomjaguarpaw commented 1 month ago

I agree they are not the same. I did not say they were the same! FWIW you can do

{-# OPTIONS_GHC -fdefer-typed-holes -Wwarn=typed-holes -Wwarn=overlapping-patterns #-}

case foo of
    Constr1 -> True
    Constr2 -> False
    _TODO -> f == x
    _ -> False
L0neGamer commented 1 month ago

How do typed holes work in the following sort of case vs TODO?

case foo of
  Constr1 -> True
  Constr2 -> False
  TODO -> f == x

There isn't a redundant pattern match so that wouldn't be warned against.

I would contend that TODO is more ergonomic than typed holes in development because with typed holes you have to remember to turn on and off the related warnings and such, meaning forgetting to do so results in bad code being left in, meanwhile a todo will continue warning unless you're explicitly turning it off, in which case you accept the consequences there.

tbidne commented 1 month ago

Maybe I'm just unreasonably lazy, but imo shuffling warnings is pretty unergonomic. If adding/removing warnings to modules/.cabal files is part of a dev tool's workflow, I'm just not going to bother. I'd rather stick to undefined at that point.

sullyj3 commented 1 month ago

It really does seem like it would be ideal for this to be in Prelude, to eliminate trivial inconveniences impeding its use.

It makes sense that that shouldn't be done yet for backwards compat reasons, but getting it into base could be a step towards that one day.

So it seems worth also thinking about about how

{-# OPTIONS_GHC -fdefer-typed-holes -Wwarn=typed-holes #-}
...
    _ -> _

might one day compare against

    TODO -> todo

(ie, no import required)

endgame commented 1 month ago

The claim is that "typed holes are slow". I asked in what way they are slow and received no response. Therefore I have no evidence on which to base a judgement that this proposal is better than typed holes. (FWIW, if typed holes really are slow then that seems like something that should be fixed in GHC rather than by adding a library workaround.)

IME it's not the holes themselves, but GHC's attempts to find valid hole fits that what cause the slowdown. On codebases which use advanced features, I almost always set -fno-show-valid-hole-fits. This seems difficult to fundamentally fix.

MangoIV commented 1 month ago

GHC's attempts to find valid hole fits

Exactly this. GHC finding valid hole fits or valid refinement holes is really slow, depending on the code base. IME they’re slow in almost all cases except the trivial ones.

tomjaguarpaw commented 1 month ago

imo shuffling warnings is pretty unergonomic

I agree!

GHC's attempts to find valid hole fits that what cause the slowdown. On codebases which use advanced features, I almost always set -fno-show-valid-hole-fits

I see, so there is a mitigation.

These are all fair points against the typed holes alternative, but they should have been made before the vote was called. I asked five months ago.

MangoIV commented 1 month ago

I asked 5 months ago

Please excuse me, @tomjaguarpaw, this is obviously on me, I should have answered this on time, I might have overlooked or forgotten to come back to this question.

merijn commented 1 month ago

@tbidne I don't think that's unreasonably lazy, but I would like to point out that you can use cabal.project.local to add (local) overrides such as GHC flags that get appended to cabal's flags.

So, the way I've been using it for years now is to append -fdefer-typed-holes and -fwarn-typed-holes (or whatever the new flag name is) in my cabal.project.local so that locally for development it "Just Works", with zero risk of those flags making it into, e.g., my CI pipeline (as cabal.project.local isn't and shouldn't be tracked in version control).

tomjaguarpaw commented 1 month ago

It's OK @MangoIV, you don't have anything to apologise for. It's your proposal and you're welcome to conduct it as you wish. There was plenty of discussion of typed holes. My question about slowness was only one component of that. When the vote was called I reread the entire discussion and I was not convinced by the arguments that the proposal was sufficiently better than typed holes to warrant inclusion in base (I have a very high bar).

Still, I commend you for putting together an excellent proposal and I would be pleased to see someone put it into a stand-alone package. As I said, I take the point that having it in a separate package somewhat defeats the utility, but nonetheless I think it would be worth trialling "in the wild". At the very least I would encourage maintainers of "alternative preludes" to consider adopting it if it fits with their design ethos. There is clearly a lot of scope for improving the ergonomics in this area.

googleson78 commented 1 month ago

Maybe I'm just unreasonably lazy, but imo shuffling warnings is pretty unergonomic. If adding/removing warnings to modules/.cabal files is part of a dev tool's workflow, I'm just not going to bother. I'd rather stick to undefined at that point.

+1 to this.

Additionally, adding the -fdefer-typed-holes flag has one (minor?major?) drawback: I can now no longer use typed holes as an error alongside with typed holes as a warning. To me todo serves the purpose of saying "I really do not care about this right now, please just let me get along with my work", whereas typed holes serve the purpose of saying "Hey compiler, what do I need to put here?". It's fine to say you can use typed holes for the "I don't care, leave me alone" case if you turn on the warning, but then you immediately lose the (original?) utility of typed holes as a dialogue with the compiler. My file will now compile, but I lose the ability to reason about whether it compiles because I've pushed some work back (ala todo) or whether it compiles because I forgot to finish my current work (ala _) (without looking through all the warnings manually).

Of course, this is really minor and workflow dependent, but I feel that it essentially encapsulates what I personally perceive the intent and semantics behind these two features to be, as well as pointing out one small limitation with -fdefer-typed-holes, so I feel that it's worth mentioning.

angerman commented 1 month ago

After re-reading this a few times, I admit, I like the motivation a lot, but I'm just not convinced about including this in base. I'm not sure if the current base-split will help with finding alternative/less-permanent options.

Hence, I'm -1 on this one in its current form. This is another one score for re-installable base, sigh.

parsonsmatt commented 1 month ago

I'm +1.

This is a nicer todo design than I've ever come up with, and I've invented it in three different work projects independently.

I can see a benefit to it landing in base. If it doesn't land in base, then I think it'd make a wonderful package to incorporate into alternative prelude packages elsewhere on Hackage.

MangoIV commented 1 month ago

As far as I understood that's it then, thank you all for your consideration, discussion and finally the vote.

I hope this can be revamped when making something like base 5 that may introduce a large amount of breakage but really rethink what a modern standard library should look like. Of course, base doesn't become one just by introducing little quality of live improvements like todo but it's quite a good testimony of how cumbersome any substantial improvements, many of which are even somewhat universally agreed on, will be, just for the reason of them creating a lot of churn in the ecosystem. Mind that this is no criticism but instead a pledge for a more glorious future after the base split.

I don't think I will want to introduce something like the special cased _todo. It has several disadvantages compared to this, very simple approach

Generally, afaiu, it just increases complexity and shifts responsibility from the core libraries to the compiler which is even less agile.

Again, thank you so much for the discussion and feedback and most importantly, your time.

endgame commented 1 month ago

o7 @MangoIV

Can I put a big +1 on "make a standalone package"? I think it would be cool to see how it goes in alternate preludes, so there's usage data when the issue is next raised?