[GHC] #16059: checkValidType is defeated by a type synonym
GHC
ghc-devs at haskell.org
Thu Jan 10 19:27:49 UTC 2019
#16059: checkValidType is defeated by a type synonym
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.10.1
Component: Compiler (Type | Version: 8.7
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC accepts | Unknown/Multiple
invalid program | Test Case:
Blocked By: | Blocking: 16140
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
For the sake of gathering more examples, this also manifests when checking
unboxed tuples. For instance, GHC compiles `B.hs` below successfully, even
though it shouldn't (since the `UnboxedTuples` extension isn't enabled in
`B`):
{{{#!hs
{-# LANGUAGE UnboxedTuples #-}
module A where
type Foo = (# #)
}}}
{{{#!hs
-- B.hs
module B where
import A
type Bar = Foo
}}}
On the other hand, in `C.hs` below:
{{{#!hs
-- C.hs
{-# LANGUAGE TemplateHaskell #-}
module C where
import Language.Haskell.TH (conT, unboxedTupleTypeName)
type Baz = $(conT (unboxedTupleTypeName 0))
}}}
GHC correctly rejects this, since there's no intermediate type synonym:
{{{
C.hs:7:1: error:
• Illegal unboxed tuple type as function argument: (# #)
Perhaps you intended to use UnboxedTuples
• In the type synonym declaration for ‘Baz’
|
7 | type Baz = $(conT (unboxedTupleTypeName 0))
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
}}}
-----
This also affects `RankNTypes`, since `B.hs` is erroneously accepted:
{{{#!hs
-- A.hs
{-# LANGUAGE RankNTypes #-}
module A where
type Foo = forall a. a
}}}
{{{#!hs
-- B.hs
module B where
import A
f :: Foo -> b -> b
f g x = g x
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16059#comment:11>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list