Skip to content
Snippets Groups Projects
Commit fa0d4809 authored by Ryan Scott's avatar Ryan Scott Committed by Marge Bot
Browse files

Parenthesize nullary constraint tuples using sigPrec (#17403)

We were using `appPrec`, not `sigPrec`, as the precedence when
determining whether or not to parenthesize `() :: Constraint`,
which lead to the parentheses being omitted in function contexts
like `(() :: Constraint) => String`. Easily fixed.

Fixes #17403.
parent 7d80f8b5
No related branches found
No related tags found
No related merge requests found
......@@ -1467,7 +1467,7 @@ pprSum _arity is_promoted args
pprTuple :: PprPrec -> TupleSort -> PromotionFlag -> IfaceAppArgs -> SDoc
pprTuple ctxt_prec ConstraintTuple NotPromoted IA_Nil
= maybeParen ctxt_prec appPrec $
= maybeParen ctxt_prec sigPrec $
text "() :: Constraint"
-- All promoted constructors have kind arguments
......
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE KindSignatures #-}
module T17403 where
import Data.Kind
f :: (() :: Constraint) => String
f = "hello world"
:load T17403
:type +v f
f :: (() :: Constraint) => String
......@@ -313,3 +313,4 @@ test('T15546', normal, ghci_script, ['T15546.script'])
test('T16876', normal, ghci_script, ['T16876.script'])
test('T17345', normal, ghci_script, ['T17345.script'])
test('T17384', normal, ghci_script, ['T17384.script'])
test('T17403', normal, ghci_script, ['T17403.script'])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment