Skip to content
  • Ryan Scott's avatar
    Don't put foralls in front of TH-spliced GADT constructors that don't need them · 9fd87ef8
    Ryan Scott authored
    Summary:
    It turns out that D2974 broke this program
    (see https://phabricator.haskell.org/rGHC729a5e452db5#58801):
    
    ```lang=haskell
    {-# LANGUAGE ConstraintKinds #-}
    {-# LANGUAGE GADTs #-}
    {-# LANGUAGE KindSignatures #-}
    {-# LANGUAGE TemplateHaskell #-}
    {-# OPTIONS_GHC -ddump-splices #-}
    module Bug where
    
    import GHC.Exts (Constraint)
    
    $([d| data Dec13 :: (* -> Constraint) -> * where
            MkDec13 :: c a => a -> Dec13 c
        |])
    ```
    
    This was actually due to a long-standing bug in `hsSyn/Convert` that put
    unnecessary `forall`s in front of GADT constructors that didn't have any
    explicitly quantified type variables.
    
    This cargo-cults the code in `Convert` that handles `ForallT` and adapts
    it to `ForallC`. Fixes #13123 (for real this time).
    
    Test Plan: make test TEST=T13123
    
    Reviewers: goldfire, austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D3002
    
    GHC Trac Issues: #13123
    9fd87ef8