
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

Hi David, mkShow is probably making two separate declarations for "show" ([FunD "show" _, FunD "show" _]) instead of one declaration with two clauses ([FunD "show" [Clause ..., Clause ...]]). Both pretty-print to the same text, but only the second one is actually valid. When there is only one constructor, both alternatives end up the same. Li-yao On 08/20/2017 02:16 AM, David Banas wrote:
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
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users

Yep, that was it. Thanks, Li-yao! -db
On Aug 20, 2017, at 12:29 AM, Li-yao Xia
wrote: Hi David,
mkShow is probably making two separate declarations for "show" ([FunD "show" _, FunD "show" _]) instead of one declaration with two clauses ([FunD "show" [Clause ..., Clause ...]]). Both pretty-print to the same text, but only the second one is actually valid. When there is only one constructor, both alternatives end up the same.
Li-yao
On 08/20/2017 02:16 AM, David Banas wrote:
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
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
participants (2)
-
David Banas
-
Li-yao Xia