Skip to content

Commit

Permalink
Add test for GADTs and scoped type variables
Browse files Browse the repository at this point in the history
  • Loading branch information
simonpj committed Nov 2, 2007
1 parent a6909cb commit f9f5741
Show file tree
Hide file tree
Showing 2 changed files with 35 additions and 0 deletions.
2 changes: 2 additions & 0 deletions tests/ghc-regress/gadt/all.T
Expand Up @@ -64,6 +64,8 @@ test('data2', normal, compile, [''])
test('termination', normal, compile, [''])
test('set', normal, compile, [''])
test('scoped', expect_broken(1823), compile, [''])
# New ones from Dimitrios
Expand Down
33 changes: 33 additions & 0 deletions tests/ghc-regress/gadt/scoped.hs
@@ -0,0 +1,33 @@
{-# OPTIONS_GHC -XGADTs -XScopedTypeVariables -XPatternSignatures #-}

-- Tests for scoped type variables and GADTs

module GADT where

data C x y where
C :: a -> C a a

data D x y where
D :: C b c -> D a c

------- All these should be ok

-- Rejected!
g1 :: forall x y . C x y -> ()
-- C (..) :: C x y
-- Inside match on C, x=y
g1 (C (p :: y)) = ()

-- OK!
g2 :: forall x y . C x y -> ()
-- C (..) :: C x y
-- Inside match on C, x=y
g2 (C (p :: x)) = ()

-- Rejected!
g3 :: forall x y . D x y -> ()
-- D (..) :: D x y
-- C (..) :: C sk y
-- sk = y
-- p :: sk
g3 (D (C (p :: y))) = ()

0 comments on commit f9f5741

Please sign in to comment.