summaryrefslogtreecommitdiff
path: root/testsuite/tests/typecheck/should_compile
diff options
context:
space:
mode:
authorRichard Eisenberg <reisenberg@janestreet.com>2022-11-10 17:36:22 -0500
committerMatthew Pickering <matthewtpickering@gmail.com>2022-12-24 17:34:19 +0000
commit3c3060e4645b12595b187e7dbaa758e8adda15e0 (patch)
tree31209d21cf03de1552fcbad677ea7940fa481da4 /testsuite/tests/typecheck/should_compile
parent6d62f6bfbb5a86131e7cbc30993f3fa510d8b3ab (diff)
downloadhaskell-3c3060e4645b12595b187e7dbaa758e8adda15e0.tar.gz
Drop support for kind constraints.wip/p547
This implements proposal 547 and closes ticket #22298. See the proposal and ticket for motivation. Compiler perf improves a bit Metrics: compile_time/bytes allocated ------------------------------------- CoOpt_Singletons(normal) -2.4% GOOD T12545(normal) +1.0% T13035(normal) -13.5% GOOD T18478(normal) +0.9% T9872d(normal) -2.2% GOOD geo. mean -0.2% minimum -13.5% maximum +1.0% Metric Decrease: CoOpt_Singletons T13035 T9872d
Diffstat (limited to 'testsuite/tests/typecheck/should_compile')
-rw-r--r--testsuite/tests/typecheck/should_compile/T13871.hs16
-rw-r--r--testsuite/tests/typecheck/should_compile/T15141.hs35
-rw-r--r--testsuite/tests/typecheck/should_compile/T17021a.hs15
-rw-r--r--testsuite/tests/typecheck/should_compile/all.T2
4 files changed, 2 insertions, 66 deletions
diff --git a/testsuite/tests/typecheck/should_compile/T13871.hs b/testsuite/tests/typecheck/should_compile/T13871.hs
deleted file mode 100644
index fa233247ca..0000000000
--- a/testsuite/tests/typecheck/should_compile/T13871.hs
+++ /dev/null
@@ -1,16 +0,0 @@
-{-# LANGUAGE Haskell2010 #-}
-{-# LANGUAGE ConstraintKinds #-}
-{-# LANGUAGE GADTs #-}
-{-# LANGUAGE TypeFamilies #-}
-{-# LANGUAGE DataKinds, PolyKinds #-}
-{-# LANGUAGE TypeOperators #-}
-module Foo where
-
-import Data.Kind
-
-data Foo (a :: Type) (b :: Type) where
- MkFoo :: (a ~ Int, b ~ Char) => Foo a b
-
-data family Sing (a :: k)
-data SFoo (z :: Foo a b) where
- SMkFoo :: SFoo MkFoo
diff --git a/testsuite/tests/typecheck/should_compile/T15141.hs b/testsuite/tests/typecheck/should_compile/T15141.hs
deleted file mode 100644
index c0cb5d8488..0000000000
--- a/testsuite/tests/typecheck/should_compile/T15141.hs
+++ /dev/null
@@ -1,35 +0,0 @@
-{-# LANGUAGE PolyKinds, TypeFamilies, TypeFamilyDependencies,
- ScopedTypeVariables, TypeOperators, GADTs,
- DataKinds #-}
-
-module T15141 where
-
-import Data.Type.Equality
-import Data.Proxy
-
-type family F a = r | r -> a where
- F () = Bool
-
-data Wumpus where
- Unify :: k1 ~ F k2 => k1 -> k2 -> Wumpus
-
-f :: forall k (a :: k). k :~: Bool -> ()
-f Refl = let x :: Proxy ('Unify a b)
- x = undefined
- in ()
-
-{-
-We want this situation:
-
-forall[1] k[1].
- [G] k ~ Bool
- forall [2] ... . [W] k ~ F kappa[2]
-
-where the inner wanted can be solved only by taking the outer
-given into account. This means that the wanted needs to be floated out.
-More germane to this bug, we need *not* to generalize over kappa.
-
-The code above builds this scenario fairly exactly, and indeed fails
-without the logic in kindGeneralize that excludes constrained variables
-from generalization.
--}
diff --git a/testsuite/tests/typecheck/should_compile/T17021a.hs b/testsuite/tests/typecheck/should_compile/T17021a.hs
index aa78cb2959..41eb3f9d92 100644
--- a/testsuite/tests/typecheck/should_compile/T17021a.hs
+++ b/testsuite/tests/typecheck/should_compile/T17021a.hs
@@ -9,16 +9,5 @@ import GHC.Exts
type family Id x where
Id x = x
---type LevId :: TYPE (Id LiftedRep) -> TYPE (Id LiftedRep)
---newtype LevId x = MkLevId x
-
-type LevId2 :: (r ~ Id LiftedRep) => TYPE r -> TYPE r
-newtype LevId2 x = MkLevId2 x
-
-{-
-MkLevId2 :: forall (r :: RuntimeRep).
- forall (c :: r ~ Id LiftedRep) -> -- c is a TyVar
- forall (x :: TYPE r).
- x -> LevId2 @r @c x
-
--} \ No newline at end of file
+type LevId :: TYPE (Id LiftedRep) -> TYPE (Id LiftedRep)
+newtype LevId x = MkLevId x
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 577ce86d65..0a1edfa866 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -588,7 +588,6 @@ test('T13785', normal, compile, [''])
test('T13804', normal, compile, [''])
test('T13822', js_broken(22364), compile, [''])
test('T13848', normal, compile, [''])
-test('T13871', normal, compile, [''])
test('T13879', normal, compile, [''])
test('T13881', normal, compile, [''])
test('T18851d', normal, compile, [''])
@@ -655,7 +654,6 @@ test('T15431', normal, compile, [''])
test('T15431a', normal, compile, [''])
test('T15428', normal, compile, [''])
test('T15412', normal, compile, [''])
-test('T15141', normal, compile, [''])
test('T15473', normal, compile_fail, [''])
test('T15499', normal, compile, [''])
test('T15586', normal, compile, [''])