TH Show instance not working.

David Banas capn.freako at gmail.com
Sun Aug 20 00:16:39 UTC 2017


Hi all,

Does anyone know why this code:

module Language.P4.UtilTest where

import Language.P4.Util (mkShow)

data Dummy = Bogus    Char
           | Nonsense Int

$(mkShow ''Dummy)

is producing this error:

Davids-Air-2:P4 dbanas$ stack ghc -- UtilTest.hs -ddump-splices
[1 of 1] Compiling Language.P4.UtilTest ( UtilTest.hs, UtilTest.o )
UtilTest.hs:24:3-16: Splicing declarations
    mkShow ''Dummy
  ======>
    instance Show Dummy where
      show (Bogus x) = show x
      show (Nonsense x) = show x

UtilTest.hs:24:3: error:
    Conflicting definitions for ‘show’
    Bound at: UtilTest.hs:24:3-16
              UtilTest.hs:24:3-16
   |
24 | $(mkShow ''Dummy)
   |   ^^^^^^^^^^^^^^

?

The TH splice expansion looks correct to me.
If I comment out the second constructor (Nonsense Int), the code compiles without error.

Thanks,
-db

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/glasgow-haskell-users/attachments/20170819/fc484284/attachment.html>


More information about the Glasgow-haskell-users mailing list