Skip to content
Snippets Groups Projects
Commit 85ac65c5 authored by Ryan Scott's avatar Ryan Scott Committed by Ben Gamari
Browse files

Fix #13947 by checking for unbounded names more

Commit 2484d4da accidentally dropped a
call to `isUnboundName` in an important location. This re-adds it.

Fixes #13947.

Test Plan: make test TEST=T13947

Reviewers: adamgundry, austin, bgamari

Reviewed By: adamgundry

Subscribers: rwbarton, thomie

GHC Trac Issues: #13947

Differential Revision: https://phabricator.haskell.org/D3718
parent ba46e63f
No related merge requests found
......@@ -1431,8 +1431,9 @@ sectionPrecErr op@(n1,_) arg_op@(n2,_) section
nest 4 (text "in the section:" <+> quotes (ppr section))]
is_unbound :: OpName -> Bool
is_unbound UnboundOp{} = True
is_unbound _ = False
is_unbound (NormalOp n) = isUnboundName n
is_unbound UnboundOp{} = True
is_unbound _ = False
ppr_opfix :: (OpName, Fixity) -> SDoc
ppr_opfix (op, fixity) = pp_op <+> brackets (ppr fixity)
......
{-# LANGUAGE TypeOperators #-}
module T13947 where
f :: () -> Int :~: Int
f = undefined
T13947.hs:4:12: error:
Not in scope: type constructor or class ‘:~:’
......@@ -127,3 +127,4 @@ test('T11592', normal, compile_fail, [''])
test('T12879', normal, compile_fail, [''])
test('T13644', expect_broken(13644), multimod_compile_fail, ['T13644','-v0'])
test('T13568', normal, multimod_compile_fail, ['T13568','-v0'])
test('T13947', normal, compile_fail, [''])
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