[Haskell-cafe] Deriving Show instance with ADT that has phantom type
Cody Goodman
codygman.consulting at gmail.com
Fri May 15 23:45:22 UTC 2015
Going through the Data Types Ala Carte paper I found this definition:
data Expr f = In (f (Expr f))
I tried to use "deriving Show"...
data Expr f = In (f (Expr f)) deriving Show
I found out that doesn't work with ADT's that have phantom types.
I tried StandaloneDeriving too since GHC recommended it:
{-# LANGUAGE StandaloneDeriving #-}
data Expr f = In (f (Expr f)) deriving Show
instance deriving Show (Expr f)
Got this error:
src/Main.hs:32:1-31: No instance for (Show (f (Expr f))) …
arising from a use of ‘showsPrec’
In the second argument of ‘(.)’, namely ‘(showsPrec 11 b1)’
In the second argument of ‘showParen’, namely
‘((.) (showString "In ") (showsPrec 11 b1))’
In the expression:
showParen ((a >= 11)) ((.) (showString "In ") (showsPrec 11 b1))
When typechecking the code for ‘showsPrec’
in a standalone derived instance for ‘Show (Expr f)’:
To see the code I am typechecking, use -ddump-deriv
Compilation failed.
Here is the derived instance output from ghc -ddump-simple:
Derived instances:
instance GHC.Show.Show (Main.Expr f_aq1) where
GHC.Show.showsPrec a_azP (Main.In b1_azQ)
= GHC.Show.showParen
((a_azP GHC.Classes.>= 11))
((GHC.Base..)
(GHC.Show.showString "In ") (GHC.Show.showsPrec 11 b1_azQ))
GHC.Show.showList = GHC.Show.showList__ (GHC.Show.showsPrec 0)
Didn't work. Can this be derived? Will I need to manually make instances?
More information about the Haskell-Cafe
mailing list