Skip to content
Snippets Groups Projects
Commit 42f3b53b authored by Kirill Zaborsky's avatar Kirill Zaborsky Committed by Ben Gamari
Browse files

Fix #13833: accept type literals with no FlexibleInstances

Test Plan: ./validate

Reviewers: bgamari, simonpj

Reviewed By: bgamari, simonpj

Subscribers: simonpj, rwbarton, thomie, carter

GHC Trac Issues: #13833

Differential Revision: https://phabricator.haskell.org/D4823
parent 7100850e
No related merge requests found
......@@ -1121,12 +1121,13 @@ tcInstHeadTyNotSynonym ty
tcInstHeadTyAppAllTyVars :: Type -> Bool
-- Used in Haskell-98 mode, for the argument types of an instance head
-- These must be a constructor applied to type variable arguments.
-- These must be a constructor applied to type variable arguments
-- or a type-level literal.
-- But we allow kind instantiations.
tcInstHeadTyAppAllTyVars ty
| Just (tc, tys) <- tcSplitTyConApp_maybe (dropCasts ty)
= ok (filterOutInvisibleTypes tc tys) -- avoid kinds
| LitTy _ <- ty = True -- accept type literals (Trac #13833)
| otherwise
= False
where
......
......@@ -125,6 +125,11 @@ Language
This is now an error unless :extension:`PolyKinds` is enabled.
- Type literals now could be used in type class instances without the extension
:extension:`FlexibleInstances`.
See :ghc-ticket:`13833`.
Compiler
~~~~~~~~
......
{-# LANGUAGE DataKinds, KindSignatures #-}
import GHC.TypeLits (Nat, Symbol)
class A (n::Nat)
instance A 0
class B (s::Symbol)
instance B "B"
main :: IO ()
main = return ()
......@@ -623,3 +623,4 @@ test('T15050', [expect_broken(15050)], compile, [''])
test('T14735', normal, compile, [''])
test('T15180', normal, compile, [''])
test('T15232', normal, compile, [''])
test('T13833', normal, compile, [''])
\ No newline at end of file
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