Skip to content
Snippets Groups Projects
Commit 00a1e50b authored by Krzysztof Gogolewski's avatar Krzysztof Gogolewski Committed by Marge Bot
Browse files

Add testcases for already fixed #16432

They were fixed by 40c7daed.

Fixes #16432
parent 2c38551e
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE GADTs, DataKinds #-}
module T23333 where
import Data.Kind
import Data.Coerce
foo1 :: (forall y. Bool ~ y) => z -> Bool
foo1 x = not x
foo2 :: (forall y. y ~ Bool) => z -> Bool
foo2 x = not x
-- Testcases from #16432
t1 :: forall f b. (forall a. Coercible (f a) a) => b -> f b
t1 = coerce
data U :: () -> Type where
MkU :: Int -> U '()
t2 :: forall n res. (('()~n) => (Int~res)) => U n -> res
t2 (MkU n) = n
t3 :: ((Bool~Bool) => (Char~res)) => res
t3 = 'a'
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