Skip to content

-ddump-splices omits required parentheses around quantified constraints

If you compile this program with -ddump-splices:

{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -ddump-splices #-}
module Bug where

import Language.Haskell.TH

data Foo x = MkFoo x

$([d| f :: (forall a. Eq (Foo a)) => Foo x -> Foo x -> Bool
      f = (==)
    |])

You'll notice something fishy:

$ /opt/ghc/8.6.1/bin/ghci Bug.hs
GHCi, version 8.6.1: http://www.haskell.org/ghc/  :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug              ( Bug.hs, interpreted )
Bug.hs:(10,3)-(12,6): Splicing declarations
    [d| f_a1Ia ::
          (forall a_a1Ic. Eq (Foo a_a1Ic)) =>
          Foo x_a1Ib -> Foo x_a1Ib -> Bool
        f_a1Ia = (==) |]
  ======>
    f_a5tj ::
      forall a_a5tk. Eq (Foo a_a5tk) => Foo x_a5ti -> Foo x_a5ti -> Bool
    f_a5tj = (==)
Ok, one module loaded.

The signature for f gets pretty-printed as:

f_a5tj :: forall a_a5tk. Eq (Foo a_a5tk) => Foo x_a5ti -> Foo x_a5ti -> Bool

Which is just plain wrong—there is a missing set of parentheses around the quantified constraint forall a_a5tk. Eq (Foo a_a5tk).

Patch incoming.

Trac metadata
Trac field Value
Version 8.6.1
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component Template Haskell
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information