[GHC] #11046: lookupTypeName does not support type operators
GHC
ghc-devs at haskell.org
Sun Nov 1 20:11:34 UTC 2015
#11046: lookupTypeName does not support type operators
-------------------------------------+-------------------------------------
Reporter: oerjan | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template | Version: 7.10.2
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:
-------------------------------------+-------------------------------------
The following non-working code (minus a missing import) was
[http://stackoverflow.com/questions/33465109/template-haskell-how-to-
lookup-type-operator-name posted on stackoverflow]:
`IssueTH.hs`:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
module IssueTH where
import Language.Haskell.TH
f :: Q [Dec]
f = do
Just n <- lookupTypeName "GHC.TypeLits.*"
return []
}}}
`Issue.hs`:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
module Issue where
import IssueTH
import GHC.TypeLits
$f
}}}
`ghc Issue.hs` fails with message:
`Pattern match failure in do expression at IssueTH.hs:7:5-10`
This gives no error if `*` is replaced by an alphanumeric type like `Nat`.
Similar tests seem to fail whenever attempting to look up a type operator
with `lookupTypeName`.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11046>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list