3

This code

{-# LANGUAGE GADTs #-}

data Expr a where
    Val :: Num a => a -> Expr a
    Eq :: Eq a => Expr a -> Expr a -> Expr Bool

eval :: Expr a -> a
eval (Val x) = x
eval (Eq x y) = (eval x) == (eval y)

instance Show a => Show (Expr a) where
    show (Val x) = "Val " ++ (show x)
    show (Eq x y) = "Eq (" ++ (show y) ++ ") (" ++ (show x) ++ ")"

fails to compile with the following error message:

Test.hs:13:32: error:
    * Could not deduce (Show a1) arising from a use of `show'
      from the context: Show a
        bound by the instance declaration at test.hs:11:10-32
      or from: (a ~ Bool, Eq a1)
        bound by a pattern with constructor:
                   Eq :: forall a. Eq a => Expr a -> Expr a -> Expr Bool,
                 in an equation for `show'
        at test.hs:13:11-16
      Possible fix:
        add (Show a1) to the context of the data constructor `Eq'
    * In the first argument of `(++)', namely `(show y)'
      In the second argument of `(++)', namely
        `(show y) ++ ") (" ++ (show x) ++ ")"'
      In the expression: "Eq (" ++ (show y) ++ ") (" ++ (show x) ++ ")" Failed, modules loaded: none.

Commenting out the last line fixes the issue and inspecting the type of Expr in GHCi reveals, that, instead of inferring Eq to be of type Eq a => (Expr a) -> (Expr a) -> Expr Bool, GHC actually infers it to be Eq a1 => (Expr a1) -> (Expr a1) -> Expr Bool for data Expr a where .... This explains the error message, since instance Show a => Show (Expr a) where ... won't enforce a1 to be an instance of Show.

However I do not understand, why GHC chooses to do so. If I had to make a guess, I'd say it has something to do with Eq returning a value, that doesn't depend on a at all and thus GHC "forgetting" about a, once Eq returns a Expr Bool. Is this - at least sort of - what is happening here?

Also, is there a clean solution to this? I tried several things, including trying to "force" the desired type via InstanceSigs and ScopedTypeVariables doing something like this:

instance Show a => Show (Expr a) where
    show :: forall a. Eq a => Expr a -> String
    show (Eq x y) = "Eq (" ++ (show (x :: Expr a)) ++ ") (" ++ (show (y :: Expr a)) ++ ")"
    ...

, but with no success. And since I'm still a Haskell novice, I'm not even sure, if this could somehow work anyways, due to my initial guess why GHC doesn't infer the "correct"/desired type in the first place.

EDIT:

Ok, so I decided to add a function

extract (Eq x _) = x

to the file (without a type signature), just to see, what return type it would have. GHC again refused to compile, but this time, the error message contained some information about skolem type variables. A quick search yielded this question, which (I think?) formalizes, what I believe the issue to be: Once Eq :: Expr a -> Expr a -> Expr Bool returns a Expr Bool, a goes "out of scope". Now we don't have any information left about a, so extract would have to have the signature exists a. Expr Bool -> a, since forall a. Expr Bool -> a won't be true for every a. But because GHC doesn't support exists, type-checking fails.

  • The easiest solution is to change signature of Eq from `Eq a => Expr a -> Expr a -> Expr Bool`, which allows `a` in this context to be whichever numeric type (which may or may not be instance of class show), to `(Eq a, Show a) => Expr a -> Expr a -> Expr Bool` which will allow to construct eq only expression only when comparing expressions of showable type. – Antisthenes Sep 06 '17 at 16:16
  • Thank you, this works; however a solution without this additional requirement in the type constructor would be interesting as well –  Sep 06 '17 at 16:47
  • With the original type there is no good solution. There is just too little you can do with an existential type. Another way is to restrict `Val` to a fixed type (or to have multiple `Val`-like constructors representing a finite set of types). – Li-yao Xia Sep 06 '17 at 16:56

2 Answers2

4

One option is not requiring a Show a superconstraint.

instance Show (Expr a) where
  showsPrec p (Eq x y) = showParen (p>9)
       $ ("Eq "++) . showsPrec 10 x . (' ':) . showsPrec 10 y

Of course this somewhat kicks the stone down the road, because now you can not write

  showsPrec p (Val x) = showParen (p>9) $ ("Val "++) . showsPrec 10 x

anymore – now the leaf-value is not Show constrained. But here you can hack your way around this by making the Num constraint a bit stronger:

data Expr a where
    Val :: RealFrac a => a -> Expr a
    Eq :: Eq a => Expr a -> Expr a -> Expr Bool
instance Show (Expr a) where
  showsPrec p (Val x) = showParen (p>9) $ ("Val "++)
          . showsPrec 10 (realToFrac x :: Double)

Well, that is a big hack, and at that point you might as well use simply

data Expr a where
    Val :: Double -> Expr Double
    Eq :: Eq a => Expr a -> Expr a -> Expr Bool

(or whatever other single type best fits your number requirements). That's not a good solution.

To retain the ability to store numbers of any type in Expr leaves, yet be able to constrain them to Show if desired, you need to be polymorphic on the constraint.

{-# LANGUAGE ConstraintKinds, KindSignatures #-}

import GHC.Exts (Constraint)

data Expr (c :: * -> Constraint) a where
    Val :: (Num a, c a) => a -> Expr a
    Eq :: Eq a => Expr a -> Expr a -> Expr Bool

Then you can do

instance Show (Expr Show a) where
  showsPrec p (Val x) = showParen (p>9) $ ("Val "++) . showsPrec 10 x
  showsPrec p (Eq x y) = showParen (p>9)
       $ ("Eq "++) . showsPrec 10 x . (' ':) . showsPrec 10 y
leftaroundabout
  • 117,950
  • 5
  • 174
  • 319
  • Thank you for your answer. As it seems, it indeed would be easiest, to just use concrete types. However your second solution is really interesting, too. I never heard of `-XConstraintKinds` before, so I will do some testing with that - experimenting with Haskell extensions truly feels like going down the rabbit hole sometimes! –  Sep 06 '17 at 21:06
  • Right now I only have a (minor) - unrelated to the original - question: The (latest) GHC User's Guide states: "[-XConstraintKinds] Allow types of kind Constraint to be used in contexts.", however I was under the impression, that contexts were something before "=>". But in your example, you used `Constraint` in the kind signature. Is that also considered a context or did they just use the term a bit more leniently? –  Sep 06 '17 at 21:13
  • 1
    I've used “`Constraint`” in the kind signature, but _the thing of kind `Constraint`_ is `c` and that's indeed used in the _context_ of the `Val` constructor. – leftaroundabout Sep 06 '17 at 21:22
  • I guess using `data Expr (c :: * -> Constraint) a where` leads to using a lot of `unsafeCoerce` to avoid traversing the whole expression just to lift an `Expr c` into an `Expr d` whenever `d a` entails `c a` for all a. :/ – gallais Sep 07 '17 at 13:32
  • @gallais yes, this is totally awkward when you want to change leaf-constraints of a given tree somehow. My suggestion assumes that this will never be necessary... – leftaroundabout Sep 07 '17 at 14:06
  • On second thought: `unsafeCoerce` may not even work because of the mismatch between the representations of the set of dictionaries. – gallais Sep 07 '17 at 14:17
2

I will only explain this point.

However I do not understand, why GHC chooses to do so.

The issue is, one can write a custom type with a Num and Eq instance, but no Show one.

newtype T = T Int deriving (Num, Eq) -- no Show, on purpose!

Then, this type checks:

e1 :: Expr T
e1 = Val (T 42)

as does this:

e2 :: Expr Bool
e2 = Eq e1 e1

However, it should be clear that e1 and e2 can not be showed. To print these, we would need Show T, which is missing.

Further, the constraint

instance Show a => Show (Expr a) where
      -- ^^^^^^

is useless here, since we do have Show Bool, but this is not enough to print e2 :: Expr Bool.

This is the problem of existential types: you get what you pay for. When we construct e2 = Eq e1 e2 we only have to "pay" the constraint Eq T. Hence, when we pattern match Eq a b we only get Eq t back (where t is a suitable type variable). We do not get to know whether Show t holds. Indeed, even if we did remember t ~ T, we would still lack the required Show T instance.

chi
  • 111,837
  • 3
  • 133
  • 218
  • Thanks for taking the time to answer, however just to clarify: The _actual_ issue is, that we don't remember, that `t ~ T`, right? That's why we can only do something like `show (Eq x y) = show (x == y)`. Because in my example, if we remembered `t ~ a`, due to the `Show a` constraint, we then should be able to deduce `Show t`. –  Sep 06 '17 at 21:41
  • 1
    @BenjaminRickels No, as I try to explain above, that is not sufficient in general. In your example, yes, that would suffice. However, since it is possible that someone chooses a `T` without a `Show` instance, GHC can not accept that code :-( You need to make `Eq x y` to require `Eq a` where `x,y::a`, otherwise you can craft expressions that can not be showed. – chi Sep 06 '17 at 21:55
  • 1
    @BenjaminRickels No. The actual issue is your instance says `Show a => Show (Expr a)`. But `a` in `Expr a` is the type of the overall expression, which for `Eq` is always `Bool`. That has no connection to the type of the two arguments to `Eq`! Because presumably you want to be able to represent an equality test of two integer-expressions, which is a Boolean expression overall; the `a` in the arguments does not have to be the same type as the `a` in the overall expression. So by this design, you **cannot** constrain the arguments by putting constraints on the overall type. – Ben Sep 06 '17 at 22:02
  • @chi and @Ben, thanks for helping me out! I think I now understand; I was constantly wondering about what if GHC could theoretically retain information about which types were originally used, to construct a `Expr Bool` with the `Eq` constructor. I thought then it should surely be possible to correlate those with `Show a` upon deconstructing `Eq`. But it didn't really occur to me, that the `a` in this case actually refers to `Bool`. In hindsight the initial error message makes a lot more sense now as well! –  Sep 07 '17 at 09:26