[GHC] #11484: Type synonym using -XTypeInType can't be spliced with TH
GHC
ghc-devs at haskell.org
Sat Jan 23 21:59:02 UTC 2016
#11484: Type synonym using -XTypeInType can't be spliced with TH
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template | Version: 8.0.1-rc1
Haskell |
Keywords: TypeInType | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following code compiles:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeInType #-}
{-# OPTIONS_GHC -ddump-splices #-}
module Foo where
import Data.Kind
type TySyn (k :: *) (a :: k) = ()
-- $([d| type TySyn2 (k :: *) (a :: k) = () |])
}}}
But uncomment the last line, and it doesn't compile:
{{{
$ /opt/ghc/head/bin/ghc Foo.hs
[1 of 1] Compiling Foo ( Foo.hs, Foo.o )
Foo.hs:10:3-43: Splicing declarations
[d| type TySyn2_aBH (k_aBI :: *) (a_aBJ :: k_aBI) = () |]
======>
type TySyn2_a4BF (k_a4BG :: Type) (a_a4BH :: k_a4BG) = ()
Foo.hs:10:3: error:
• Couldn't match expected kind ‘GHC.Prim.Any’ with actual kind ‘k1’
• In the type declaration for ‘TySyn2’
Foo.hs:10:3: error:
• Kind variable ‘k_a4BG’ is implicitly bound in datatype
‘TySyn2’, but does not appear as the kind of any
of its type variables. Perhaps you meant
to bind it (with TypeInType) explicitly somewhere?
Type variables with inferred kinds: k_a4BG (a_a4BH :: GHC.Prim.Any)
• In the type declaration for ‘TySyn2’
}}}
There are two issues here:
1. The error message claims that `TySyn2` is a datatype when it is
actually a type synonym. This should be easy enough to fix; just change
[http://git.haskell.org/ghc.git/blob/89bdac7635e6ed08927d760aa885d3e7ef3edb81:/compiler/typecheck/TcHsType.hs#l1874
the code] that throws the error message to invoke
[http://git.haskell.org/ghc.git/blob/89bdac7635e6ed08927d760aa885d3e7ef3edb81:/compiler/types/TyCon.hs#l1957
tyConFlavour].
2. For some reason, the type variable `a` in `TySyn2` fails to kind-check.
Somehow, an `Any` got in there, but I'm not sure where it snuck in.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11484>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list