Vladislav Zavialov pushed to branch wip/int-index/visible-forall-gadts at Glasgow Haskell Compiler / GHC

Commits:

3 changed files:

Changes:

  • compiler/Language/Haskell/Syntax/Decls.hs
    ... ... @@ -970,9 +970,10 @@ data ConDecl pass
    970 970
           -- The following fields describe the type after the '::'
    
    971 971
           -- See Note [GADT abstract syntax]
    
    972 972
           , con_outer_bndrs :: XRec pass (HsOuterSigTyVarBndrs pass)
    
    973
    -        -- ^ The outermost type variable binders, be they explicit or
    
    974
    -        --   implicit.  The 'XRec' is used to anchor exact print
    
    975
    -        --   annotations, AnnForall and AnnDot.
    
    973
    +        -- ^ The outermost type variable binders, be they explicit or implicit;
    
    974
    +        --   cf. HsSigType that also stores the outermost sig_bndrs separately
    
    975
    +        --   from the forall telescopes in sig_body.
    
    976
    +        --   See Note [Representing type signatures] in Language.Haskell.Syntax.Type
    
    976 977
           , con_inner_bndrs :: [HsForAllTelescope pass]
    
    977 978
             -- ^ The forall telescopes other than the outermost invisible forall.
    
    978 979
           , con_mb_cxt  :: Maybe (LHsContext pass)   -- ^ User-written context (if any)
    

  • docs/users_guide/9.14.1-notes.rst
    ... ... @@ -72,6 +72,18 @@ Language
    72 72
     
    
    73 73
     * The :extension:`MonadComprehensions` extension now implies :extension:`ParallelListComp` as was originally intended (see `Monad Comprehensions <https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/monad_comprehensions.html>`_).
    
    74 74
     
    
    75
    +* In accordance with `GHC Proposal #281 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0281-visible-forall.rst>`_,
    
    76
    +  section 4.7 "Data constructors", the :extension:`RequiredTypeArguments`
    
    77
    +  extension now allows visible forall in types of data constructors
    
    78
    +  (:ghc-ticket:`25127`). The following declaration is now accepted by GHC:
    
    79
    +
    
    80
    +  ::
    
    81
    +
    
    82
    +    data T a where
    
    83
    +      Typed :: forall a -> a -> T a
    
    84
    +
    
    85
    +  See :ref:`visible-forall-in-gadts` for details.
    
    86
    +
    
    75 87
     Compiler
    
    76 88
     ~~~~~~~~
    
    77 89
     
    

  • docs/users_guide/exts/required_type_arguments.rst
    ... ... @@ -428,6 +428,8 @@ The :extension:`RequiredTypeArguments` extension does not add dependent
    428 428
     functions, which would be a much bigger step. Rather :extension:`RequiredTypeArguments`
    
    429 429
     just makes it possible for the type arguments of a function to be compulsory.
    
    430 430
     
    
    431
    +.. _visible-forall-in-gadts:
    
    432
    +
    
    431 433
     Visible forall in GADTs
    
    432 434
     ~~~~~~~~~~~~~~~~~~~~~~~
    
    433 435