Skip to content
Snippets Groups Projects

'forall' always a keyword, plus the dot type operator

Merged Vladislav Zavialov requested to merge wip/forall-keyword into master

This merge request:

  1. implements the "Make forall a keyword in types" proposal (accepted)
  2. implements the "The dot type operator" proposal (accepted)
  3. fixes a bad error message about existential quantification, Trac #16311

It also improves handling of Unicode syntax in hintExplicitForall and adds two related utilities, starSym and forallSym.

Edited by Vladislav Zavialov

Merge request reports

Loading
Loading

Activity

Filter activity
  • Approvals
  • Assignees & reviewers
  • Comments (from bots)
  • Comments (from users)
  • Commits & branches
  • Edits
  • Labels
  • Lock status
  • Mentions
  • Merge request status
  • Tracking
  • LGTM, although I don't think we can really land this yet until we get some sort of indication that forall-always-a-keyword-in-types proposal will be accepted.

  • added 1 commit

    Compare with previous version

  • Vladislav Zavialov resolved all discussions

    resolved all discussions

  • I don't think we can really land this yet until we get some sort of indication that forall-always-a-keyword-in-types proposal will be accepted

    The response to this proposal has been positive so far, so I'm being optimistic. We can wait for the committee to make a decision, but we can also merge and revert in case of rejection. ghc-proposals/README.md is clear on this:

    In the case that the proposed change has already been implemented in GHC, it will be reverted.

    I don't care if we wait or merge optimistically, but I do care that it gets into the GHC 8.8 release in case the proposal is accepted.

  • Fortunately, my comments no longer apply, since the proposal was just accepted :)

    Let's do this.

  • Ryan Scott approved this merge request

    approved this merge request

  • assigned to @marge-bot

  • I will attempt to batch this MR (!369 (closed))...

  • This should have been squashed before it was merged I think. The first two commits failed CI.

  • Ryan Scott removed assignee

    removed assignee

  • Ryan Scott mentioned in merge request !369 (closed)

    mentioned in merge request !369 (closed)

  • Batch MR !369 (closed) failed: Someone canceled the CI. I will retry later...

  • 3767 3767 then parseErrorSDoc span $ text $ "parse error in if statement"
    3768 3768 else parseErrorSDoc span $ text $ "parse error in if statement: "++msg
    3769 3769
    3770 -- Hint about explicit-forall, assuming UnicodeSyntax is on
    3771 hintExplicitForall :: SrcSpan -> P ()
    3772 hintExplicitForall span = do
    3770 -- Hint about explicit-forall
    3771 hintExplicitForall :: Located Token -> P ()
    3772 hintExplicitForall tok = do
    3773 3773 forall <- getBit ExplicitForallBit
    3774 3774 rulePrag <- getBit InRulePragBit
    3775 unless (forall || rulePrag) $ parseErrorSDoc span $ vcat
    3776 [ text "Illegal symbol '\x2200' in type" -- U+2200 FOR ALL
    3775 unless (forall || rulePrag) $ parseErrorSDoc (getLoc tok) $ vcat
    3776 [ text "Illegal symbol" <+> quotes forallSymDoc <+> text "in type"
    3777 3777 , text "Perhaps you intended to use RankNTypes or a similar language"
    • Can we suggest ScopedTypeVariables here? We really don't know what the user wants. But GHC never elsewhere suggests ScopedTypeVariables, and the lack of ScopedTypeVariables leads to pernicious errors. On the other hand, if the user wants RankNTypes, GHC will warn appropriately after they enable ScopedTypeVariables.

    • Can we suggest ScopedTypeVariables here?

      I'm afraid this doesn't qualify as strictly an improvement, sometimes the user might want RankNTypes without ScopedTypeVariables. I agree with the general idea that we should detect the cases when the forall is Rank-1 and suggest something other than RankNTypes. This might be something we should do in the typechecker instead of the parser, so let's discuss and implement it separately from this MR.

    • I know it's not strictly an improvement locally. But consider these workflows:

      1a. User is writing a higher-rank type without extensions. GHC suggests to enable RankNTypes. Program is accepted.

      1b. User is writing a higher-rank type without extensions. GHC suggests to enable ScopedTypeVariables. User compiles again, and GHC suggests to enable RankNTypes. Program is accepted.

      2a. User is writing a program that requires scoped type variables. GHC suggests to enable RankNTypes. Program is rejected with inscrutable type errors claiming that a is not a0.

      2b. User is writing a program that requires scoped type variables. GHC suggests to enable ScopedTypeVariables. Program is accepted.

      The question is: what's worse: 1b, or 2a? I claim that 2a is worse, and so I favor making the change so that we avoid 2a in favor of sometimes incurring 1b.

    • Okay. I don't like that in 1b and 2a the user ends up with extensions they don't actually need to make their program compile. The current error message is

      Perhaps you intended to use RankNTypes or a similar language extension

      So what about

      Perhaps you intended to use RankNTypes, ScopedTypeVariables, or a similar language extension

      and let the user decide which one they meant.

    • Not a bad idea. But let's list all of them: RankNTypes, QuantifiedConstraints, ScopedTypeVariables, LiberalTypeSynonyms, and ExistentialQuantification. Or we could just suggest ExplicitForAll. I still favor just listing ScopedTypeVariables, but if you want to be more inclusive, I won't stop you.

    • Hm, fair enough. But listing them all would bloat the error message and overwhelm the user (at least if the user was me). Let's say I bite the bullet and change RankNTypes to ScopedTypeVariables in this error message. What do I do with some of the test cases, then? For example T3155:

      unR :: (forall ix. r ix -> ix) -> AnyR s r -> Any s

      It's clearly a regression if we start suggesting ScopedTypeVariables here, and I don't want this particular MR introduce any sort of regression to error messages... I'm not opposed to your idea, but it's a trade-off and so far this MR is a clear-cut improvement, which implements accepted proposals and fixes an earlier error message regression.

      I created a ticket to discuss this, https://ghc.haskell.org/trac/ghc/ticket/16321. I think the right way forward here is to implement a proper diagnostic in a later pass instead of doing guesswork during parsing. But that's clearly out of scope.

    • Even if we end up simply replacing RankNTypes with ScopedTypeVariables because it's a good stopgap solution, I'd rather see it in a separate commit and a separate MR.

    • OK. I favor doing it while in the area (just for efficiency), but I can't argue against your stance. Don't let this issue stop the merging.

    • Please register or sign in to reply
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Please register or sign in to reply
    Loading