[GHC] #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types
GHC
ghc-devs at haskell.org
Thu Jun 1 20:43:55 UTC 2017
#13776: -ddump-splices produces unnecessarily qualified names for tuple and list
types
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template | Version: 8.0.1
Haskell |
Keywords: newcomer | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
If you compile this:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -ddump-splices #-}
module Bug where
import Language.Haskell.TH
f :: $(conT ''(,) `appT` conT ''Int `appT` conT ''Int)
f = (1,2)
g :: $(conT ''[] `appT` conT ''Int)
g = []
}}}
You'll get some unsavory output:
{{{
Bug.hs:10:8-34: Splicing type
conT ''[] `appT` conT ''Int ======> GHC.Types.[] Int
Bug.hs:7:8-53: Splicing type
conT ''(,) `appT` conT ''Int `appT` conT ''Int
======>
GHC.Tuple.(,) Int Int
}}}
It's unsavory because if you actually try to use the spliced output in
Haskell code:
{{{#!hs
module Bug2 where
f :: GHC.Tuple.(,) Int Int
f = (1,2)
g :: GHC.Types.[] Int
g = []
}}}
Then it won't parse.
Expressions have the same problem:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -ddump-splices #-}
module Bug3 where
import Language.Haskell.TH
f :: (Int, Int)
f = $(conE '(,) `appE` litE (integerL 1) `appE` litE (integerL 1))
g :: [Int]
g = $(conE '[])
}}}
{{{
Bug3.hs:8:7-65: Splicing expression
conE '(,) `appE` litE (integerL 1) `appE` litE (integerL 1)
======>
(GHC.Tuple.(,) 1) 1
Bug3.hs:11:7-14: Splicing expression conE '[] ======> GHC.Types.[]
}}}
And patterns:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -ddump-splices #-}
module Bug4 where
import Language.Haskell.TH
f :: (Int, Int) -> ()
f $(conP '(,) [litP (integerL 1), litP (integerL 1)]) = ()
g :: [Int] -> ()
g $(conP '[] []) = ()
}}}
{{{
Bug4.hs:8:5-52: Splicing pattern
conP '(,) [litP (integerL 1), litP (integerL 1)]
======>
GHC.Tuple.(,) 1 1
Bug4.hs:11:5-15: Splicing pattern conP '[] [] ======> GHC.Types.[]
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13776>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list