
#12407: Template Haskell thinks an unboxed tuple name is illegal to splice in -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Template | Version: 8.0.1 Haskell | Keywords: | 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: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE UnboxedTuples #-} module Bug where import Language.Haskell.TH.Lib import Language.Haskell.TH.Syntax $(do let ubxTup = conT (unboxedTupleTypeName 2) `appT` conT ''Int `appT` conT ''Int x <- newName "x" y <- newName "y" [d| f :: $(ubxTup) -> $(ubxTup) f $(conP (unboxedTupleDataName 2) [varP x, varP y]) = $(conE (unboxedTupleDataName 2) `appE` varE x `appE` varE y) |]) }}} {{{ $ /opt/ghc/8.0.1/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:8:3: error: Illegal type constructor or class name: ‘(#,#)’ When splicing a TH declaration: f_0 :: GHC.Tuple.(#,#) GHC.Types.Int GHC.Types.Int -> GHC.Tuple.(#,#) GHC.Types.Int GHC.Types.Int }}} Patch coming soon. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12407 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler