0
votes

I was just working through Chris Done's ADT with default example gist available here and ran into a problem: my ADT, with fields defined by higher kinded type families, is not working with a deriving show instance. GHC is telling me I need to derive a Show instance for a Type Family, but I'm not sure how to do. Here's what I have, so far, any comments would be helpful.

In the following example (using ghc 8.8.1), the objective is to define an instance of Show for ShowMe, using derive if possible.

{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE ConstraintKinds #-}

data Tag = A | B deriving (Show)

type family TF (p :: Tag) a where
  TF 'A a = ()
  TF 'B a = a

data ShowMe p = ShowMe
  { a :: !(TF p String)
  , b :: String
  }

main =  connect showMeDefaults { a = "some string" }
   where
     connect :: ShowMe B -> IO ()
     connect _ = pure ()
     showMeDefaults :: ShowMe A
     showMeDefaults = ShowMe { a = (), b = "asdf" }

-- This works to define Show
{-
instance Show (ShowMe p) where
  show _ = "hello"
-}
-- This instance is the line that causes an error
deriving instance Show (ShowMe p)

Subsequently, I'm getting an error that I'm not familiar with from GHC:

show_tf.hs:35:1: error:
    • No instance for (Show (TF p String))
        arising from a use of ‘showsPrec’
    • In the first argument of ‘(.)’, namely ‘(showsPrec 0 b1)’
      In the second argument of ‘(.)’, namely
        ‘((.)
            (showsPrec 0 b1)
            ((.)
               GHC.Show.showCommaSpace
               ((.)
                  (showString "b = ") ((.) (showsPrec 0 b2) (showString "}")))))’
      In the second argument of ‘(.)’, namely
        ‘((.)
            (showString "a = ")
            ((.)
               (showsPrec 0 b1)
               ((.)
                  GHC.Show.showCommaSpace
                  ((.)
                     (showString "b = ") ((.) (showsPrec 0 b2) (showString "}"))))))’
      When typechecking the code for ‘showsPrec’
        in a derived instance for ‘Show (ShowMe p)’:
        To see the code I am typechecking, use -ddump-deriv
   |
35 | deriving instance Show (ShowMe p)

If we recompile, using the ghc -ddump-deriv, the following is returned:

[1 of 1] Compiling Main             ( show_tf.hs, show_tf.o )

==================== Derived instances ====================
Derived class instances:
  instance GHC.Show.Show Main.Tag where
    GHC.Show.showsPrec _ Main.A = GHC.Show.showString "A"
    GHC.Show.showsPrec _ Main.B = GHC.Show.showString "B"


Derived type family instances:



==================== Filling in method body ====================
GHC.Show.Show [Main.Tag]
  GHC.Show.show = GHC.Show.$dmshow @(Main.Tag)



==================== Filling in method body ====================
GHC.Show.Show [Main.Tag]
  GHC.Show.showList = GHC.Show.$dmshowList @(Main.Tag)


Linking show_tf ...

Conceptually, I think what I should be able to derive a Show instance for TF, but when I do that, I get the following:

show_tf.hs:36:31: error:
    • Illegal type synonym family application ‘TF 'A a’ in instance:
        Show (TF 'A a)
    • In the stand-alone deriving instance for
        ‘(Show a) => Show (TF 'A a)’

   |
36 | deriving instance (Show a) => Show (TF 'A a)

This error also appears if I just try to define the Show instance myself for TF 'A a. I've searched "Illegal type synonym", and haven't come up up with a way around this.

1

1 Answers

1
votes

You need to add

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}

and then suggest the wanted context to GHC:

deriving instance Show (TF p String) => Show (ShowMe p)

GHC won't add that context automatically since it can be surprising to the programmer.