[GHC] #10193: TypeRep Show instance doesn't add parens around type operators
GHC
ghc-devs at haskell.org
Thu Mar 26 15:02:02 UTC 2015
#10193: TypeRep Show instance doesn't add parens around type operators
-------------------------------------+-------------------------------------
Reporter: | Owner:
pawel.nowak | Status: new
Type: bug | Milestone:
Priority: normal | Version: 7.10.1-rc3
Component: | Operating System: Unknown/Multiple
libraries/base | Type of failure: Incorrect result
Keywords: | at runtime
Architecture: | Blocked By:
Unknown/Multiple | Related Tickets:
Test Case: |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
The following code
{{{#!hs
{-# LANGUAGE AutoDeriveTypeable #-}
{-# LANGUAGE TypeOperators #-}
import Data.Typeable
data a :*: b = Pair a b
main = print (typeOf (Pair 'a' 'b'))
}}}
prints
{{{#!hs
:*: Char Char
}}}
which is not valid Haskell. I belive it should print
{{{#!hs
(:*:) Char Char
}}}
In my particular case I am using Hint to interpret a type involving type
operators. Hint uses showed TypeRep as a type annotation:
{{{#!hs
let type_str = show $ Data.Typeable.typeOf wit
...
let expr_typesig = concat [parens e, " :: ", type_str]
}}}
What results in a parse error.
I can write a patch if someone confirms that's the desired behavior and
doesn't break anything.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10193>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list